module KB.Text.Shape
(
withContext
, Context(..)
, createContext
, destroyContext
, Handles.Font
, pushFontFromFile
, pushFontFromMemory
, pushFont
, popFont
, run
, Run(..)
, Glyph(..)
, gpos
, GPOS(..)
, text_
, char_
, withFeature_
, pushFeature_
, popFeature_
, stripGlyph
) where
import Control.Monad
import Data.IORef
import Foreign
import Foreign.C
import Prelude hiding (id)
import Control.Exception (bracket)
import Data.ByteString (ByteString)
import Data.ByteString.Unsafe qualified as ByteString
import Data.Char (chr, ord)
import Data.IntMap (IntMap)
import Data.IntMap.Strict qualified as IntMap
import Data.Text (Text)
import Data.Text.Foreign qualified as Text
import GHC.Records (HasField(..))
import KB.Text.Shape.FFI.API.Context qualified as ShapeContext
import KB.Text.Shape.FFI.Enums qualified as Enums
import KB.Text.Shape.FFI.Flags qualified as Flags
import KB.Text.Shape.FFI.Handles qualified as Handles
import KB.Text.Shape.FFI.Iterators qualified as Iterators
import KB.Text.Shape.FFI.Structs qualified as Structs
withContext :: (Context -> IO r) -> IO r
withContext :: forall r. (Context -> IO r) -> IO r
withContext = IO Context -> (Context -> IO ()) -> (Context -> IO r) -> IO r
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket IO Context
createContext Context -> IO ()
destroyContext
data Context = Context
{ Context -> ShapeContext
handle :: Handles.ShapeContext
, Context -> IORef (IntMap ByteStringRC)
fonts :: IORef (IntMap ByteStringRC)
}
data ByteStringRC = ByteStringRC ByteString Int
createContext :: IO Context
createContext :: IO Context
createContext = do
handle <- FunPtr Allocator -> Ptr () -> IO ShapeContext
ShapeContext.kbts_CreateShapeContext FunPtr Allocator
forall a. FunPtr a
nullFunPtr Ptr ()
forall a. Ptr a
nullPtr
when (handle == Handles.ShapeContext nullPtr) $
error "kbts_CreateShapeContext: failed to init"
fonts <- newIORef mempty
pure Context{handle, fonts}
destroyContext :: Context -> IO ()
destroyContext :: Context -> IO ()
destroyContext Context{ShapeContext
handle :: Context -> ShapeContext
handle :: ShapeContext
handle} = ShapeContext -> IO ()
ShapeContext.kbts_DestroyShapeContext ShapeContext
handle
pushFontFromFile :: Context -> FilePath -> Int -> IO Handles.Font
pushFontFromFile :: Context -> [Char] -> Int -> IO Font
pushFontFromFile Context
ctx [Char]
path Int
fontIndex = do
font <- [Char] -> (CString -> IO Font) -> IO Font
forall a. [Char] -> (CString -> IO a) -> IO a
withCString [Char]
path \CString
pathPtr ->
ShapeContext -> CString -> CInt -> IO Font
ShapeContext.kbts_ShapePushFontFromFile Context
ctx.handle CString
pathPtr (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
fontIndex)
let err = ShapeContext -> ShapeError
ShapeContext.kbts_ShapeError Context
ctx.handle
when (err /= Enums.SHAPE_ERROR_NONE) $
error $ "kbts_ShapePushFontFromFile: failed to load font. " <> show err
_ <- keepFont ctx font mempty
pure font
pushFontFromMemory :: Context -> ByteString -> Int -> IO Handles.Font
pushFontFromMemory :: Context -> ByteString -> Int -> IO Font
pushFontFromMemory Context
ctx ByteString
fontData Int
fontIndex =
ByteString -> (CStringLen -> IO Font) -> IO Font
forall a. ByteString -> (CStringLen -> IO a) -> IO a
ByteString.unsafeUseAsCStringLen ByteString
fontData \(CString
memoryPtr, Int
memorySize) -> do
font <- ShapeContext -> Ptr () -> CSize -> CInt -> IO Font
ShapeContext.kbts_ShapePushFontFromMemory Context
ctx.handle (CString -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr CString
memoryPtr) (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
memorySize) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
fontIndex)
let err = ShapeContext -> ShapeError
ShapeContext.kbts_ShapeError Context
ctx.handle
when (err /= Enums.SHAPE_ERROR_NONE) $
error $ "kbts_ShapePushFontFromMemory: failed to load font. " <> show err
_ <- keepFont ctx font fontData
pure font
keepFont :: Context -> Handles.Font -> ByteString -> IO Int
keepFont :: Context -> Font -> ByteString -> IO Int
keepFont Context
ctx Font
font ByteString
bytes = IORef (IntMap ByteStringRC)
-> (IntMap ByteStringRC -> (IntMap ByteStringRC, Int)) -> IO Int
forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef' Context
ctx.fonts ((IntMap ByteStringRC -> (IntMap ByteStringRC, Int)) -> IO Int)
-> (IntMap ByteStringRC -> (IntMap ByteStringRC, Int)) -> IO Int
forall a b. (a -> b) -> a -> b
$ (Int, IntMap ByteStringRC) -> (IntMap ByteStringRC, Int)
forall {b} {a}. (b, a) -> (a, b)
swap ((Int, IntMap ByteStringRC) -> (IntMap ByteStringRC, Int))
-> (IntMap ByteStringRC -> (Int, IntMap ByteStringRC))
-> IntMap ByteStringRC
-> (IntMap ByteStringRC, Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe ByteStringRC -> (Int, Maybe ByteStringRC))
-> Int -> IntMap ByteStringRC -> (Int, IntMap ByteStringRC)
forall (f :: * -> *) a.
Functor f =>
(Maybe a -> f (Maybe a)) -> Int -> IntMap a -> f (IntMap a)
IntMap.alterF Maybe ByteStringRC -> (Int, Maybe ByteStringRC)
addRef (Font -> Int
forall h a. Coercible h (Ptr a) => h -> Int
Handles.intHandle Font
font)
where
swap :: (b, a) -> (a, b)
swap (b
a, a
b) = (a
b, b
a)
addRef :: Maybe ByteStringRC -> (Int, Maybe ByteStringRC)
addRef :: Maybe ByteStringRC -> (Int, Maybe ByteStringRC)
addRef = \case
Maybe ByteStringRC
Nothing -> (Int
1, ByteStringRC -> Maybe ByteStringRC
forall a. a -> Maybe a
Just (ByteStringRC -> Maybe ByteStringRC)
-> ByteStringRC -> Maybe ByteStringRC
forall a b. (a -> b) -> a -> b
$ ByteString -> Int -> ByteStringRC
ByteStringRC ByteString
bytes Int
1)
Just (ByteStringRC ByteString
oldBytes Int
oldC) -> (Int
newC, ByteStringRC -> Maybe ByteStringRC
forall a. a -> Maybe a
Just (ByteStringRC -> Maybe ByteStringRC)
-> ByteStringRC -> Maybe ByteStringRC
forall a b. (a -> b) -> a -> b
$ ByteString -> Int -> ByteStringRC
ByteStringRC ByteString
oldBytes Int
newC)
where
newC :: Int
newC = Int
oldC Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
releaseFont :: Context -> Handles.Font -> IO Int
releaseFont :: Context -> Font -> IO Int
releaseFont Context
ctx Font
font = IORef (IntMap ByteStringRC)
-> (IntMap ByteStringRC -> (IntMap ByteStringRC, Int)) -> IO Int
forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef' Context
ctx.fonts ((IntMap ByteStringRC -> (IntMap ByteStringRC, Int)) -> IO Int)
-> (IntMap ByteStringRC -> (IntMap ByteStringRC, Int)) -> IO Int
forall a b. (a -> b) -> a -> b
$ (Int, IntMap ByteStringRC) -> (IntMap ByteStringRC, Int)
forall {b} {a}. (b, a) -> (a, b)
swap ((Int, IntMap ByteStringRC) -> (IntMap ByteStringRC, Int))
-> (IntMap ByteStringRC -> (Int, IntMap ByteStringRC))
-> IntMap ByteStringRC
-> (IntMap ByteStringRC, Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe ByteStringRC -> (Int, Maybe ByteStringRC))
-> Int -> IntMap ByteStringRC -> (Int, IntMap ByteStringRC)
forall (f :: * -> *) a.
Functor f =>
(Maybe a -> f (Maybe a)) -> Int -> IntMap a -> f (IntMap a)
IntMap.alterF Maybe ByteStringRC -> (Int, Maybe ByteStringRC)
delRef (Font -> Int
forall h a. Coercible h (Ptr a) => h -> Int
Handles.intHandle Font
font)
where
swap :: (b, a) -> (a, b)
swap (b
a, a
b) = (a
b, b
a)
delRef :: Maybe ByteStringRC -> (Int, Maybe ByteStringRC)
delRef :: Maybe ByteStringRC -> (Int, Maybe ByteStringRC)
delRef = \case
Maybe ByteStringRC
Nothing -> (-Int
1, Maybe ByteStringRC
forall a. Maybe a
Nothing)
Just (ByteStringRC ByteString
_old Int
1) -> (Int
0, Maybe ByteStringRC
forall a. Maybe a
Nothing)
Just (ByteStringRC ByteString
stillUsed Int
oldC) -> (Int
newC, ByteStringRC -> Maybe ByteStringRC
forall a. a -> Maybe a
Just (ByteStringRC -> Maybe ByteStringRC)
-> ByteStringRC -> Maybe ByteStringRC
forall a b. (a -> b) -> a -> b
$ ByteString -> Int -> ByteStringRC
ByteStringRC ByteString
stillUsed Int
newC)
where newC :: Int
newC = Int
oldC Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1
pushFont :: Context -> Handles.Font -> IO Int
pushFont :: Context -> Font -> IO Int
pushFont Context
ctx Font
font = do
font' <- ShapeContext -> Font -> IO Font
ShapeContext.kbts_ShapePushFont Context
ctx.handle Font
font
keepFont ctx font' mempty
popFont :: Context -> IO (Int, Handles.Font)
popFont :: Context -> IO (Int, Font)
popFont Context
ctx = do
font <- ShapeContext -> IO Font
ShapeContext.kbts_ShapePopFont Context
ctx.handle
kept <- releaseFont ctx font
pure (kept, font)
run :: Context -> ((?shapeContext :: Handles.ShapeContext) => IO ()) -> IO [(Run, [Glyph])]
run :: Context
-> ((?shapeContext::ShapeContext) => IO ()) -> IO [(Run, [Glyph])]
run Context
ctx (?shapeContext::ShapeContext) => IO ()
action = do
ShapeContext -> Direction -> Language -> IO ()
ShapeContext.kbts_ShapeBegin Context
ctx.handle Direction
Enums.DIRECTION_DONT_KNOW Language
Enums.LANGUAGE_DONT_KNOW
IO ()
shapeAction
ShapeContext -> IO ()
ShapeContext.kbts_ShapeEnd Context
ctx.handle
Context -> IO [(Run, [Glyph])]
iterateRun Context
ctx
where
shapeAction :: IO ()
shapeAction = let ?shapeContext = Context
ctx.handle in IO ()
(?shapeContext::ShapeContext) => IO ()
action
char_ :: (?shapeContext :: Handles.ShapeContext) => Char -> IO ()
char_ :: (?shapeContext::ShapeContext) => Char -> IO ()
char_ Char
c = ShapeContext -> CInt -> IO ()
ShapeContext.kbts_ShapeCodepoint ?shapeContext::ShapeContext
ShapeContext
?shapeContext (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Int
ord Char
c))
text_ :: (?shapeContext :: Handles.ShapeContext) => Text -> IO ()
text_ :: (?shapeContext::ShapeContext) => Text -> IO ()
text_ Text
t =
Text -> (CStringLen -> IO ()) -> IO ()
forall a. Text -> (CStringLen -> IO a) -> IO a
Text.withCStringLen Text
t \(CString
strPtr, Int
strLen) ->
ShapeContext -> CString -> CInt -> UserIdGenerationMode -> IO ()
ShapeContext.kbts_ShapeUtf8
?shapeContext::ShapeContext
ShapeContext
?shapeContext
CString
strPtr
(Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
strLen)
UserIdGenerationMode
Enums.USER_ID_GENERATION_MODE_CODEPOINT_INDEX
withFeature_ :: (?shapeContext :: Handles.ShapeContext) => Enums.FeatureTag -> Int -> IO r -> IO r
withFeature_ :: forall r.
(?shapeContext::ShapeContext) =>
FeatureTag -> Int -> IO r -> IO r
withFeature_ FeatureTag
tag Int
value IO r
action = do
ShapeContext -> FeatureTag -> CInt -> IO ()
ShapeContext.kbts_ShapePushFeature ?shapeContext::ShapeContext
ShapeContext
?shapeContext FeatureTag
tag (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
value)
r <- IO r
action
_ <- ShapeContext.kbts_ShapePopFeature ?shapeContext tag
pure r
pushFeature_ :: (?shapeContext :: Handles.ShapeContext) => Enums.FeatureTag -> Int -> IO ()
pushFeature_ :: (?shapeContext::ShapeContext) => FeatureTag -> Int -> IO ()
pushFeature_ FeatureTag
tag Int
value = ShapeContext -> FeatureTag -> CInt -> IO ()
ShapeContext.kbts_ShapePushFeature ?shapeContext::ShapeContext
ShapeContext
?shapeContext FeatureTag
tag (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
value)
popFeature_ :: (?shapeContext :: Handles.ShapeContext) => Enums.FeatureTag -> IO Int
popFeature_ :: (?shapeContext::ShapeContext) => FeatureTag -> IO Int
popFeature_ FeatureTag
tag = CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CInt -> Int) -> IO CInt -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ShapeContext -> FeatureTag -> IO CInt
ShapeContext.kbts_ShapePopFeature ?shapeContext::ShapeContext
ShapeContext
?shapeContext FeatureTag
tag
data Run = Run
{ Run -> Font
font :: Handles.Font
, Run -> Script
script :: Enums.Script
, Run -> Direction
paragraphDirection :: Enums.Direction
, Run -> Direction
direction :: Enums.Direction
, Run -> BreakFlags
flags :: Flags.BreakFlags
} deriving (Run -> Run -> Bool
(Run -> Run -> Bool) -> (Run -> Run -> Bool) -> Eq Run
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Run -> Run -> Bool
== :: Run -> Run -> Bool
$c/= :: Run -> Run -> Bool
/= :: Run -> Run -> Bool
Eq, Int -> Run -> [Char] -> [Char]
[Run] -> [Char] -> [Char]
Run -> [Char]
(Int -> Run -> [Char] -> [Char])
-> (Run -> [Char]) -> ([Run] -> [Char] -> [Char]) -> Show Run
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
$cshowsPrec :: Int -> Run -> [Char] -> [Char]
showsPrec :: Int -> Run -> [Char] -> [Char]
$cshow :: Run -> [Char]
show :: Run -> [Char]
$cshowList :: [Run] -> [Char] -> [Char]
showList :: [Run] -> [Char] -> [Char]
Show)
iterateRun :: Context -> IO [(Run, [Glyph])]
iterateRun :: Context -> IO [(Run, [Glyph])]
iterateRun Context
ctx =
(Ptr Run -> IO [(Run, [Glyph])]) -> IO [(Run, [Glyph])]
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca \Ptr Run
runPtr ->
(Ptr (Ptr Glyph) -> IO [(Run, [Glyph])]) -> IO [(Run, [Glyph])]
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca \Ptr (Ptr Glyph)
glyphOutPtr ->
IO Bool -> IO (Run, [Glyph]) -> IO [(Run, [Glyph])]
forall (m :: * -> *) a. Monad m => m Bool -> m a -> m [a]
stepWhile (Ptr Run -> IO Bool
step Ptr Run
runPtr) (Ptr Run -> Ptr (Ptr Glyph) -> IO (Run, [Glyph])
collect Ptr Run
runPtr Ptr (Ptr Glyph)
glyphOutPtr)
where
step :: Ptr Run -> IO Bool
step Ptr Run
runPtr = (Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
0) (Int -> Bool) -> IO Int -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ShapeContext -> Ptr Run -> IO Int
ShapeContext.kbts_ShapeRun Context
ctx.handle Ptr Run
runPtr
collect :: Ptr Run -> Ptr (Ptr Glyph) -> IO (Run, [Glyph])
collect Ptr Run
runPtr Ptr (Ptr Glyph)
glyphOutPtr = do
Structs.Run{..} <- Ptr Run -> IO Run
forall a. Storable a => Ptr a -> IO a
peek Ptr Run
runPtr
(Run{..},) <$> iterateGlyphs glyphOutPtr (Structs.runGlyphIterator runPtr)
iterateGlyphs :: Ptr (Ptr Structs.Glyph) -> Ptr Structs.GlyphIterator -> IO [Glyph]
iterateGlyphs :: Ptr (Ptr Glyph) -> Ptr GlyphIterator -> IO [Glyph]
iterateGlyphs Ptr (Ptr Glyph)
glyphOutPtr Ptr GlyphIterator
it = IO Bool -> IO Glyph -> IO [Glyph]
forall (m :: * -> *) a. Monad m => m Bool -> m a -> m [a]
stepWhile IO Bool
step IO Glyph
fetch
where
step :: IO Bool
step = (Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
0) (Int -> Bool) -> IO Int -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr GlyphIterator -> Ptr (Ptr Glyph) -> IO Int
Iterators.kbts_GlyphIteratorNext Ptr GlyphIterator
it Ptr (Ptr Glyph)
glyphOutPtr
fetch :: IO Glyph
fetch = do
Ptr (Ptr Glyph) -> IO (Ptr Glyph)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr Glyph)
glyphOutPtr IO (Ptr Glyph) -> (Ptr Glyph -> IO Glyph) -> IO Glyph
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Glyph -> IO Glyph
forall a. Storable a => Ptr a -> IO a
peek IO Glyph -> (Glyph -> IO Glyph) -> IO Glyph
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Glyph -> IO Glyph
stripGlyph
stepWhile :: Monad m => m Bool -> m a -> m [a]
stepWhile :: forall (m :: * -> *) a. Monad m => m Bool -> m a -> m [a]
stepWhile m Bool
step m a
fetch = do
result <- m Bool
step
if result then do
x <- fetch
(x :) <$> stepWhile step fetch
else
pure []
data Glyph = Glyph
{
Glyph -> Char
codepoint :: Char
, Glyph -> Word16
id :: Word16
, Glyph -> Word16
uid :: Word16
, Glyph -> Int
codepointIndex :: Int
, Glyph -> Int
offsetX :: Int
, Glyph -> Int
offsetY :: Int
, Glyph -> Int
advanceX :: Int
, Glyph -> Int
advanceY :: Int
, Glyph -> Maybe Glyph
attachGlyph :: Maybe Glyph
, Glyph -> Word64
decomposition :: Word64
, Glyph -> Word32
classes :: Word32
, Glyph -> GlyphFlags
flags :: Flags.GlyphFlags
, Glyph -> UnicodeJoiningType
joiningType :: Enums.UnicodeJoiningType
, Glyph -> Word8
unicodeFlags :: Word8
, Glyph -> Word8
syllabicClass :: Word8
, Glyph -> Word8
syllabicPosition :: Word8
, Glyph -> Word8
useClass :: Word8
, Glyph -> Word8
combiningClass :: Word8
}
deriving (Glyph -> Glyph -> Bool
(Glyph -> Glyph -> Bool) -> (Glyph -> Glyph -> Bool) -> Eq Glyph
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Glyph -> Glyph -> Bool
== :: Glyph -> Glyph -> Bool
$c/= :: Glyph -> Glyph -> Bool
/= :: Glyph -> Glyph -> Bool
Eq, Int -> Glyph -> [Char] -> [Char]
[Glyph] -> [Char] -> [Char]
Glyph -> [Char]
(Int -> Glyph -> [Char] -> [Char])
-> (Glyph -> [Char]) -> ([Glyph] -> [Char] -> [Char]) -> Show Glyph
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
$cshowsPrec :: Int -> Glyph -> [Char] -> [Char]
showsPrec :: Int -> Glyph -> [Char] -> [Char]
$cshow :: Glyph -> [Char]
show :: Glyph -> [Char]
$cshowList :: [Glyph] -> [Char] -> [Char]
showList :: [Glyph] -> [Char] -> [Char]
Show)
instance HasField "gpos" Glyph (GPOS Int) where
{-# INLINE getField #-}
getField :: Glyph -> GPOS Int
getField = Glyph -> GPOS Int
gpos
{-# INLINE gpos #-}
gpos :: Glyph -> GPOS Int
gpos :: Glyph -> GPOS Int
gpos Glyph{Int
offsetX :: Glyph -> Int
offsetX :: Int
offsetX, Int
offsetY :: Glyph -> Int
offsetY :: Int
offsetY, Int
advanceX :: Glyph -> Int
advanceX :: Int
advanceX, Int
advanceY :: Glyph -> Int
advanceY :: Int
advanceY} = GPOS{Int
offsetX :: Int
offsetX :: Int
offsetX, Int
offsetY :: Int
offsetY :: Int
offsetY, Int
advanceX :: Int
advanceX :: Int
advanceX, Int
advanceY :: Int
advanceY :: Int
advanceY}
data GPOS a = GPOS
{ forall a. GPOS a -> a
offsetX, forall a. GPOS a -> a
offsetY, forall a. GPOS a -> a
advanceX, forall a. GPOS a -> a
advanceY :: a
}
deriving (GPOS a -> GPOS a -> Bool
(GPOS a -> GPOS a -> Bool)
-> (GPOS a -> GPOS a -> Bool) -> Eq (GPOS a)
forall a. Eq a => GPOS a -> GPOS a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => GPOS a -> GPOS a -> Bool
== :: GPOS a -> GPOS a -> Bool
$c/= :: forall a. Eq a => GPOS a -> GPOS a -> Bool
/= :: GPOS a -> GPOS a -> Bool
Eq, Int -> GPOS a -> [Char] -> [Char]
[GPOS a] -> [Char] -> [Char]
GPOS a -> [Char]
(Int -> GPOS a -> [Char] -> [Char])
-> (GPOS a -> [Char])
-> ([GPOS a] -> [Char] -> [Char])
-> Show (GPOS a)
forall a. Show a => Int -> GPOS a -> [Char] -> [Char]
forall a. Show a => [GPOS a] -> [Char] -> [Char]
forall a. Show a => GPOS a -> [Char]
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
$cshowsPrec :: forall a. Show a => Int -> GPOS a -> [Char] -> [Char]
showsPrec :: Int -> GPOS a -> [Char] -> [Char]
$cshow :: forall a. Show a => GPOS a -> [Char]
show :: GPOS a -> [Char]
$cshowList :: forall a. Show a => [GPOS a] -> [Char] -> [Char]
showList :: [GPOS a] -> [Char] -> [Char]
Show, (forall a b. (a -> b) -> GPOS a -> GPOS b)
-> (forall a b. a -> GPOS b -> GPOS a) -> Functor GPOS
forall a b. a -> GPOS b -> GPOS a
forall a b. (a -> b) -> GPOS a -> GPOS b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> GPOS a -> GPOS b
fmap :: forall a b. (a -> b) -> GPOS a -> GPOS b
$c<$ :: forall a b. a -> GPOS b -> GPOS a
<$ :: forall a b. a -> GPOS b -> GPOS a
Functor)
stripGlyph :: Structs.Glyph -> IO Glyph
stripGlyph :: Glyph -> IO Glyph
stripGlyph Structs.Glyph{Int
Int32
Word8
Word16
Word32
Word64
Ptr ()
Ptr Glyph
UnicodeJoiningType
UnicodeJoiningFeature
GlyphFlags
prev :: Ptr Glyph
next :: Ptr Glyph
codepoint :: Word32
id :: Word16
uid :: Word16
userIdOrCodepointIndex :: Int
offsetX :: Int32
offsetY :: Int32
advanceX :: Int32
advanceY :: Int32
attachGlyph :: Ptr Glyph
config :: Ptr ()
decomposition :: Word64
classes :: Word32
flags :: GlyphFlags
parentInfo :: Word32
ligatureUid :: Word16
ligatureComponentIndexPlusOne :: Word16
ligatureComponentCount :: Word16
joiningFeature :: UnicodeJoiningFeature
joiningType :: UnicodeJoiningType
unicodeFlags :: Word8
syllabicClass :: Word8
syllabicPosition :: Word8
useClass :: Word8
combiningClass :: Word8
markOrdering :: Word8
markOrdering :: Glyph -> Word8
combiningClass :: Glyph -> Word8
useClass :: Glyph -> Word8
syllabicPosition :: Glyph -> Word8
syllabicClass :: Glyph -> Word8
unicodeFlags :: Glyph -> Word8
joiningType :: Glyph -> UnicodeJoiningType
joiningFeature :: Glyph -> UnicodeJoiningFeature
ligatureComponentCount :: Glyph -> Word16
ligatureComponentIndexPlusOne :: Glyph -> Word16
ligatureUid :: Glyph -> Word16
parentInfo :: Glyph -> Word32
flags :: Glyph -> GlyphFlags
classes :: Glyph -> Word32
decomposition :: Glyph -> Word64
config :: Glyph -> Ptr ()
attachGlyph :: Glyph -> Ptr Glyph
advanceY :: Glyph -> Int32
advanceX :: Glyph -> Int32
offsetY :: Glyph -> Int32
offsetX :: Glyph -> Int32
userIdOrCodepointIndex :: Glyph -> Int
uid :: Glyph -> Word16
id :: Glyph -> Word16
codepoint :: Glyph -> Word32
next :: Glyph -> Ptr Glyph
prev :: Glyph -> Ptr Glyph
..} = do
attached <-
if Ptr Glyph
attachGlyph Ptr Glyph -> Ptr Glyph -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr Glyph
forall a. Ptr a
nullPtr then
Maybe Glyph -> IO (Maybe Glyph)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Glyph
forall a. Maybe a
Nothing
else
Glyph -> Maybe Glyph
forall a. a -> Maybe a
Just (Glyph -> Maybe Glyph) -> IO Glyph -> IO (Maybe Glyph)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Ptr Glyph -> IO Glyph
forall a. Storable a => Ptr a -> IO a
peek Ptr Glyph
attachGlyph IO Glyph -> (Glyph -> IO Glyph) -> IO Glyph
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Glyph -> IO Glyph
stripGlyph)
pure Glyph
{ codepoint = chr (fromIntegral codepoint)
, codepointIndex = userIdOrCodepointIndex
, attachGlyph = attached
, offsetX = fromIntegral offsetX
, offsetY = fromIntegral offsetY
, advanceX = fromIntegral advanceX
, advanceY = fromIntegral advanceY
, ..
}