nanovg-0.8.1.0: Haskell bindings for nanovg
Safe HaskellNone
LanguageHaskell2010

NanoVG

Synopsis

Documentation

newtype FileName Source #

Newtype to avoid accidental use of strings

Constructors

FileName 

Fields

newtype Context Source #

Opaque context that needs to be passed around

Constructors

Context (Ptr Context) 

newtype Extent Source #

Constructors

Extent (V2 CFloat) 

Instances

Instances details
Eq Extent Source # 
Instance details

Defined in NanoVG.Internal.Paint

Methods

(==) :: Extent -> Extent -> Bool #

(/=) :: Extent -> Extent -> Bool #

Ord Extent Source # 
Instance details

Defined in NanoVG.Internal.Paint

Read Extent Source # 
Instance details

Defined in NanoVG.Internal.Paint

Show Extent Source # 
Instance details

Defined in NanoVG.Internal.Paint

Storable Extent Source # 
Instance details

Defined in NanoVG.Internal.Paint

beginFrame :: Context -> Float -> Float -> 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.

endFrame :: Context -> IO () Source #

Ends drawing flushing remaining render state.

Color utils

data Color Source #

rgba

Constructors

Color !CFloat !CFloat !CFloat !CFloat 

Instances

Instances details
Eq Color Source # 
Instance details

Defined in NanoVG.Internal.Color

Methods

(==) :: Color -> Color -> Bool #

(/=) :: Color -> Color -> Bool #

Ord Color Source # 
Instance details

Defined in NanoVG.Internal.Color

Methods

compare :: Color -> Color -> Ordering #

(<) :: Color -> Color -> Bool #

(<=) :: Color -> Color -> Bool #

(>) :: Color -> Color -> Bool #

(>=) :: Color -> Color -> Bool #

max :: Color -> Color -> Color #

min :: Color -> Color -> Color #

Read Color Source # 
Instance details

Defined in NanoVG.Internal.Color

Show Color Source # 
Instance details

Defined in NanoVG.Internal.Color

Methods

showsPrec :: Int -> Color -> ShowS #

show :: Color -> String #

showList :: [Color] -> ShowS #

Storable Color Source # 
Instance details

Defined in NanoVG.Internal.Color

Methods

sizeOf :: Color -> Int #

alignment :: Color -> Int #

peekElemOff :: Ptr Color -> Int -> IO Color #

pokeElemOff :: Ptr Color -> Int -> Color -> IO () #

peekByteOff :: Ptr b -> Int -> IO Color #

pokeByteOff :: Ptr b -> Int -> Color -> IO () #

peek :: Ptr Color -> IO Color #

poke :: Ptr Color -> Color -> IO () #

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

newtype Transformation Source #

Affine matrix

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

Constructors

Transformation (M23 CFloat) 

Instances

Instances details
Eq Transformation Source # 
Instance details

Defined in NanoVG.Internal.Transformation

Ord Transformation Source # 
Instance details

Defined in NanoVG.Internal.Transformation

Read Transformation Source # 
Instance details

Defined in NanoVG.Internal.Transformation

Show Transformation Source # 
Instance details

Defined in NanoVG.Internal.Transformation

Storable Transformation Source # 
Instance details

Defined in NanoVG.Internal.Transformation

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

newtype Image Source #

Newtype to avoid accidental use of ints

Constructors

Image 

Fields

Instances

Instances details
Eq Image Source # 
Instance details

Defined in NanoVG.Internal.Types

Methods

(==) :: Image -> Image -> Bool #

(/=) :: Image -> Image -> Bool #

Ord Image Source # 
Instance details

Defined in NanoVG.Internal.Types

Methods

compare :: Image -> Image -> Ordering #

(<) :: Image -> Image -> Bool #

(<=) :: Image -> Image -> Bool #

(>) :: Image -> Image -> Bool #

(>=) :: Image -> Image -> Bool #

max :: Image -> Image -> Image #

min :: Image -> Image -> Image #

Read Image Source # 
Instance details

Defined in NanoVG.Internal.Types

Show Image Source # 
Instance details

Defined in NanoVG.Internal.Types

Methods

showsPrec :: Int -> Image -> ShowS #

show :: Image -> String #

showList :: [Image] -> ShowS #

createImage :: Context -> FileName -> Set ImageFlags -> IO (Maybe Image) Source #

Creates image by loading it from the disk from specified file name.

createImageMem :: Context -> Set ImageFlags -> ByteString -> IO (Maybe Image) Source #

