Safe Haskell | None |
---|---|
Language | Haskell2010 |
- newtype FileName = FileName {}
- newtype Context = Context (Ptr Context)
- newtype Extent = Extent (V2 CFloat)
- data Solidity
- data LineCap
- beginFrame :: Context -> CInt -> CInt -> Float -> IO ()
- cancelFrame :: Context -> IO ()
- endFrame :: Context -> IO ()
- data Color = Color !CFloat !CFloat !CFloat !CFloat
- rgb :: CUChar -> CUChar -> CUChar -> Color
- rgbf :: CFloat -> CFloat -> CFloat -> Color
- rgba :: CUChar -> CUChar -> CUChar -> CUChar -> Color
- rgbaf :: CFloat -> CFloat -> CFloat -> CFloat -> Color
- lerpRGBA :: Color -> Color -> CFloat -> Color
- transRGBA :: Color -> CUChar -> Color
- transRGBAf :: Color -> CFloat -> Color
- hsl :: CFloat -> CFloat -> CFloat -> Color
- hsla :: CFloat -> CFloat -> CFloat -> CUChar -> Color
- save :: Context -> IO ()
- restore :: Context -> IO ()
- reset :: Context -> IO ()
- strokeColor :: Context -> Color -> IO ()
- strokePaint :: Context -> Paint -> IO ()
- fillColor :: Context -> Color -> IO ()
- fillPaint :: Context -> Paint -> IO ()
- miterLimit :: Context -> CFloat -> IO ()
- strokeWidth :: Context -> CFloat -> IO ()
- lineCap :: Context -> LineCap -> IO ()
- lineJoin :: Context -> LineCap -> IO ()
- globalAlpha :: Context -> CFloat -> IO ()
- newtype Transformation = Transformation (M23 CFloat)
- resetTransform :: Context -> IO ()
- transform :: Context -> CFloat -> CFloat -> CFloat -> CFloat -> CFloat -> CFloat -> IO ()
- translate :: Context -> CFloat -> CFloat -> IO ()
- rotate :: Context -> CFloat -> IO ()
- skewX :: Context -> CFloat -> IO ()
- skewY :: Context -> CFloat -> IO ()
- scale :: Context -> CFloat -> CFloat -> IO ()
- currentTransform :: Context -> IO Transformation
- transformIdentity :: IO Transformation
- transformTranslate :: CFloat -> CFloat -> IO Transformation
- transformScale :: CFloat -> CFloat -> IO Transformation
- transformRotate :: CFloat -> IO Transformation
- transformSkewX :: CFloat -> IO Transformation
- transformSkewY :: CFloat -> IO Transformation
- transformMultiply :: Transformation -> Transformation -> IO Transformation
- transformPremultiply :: Transformation -> Transformation -> IO Transformation
- transformInverse :: Transformation -> IO Transformation
- transformPoint :: Transformation -> CFloat -> CFloat -> (CFloat, CFloat)
- degToRad :: CFloat -> CFloat
- radToDeg :: CFloat -> CFloat
- newtype Image = Image {
- imageHandle :: CInt
- createImage :: Context -> FileName -> CInt -> IO (Maybe Image)
- createImageMem :: Context -> ImageFlags -> ByteString -> IO (Maybe Image)
- createImageRGBA :: Context -> CInt -> CInt -> ImageFlags -> ByteString -> IO (Maybe Image)
- updateImage :: Context -> Image -> ByteString -> IO ()
- imageSize :: Context -> Image -> IO (CInt, CInt)
- deleteImage :: Context -> Image -> IO ()
- data Paint = Paint {
- xform :: Transformation
- extent :: Extent
- radius :: !CFloat
- feather :: !CFloat
- innerColor :: !Color
- outerColor :: !Color
- image :: !Image
- linearGradient :: Context -> CFloat -> CFloat -> CFloat -> CFloat -> Color -> Color -> IO Paint
- boxGradient :: Context -> CFloat -> CFloat -> CFloat -> CFloat -> CFloat -> CFloat -> Color -> Color -> IO Paint
- radialGradient :: Context -> CFloat -> CFloat -> CFloat -> CFloat -> Color -> Color -> IO Paint
- imagePattern :: Context -> CFloat -> CFloat -> CFloat -> CFloat -> CFloat -> Image -> CFloat -> IO Paint
- scissor :: Context -> CFloat -> CFloat -> CFloat -> CFloat -> IO ()
- intersectScissor :: Context -> CFloat -> CFloat -> CFloat -> CFloat -> IO ()
- resetScissor :: Context -> IO ()
- beginPath :: Context -> IO ()
- moveTo :: Context -> CFloat -> CFloat -> IO ()
- lineTo :: Context -> CFloat -> CFloat -> IO ()
- bezierTo :: Context -> CFloat -> CFloat -> CFloat -> CFloat -> CFloat -> CFloat -> IO ()
- quadTo :: Context -> CFloat -> CFloat -> CFloat -> CFloat -> IO ()
- arcTo :: Context -> CFloat -> CFloat -> CFloat -> CFloat -> CFloat -> IO ()
- closePath :: Context -> IO ()
- data Winding
- pathWinding :: Context -> CInt -> IO ()
- arc :: Context -> CFloat -> CFloat -> CFloat -> CFloat -> CFloat -> Winding -> IO ()
- rect :: Context -> CFloat -> CFloat -> CFloat -> CFloat -> IO ()
- roundedRect :: Context -> CFloat -> CFloat -> CFloat -> CFloat -> CFloat -> IO ()
- ellipse :: Context -> CFloat -> CFloat -> CFloat -> CFloat -> IO ()
- circle :: Context -> CFloat -> CFloat -> CFloat -> IO ()
- fill :: Context -> IO ()
- stroke :: Context -> IO ()
- newtype Font = Font {
- fontHandle :: CInt
- createFont :: Context -> Text -> FileName -> IO (Maybe Font)
- createFontMem :: Context -> Text -> ByteString -> IO (Maybe Font)
- findFont :: Context -> Text -> IO (Maybe Font)
- fontSize :: Context -> CFloat -> IO ()
- fontBlur :: Context -> CFloat -> IO ()
- textLetterSpacing :: Context -> CFloat -> IO ()
- textLineHeight :: Context -> CFloat -> IO ()
- data Align
- textAlign :: Context -> Set Align -> IO ()
- fontFaceId :: Context -> Font -> IO ()
- fontFace :: Context -> Text -> IO ()
- text :: Context -> CFloat -> CFloat -> Text -> IO ()
- textBox :: Context -> CFloat -> CFloat -> CFloat -> Text -> IO ()
- newtype Bounds = Bounds (V4 CFloat)
- textBounds :: Context -> CFloat -> CFloat -> Text -> IO Bounds
- textBoxBounds :: Context -> CFloat -> CFloat -> CFloat -> Text -> IO Bounds
- data GlyphPosition = GlyphPosition {
- str :: !(Ptr CChar)
- glyphX :: !CFloat
- glyphPosMinX :: !CFloat
- glyphPosMaxX :: !CFloat
- type GlyphPositionPtr = Ptr GlyphPosition
- textGlyphPositions :: Context -> CFloat -> CFloat -> Ptr CChar -> Ptr CChar -> CInt -> IO (Vector GlyphPosition)
- textMetrics :: Context -> IO (CFloat, CFloat, CFloat)
- data TextRow = TextRow {}
- type TextRowPtr = Ptr TextRow
- textBreakLines :: Context -> Text -> CFloat -> CInt -> (TextRow -> CInt -> IO ()) -> IO ()
- data CreateFlags
- createGL3 :: Set CreateFlags -> IO Context
- deleteGL3 :: Context -> IO ()
- createImageFromHandleGL3 :: Context -> GLuint -> CInt -> CInt -> CreateFlags -> IO Image
- imageHandleGL3 :: Context -> Image -> IO GLuint
- data V2 a = V2 !a !a
- data V3 a = V3 !a !a !a
- data V4 a = V4 !a !a !a !a
- type M23 a = V2 (V3 a)
Documentation
beginFrame :: Context -> CInt -> CInt -> Float -> IO () Source #
Begin drawing a new frame
Calls to nanovg drawing API should be wrapped in beginFrame
& endFrame
.
beginFrame
defines the size of the window to render to in relation currently
set viewport (i.e. glViewport on GL backends). Device pixel ration allows to
control the rendering on Hi-DPI devices.
For example, GLFW returns two dimension for an opened window: window size and frame buffer size. In that case you would set windowWidth/Height to the window size devicePixelRatio to: frameBufferWidth / windowWidth.
cancelFrame :: Context -> IO () Source #
Cancels drawing the current frame.
Color utils
rgba
rgb :: CUChar -> CUChar -> CUChar -> Color Source #
Returns a color value from red, green, blue values. Alpha will be set to 255 (1.0f).
rgbf :: CFloat -> CFloat -> CFloat -> Color Source #
Returns a color value from red, green, blue values. Alpha will be set to 1.0f.
rgba :: CUChar -> CUChar -> CUChar -> CUChar -> Color Source #
Returns a color value from red, green, blue and alpha values.
rgbaf :: CFloat -> CFloat -> CFloat -> CFloat -> Color Source #
Returns a color value from red, green, blue and alpha values.
lerpRGBA :: Color -> Color -> CFloat -> Color Source #
Linearly interpolates from color c0 to c1, and returns resulting color value.
hsl :: CFloat -> CFloat -> CFloat -> Color Source #
Returns color value specified by hue, saturation and lightness. HSL values are all in range [0..1], alpha will be set to 255.
hsla :: CFloat -> CFloat -> CFloat -> CUChar -> Color Source #
Returns color value specified by hue, saturation and lightness and alpha. HSL values are all in range [0..1], alpha in range [0..255]
State handling
save :: Context -> IO () Source #
Pushes and saves the current render state into a state stack.
A matching restore
must be used to restore the state.
reset :: Context -> IO () Source #
Resets current render state to default values. Does not affect the render state stack.
Render styles
strokePaint :: Context -> Paint -> IO () Source #
Sets current stroke style to a paint, which can be a one of the gradients or a pattern.
fillPaint :: Context -> Paint -> IO () Source #
Sets current fill style to a paint, which can be a one of the gradients or a pattern.
miterLimit :: Context -> CFloat -> IO () Source #
Sets the miter limit of the stroke style. Miter limit controls when a sharp corner is beveled.
globalAlpha :: Context -> CFloat -> IO () Source #
Sets the transparency applied to all rendered shapes. Already transparent paths will get proportionally more transparent as well.
Transforms
newtype Transformation Source #
Affine matrix
[sx kx tx] [ky sy ty] [ 0 0 1]
resetTransform :: Context -> IO () Source #
Resets current transform to a identity matrix.
transform :: Context -> CFloat -> CFloat -> CFloat -> CFloat -> CFloat -> CFloat -> IO () Source #
Premultiplies current coordinate system by specified matrix. The parameters are interpreted as matrix as follows:
[a c e] [b d f] [0 0 1]
rotate :: Context -> CFloat -> IO () Source #
Rotates current coordinate system. Angle is specified in radians.
skewX :: Context -> CFloat -> IO () Source #
Skews the current coordinate system along X axis. Angle is specified in radians.
skewY :: Context -> CFloat -> IO () Source #
Skews the current coordinate system along Y axis. Angle is specified in radians.
currentTransform :: Context -> IO Transformation Source #
Returns the current transformation matrix.
transformIdentity :: IO Transformation Source #
Sets the transform to identity matrix.
transformTranslate :: CFloat -> CFloat -> IO Transformation Source #
Sets the transform to translation matrix matrix.
transformScale :: CFloat -> CFloat -> IO Transformation Source #
Sets the transform to scale matrix.
transformRotate :: CFloat -> IO Transformation Source #
Sets the transform to rotate matrix. Angle is specified in radians.
transformSkewX :: CFloat -> IO Transformation Source #
Sets the transform to skew-x matrix. Angle is specified in radians.
transformSkewY :: CFloat -> IO Transformation Source #
Sets the transform to skew-y matrix. Angle is specified in radians.
transformMultiply :: Transformation -> Transformation -> IO Transformation Source #
Sets the transform to the result of multiplication of two transforms, of A = A*B.
transformPremultiply :: Transformation -> Transformation -> IO Transformation Source #
Sets the transform to the result of multiplication of two transforms, of A = B*A.
transformInverse :: Transformation -> IO Transformation Source #
Sets the destination to inverse of specified transform. Returns 1 if the inverse could be calculated, else 0.
transformPoint :: Transformation -> CFloat -> CFloat -> (CFloat, CFloat) Source #
Transform a point by given transform.
Images
Newtype to avoid accidental use of ints
Image | |
|
createImage :: Context -> FileName -> CInt -> IO (Maybe Image) Source #
Creates image by loading it from the disk from specified file name.
createImageMem :: Context -> ImageFlags -> ByteString -> IO (Maybe Image) Source #
Creates image by loading it from the specified chunk of memory.
createImageRGBA :: Context -> CInt -> CInt -> ImageFlags -> ByteString -> IO (Maybe Image) Source #
Creates image from specified image data.
updateImage :: Context -> Image -> ByteString -> IO () Source #
Updates image data specified by image handle.
Paints
Paint | |
|
linearGradient :: Context -> CFloat -> CFloat -> CFloat -> CFloat -> Color -> Color -> IO Paint Source #
Creates and returns a linear gradient. Parameters (sx,sy)-(ex,ey) specify the start and end coordinates
of the linear gradient, icol specifies the start color and ocol the end color.
The gradient is transformed by the current transform when it is passed to fillPaint
or strokePaint
.
boxGradient :: Context -> CFloat -> CFloat -> CFloat -> CFloat -> CFloat -> CFloat -> Color -> Color -> IO Paint Source #
Creates and returns a box gradient. Box gradient is a feathered rounded rectangle, it is useful for rendering
drop shadows or highlights for boxes. Parameters (x,y) define the top-left corner of the rectangle,
(w,h) define the size of the rectangle, r defines the corner radius, and f feather. Feather defines how blurry
the border of the rectangle is. Parameter icol specifies the inner color and ocol the outer color of the gradient.
The gradient is transformed by the current transform when it is passed to fillPaint
or strokePaint
.
radialGradient :: Context -> CFloat -> CFloat -> CFloat -> CFloat -> Color -> Color -> IO Paint Source #
Creates and returns a radial gradient. Parameters (cx,cy) specify the center, inr and outr specify
the inner and outer radius of the gradient, icol specifies the start color and ocol the end color.
The gradient is transformed by the current transform when it is passed to fillPaint
or strokePaint
.
imagePattern :: Context -> CFloat -> CFloat -> CFloat -> CFloat -> CFloat -> Image -> CFloat -> IO Paint Source #
Creates and returns an image patter. Parameters (ox,oy) specify the left-top location of the image pattern,
(ex,ey) the size of one image, angle rotation around the top-left corner, image is handle to the image to render.
The gradient is transformed by the current transform when it is passed to fillPaint
or strokePaint
.
Scissoring
scissor :: Context -> CFloat -> CFloat -> CFloat -> CFloat -> IO () Source #
Sets the current scissor rectangle. The scissor rectangle is transformed by the current transform.
intersectScissor :: Context -> CFloat -> CFloat -> CFloat -> CFloat -> IO () Source #
Intersects current scissor rectangle with the specified rectangle. The scissor rectangle is transformed by the current transform. Note: in case the rotation of previous scissor rect differs from the current one, the intersection will be done between the specified rectangle and the previous scissor rectangle transformed in the current transform space. The resulting shape is always rectangle.
resetScissor :: Context -> IO () Source #
Reset and disables scissoring.
Paths
moveTo :: Context -> CFloat -> CFloat -> IO () Source #
Starts new sub-path with specified point as first point.
lineTo :: Context -> CFloat -> CFloat -> IO () Source #
Adds line segment from the last point in the path to the specified point.
bezierTo :: Context -> CFloat -> CFloat -> CFloat -> CFloat -> CFloat -> CFloat -> IO () Source #
Adds cubic bezier segment from last point in the path via two control points to the specified point.
quadTo :: Context -> CFloat -> CFloat -> CFloat -> CFloat -> IO () Source #
Adds quadratic bezier segment from last point in the path via a control point to the specified point
arcTo :: Context -> CFloat -> CFloat -> CFloat -> CFloat -> CFloat -> IO () Source #
Adds an arc segment at the corner defined by the last path point, and two specified points.
pathWinding :: Context -> CInt -> IO () Source #
Sets the current sub-path winding, see NVGwinding and NVGsolidity.
arc :: Context -> CFloat -> CFloat -> CFloat -> CFloat -> CFloat -> Winding -> IO () Source #
Creates new circle arc shaped sub-path. The arc center is at cx,cy, the arc radius is r, and the arc is drawn from angle a0 to a1, and swept in direction dir (NVG_CCW, or NVG_CW). Angles are specified in radians.
rect :: Context -> CFloat -> CFloat -> CFloat -> CFloat -> IO () Source #
Creates new rectangle shaped sub-path.
roundedRect :: Context -> CFloat -> CFloat -> CFloat -> CFloat -> CFloat -> IO () Source #
Creates new rounded rectangle shaped sub-path.
ellipse :: Context -> CFloat -> CFloat -> CFloat -> CFloat -> IO () Source #
Creates new ellipse shaped sub-path.
circle :: Context -> CFloat -> CFloat -> CFloat -> IO () Source #
Creates new circle shaped sub-path.
Text
Newtype to avoid accidental use of ints
Font | |
|
createFont :: Context -> Text -> FileName -> IO (Maybe Font) Source #
Creates font by loading it from the disk from specified file name. Returns handle to the font.
createFontMem :: Context -> Text -> ByteString -> IO (Maybe Font) Source #
Creates image by loading it from the specified memory chunk. Returns handle to the font.
findFont :: Context -> Text -> IO (Maybe Font) Source #
Finds a loaded font of specified name, and returns handle to it, or -1 if the font is not found.
textLetterSpacing :: Context -> CFloat -> IO () Source #
Sets the letter spacing of current text style.
textLineHeight :: Context -> CFloat -> IO () Source #
Sets the proportional line height of current text style. The line height is specified as multiple of font size.
textAlign :: Context -> Set Align -> IO () Source #
Sets the text align of current text style, see NVGalign for options.
fontFaceId :: Context -> Font -> IO () Source #
Sets the font face based on specified id of current text style.
fontFace :: Context -> Text -> IO () Source #
Sets the font face based on specified name of current text styl
textBox :: Context -> CFloat -> CFloat -> CFloat -> Text -> IO () Source #
Draws multi-line text string at specified location wrapped at the specified width. If end is specified only the sub-string up to the end is drawn. | White space is stripped at the beginning of the rows, the text is split at word boundaries or when new-line characters are encountered. | Words longer than the max width are slit at nearest character (i.e. no hyphenation).
textBounds :: Context -> CFloat -> CFloat -> Text -> IO Bounds Source #
Measures the specified text string. Parameter bounds should be a pointer to float[4], if the bounding box of the text should be returned. The bounds value are [xmin,ymin, xmax,ymax] Returns the horizontal advance of the measured text (i.e. where the next character should drawn). Measured values are returned in local coordinate space.
textBoxBounds :: Context -> CFloat -> CFloat -> CFloat -> Text -> IO Bounds Source #
Measures the specified multi-text string. Parameter bounds should be a pointer to float[4], if the bounding box of the text should be returned. The bounds value are [xmin,ymin, xmax,ymax] Measured values are returned in local coordinate space.
data GlyphPosition Source #
GlyphPosition | |
|
type GlyphPositionPtr = Ptr GlyphPosition Source #
textGlyphPositions :: Context -> CFloat -> CFloat -> Ptr CChar -> Ptr CChar -> CInt -> IO (Vector GlyphPosition) Source #
High level wrapper around NanoVG.Internal.textGlyphPositions Might be changed to return a vector in the future
textMetrics :: Context -> IO (CFloat, CFloat, CFloat) Source #
Returns the vertical metrics based on the current text style. Measured values are returned in local coordinate space.
TextRow | |
|
type TextRowPtr = Ptr TextRow Source #
textBreakLines :: Context -> Text -> CFloat -> CInt -> (TextRow -> CInt -> IO ()) -> IO () Source #
High level wrapper around NanoVG.Internal.textBreakLines This uses the fonts for width calculations so make sure you have them setup properly
GL
data CreateFlags Source #
createImageFromHandleGL3 :: Context -> GLuint -> CInt -> CInt -> CreateFlags -> IO Image Source #
Vector types
Vector of 2 strict elements
V2 !a !a |
Vector of 3 strict elements
V3 !a !a !a |
Vector of 4 strict elements
V4 !a !a !a !a |