kb-text-shape
Safe HaskellNone
LanguageGHC2021

KB.Text.Shape.FFI.Structs

Documentation

data FontInfo Source #

Constructors

FontInfo 

Fields

Instances

Instances details
Storable FontInfo Source # 
Instance details

Defined in KB.Text.Shape.FFI.Structs

Show FontInfo Source # 
Instance details

Defined in KB.Text.Shape.FFI.Structs

Eq FontInfo Source # 
Instance details

Defined in KB.Text.Shape.FFI.Structs

data Run Source #

Instances

Instances details
Storable Run Source # 
Instance details

Defined in KB.Text.Shape.FFI.Structs

Methods

sizeOf :: Run -> Int #

alignment :: Run -> Int #

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

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

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

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

peek :: Ptr Run -> IO Run #

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

Show Run Source # 
Instance details

Defined in KB.Text.Shape.FFI.Structs

Methods

showsPrec :: Int -> Run -> ShowS #

show :: Run -> String #

showList :: [Run] -> ShowS #

data Arena Source #

Instances

Instances details
Storable Arena Source # 
Instance details

Defined in KB.Text.Shape.FFI.Structs

Methods

sizeOf :: Arena -> Int #

alignment :: Arena -> Int #

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

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

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

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

peek :: Ptr Arena -> IO Arena #

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

Show Arena Source # 
Instance details

Defined in KB.Text.Shape.FFI.Structs

Methods

showsPrec :: Int -> Arena -> ShowS #

show :: Arena -> String #

showList :: [Arena] -> ShowS #

data Glyph Source #

Constructors

Glyph 

Fields

  • prev :: Ptr Glyph
     
  • next :: Ptr Glyph
     
  • codepoint :: Word32
     
  • id :: Word16

    Glyph index. This is what you want to use to query outline data.

  • uid :: Word16
     
  • userIdOrCodepointIndex :: Int

    This field is kept and returned as-is throughout the shaping process.

    When you are using the context API, it contains a codepoint index always! To get the original user ID with the context API, you need to get the corresponding kbts_shape_codepoint with kbts_ShapeGetShapeCodepoint(Context, Glyph->UserIdOrCodepointIndex, ...);

  • offsetX :: Int32
     
  • offsetY :: Int32
     
  • advanceX :: Int32
     
  • advanceY :: Int32
     
  • attachGlyph :: Ptr Glyph

    Set by GPOS attachments

    Earlier on, we used to assume that, if a glyph had no advance, or had the MARK glyph class, then it could be handled as a mark in layout operations. This is inaccurate. Unicode makes a distinction between attached marks and standalone marks. For our purposes, attached marks are marks that have found a valid base character to attach to. In practice, this means that the font contains a valid display position/configuration for it in the current context. In contrast, standalone marks are marks that aren't attached to anything. Fonts may still have glyphs for them, in which case we want to display those just like regular glyphs that take up horizontal space on the line. When fonts don't have glyphs for them, they simply stay around as zero-width glyphs. Standalone marks have notably different behavior compared to attached marks, and so, once we start applying positioning features, it becomes worthwhile to track exactly which glyph has attached to which.

  • config :: Ptr ()
     
  • decomposition :: Word64
     
  • classes :: Word32
     
  • flags :: GlyphFlags
     
  • parentInfo :: Word32
     
  • ligatureUid :: Word16

    This is set by GSUB and used by GPOS. A 0-index means that we should attach to the last component in the ligature.

    From the Microsoft docs: To correctly access the subtables, the client must keep track of the component associated with the mark.

    For a given mark assigned to a particular class, the appropriate base attachment point is determined by which ligature component the mark is associated with. This is dependent on the original character string and subsequent character- or glyph-sequence processing, not the font data alone. While a text-layout client is performing any character-based preprocessing or any glyph-substitution operations using the GSUB table, the text-layout client must keep track of associations of marks to particular ligature-glyph components.

  • ligatureComponentIndexPlusOne :: Word16
     
  • ligatureComponentCount :: Word16
     
  • joiningFeature :: UnicodeJoiningFeature

    Set in GSUB and used in GPOS, for STCH.

  • joiningType :: UnicodeJoiningType
     
  • unicodeFlags :: Word8
     
  • syllabicClass :: Word8
     
  • syllabicPosition :: Word8
     
  • useClass :: Word8
     
  • combiningClass :: Word8
     
  • markOrdering :: Word8

    Only used temporarily in NORMALIZE for Arabic mark reordering.

Instances

Instances details
Storable Glyph Source # 
Instance details

Defined in KB.Text.Shape.FFI.Structs

Methods

sizeOf :: Glyph -> Int #

alignment :: Glyph -> Int #

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

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

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

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

peek :: Ptr Glyph -> IO Glyph #

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

Show Glyph Source # 
Instance details

Defined in KB.Text.Shape.FFI.Structs

Methods

showsPrec :: Int -> Glyph -> ShowS #

show :: Glyph -> String #

showList :: [Glyph] -> ShowS #

data Codepoint Source #

Constructors

Codepoint 

Fields

data FeatureOverride Source #

Constructors

FeatureOverride 

Fields

data Break Source #

Constructors

Break 

Fields

  • position :: Int

    The break code mostly works in relative positions, but we convert to absolute positions for the user. That way, breaks can be trivially stored and compared and such and it just works.

  • flags :: BreakFlags
     
  • direction :: Direction

    Only valid if KBTS_BREAK_FLAG_DIRECTION is set.

  • paragraphDirection :: Direction

    Only valid if KBTS_BREAK_FLAG_PARAGRAPH_DIRECTION is set.

  • script :: Script

    Only valid if KBTS_BREAK_FLAG_SCRIPT is set.

Instances

Instances details
Storable Break Source # 
Instance details

Defined in KB.Text.Shape.FFI.Structs

Methods

sizeOf :: Break -> Int #

alignment :: Break -> Int #

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

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

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

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

peek :: Ptr Break -> IO Break #

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

Show Break Source # 
Instance details

Defined in KB.Text.Shape.FFI.Structs

Methods

showsPrec :: Int -> Break -> ShowS #

show :: Break -> String #

showList :: [Break] -> ShowS #

Eq Break Source # 
Instance details

Defined in KB.Text.Shape.FFI.Structs

Methods

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

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