Creates image by loading it from the specified chunk of memory.

createImageRGBA :: Context -> CInt -> CInt -> Set 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

data Paint Source #

Instances

Instances details
Eq Paint Source # 
Instance details

Defined in NanoVG.Internal.Paint

Methods

(==) :: Paint -> Paint -> Bool #

(/=) :: Paint -> Paint -> Bool #

Ord Paint Source # 
Instance details

Defined in NanoVG.Internal.Paint

Methods

compare :: Paint -> Paint -> Ordering #

(<) :: Paint -> Paint -> Bool #

(<=) :: Paint -> Paint -> Bool #

(>) :: Paint -> Paint -> Bool #

(>=) :: Paint -> Paint -> Bool #

max :: Paint -> Paint -> Paint #

min :: Paint -> Paint -> Paint #

Read Paint Source # 
Instance details

Defined in NanoVG.Internal.Paint

Show Paint Source # 
Instance details

Defined in NanoVG.Internal.Paint

Methods

showsPrec :: Int -> Paint -> ShowS #

show :: Paint -> String #

showList :: [Paint] -> ShowS #

Storable Paint Source # 
Instance details

Defined in NanoVG.Internal.Paint

Methods

sizeOf :: Paint -> Int #

alignment :: Paint -> Int #

peekElemOff :: Ptr Paint -> Int -> IO Paint #

pokeElemOff :: Ptr Paint -> Int -> Paint -> IO () #

peekByteOff :: Ptr b -> Int -> IO Paint #

pokeByteOff :: Ptr b -> Int -> Paint -> IO () #

peek :: Ptr Paint -> IO Paint #

poke :: Ptr Paint -> Paint -> IO () #

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.

data Winding Source #

Constructors

CCW 
CW 

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. Receives x, y, w and h

roundedRect :: Context -> CFloat -> CFloat -> CFloat -> CFloat -> CFloat -> IO () Source #

Creates new rounded rectangle shaped sub-path. In addition to x, y, w and h, it receives | r, indicating the radius (equal in all corners)

roundedRectVarying :: Context -> CFloat -> CFloat -> CFloat -> CFloat -> CFloat -> CFloat -> CFloat -> CFloat -> IO () Source #

Creates new rounded rectangle shaped sub-path. In addition to x, y, w and h, it receives | rtl, rtr, rbr, rbl, the radius of each corner in clockwise order starting from top left

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.

Global Composite

data BlendFactor Source #

Instances

Instances details
Enum BlendFactor Source #

Composite operation

The composite operations in NanoVG are modeled after HTML Canvas API, and the blend func is based on OpenGL (see corresponding manuals for more info). The colors in the blending state have premultiplied alpha.

Instance details

Defined in NanoVG.Internal.GlobalComposite

Eq BlendFactor Source # 
Instance details

Defined in NanoVG.Internal.GlobalComposite

Ord BlendFactor Source # 
Instance details

Defined in NanoVG.Internal.GlobalComposite

Read BlendFactor Source # 
Instance details

Defined in NanoVG.Internal.GlobalComposite

Show BlendFactor Source # 
Instance details

Defined in NanoVG.Internal.GlobalComposite

data CompositeOperation Source #

Instances

Instances details
Enum CompositeOperation Source # 
Instance details

Defined in NanoVG.Internal.GlobalComposite

Eq CompositeOperation Source # 
Instance details

Defined in NanoVG.Internal.GlobalComposite

Ord CompositeOperation Source # 
Instance details

Defined in NanoVG.Internal.GlobalComposite

Read CompositeOperation Source # 
Instance details

Defined in NanoVG.Internal.GlobalComposite

Show CompositeOperation Source # 
Instance details

Defined in NanoVG.Internal.GlobalComposite

globalCompositeOperation :: Context -> CompositeOperation -> IO () Source #

Sets the composite operation. The op parameter should be one of NVGcompositeOperation.

globalCompositeBlendFunc :: Context -> BlendFactor -> BlendFactor -> IO () Source #

Sets the composite operation with custom pixel arithmetic. The parameters should be one of NVGblendFactor.

globalCompositeBlendFuncSeparate :: Context -> BlendFactor -> BlendFactor -> BlendFactor -> BlendFactor -> IO () Source #

Sets the composite operation with custom pixel arithmetic for RGB and alpha components separately. The parameters should be one of NVGblendFactor.

Text

newtype Font Source #

Newtype to avoid accidental use of ints

Constructors

Font 

Fields

Instances

Instances details
Eq Font Source # 
Instance details

