{-# LINE 1 "src/NanoVG/Internal/Text.chs" #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
module NanoVG.Internal.Text where
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Ptr as C2HSImp
import qualified Foreign.Storable as C2HSImp
import Control.Applicative (pure)
import Data.ByteString hiding (null)
import qualified Data.Set as S
import qualified Data.Text as T
import Foreign.C.Types
import Foreign.Marshal.Alloc
import Foreign.Ptr
import Foreign.Storable
import NanoVG.Internal.Context
import NanoVG.Internal.FFIHelpers
import NanoVG.Internal.FixedVector
import NanoVG.Internal.Types
import Prelude hiding (null)
{-# LINE 21 "src/NanoVG/Internal/Text.chs" #-}
data Align = AlignLeft
| AlignCenter
| AlignRight
| AlignTop
| AlignMiddle
| AlignBottom
| AlignBaseline
deriving (Show,Read,Eq,Ord)
instance Enum Align where
succ :: Align -> Align
succ Align
AlignLeft = Align
AlignCenter
succ Align
AlignCenter = Align
AlignRight
succ Align
AlignRight = Align
AlignTop
succ Align
AlignTop = Align
AlignMiddle
succ Align
AlignMiddle = Align
AlignBottom
succ Align
AlignBottom = Align
AlignBaseline
succ Align
AlignBaseline = String -> Align
forall a. HasCallStack => String -> a
error String
"Align.succ: AlignBaseline has no successor"
pred :: Align -> Align
pred Align
AlignCenter = Align
AlignLeft
pred Align
AlignRight = Align
AlignCenter
pred Align
AlignTop = Align
AlignRight
pred Align
AlignMiddle = Align
AlignTop
pred Align
AlignBottom = Align
AlignMiddle
pred Align
AlignBaseline = Align
AlignBottom
pred AlignLeft = String -> Align
forall a. HasCallStack => String -> a
error String
"Align.pred: AlignLeft has no predecessor"
enumFromTo from to = go from
where
end = fromEnum to
go v = case compare (fromEnum v) end of
LT -> v : go (succ v)
EQ -> [v]
GT -> []
enumFrom from = enumFromTo from AlignBaseline
fromEnum AlignLeft = 1
fromEnum AlignCenter = 2
fromEnum AlignRight = 4
fromEnum AlignTop = 8
fromEnum AlignMiddle = 16
fromEnum AlignBottom = 32
fromEnum AlignBaseline = 64
toEnum 1 = AlignLeft
toEnum 2 = AlignCenter
toEnum 4 = AlignRight
toEnum 8 = AlignTop
toEnum 16 = AlignMiddle
toEnum 32 = AlignBottom
toEnum 64 = AlignBaseline
toEnum unmatched = error ("Align.toEnum: Cannot match " ++ show unmatched)
{-# LINE 25 "src/NanoVG/Internal/Text.chs" #-}
newtype Font = Font {fontHandle :: CInt} deriving (Show,Read,Eq,Ord)
data TextRow =
TextRow {
start :: !(Ptr CChar)
, end :: !(Ptr CChar)
, next :: !(Ptr CChar)
, width :: !CFloat
, textRowMinX :: !CFloat
, textRowMaxX :: !CFloat}
deriving (Show,Eq,Ord)
instance Storable TextRow where
sizeOf _ = 40
alignment _ = 8
{-# LINE 46 "src/NanoVG/Internal/Text.chs" #-}
peek p =
do start <- (\ptr -> do {C2HSImp.peekByteOff ptr 0 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p
end <- (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p
next <- (\ptr -> do {C2HSImp.peekByteOff ptr 16 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p
width <- (\ptr -> do {C2HSImp.peekByteOff ptr 24 :: IO C2HSImp.CFloat}) p
minX <- (\ptr -> do {C2HSImp.peekByteOff ptr 28 :: IO C2HSImp.CFloat}) p
maxX <- (\ptr -> do {C2HSImp.peekByteOff ptr 32 :: IO C2HSImp.CFloat}) p
pure (TextRow start end next width minX maxX)
poke p (TextRow {..}) =
do (\ptr val -> do {C2HSImp.pokeByteOff ptr 0 (val :: (C2HSImp.Ptr C2HSImp.CChar))}) p start
(\ptr val -> do {C2HSImp.pokeByteOff ptr 8 (val :: (C2HSImp.Ptr C2HSImp.CChar))}) p end
(\ptr val -> do {C2HSImp.pokeByteOff ptr 16 (val :: (C2HSImp.Ptr C2HSImp.CChar))}) p next
(\ptr val -> do {C2HSImp.pokeByteOff ptr 24 (val :: C2HSImp.CFloat)}) p width
(\ptr val -> do {C2HSImp.pokeByteOff ptr 28 (val :: C2HSImp.CFloat)}) p textRowMinX
(\ptr val -> do {C2HSImp.pokeByteOff ptr 32 (val :: C2HSImp.CFloat)}) p textRowMaxX
type TextRowPtr = C2HSImp.Ptr (TextRow)
{-# LINE 63 "src/NanoVG/Internal/Text.chs" #-}
data GlyphPosition =
GlyphPosition {
str :: !(Ptr CChar)
, glyphX :: !CFloat
, glyphPosMinX :: !CFloat
, glyphPosMaxX :: !CFloat} deriving (Show,Eq,Ord)
instance Storable GlyphPosition where
sizeOf _ = 24
alignment _ = 8
{-# LINE 77 "src/NanoVG/Internal/Text.chs" #-}
peek p =
do str <- (\ptr -> do {C2HSImp.peekByteOff ptr 0 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p
x <- (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO C2HSImp.CFloat}) p
minx <- (\ptr -> do {C2HSImp.peekByteOff ptr 12 :: IO C2HSImp.CFloat}) p
maxx <- (\ptr -> do {C2HSImp.peekByteOff ptr 16 :: IO C2HSImp.CFloat}) p
pure (GlyphPosition str x minx maxx)
poke p (GlyphPosition str x minx maxx) =
do (\ptr val -> do {C2HSImp.pokeByteOff ptr 0 (val :: (C2HSImp.Ptr C2HSImp.CChar))}) p str
(\ptr val -> do {C2HSImp.pokeByteOff ptr 8 (val :: C2HSImp.CFloat)}) p x
(\ptr val -> do {C2HSImp.pokeByteOff ptr 12 (val :: C2HSImp.CFloat)}) p minx
(\ptr val -> do {C2HSImp.pokeByteOff ptr 16 (val :: C2HSImp.CFloat)}) p maxx
type GlyphPositionPtr = C2HSImp.Ptr (GlyphPosition)
{-# LINE 90 "src/NanoVG/Internal/Text.chs" #-}
safeFont :: CInt -> Maybe Font
safeFont :: CInt -> Maybe Font
safeFont CInt
i
| CInt
i CInt -> CInt -> Bool
forall a. Ord a => a -> a -> Bool
< CInt
0 = Maybe Font
forall a. Maybe a
Nothing
| Bool
otherwise = Font -> Maybe Font
forall a. a -> Maybe a
Just (CInt -> Font
Font CInt
i)
createFont :: (Context) -> (T.Text) -> (FileName) -> IO ((Maybe Font))
createFont :: Context -> Text -> FileName -> IO (Maybe Font)
createFont Context
a1 Text
a2 FileName
a3 =
let {a1' :: Context
a1' = Context -> Context
forall a. a -> a
id Context
a1} in
Text -> (Ptr CChar -> IO (Maybe Font)) -> IO (Maybe Font)
forall b. Text -> (Ptr CChar -> IO b) -> IO b
withCString Text
a2 ((Ptr CChar -> IO (Maybe Font)) -> IO (Maybe Font))
-> (Ptr CChar -> IO (Maybe Font)) -> IO (Maybe Font)
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
a2' ->
(Text -> (Ptr CChar -> IO (Maybe Font)) -> IO (Maybe Font)
forall b. Text -> (Ptr CChar -> IO b) -> IO b
withCString(Text -> (Ptr CChar -> IO (Maybe Font)) -> IO (Maybe Font))
-> (FileName -> Text)
-> FileName
-> (Ptr CChar -> IO (Maybe Font))
-> IO (Maybe Font)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.FileName -> Text
unwrapFileName) FileName
a3 ((Ptr CChar -> IO (Maybe Font)) -> IO (Maybe Font))
-> (Ptr CChar -> IO (Maybe Font)) -> IO (Maybe Font)
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
a3' ->
Context -> Ptr CChar -> Ptr CChar -> IO CInt
createFont'_ Context
a1' Ptr CChar
a2' Ptr CChar
a3' IO CInt -> (CInt -> IO (Maybe Font)) -> IO (Maybe Font)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \CInt
res ->
let {res' :: Maybe Font
res' = CInt -> Maybe Font
safeFont CInt
res} in
return (res')
{-# LINE 100 "src/NanoVG/Internal/Text.chs" #-}
createFontAtIndex :: (Context) -> (T.Text) -> (FileName) -> (CInt) -> IO ((Maybe Font))
createFontAtIndex a1 a2 a3 a4 =
let {a1' = id a1} in
withCString a2 $ \a2' ->
(withCString.unwrapFileName) a3 $ \a3' ->
let {a4' = fromIntegral a4} in
createFontAtIndex'_ a1' a2' a3' a4' >>= \res ->
let {res' = safeFont res} in
return (res')
{-# LINE 106 "src/NanoVG/Internal/Text.chs" #-}
createFontMem :: (Context) -> (T.Text) -> (ByteString) -> IO ((Maybe Font))
createFontMem a1 a2 a3 =
let {a1' = id a1} in
withCString a2 $ \a2' ->
useAsCStringLen' a3 $ \(a3'1, a3'2) ->
one $ \a4' ->
createFontMem'_ a1' a2' a3'1 a3'2 a4' >>= \res ->
let {res' = safeFont res} in
return (res')
{-# LINE 111 "src/NanoVG/Internal/Text.chs" #-}
createFontMemAtIndex :: (Context) -> (T.Text) -> (ByteString) -> (CInt) -> IO ((Maybe Font))
createFontMemAtIndex a1 a2 a3 a5 =
let {a1' = id a1} in
withCString a2 $ \a2' ->
useAsCStringLen' a3 $ \(a3'1, a3'2) ->
one $ \a4' ->
let {a5' = fromIntegral a5} in
createFontMemAtIndex'_ a1' a2' a3'1 a3'2 a4' a5' >>= \res ->
let {res' = safeFont res} in
return (res')
{-# LINE 117 "src/NanoVG/Internal/Text.chs" #-}
findFont :: (Context) -> (T.Text) -> IO ((Maybe Font))
findFont a1 a2 =
let {a1' = id a1} in
withCString a2 $ \a2' ->
findFont'_ a1' a2' >>= \res ->
let {res' = safeFont res} in
return (res')
{-# LINE 121 "src/NanoVG/Internal/Text.chs" #-}
addFallbackFontId :: (Context) -> (CInt) -> (CInt) -> IO ((Maybe Font))
addFallbackFontId a1 a2 a3 =
let {a1' = id a1} in
let {a2' = fromIntegral a2} in
let {a3' :: CInt
a3' = CInt -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
a3} in
Context -> CInt -> CInt -> IO CInt
addFallbackFontId'_ Context
a1' CInt
a2' CInt
a3' IO CInt -> (CInt -> IO (Maybe Font)) -> IO (Maybe Font)
>>= \res ->
let {res' = safeFont res} in
return (res')
{-# LINE 125 "src/NanoVG/Internal/Text.chs" #-}
addFallbackFont :: (Context) -> (T.Text) -> (T.Text) -> IO ((Maybe Font))
addFallbackFont a1 a2 a3 =
let {a1' = id a1} in
withCString a2 $ \a2' ->
withCString a3 $ \a3' ->
addFallbackFont'_ a1' a2' a3' >>= \res ->
let {res' = safeFont res} in
return (res')
{-# LINE 129 "src/NanoVG/Internal/Text.chs" #-}
resetFallbackFontsId :: (Context) -> (CInt) -> IO ()
resetFallbackFontsId a1 a2 =
let {a1' = id a1} in
let {a2' = fromIntegral a2} in
resetFallbackFontsId'_ a1' a2' >>
return ()
{-# LINE 133 "src/NanoVG/Internal/Text.chs" #-}
resetFallbackFonts :: (Context) -> (T.Text) -> IO ()
resetFallbackFonts a1 a2 =
let {a1' = id a1} in
withCString a2 $ \a2' ->
resetFallbackFonts'_ a1' a2' >>
return ()
{-# LINE 137 "src/NanoVG/Internal/Text.chs" #-}
fontSize :: (Context) -> (CFloat) -> IO ()
fontSize a1 a2 =
let {a1' = id a1} in
let {a2' = realToFrac a2} in
fontSize'_ a1' a2' >>
return ()
{-# LINE 141 "src/NanoVG/Internal/Text.chs" #-}
fontBlur :: (Context) -> (CFloat) -> IO ()
fontBlur a1 a2 =
let {a1' = id a1} in
let {a2' = realToFrac a2} in
fontBlur'_ a1' a2' >>
return ()
{-# LINE 145 "src/NanoVG/Internal/Text.chs" #-}
textLetterSpacing :: (Context) -> (CFloat) -> IO ()
textLetterSpacing a1 a2 =
let {a1' = id a1} in
let {a2' = realToFrac a2} in
textLetterSpacing'_ a1' a2' >>
return ()
{-# LINE 149 "src/NanoVG/Internal/Text.chs" #-}
textLineHeight :: (Context) -> (CFloat) -> IO ()
textLineHeight a1 a2 =
let {a1' = id a1} in
let {a2' = realToFrac a2} in
textLineHeight'_ a1' a2' >>
return ()
{-# LINE 153 "src/NanoVG/Internal/Text.chs" #-}
textAlign :: (Context) -> (S.Set Align) -> IO ()
textAlign a1 a2 =
let {a1' = id a1} in
let {a2' = bitMask a2} in
textAlign'_ a1' a2' >>
return ()
{-# LINE 157 "src/NanoVG/Internal/Text.chs" #-}
fontFaceId :: (Context) -> (Font) -> IO ()
fontFaceId a1 a2 =
let {a1' = id a1} in
let {a2' = fontHandle a2} in
fontFaceId'_ a1' a2' >>
return ()
{-# LINE 161 "src/NanoVG/Internal/Text.chs" #-}
fontFace :: (Context) -> (T.Text) -> IO ()
fontFace a1 a2 =
let {a1' = id a1} in
withCString a2 $ \a2' ->
fontFace'_ a1' a2' >>
return ()
{-# LINE 165 "src/NanoVG/Internal/Text.chs" #-}
text :: (Context) -> (CFloat) -> (CFloat) -> (Ptr CChar) -> (Ptr CChar) -> IO ()
text a1 a2 a3 a4 a5 =
let {a1' = id a1} in
let {a2' = realToFrac a2} in
let {a3' = realToFrac a3} in
let {a4' = id a4} in
let {a5' = id a5} in
text'_ a1' a2' a3' a4' a5' >>
return ()
{-# LINE 169 "src/NanoVG/Internal/Text.chs" #-}
textBox :: (Context) -> (CFloat) -> (CFloat) -> (CFloat) -> (T.Text) -> IO ()
textBox a1 a2 a3 a4 a5 =
let {a1' = id a1} in
let {a2' = realToFrac a2} in
let {a3' = realToFrac a3} in
let {a4' = realToFrac a4} in
withCString a5 $ \a5' ->
null $ \a6' ->
textBox'_ a1' a2' a3' a4' a5' a6' >>
return ()
{-# LINE 175 "src/NanoVG/Internal/Text.chs" #-}
newtype Bounds = Bounds (V4 CFloat) deriving (Show,Read,Eq,Ord)
instance Storable Bounds where
sizeOf _ = sizeOf (0 :: CFloat) * 4
alignment _ = alignment (0 :: CFloat)
peek p =
do let p' = castPtr p :: Ptr CFloat
a <- peekElemOff p' 0
b <- peekElemOff p' 1
c <- peekElemOff p' 2
d <- peekElemOff p' 3
pure (Bounds (V4 a b c d))
poke :: Ptr Bounds -> Bounds -> IO ()
poke Ptr Bounds
p (Bounds (V4 CFloat
a CFloat
b CFloat
c CFloat
d)) =
do let p' :: Ptr CFloat
p' = Ptr Bounds -> Ptr CFloat
forall a b. Ptr a -> Ptr b
castPtr Ptr Bounds
p :: Ptr CFloat
Ptr CFloat -> Int -> CFloat -> IO ()
forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr CFloat
p' Int
0 CFloat
a
Ptr CFloat -> Int -> CFloat -> IO ()
forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr CFloat
p' Int
1 CFloat
b
Ptr CFloat -> Int -> CFloat -> IO ()
forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr CFloat
p' Int
2 CFloat
c
Ptr CFloat -> Int -> CFloat -> IO ()
forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr CFloat
p' Int
3 CFloat
d
peekBounds :: Ptr CFloat -> IO Bounds
peekBounds :: Ptr CFloat -> IO Bounds
peekBounds = Ptr Bounds -> IO Bounds
forall a. Storable a => Ptr a -> IO a
peek (Ptr Bounds -> IO Bounds)
-> (Ptr CFloat -> Ptr Bounds) -> Ptr CFloat -> IO Bounds
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr CFloat -> Ptr Bounds
forall a b. Ptr a -> Ptr b
castPtr
allocaBounds :: (Ptr CFloat -> IO b) -> IO b
allocaBounds :: (Ptr CFloat -> IO b) -> IO b
allocaBounds Ptr CFloat -> IO b
f = (Ptr Bounds -> IO b) -> IO b
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca (\(Ptr Bounds
p :: Ptr Bounds) -> Ptr CFloat -> IO b
f (Ptr Bounds -> Ptr CFloat
forall a b. Ptr a -> Ptr b
castPtr Ptr Bounds
p))
textBounds :: (Context) -> (CFloat) -> (CFloat) -> (T.Text) -> IO ((Bounds))
textBounds :: Context -> CFloat -> CFloat -> Text -> IO Bounds
textBounds Context
a1 CFloat
a2 CFloat
a3 Text
a4 =
let {a1' :: Context
a1' = Context -> Context
forall a. a -> a
id Context
a1} in
let {a2' :: CFloat
a2' = CFloat -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
a2} in
let {a3' :: CFloat
a3' = CFloat -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
a3} in
Text -> (Ptr CChar -> IO Bounds) -> IO Bounds
forall b. Text -> (Ptr CChar -> IO b) -> IO b
withCString Text
a4 ((Ptr CChar -> IO Bounds) -> IO Bounds)
-> (Ptr CChar -> IO Bounds) -> IO Bounds
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
a4' ->
(Ptr CChar -> IO Bounds) -> IO Bounds
forall a b. (Ptr a -> b) -> b
null ((Ptr CChar -> IO Bounds) -> IO Bounds)
-> (Ptr CChar -> IO Bounds) -> IO Bounds
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
a5' ->
(Ptr CFloat -> IO Bounds) -> IO Bounds
forall b. (Ptr CFloat -> IO b) -> IO b
allocaBounds ((Ptr CFloat -> IO Bounds) -> IO Bounds)
-> (Ptr CFloat -> IO Bounds) -> IO Bounds
forall a b. (a -> b) -> a -> b
$ \a6' ->
textBounds'_ a1' a2' a3' a4' a5' a6' >>
peekBounds a6'>>= \a6'' ->
return (a6'')
{-# LINE 207 "src/NanoVG/Internal/Text.chs" #-}
textBoxBounds :: (Context) -> (CFloat) -> (CFloat) -> (CFloat) -> (T.Text) -> IO ((Bounds))
textBoxBounds a1 a2 a3 a4 a5 =
let {a1' = id a1} in
let {a2' = realToFrac a2} in
let {a3' = realToFrac a3} in
let {a4' = realToFrac a4} in
withCString a5 $ \a5' ->
null $ \a6' ->
allocaBounds $ \a7' ->
textBoxBounds'_ a1' a2' a3' a4' a5' a6' a7' >>
peekBounds a7'>>= \a7'' ->
return (a7'')
{-# LINE 213 "src/NanoVG/Internal/Text.chs" #-}
textGlyphPositions :: (Context) -> (CFloat) -> (CFloat) -> (Ptr CChar) -> (Ptr CChar) -> (GlyphPositionPtr) -> (CInt) -> IO ((CInt))
textGlyphPositions a1 a2 a3 a4 a5 a6 a7 =
let {a1' = id a1} in
let {a2' = realToFrac a2} in
let {a3' = realToFrac a3} in
let {a4' = id a4} in
let {a5' = id a5} in
let {a6' = id a6} in
let {a7' = fromIntegral a7} in
textGlyphPositions'_ a1' a2' a3' a4' a5' a6' a7' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 218 "src/NanoVG/Internal/Text.chs" #-}
textMetrics :: (Context) -> IO ((CFloat), (CFloat), (CFloat))
textMetrics a1 =
let {a1' = id a1} in
alloca $ \a2' ->
alloca $ \a3' ->
alloca $ \a4' ->
textMetrics'_ a1' a2' a3' a4' >>
peek a2'>>= \a2'' ->
peek a3'>>= \a3'' ->
peek a4'>>= \a4'' ->
return (a2'', a3'', a4'')
{-# LINE 223 "src/NanoVG/Internal/Text.chs" #-}
textBreakLines :: (Context) -> (Ptr CChar) -> (Ptr CChar) -> (CFloat) -> (TextRowPtr) -> (CInt) -> IO ((CInt))
textBreakLines a1 a2 a3 a4 a5 a6 =
let {a1' = id a1} in
let {a2' = id a2} in
let {a3' = id a3} in
let {a4' = realToFrac a4} in
let {a5' = id a5} in
let {a6' = fromIntegral a6} in
textBreakLines'_ a1' a2' a3' a4' a5' a6' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 229 "src/NanoVG/Internal/Text.chs" #-}
foreign import ccall unsafe "NanoVG/Internal/Text.chs.h nvgCreateFont"
createFont'_ :: ((Context) -> ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (IO C2HSImp.CInt))))
foreign import ccall unsafe "NanoVG/Internal/Text.chs.h nvgCreateFontAtIndex"
createFontAtIndex'_ :: ((Context) -> ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))))
foreign import ccall unsafe "NanoVG/Internal/Text.chs.h nvgCreateFontMem"
createFontMem'_ :: ((Context) -> ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CUChar) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO C2HSImp.CInt))))))
foreign import ccall unsafe "NanoVG/Internal/Text.chs.h nvgCreateFontMemAtIndex"
createFontMemAtIndex'_ :: ((Context) -> ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CUChar) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))))))
foreign import ccall unsafe "NanoVG/Internal/Text.chs.h nvgFindFont"
findFont'_ :: ((Context) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (IO C2HSImp.CInt)))
foreign import ccall unsafe "NanoVG/Internal/Text.chs.h nvgAddFallbackFontId"
addFallbackFontId'_ :: ((Context) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO C2HSImp.CInt))))
foreign import ccall unsafe "NanoVG/Internal/Text.chs.h nvgAddFallbackFont"
addFallbackFont'_ :: ((Context) -> ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (IO C2HSImp.CInt))))
foreign import ccall unsafe "NanoVG/Internal/Text.chs.h nvgResetFallbackFontsId"
resetFallbackFontsId'_ :: ((Context) -> (C2HSImp.CInt -> (IO ())))
foreign import ccall unsafe "NanoVG/Internal/Text.chs.h nvgResetFallbackFonts"
resetFallbackFonts'_ :: ((Context) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (IO ())))
foreign import ccall unsafe "NanoVG/Internal/Text.chs.h nvgFontSize"
fontSize'_ :: ((Context) -> (C2HSImp.CFloat -> (IO ())))
foreign import ccall unsafe "NanoVG/Internal/Text.chs.h nvgFontBlur"
fontBlur'_ :: ((Context) -> (C2HSImp.CFloat -> (IO ())))
foreign import ccall unsafe "NanoVG/Internal/Text.chs.h nvgTextLetterSpacing"
textLetterSpacing'_ :: ((Context) -> (C2HSImp.CFloat -> (IO ())))
foreign import ccall unsafe "NanoVG/Internal/Text.chs.h nvgTextLineHeight"
textLineHeight'_ :: ((Context) -> (C2HSImp.CFloat -> (IO ())))
foreign import ccall unsafe "NanoVG/Internal/Text.chs.h nvgTextAlign"
textAlign'_ :: ((Context) -> (C2HSImp.CInt -> (IO ())))
foreign import ccall unsafe "NanoVG/Internal/Text.chs.h nvgFontFaceId"
fontFaceId'_ :: ((Context) -> (C2HSImp.CInt -> (IO ())))
foreign import ccall unsafe "NanoVG/Internal/Text.chs.h nvgFontFace"
fontFace'_ :: ((Context) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (IO ())))
foreign import ccall unsafe "NanoVG/Internal/Text.chs.h nvgText"
text'_ :: ((Context) -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (IO C2HSImp.CFloat))))))
foreign import ccall unsafe "NanoVG/Internal/Text.chs.h nvgTextBox"
textBox'_ :: ((Context) -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (IO ())))))))
foreign import ccall unsafe "NanoVG/Internal/Text.chs.h nvgTextBounds"
textBounds'_ :: ((Context) -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO C2HSImp.CFloat)))))))
foreign import ccall unsafe "NanoVG/Internal/Text.chs.h nvgTextBoxBounds"
textBoxBounds'_ :: ((Context) -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))))))
foreign import ccall unsafe "NanoVG/Internal/Text.chs.h nvgTextGlyphPositions"
textGlyphPositions'_ :: ((Context) -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CChar) -> ((GlyphPositionPtr) -> (C2HSImp.CInt -> (IO C2HSImp.CInt))))))))
foreign import ccall unsafe "NanoVG/Internal/Text.chs.h nvgTextMetrics"
textMetrics'_ :: ((Context) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))))
foreign import ccall unsafe "NanoVG/Internal/Text.chs.h nvgTextBreakLines"
textBreakLines'_ :: ((Context) -> ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CFloat -> ((TextRowPtr) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))))))