nanovg-0.1.0.1: Haskell bindings for nanovg

Safe HaskellNone
LanguageHaskell2010

NanoVG.Internal

Contents

Synopsis

Documentation

newtype FileName Source

Newtype to avoid accidental use of strings

Constructors

FileName 

Fields

unwrapFileName :: Text
 

newtype Image Source

Newtype to avoid accidental use of ints

Constructors

Image 

Fields

imageHandle :: CInt
 

newtype Font Source

Newtype to avoid accidental use of ints

Affine matrix

[sx kx tx]
[ky sy ty]
[ 0  0  1]

Constructors

Font 

Fields

fontHandle :: CInt
 

newtype Context Source

Opaque context that needs to be passed around

Constructors

Context (Ptr Context) 

data GlyphPosition Source

Constructors

GlyphPosition 

Fields

str :: !(Ptr CChar)

Pointer of the glyph in the input string.

glyphX :: !CFloat

The x-coordinate of the logical glyph position.

glyphPosMinX :: !CFloat

The left bound of the glyph shape.

glyphPosMaxX :: !CFloat

The right bound of the glyph shape.

data TextRow Source

Constructors

TextRow 

Fields

start :: !(Ptr CChar)

Pointer to the input text where the row starts.

end :: !(Ptr CChar)

Pointer to the input text where the row ends (one past the last character).

next :: !(Ptr CChar)

Pointer to the beginning of the next row.

width :: !CFloat

Logical width of the row.

textRowMinX :: !CFloat

Actual bounds of the row. Logical with and bounds can differ because of kerning and some parts over extending.

textRowMaxX :: !CFloat
 

cancelFrame :: Context -> IO () Source

Cancels drawing the current frame.

endFrame :: Context -> IO () Source

Ends drawing flushing remaining render state.

Color utils

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.

transRGBA :: Color -> CUChar -> Color Source

Sets transparency of a color value.

transRGBAf :: Color -> CFloat -> Color Source

Sets transparency of a 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.

restore :: Context -> IO () Source

Pops and restores current render state.

reset :: Context -> IO () Source

Resets current render state to default values. Does not affect the render state stack.

Render styles

strokeColor :: Context -> Color -> IO () Source

Sets current stroke style to a solid color.

strokePaint :: Context -> Paint -> IO () Source

Sets current stroke style to a paint, which can be a one of the gradients or a pattern.

fillColor :: Context -> Color -> IO () Source

Sets current fill style to a solid color.

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.

strokeWidth :: Context -> CFloat -> IO () Source

Sets the stroke width of the stroke style.

lineCap :: Context -> LineCap -> IO () Source

Sets how the end of the line (cap) is drawn, Can be one of: Butt (default), Round, Square.

lineJoin :: Context -> LineCap -> IO () Source

Sets how sharp path corners are drawn. Can be one of Miter (default), Round, 'Bevel.

globalAlpha :: Context -> CFloat -> IO () Source

Sets the transparency applied to all rendered shapes. Already transparent paths will get proportionally more transparent as well.

Transforms

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]

translate :: Context -> CFloat -> CFloat -> IO () Source

Translates current coordinate system.

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.

scale :: Context -> CFloat -> CFloat -> IO () Source

Scales the current coordinate system.

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.

degToRad :: CFloat -> CFloat Source

Converts degrees to radians.

radToDeg :: CFloat -> CFloat Source

Converts radians to degrees.

Images

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.

imageSize :: Context -> Image -> IO (CInt, CInt) Source

Returns the dimensions of a created image.

deleteImage :: Context -> Image -> IO () Source

Deletes created image.

Paints

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

beginPath :: Context -> IO () Source

Clears the current path and sub-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.

closePath :: Context -> IO () Source

Closes current sub-path with a line segment.

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.

fill :: Context -> IO () Source

Fills the current path with current fill style.

stroke :: Context -> IO () Source

Fills the current path with current stroke style.

Text

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.

fontSize :: Context -> CFloat -> IO () Source

Sets the font size of current text style.

fontBlur :: Context -> CFloat -> IO () Source

Sets the blur of current text style.

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

text :: Context -> CFloat -> CFloat -> Ptr CChar -> Ptr CChar -> IO () Source

Draws text string at specified location. If end is specified only the sub-string up to the end is drawn.

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.

textGlyphPositions :: Context -> CFloat -> CFloat -> Ptr CChar -> Ptr CChar -> GlyphPositionPtr -> CInt -> IO CInt Source

Calculates the glyph x positions of the specified text. If end is specified only the sub-string will be used. Measured values are returned in local coordinate space.

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.

textBreakLines :: Context -> Ptr CChar -> Ptr CChar -> CFloat -> TextRowPtr -> CInt -> IO CInt Source

Breaks the specified text into lines. If end is specified only the sub-string will be used. 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).

GL