Defined in NanoVG.Internal.Text

Methods

(==) :: Font -> Font -> Bool #

(/=) :: Font -> Font -> Bool #

Ord Font Source # 
Instance details

Defined in NanoVG.Internal.Text

Methods

compare :: Font -> Font -> Ordering #

(<) :: Font -> Font -> Bool #

(<=) :: Font -> Font -> Bool #

(>) :: Font -> Font -> Bool #

(>=) :: Font -> Font -> Bool #

max :: Font -> Font -> Font #

min :: Font -> Font -> Font #

Read Font Source # 
Instance details

Defined in NanoVG.Internal.Text

Show Font Source # 
Instance details

Defined in NanoVG.Internal.Text

Methods

showsPrec :: Int -> Font -> ShowS #

show :: Font -> String #

showList :: [Font] -> ShowS #

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.

createFontAtIndex :: Context -> Text -> FileName -> CInt -> IO (Maybe Font) Source #

Creates font by loading it from the disk from specified file name. fontIndex specifies which font face to load from a .ttf/.ttc file. Returns handle to the font.

createFontMem :: Context -> Text -> ByteString -> IO (Maybe Font) Source #

Creates font by loading it from the specified memory chunk. Returns handle to the font.

createFontMemAtIndex :: Context -> Text -> ByteString -> CInt -> IO (Maybe Font) Source #

Creates font by loading it from the specified memory chunk. fontIndex specifies which font face to load from a .ttf/.ttc file. 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.

addFallbackFontId :: Context -> CInt -> CInt -> IO (Maybe Font) Source #

Adds a fallback font by handle.

addFallbackFont :: Context -> Text -> Text -> IO (Maybe Font) Source #

Adds a fallback font by name.

resetFallbackFontsId :: Context -> CInt -> IO () Source #

Resets fallback fonts by handle.

resetFallbackFonts :: Context -> Text -> IO () Source #

Resets fallback fonts by name.

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.

data Align Source #

Instances

Instances details
Enum Align Source # 
Instance details

Defined in NanoVG.Internal.Text

Eq Align Source # 
Instance details

Defined in NanoVG.Internal.Text

Methods

(==) :: Align -> Align -> Bool #

(/=) :: Align -> Align -> Bool #

Ord Align Source # 
Instance details

Defined in NanoVG.Internal.Text

Methods

compare :: Align -> Align -> Ordering #

(<) :: Align -> Align -> Bool #

(<=) :: Align -> Align -> Bool #

(>) :: Align -> Align -> Bool #

(>=) :: Align -> Align -> Bool #

max :: Align -> Align -> Align #

min :: Align -> Align -> Align #

Read Align Source # 
Instance details

Defined in NanoVG.Internal.Text

Show Align Source # 
Instance details

Defined in NanoVG.Internal.Text

Methods

showsPrec :: Int -> Align -> ShowS #

show :: Align -> String #

showList :: [Align] -> ShowS #

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 -> Text -> IO () Source #

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).

newtype Bounds Source #

Constructors

Bounds (V4 CFloat) 

Instances

Instances details
Eq Bounds Source # 
Instance details

Defined in NanoVG.Internal.Text

Methods

(==) :: Bounds -> Bounds -> Bool #

(/=) :: Bounds -> Bounds -> Bool #

Ord Bounds Source # 
Instance details

Defined in NanoVG.Internal.Text

Read Bounds Source # 
Instance details

Defined in NanoVG.Internal.Text

Show Bounds Source # 
Instance details

Defined in NanoVG.Internal.Text

Storable Bounds Source # 
Instance details

Defined in NanoVG.Internal.Text

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 #

Constructors

GlyphPosition 

Fields

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.

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
     

Instances

Instances details
Eq TextRow Source # 
Instance details

Defined in NanoVG.Internal.Text

Methods

(==) :: TextRow -> TextRow -> Bool #

(/=) :: TextRow -> TextRow -> Bool #

Ord TextRow Source # 
Instance details

Defined in NanoVG.Internal.Text

Show TextRow Source # 
Instance details

Defined in NanoVG.Internal.Text

Storable TextRow Source # 
Instance details

Defined in NanoVG.Internal.Text

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 #

Instances

Instances details
Enum CreateFlags Source # 
Instance details

Defined in NanoVG.Internal.CreateContext

Eq CreateFlags Source # 
Instance details

Defined in NanoVG.Internal.CreateContext

Ord CreateFlags Source # 
Instance details

Defined in NanoVG.Internal.CreateContext

Read CreateFlags Source # 
Instance details

