nanovg-0.8.0.0: Haskell bindings for nanovg
Safe HaskellSafe-Inferred
LanguageHaskell2010

NanoVG.Internal.Text

Synopsis

Documentation

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 #

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 #

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

data GlyphPosition Source #

Constructors

GlyphPosition 

Fields

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 image by loading it from the specified memory chunk. Returns handle to the font.

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

Creates image 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.

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

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.

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