{-# LINE 1 "src/KB/Text/Shape/FFI/API/Direct.hsc" #-}
module KB.Text.Shape.FFI.API.Direct where
import Prelude hiding (id, error)
import Foreign
import Foreign.C
import KB.Text.Shape.FFI.Allocator (Allocator)
import KB.Text.Shape.FFI.Handles
import KB.Text.Shape.FFI.Enums
import KB.Text.Shape.FFI.Structs
foreign import ccall safe "kbts_ShapeDirect" kbts_ShapeDirect
:: ShapeConfig
-> Ptr GlyphStorage
-> Direction
-> FunPtr Allocator
-> Ptr ()
-> Ptr GlyphIterator
-> IO ShapeError
foreign import ccall unsafe "kbts_ShapeDirectFixedMemory" kbts_ShapeDirectFixedMemory
:: ShapeConfig
-> Ptr GlyphStorage
-> Direction
-> Ptr ()
-> CInt
-> IO ShapeError
{-# LINE 37 "src/KB/Text/Shape/FFI/API/Direct.hsc" #-}
foreign import ccall safe "hs_FontFromFile" hs_FontFromFile
:: Ptr CChar
-> CInt
-> FunPtr Allocator
-> Ptr ()
-> Ptr (Ptr ())
-> Ptr CInt
-> Ptr Font
-> IO LoadFontError
{-# LINE 48 "src/KB/Text/Shape/FFI/API/Direct.hsc" #-}
foreign import ccall unsafe "kbts_FontCount" kbts_FontCount
:: Ptr ()
-> CInt
-> CInt
foreign import ccall safe "hs_FontFromMemory" hs_FontFromMemory
:: Ptr ()
-> CInt
-> CInt
-> FunPtr Allocator
-> Ptr ()
-> Font
-> IO LoadFontError
foreign import ccall safe "kbts_FreeFont" kbts_FreeFont
:: Font
-> IO ()
foreign import ccall unsafe "kbts_FontIsValid" kbts_FontIsValid
:: Font
-> CInt
data LoadFontState = LoadFontState
deriving (Int -> LoadFontState -> ShowS
[LoadFontState] -> ShowS
LoadFontState -> String
(Int -> LoadFontState -> ShowS)
-> (LoadFontState -> String)
-> ([LoadFontState] -> ShowS)
-> Show LoadFontState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LoadFontState -> ShowS
showsPrec :: Int -> LoadFontState -> ShowS
$cshow :: LoadFontState -> String
show :: LoadFontState -> String
$cshowList :: [LoadFontState] -> ShowS
showList :: [LoadFontState] -> ShowS
Show)
instance Storable LoadFontState where
alignment :: LoadFontState -> Int
alignment ~LoadFontState
_ = Int
8
{-# LINE 95 "src/KB/Text/Shape/FFI/API/Direct.hsc" #-}
sizeOf ~_ = (144)
{-# LINE 96 "src/KB/Text/Shape/FFI/API/Direct.hsc" #-}
peek _ptr = pure LoadFontState
poke :: Ptr LoadFontState -> LoadFontState -> IO ()
poke Ptr LoadFontState
ptr LoadFontState{} = Ptr LoadFontState -> Word8 -> Int -> IO ()
forall a. Ptr a -> Word8 -> Int -> IO ()
fillBytes Ptr LoadFontState
ptr Word8
0x00 ((Int
144))
{-# LINE 98 "src/KB/Text/Shape/FFI/API/Direct.hsc" #-}
foreign import ccall unsafe "kbts_LoadFont" kbts_LoadFont
:: Font
-> Ptr LoadFontState
-> Ptr ()
-> CInt
-> CInt
-> Ptr Int
-> Ptr Int
-> IO LoadFontError
foreign import ccall unsafe "kbts_PlaceBlob" kbts_PlaceBlob
:: Font
-> Ptr LoadFontState
-> Ptr ()
-> Ptr ()
-> IO LoadFontError
foreign import ccall unsafe "kbts_GetFontInfo" kbts_GetFontInfo
:: Font
-> Ptr FontInfo
-> IO ()
foreign import ccall unsafe "kbts_SizeOfShapeConfig" kbts_SizeOfShapeConfig
:: Font
-> Script
-> Language
-> CInt
foreign import ccall unsafe "kbts_PlaceShapeConfig" kbts_PlaceShapeConfig
:: Font
-> Script
-> Language
-> Ptr ()
-> IO ShapeConfig
foreign import ccall unsafe "kbts_CreateShapeConfig" kbts_CreateShapeConfig
:: Font
-> Script
-> Language
-> FunPtr Allocator
-> Ptr ()
-> IO ShapeConfig
foreign import ccall unsafe "kbts_DestroyShapeConfig" kbts_DestroyShapeConfig
:: ShapeConfig
-> IO ()
foreign import ccall unsafe "kbts_InitializeGlyphStorage" kbts_InitializeGlyphStorage
:: Ptr GlyphStorage
-> FunPtr Allocator
-> Ptr ()
-> IO Int
foreign import ccall unsafe "kbts_InitializeGlyphStorageFixedMemory" kbts_InitializeGlyphStorageFixedMemory
:: Ptr GlyphStorage
-> Ptr ()
-> CInt
-> IO Int
foreign import ccall unsafe "kbts_PushGlyph" kbts_PushGlyph
:: Ptr GlyphStorage
-> Font
-> CInt
-> GlyphConfig
-> CInt
-> IO (Ptr Glyph)
foreign import ccall unsafe "kbts_ClearActiveGlyphs" kbts_ClearActiveGlyphs
:: Ptr GlyphStorage
-> IO ()
foreign import ccall unsafe "kbts_FreeAllGlyphs" kbts_FreeAllGlyphs
:: Ptr GlyphStorage
-> IO ()
foreign import ccall unsafe "hs_CodepointToGlyph" hs_CodepointToGlyph
:: Font
-> CInt
-> GlyphConfig
-> CInt
-> Ptr Glyph
-> IO ()
foreign import ccall unsafe "kbts_CodepointToGlyphId" kbts_CodepointToGlyphId
:: Font
-> CInt
-> IO Int
foreign import ccall unsafe "hs_ActiveGlyphIterator" hs_ActiveGlyphIterator
:: Ptr GlyphStorage
-> Ptr GlyphIterator
-> IO ()
foreign import ccall unsafe "kbts_SizeOfGlyphConfig" kbts_SizeOfGlyphConfig
:: Ptr FeatureOverride
-> CInt
-> CInt
foreign import ccall unsafe "kbts_PlaceGlyphConfig" kbts_PlaceGlyphConfig
:: Ptr FeatureOverride
-> CInt
-> Ptr ()
-> IO GlyphConfig
foreign import ccall safe "kbts_CreateGlyphConfig" kbts_CreateGlyphConfig
:: Ptr FeatureOverride
-> CInt
-> FunPtr Allocator
-> Ptr ()
-> IO GlyphConfig
foreign import ccall unsafe "kbts_DestroyGlyphConfig" kbts_DestroyGlyphConfig
:: GlyphConfig
-> IO ()