Defined in NanoVG.Internal.CreateContext

Show CreateFlags Source # 
Instance details

Defined in NanoVG.Internal.CreateContext

Vector types

data V2 a Source #

Vector of 2 strict elements

Constructors

V2 !a !a 

Instances

Instances details
Functor V2 Source # 
Instance details

Defined in NanoVG.Internal.FixedVector

Methods

fmap :: (a -> b) -> V2 a -> V2 b #

(<$) :: a -> V2 b -> V2 a #

Foldable V2 Source # 
Instance details

Defined in NanoVG.Internal.FixedVector

Methods

fold :: Monoid m => V2 m -> m #

foldMap :: Monoid m => (a -> m) -> V2 a -> m #

foldMap' :: Monoid m => (a -> m) -> V2 a -> m #

foldr :: (a -> b -> b) -> b -> V2 a -> b #

foldr' :: (a -> b -> b) -> b -> V2 a -> b #

foldl :: (b -> a -> b) -> b -> V2 a -> b #

foldl' :: (b -> a -> b) -> b -> V2 a -> b #

foldr1 :: (a -> a -> a) -> V2 a -> a #

foldl1 :: (a -> a -> a) -> V2 a -> a #

toList :: V2 a -> [a] #

null :: V2 a -> Bool #

length :: V2 a -> Int #

elem :: Eq a => a -> V2 a -> Bool #

maximum :: Ord a => V2 a -> a #

minimum :: Ord a => V2 a -> a #

sum :: Num a => V2 a -> a #

product :: Num a => V2 a -> a #

Traversable V2 Source # 
Instance details

Defined in NanoVG.Internal.FixedVector

Methods

traverse :: Applicative f => (a -> f b) -> V2 a -> f (V2 b) #

sequenceA :: Applicative f => V2 (f a) -> f (V2 a) #

mapM :: Monad m => (a -> m b) -> V2 a -> m (V2 b) #

sequence :: Monad m => V2 (m a) -> m (V2 a) #

Eq a => Eq (V2 a) Source # 
Instance details

Defined in NanoVG.Internal.FixedVector

Methods

(==) :: V2 a -> V2 a -> Bool #

(/=) :: V2 a -> V2 a -> Bool #

Ord a => Ord (V2 a) Source # 
Instance details

Defined in NanoVG.Internal.FixedVector

Methods

compare :: V2 a -> V2 a -> Ordering #

(<) :: V2 a -> V2 a -> Bool #

(<=) :: V2 a -> V2 a -> Bool #

(>) :: V2 a -> V2 a -> Bool #

(>=) :: V2 a -> V2 a -> Bool #

max :: V2 a -> V2 a -> V2 a #

min :: V2 a -> V2 a -> V2 a #

Read a => Read (V2 a) Source # 
Instance details

Defined in NanoVG.Internal.FixedVector

Show a => Show (V2 a) Source # 
Instance details

Defined in NanoVG.Internal.FixedVector

Methods

showsPrec :: Int -> V2 a -> ShowS #

show :: V2 a -> String #

showList :: [V2 a] -> ShowS #

data V3 a Source #

Vector of 3 strict elements

Constructors

V3 !a !a !a 

Instances

Instances details
Functor V3 Source # 
Instance details

Defined in NanoVG.Internal.FixedVector

Methods

fmap :: (a -> b) -> V3 a -> V3 b #

(<$) :: a -> V3 b -> V3 a #

Foldable V3 Source # 
Instance details

Defined in NanoVG.Internal.FixedVector

Methods

fold :: Monoid m => V3 m -> m #

foldMap :: Monoid m => (a -> m) -> V3 a -> m #

foldMap' :: Monoid m => (a -> m) -> V3 a -> m #

foldr :: (a -> b -> b) -> b -> V3 a -> b #

foldr' :: (a -> b -> b) -> b -> V3 a -> b #

foldl :: (b -> a -> b) -> b -> V3 a -> b #

foldl' :: (b -> a -> b) -> b -> V3 a -> b #

foldr1 :: (a -> a -> a) -> V3 a -> a #

foldl1 :: (a -> a -> a) -> V3 a -> a #

toList :: V3 a -> [a] #

null :: V3 a -> Bool #

length :: V3 a -> Int #

elem :: Eq a => a -> V3 a -> Bool #

maximum :: Ord a => V3 a -> a #

minimum :: Ord a => V3 a -> a #

sum :: Num a => V3 a -> a #

product :: Num a => V3 a -> a #

Traversable V3 Source # 
Instance details

Defined in NanoVG.Internal.FixedVector

Methods

traverse :: Applicative f => (a -> f b) -> V3 a -> f (V3 b) #

sequenceA :: Applicative f => V3 (f a) -> f (V3 a) #

mapM :: Monad m => (a -> m b) -> V3 a -> m (V3 b) #

sequence :: Monad m => V3 (m a) -> m (V3 a) #

Eq a => Eq (V3 a) Source # 
Instance details

Defined in NanoVG.Internal.FixedVector

Methods

(==) :: V3 a -> V3 a -> Bool #

(/=) :: V3 a -> V3 a -> Bool #

Ord a => Ord (V3 a) Source # 
Instance details

Defined in NanoVG.Internal.FixedVector

Methods

compare :: V3 a -> V3 a -> Ordering #

(<) :: V3 a -> V3 a -> Bool #

(<=) :: V3 a -> V3 a -> Bool #

(>) :: V3 a -> V3 a -> Bool #

(>=) :: V3 a -> V3 a -> Bool #

max :: V3 a -> V3 a -> V3 a #

min :: V3 a -> V3 a -> V3 a #

Read a => Read (V3 a) Source # 
Instance details

Defined in NanoVG.Internal.FixedVector

Show a => Show (V3 a) Source # 
Instance details

Defined in NanoVG.Internal.FixedVector

Methods

showsPrec :: Int -> V3 a -> ShowS #

show :: V3 a -> String #

showList :: [V3 a] -> ShowS #

data V4 a Source #

Vector of 4 strict elements

Constructors

V4 !a !a !a !a 

Instances

Instances details
Functor V4 Source # 
Instance details

Defined in NanoVG.Internal.FixedVector

Methods

fmap :: (a -> b) -> V4 a -> V4 b #

(<$) :: a -> V4 b -> V4 a #

Foldable V4 Source # 
Instance details

Defined in NanoVG.Internal.FixedVector

Methods

fold :: Monoid m => V4 m -> m #

foldMap :: Monoid m => (a -> m) -> V4 a -> m #

foldMap' :: Monoid m => (a -> m) -> V4 a -> m #

foldr :: (a -> b -> b) -> b -> V4 a -> b #

foldr' :: (a -> b -> b) -> b -> V4 a -> b #

foldl :: (b -> a -> b) -> b -> V4 a -> b #

foldl' :: (b -> a -> b) -> b -> V4 a -> b #

foldr1 :: (a -> a -> a) -> V4 a -> a #

foldl1 :: (a -> a -> a) -> V4 a -> a #

toList :: V4 a -> [a] #

null :: V4 a -> Bool #

length :: V4 a -> Int #

elem :: Eq a => a -> V4 a -> Bool #

maximum :: Ord a => V4 a -> a #

minimum :: Ord a => V4 a -> a #

sum :: Num a => V4 a -> a #

product :: Num a => V4 a -> a #

Traversable V4 Source # 
Instance details

Defined in NanoVG.Internal.FixedVector

Methods

traverse :: Applicative f => (a -> f b) -> V4 a -> f (V4 b) #

sequenceA :: Applicative f => V4 (f a) -> f (V4 a) #

mapM :: Monad m => (a -> m b) -> V4 a -> m (V4 b) #

sequence :: Monad m => V4 (m a) -> m (V4 a) #

Eq a => Eq (V4 a) Source # 
Instance details

Defined in NanoVG.Internal.FixedVector

Methods

(==) :: V4 a -> V4 a -> Bool #

(/=) :: V4 a -> V4 a -> Bool #

Ord a => Ord (V4 a) Source # 
Instance details

Defined in NanoVG.Internal.FixedVector

Methods

compare :: V4 a -> V4 a -> Ordering #

(<) :: V4 a -> V4 a -> Bool #

(<=) :: V4 a -> V4 a -> Bool #

(>) :: V4 a -> V4 a -> Bool #

(>=) :: V4 a -> V4 a -> Bool #

max :: V4 a -> V4 a -> V4 a #

min :: V4 a -> V4 a -> V4 a #

Read a => Read (V4 a) Source # 
Instance details

Defined in NanoVG.Internal.FixedVector

Show a => Show (V4 a) Source # 
Instance details

Defined in NanoVG.Internal.FixedVector

Methods

showsPrec :: Int -> V4 a -> ShowS #

show :: V4 a -> String #

showList :: [V4 a] -> ShowS #

type M23 a = V2 (V3 a) Source #

Type synonym for 2x3 matrices