-- Hoogle documentation, generated by Haddock
-- See Hoogle, http://www.haskell.org/hoogle/
-- | Pure-functional Harfbuzz language bindings
--
-- HarfBuzz is a text shaping library. Using the HarfBuzz library allows
-- programs to convert a sequence of Unicode input into properly
-- formatted and positioned glyph output; for practically any writing
-- system and written language. NOTE: You may need to install Harfbuzz
-- 3.3.0 (Jan 2022) or newer from source, it hasn't been widely packaged
-- yet.
@package harfbuzz-pure
@version 1.0.4.0
-- | Published almost entirely for benchmarks, comparing to stdlib! Should
-- have little direct interest to Harfbuzz callers, & I'm not
-- promising a stable API. This is here because, as it turns out,
-- Harfbuzz can return a lot of output!
module Data.Text.Glyphize.Array
-- | Clone the given array so it can be freed without the losing access to
-- the data. Uses memcpy so it gets very heavily optimized by
-- the OS.
clonePtr :: Storable a => Ptr a -> Int -> IO (ForeignPtr a)
-- | Iterate over an array in a ForeignPtr, no matter how small or large it
-- is.
peekLazy :: Storable a => ForeignPtr a -> Int -> [a]
-- | Variation of peekArray, taking a tail to append to the decoded list.
peekEager :: Storable a => [a] -> Int -> Ptr a -> IO [a]
-- | How many words should be decoded by peekLazy &
-- iterateLazy.
chunkSize :: Int
-- | Convert an array from C code into a Haskell list, performant no matter
-- how small or large it is.
iterateLazy :: Storable a => Ptr a -> Int -> IO [a]
-- | This "function" has a superficial similarity to unsafePerformIO
-- but it is in fact a malevolent agent of chaos. It unpicks the seams of
-- reality (and the IO monad) so that the normal rules no longer
-- apply. It lulls you into thinking it is reasonable, but when you are
-- not looking it stabs you in the back and aliases all of your mutable
-- buffers. The carcass of many a seasoned Haskell programmer lie strewn
-- at its feet.
--
-- Witness the trail of destruction:
--
--
--
-- Do not talk about "safe"! You do not know what is safe!
--
-- Yield not to its blasphemous call! Flee traveller! Flee or you will be
-- corrupted and devoured!
accursedUnutterablePerformIO :: IO a -> a
-- | Harfbuzz produces ~40x as much output data as its input data. In many
-- applications that input data would be a large fraction of its heap. As
-- such, unless callers are processing these results, it is usually more
-- efficient for Haskell to recompute the glyphs than to store them.
--
-- This synonym of oneShot is used to instruct Haskell of this
-- fact.
noCache :: (a -> b) -> a -> b
-- | HarfBuzz is a text shaping library. Using the HarfBuzz library allows
-- programs to convert a sequence of Unicode input into properly
-- formatted and positioned glyph output for practically any writing
-- system and language. See shape for the central function all
-- other datatypes serves to support.
module Data.Text.Glyphize
-- | Shapes the text in the given Buffer according to the given
-- Font yielding glyphs and their positions. If any
-- Features are given they will be applied during shaping. If two
-- Features have the same tag but overlapping ranges the value of
-- the Feature with the higher index takes precedance.
shape :: Font -> Buffer -> [Feature] -> [(GlyphInfo, GlyphPos)]
-- | Returns the library version as 3 integer components.
version :: (Int, Int, Int)
-- | Tests the library version against a minimum value, as 3 integer
-- components.
versionAtLeast :: Int -> Int -> Int -> Bool
-- | Returns library version as a string with 3 integer components.
versionString :: String
-- | Indicates that Harfbuzz has ran out of memory during a computation.
-- Should be extremely rare!
data HarfbuzzError
OutOfMemory :: HarfbuzzError
-- | Text to be shaped or the resulting glyphs, for which
-- languagescriptdirection/etc.
data Buffer
Buffer :: Text -> Maybe ContentType -> Maybe Direction -> Maybe String -> Maybe String -> Bool -> Bool -> Bool -> Bool -> Bool -> ClusterLevel -> Char -> Char -> Char -> Buffer
-- | The Unicode text, in visual order, for HarfBuzz to convert into
-- glyphs. See
-- https://hackage.haskell.org/package/text-2.0.1/docs/Data-Text-Internal-Lazy.html#t:Text
-- for details.
[text] :: Buffer -> Text
-- | What the bytes of the ByteString contents represents, namely unicode
-- characters (before shaping) or glyphs (result of shaping). Typically
-- callers should leave this as `Just ContentTypeUnicode`.
[contentType] :: Buffer -> Maybe ContentType
-- | The text flow direction of the buffer. No shaping can happen without
-- setting buffer direction, and it controls the visual direction for the
-- output glyphs; for RTL direction the glyphs will be reversed. Many
-- layout features depend on the proper setting of the direction, for
-- example, reversing RTL text before shaping, then shaping with LTR
-- direction is not the same as keeping the text in logical order and
-- shaping with RTL direction.
[direction] :: Buffer -> Maybe Direction
-- | Script is crucial for choosing the proper shaping behaviour for
-- scripts that require it (e.g. Arabic) and the which OpenType features
-- defined in the font to be applied.
[script] :: Buffer -> Maybe String
-- | Languages are crucial for selecting which OpenType feature to apply to
-- the buffer which can result in applying language-specific behaviour.
-- Languages are orthogonal to the scripts, and though they are related,
-- they are different concepts and should not be confused with each
-- other.
[language] :: Buffer -> Maybe String
-- | special handling of the beginning of text paragraph can be applied to
-- this buffer. Should usually be set, unless you are passing to the
-- buffer only part of the text without the full context.
[beginsText] :: Buffer -> Bool
-- | special handling of the end of text paragraph can be applied to this
-- buffer.
[endsText] :: Buffer -> Bool
-- | character with Default_Ignorable Unicode property should use the
-- corresponding glyph from the font, instead of hiding them (done by
-- replacing them with the space glyph and zeroing the advance width.)
-- Takes precedance over removeDefaultIgnorables.
[preserveDefaultIgnorables] :: Buffer -> Bool
-- | character with Default_Ignorable Unicode property should be removed
-- from glyph string instead of hiding them (done by replacing them with
-- the space glyph and zeroing the advance width.)
[removeDefaultIgnorables] :: Buffer -> Bool
-- | a dotted circle should not be inserted in the rendering of incorrect
-- character sequences (such as 093E).
[don'tInsertDottedCircle] :: Buffer -> Bool
-- | dictates one aspect of how HarfBuzz will treat non-base characters
-- during shaping.
[clusterLevel] :: Buffer -> ClusterLevel
-- | The glyph number that replaces invisible characters in the shaping
-- result. If set to zero (default), the glyph for the U+0020 SPACE
-- character is used. Otherwise, this value is used verbatim.
[invisibleGlyph] :: Buffer -> Char
-- | the glyph number that replaces invalid entries for a given encoding
-- when adding text to buffer.
[replacementCodepoint] :: Buffer -> Char
-- | the glyph number that replaces replaces characters not found in the
-- font.
[notFoundGlyph] :: Buffer -> Char
-- | Whether the given text is Unicode or font-specific "glyphs".
data ContentType
ContentTypeUnicode :: ContentType
ContentTypeGlyphs :: ContentType
-- | Defines how fine the groupings represented by GlyphInfo's
-- cluster property are.`
data ClusterLevel
ClusterMonotoneGraphemes :: ClusterLevel
ClusterMonotoneChars :: ClusterLevel
ClusterChars :: ClusterLevel
-- | The direction of a text segment or buffer.
data Direction
DirLTR :: Direction
DirRTL :: Direction
DirTTB :: Direction
DirBTT :: Direction
-- | An empty buffer with sensible default properties.
defaultBuffer :: Buffer
-- | Converts a string to an Direction. Matching is loose and
-- applies only to the first letter. For examples, LTR and
-- "left-to-right" will both return HB_DIRECTION_LTR.
dirFromStr :: [Char] -> Maybe Direction
-- | Converts an Direction to a string.
dirToStr :: Direction -> String
-- | Reverses a text direction.
dirReverse :: Direction -> Direction
-- | Tests whether a text direction moves backward (from right to left, or
-- from bottom to top).
dirBackward :: Direction -> Bool
-- | Tests whether a text direction moves forward (from left to right, or
-- from top to bottom).
dirForward :: Direction -> Bool
-- | Tests whether a text direction is horizontal.
dirHorizontal :: Direction -> Bool
-- | Tests whether a text direction is vertical.
dirVertical :: Direction -> Bool
-- | Fetches the Direction of a script when it is set horizontally.
-- All right-to-left scripts will return DirRTL. All left-to-right
-- scripts will return DirLTR. Scripts that can be written either
-- horizontally or vertically will return Nothing. Unknown scripts
-- will return DirLTR.
scriptHorizontalDir :: String -> Maybe Direction
-- | Fetch the default language from current locale. NOTE that the first
-- time this function is called, it calls (C code) "setlocale (LC_CTYPE,
-- nullptr)" to fetch current locale. The underlying setlocale function
-- is, in many implementations, NOT threadsafe. To avoid problems, call
-- this function once before multiple threads can call it. This function
-- may be used to fill in missing fields on a Buffer.
languageDefault :: IO String
-- | Converts a String into a "tag" Word32. Valid tags are 4
-- Chars. Shorter input Strings will be padded with spaces.
-- Longer input strings will be truncated.
tag_from_string :: String -> Word32
-- | Converts a "tag" Word32 into a 4 Char String.
tag_to_string :: Word32 -> String
-- | Fills in unset segment properties based on buffer unicode contents. If
-- buffer is not empty it must have ContentType
-- ContentTypeUnicode. If buffer script is not set it will be set
-- to the Unicode script of the first character in the buffer that has a
-- script other than "common", "inherited", or "unknown". Next if the
-- buffer direction is not set it will be set to the natural horizontal
-- direction of the buffer script as returned by
-- scriptHorizontalDir. If scriptHorizontalDir returns
-- Nothing, then DirLTR is used. Finally if buffer language
-- is not set, it will be set to the process's default language as
-- returned by languageDefault. This may change in the future by
-- taking buffer script into consideration when choosting a language.
-- Note that languageDefault is not thread-safe the first time it
-- is called. See documentation for that function for details.
guessSegmentProperties :: Buffer -> Buffer
-- | Holds information about the glyphs & their relation to input text.
data GlyphInfo
GlyphInfo :: Word32 -> Word32 -> Bool -> Bool -> Bool -> GlyphInfo
-- | Glyph index (or unicode codepoint)
[codepoint] :: GlyphInfo -> Word32
-- | The index of the character in the original text that corresponds to
-- this GlyphInfo. More than one GlyphInfo may have the
-- same cluster value if they resulted from the same character,
-- & when more than one character gets merged into the same glyph
-- GlyphInfo will have the smallest cluster value of them. By
-- default some characters are merged into the same cluster even when
-- they are seperate glyphs, Buffer's clusterLevel property
-- allows selecting more fine grained cluster handling.
[cluster] :: GlyphInfo -> Word32
-- | Indicates that if input text is broken at the beginning of the cluster
-- this glyph is part of, then both sides need to be re-shaped, as the
-- result might be different. On the flip side, it means that when this
-- flag is not present, then it is safe to break the glyph-run at the
-- beginning of this cluster, and the two sides will represent the exact
-- same result one would get if breaking input text at the beginning of
-- this cluster and shaping the two sides separately. This can be used to
-- optimize paragraph layout, by avoiding re-shaping of each line after
-- line-breaking.
[unsafeToBreak] :: GlyphInfo -> Bool
-- | Indicates that if input text is changed on one side of the beginning
-- of the cluster this glyph is part of, then the shaping results for the
-- other side might change. Note that the absence of this flag will NOT
-- by itself mean that it IS safe to concat text. Only two pieces of text
-- both of which clear of this flag can be concatenated safely. See
-- https://harfbuzz.github.io/harfbuzz-hb-buffer.html#HB_GLYPH_FLAG_UNSAFE_TO_CONCAT
-- for more details.
[unsafeToConcat] :: GlyphInfo -> Bool
-- | In scripts that use elongation (Arabic, Mongolian, Syriac, etc.), this
-- flag signifies that it is safe to insert a U+0640 TATWEEL character
-- before this cluster for elongation. This flag does not determine the
-- script-specific elongation places, but only when it is safe to do the
-- elongation without interrupting text shaping.
[safeToInsertTatweel] :: GlyphInfo -> Bool
-- | Holds positions of the glyph in both horizontal & vertical
-- directions. All positions are relative to current point.
data GlyphPos
GlyphPos :: Int32 -> Int32 -> Int32 -> Int32 -> GlyphPos
-- | How much the line advances after drawing this glyph when setting text
-- in horizontal direction.
[x_advance] :: GlyphPos -> Int32
-- | How much the line advances after drawing this glyph when setting text
-- in vertical direction.
[y_advance] :: GlyphPos -> Int32
-- | How much the glyph moves on the X-axis before drawing it, this should
-- not effect how much the line advances.
[x_offset] :: GlyphPos -> Int32
-- | How much the glyph moves on the Y-axis before drawing it, this should
-- not effect how much the line advances.
[y_offset] :: GlyphPos -> Int32
-- | The structure that holds information about requested feature
-- application. The feature will be applied with the given value to all
-- glyphs which are in clusters between start (inclusive) and end
-- (exclusive). Setting start to HB_FEATURE_GLOBAL_START and end to
-- HB_FEATURE_GLOBAL_END specifies that the feature always applies to the
-- entire buffer.
data Feature
Feature :: Word32 -> Word32 -> Word -> Word -> Feature
-- | Tag of the feature. Use featTag to decode as an ASCII string.
[featTag'] :: Feature -> Word32
-- | The value of the feature. 0 disables the feature, non-zero (usually 1)
-- enables the feature. For features implemented as lookup type 3 (like
-- "salt") the value is a one based index into the alternates.
[featValue] :: Feature -> Word32
-- | The cluster to start applying this feature setting (inclusive).
[featStart] :: Feature -> Word
-- | The cluster to end applying this feature setting (exclusive).
[featEnd] :: Feature -> Word
-- | Tag of the feature.
featTag :: Feature -> String
-- | Data type for holding variation data. Registered OpenType
-- variation-axis tags are listed in OpenType Axis Tag Registry.
data Variation
Variation :: Word32 -> Float -> Variation
-- | Tag of the variation-axis name. Use varTag to decode as an
-- ASCII string.
[varTag'] :: Variation -> Word32
-- | Value of the variation axis.
[varValue] :: Variation -> Float
-- | Tag of the variation-axis.
varTag :: Variation -> String
-- | Parses a string into a hb_feature_t. The format for specifying feature
-- strings follows. All valid CSS font-feature-settings values other than
-- "normal" and the global values are also accepted. CSS string escapes
-- are not supported. See
-- https://harfbuzz.github.io/harfbuzz-hb-common.html#hb-feature-from-string
-- for additional details. The range indices refer to the positions
-- between Unicode characters. The position before the first character is
-- always 0.
parseFeature :: String -> Maybe Feature
-- | Converts a Feature into a String in the format
-- understood by parseFeature.
unparseFeature :: Feature -> String
-- | Parses a string into a hb_variation_t. The format for specifying
-- variation settings follows. All valid CSS font-variation-settings
-- values other than "normal" and "inherited" are also accepted, though,
-- not documented below. The format is a tag, optionally followed by an
-- equals sign, followed by a number. For example wght=500, or slnt=-7.5.
parseVariation :: String -> Maybe Variation
-- | Converts a Variation into a String in the format
-- understood by parseVariation.
unparseVariation :: Variation -> String
-- | Special setting for featStart to apply the feature from the
-- start of the buffer.
globalStart :: Word
-- | Special setting for featEnd to apply the feature to the end of
-- the buffer.
globalEnd :: Word
-- | Fetches the number of Faces in a ByteString.
countFace :: ByteString -> Word
-- | A Font face.
type Face = ForeignPtr Face'
-- | Constructs a new face object from the specified blob and a face index
-- into that blob. The face index is used for blobs of file formats such
-- as TTC and and DFont that can contain more than one face. Face indices
-- within such collections are zero-based. Note: If the blob font format
-- is not a collection, index is ignored. Otherwise, only the lower
-- 16-bits of index are used. The unmodified index can be accessed via
-- faceIndex. Note: The high 16-bits of index, if non-zero, are
-- used by createFont to load named-instances in variable fonts.
-- See createFont for details.
createFace :: ByteString -> Word -> Face
-- | Creates aFace object from the specified FT_Face. Not
-- thread-safe due to FreeType dependency.
ftCreateFace :: FT_Face -> IO Face
-- | Fetches the singleton empty Face object.
emptyFace :: Face
-- | Fetches a list of all table tags for a face, if possible. The list
-- returned will begin at the offset provided
faceTableTags :: Face -> Word -> Word -> (Word, [String])
-- | Fetches the glyph-count value of the specified face object.
faceGlyphCount :: Face -> Word
-- | Collects all of the Unicode characters covered by Face into a
-- list of unique values.
faceCollectUnicodes :: Face -> [Word32]
-- | Collects all Unicode "Variation Selector" characters covered by
-- Face into a list of unique values.
faceCollectVarSels :: Face -> [Word32]
-- | Collects all Unicode characters for variation_selector covered by
-- Face into a list of unique values.
faceCollectVarUnicodes :: Face -> Word32 -> [Word32]
-- | Fetches the face-index corresponding to the given Face.
faceIndex :: Face -> Word
-- | Fetches the units-per-em (upem) value of the specified Face
-- object.
faceUpem :: Face -> Word
-- | Fetches the binary blob that contains the specified Face.
-- Returns an empty ByteString if referencing face data is not
-- possible.
faceBlob :: Face -> ByteString
-- | Fetches the specified table within the specified face.
faceTable :: Face -> String -> ByteString
-- | Data type for holding fonts
type Font = ForeignPtr Font'
-- | Constructs a new Font object from the specified Face.
-- Note: If face's index value (as passed to createFace has
-- non-zero top 16-bits, those bits minus one are passed to
-- hb_font_set_var_named_instance(), effectively loading a named-instance
-- of a variable font, instead of the default-instance. This allows
-- specifying which named-instance to load by default when creating the
-- face.
createFont :: Face -> Font
-- | Creates an Font object from the specified FT_Face. Note: You
-- must set the face size on ft_face before calling ftCreateFont
-- on it. HarfBuzz assumes size is always set and will access
-- frSize` member of FT_Face unconditionally.
ftCreateFont :: FT_Face -> IO Font
-- | Fetches the empty Font object.
emptyFont :: Font
-- | Fetches the Face associated with the specified Font
-- object.
fontFace :: Font -> Face
-- | Fetches the glyph ID for a Unicode codepoint in the specified
-- Font, with an optional variation selector.
fontGlyph :: Font -> Char -> Maybe Char -> Maybe Word32
-- | Fetches the advance for a glyph ID from the specified font, in a text
-- segment of the specified direction. Calls the appropriate
-- direction-specific variant (horizontal or vertical) depending on the
-- value of direction .
fontGlyphAdvance :: Font -> Word32 -> Maybe Direction -> (Int32, Int32)
-- | Fetches the (x,y) coordinates of a specified contour-point index in
-- the specified glyph, within the specified font.
fontGlyphContourPoint :: Font -> Word32 -> Int -> Maybe (Int32, Int32)
-- | Fetches the (X,Y) coordinates of a specified contour-point index in
-- the specified glyph ID in the specified font, with respect to the
-- origin in a text segment in the specified direction. Calls the
-- appropriate direction-specific variant (horizontal or vertical)
-- depending on the value of direction .
fontGlyphContourPointForOrigin :: Font -> Word32 -> Int -> Maybe Direction -> Maybe (Int32, Int32)
-- | Fetches the glyph ID that corresponds to a name string in the
-- specified Font.
fontGlyphFromName :: Font -> String -> Maybe Word32
-- | Fetches the advance for a glyph ID in the specified Font, for
-- horizontal text segments.
fontGlyphHAdvance :: Font -> Word32 -> Int32
-- | Fetches the advance for a glyph ID in the specified Font, for
-- vertical text segments.
fontGlyphVAdvance :: Font -> Word32 -> Int32
-- | Fetches the kerning-adjustment value for a glyph-pair in the specified
-- Font, for horizontal text segments.
fontGlyphHKerning :: Font -> Word32 -> Word32 -> Int32
-- | Fetches the (X,Y) coordinate of the origin for a glyph ID in the
-- specified Font, for horizontal text segments.
fontGlyphHOrigin :: Font -> Word32 -> Maybe (Int32, Int32)
-- | Fetches the (X,Y) coordinates of the origin for a glyph ID in the
-- specified Font, for vertical text segments.
fontGlyphVOrigin :: Font -> Word32 -> Maybe (Int32, Int32)
-- | Fetches the kerning-adjustment value for a glyph-pair in the specified
-- Font. Calls the appropriate direction-specific variant
-- (horizontal or vertical) depending on the value of given
-- Direction.
fontGlyphKerningForDir :: Font -> Word32 -> Word32 -> Maybe Direction -> (Int32, Int32)
-- | Fetches the glyph-name string for a glyph ID in the specified
-- Font.
fontGlyphName :: Font -> Word32 -> Maybe String
-- | Variant of fontGlyphName which lets you specify the maximum of
-- the return value. Defaults to 32.
fontGlyphName_ :: Font -> Word32 -> Int -> Maybe String
-- | Fetches the (X,Y) coordinates of the origin for a glyph in the
-- specified Font. Calls the appropriate direction-specific
-- variant (horizontal or vertical) depending on the value of given
-- Direction.
fontGlyphOriginForDir :: Font -> Word32 -> Maybe Direction -> (Int32, Int32)
-- | Fetches the nominal glyph ID for a Unicode codepoint in the specified
-- font. This version of the function should not be used to fetch glyph
-- IDs for codepoints modified by variation selectors. For
-- variation-selector support use fontVarGlyph or use
-- fontGlyph.
fontNominalGlyph :: Font -> Char -> Maybe Word32
-- | Fetches the horizontal & vertical points-per-em (ppem) of a
-- Font.
fontPPEm :: Font -> (Word32, Word32)
-- | Fetches the "point size" of a Font. Used in CoreText to
-- implement optical sizing.
fontPtEm :: Font -> Float
-- | Fetches the horizontal and vertical scale of a Font.
fontScale :: Font -> (Int, Int)
-- | Fetches the glyph ID for a Unicode codepoint when followed by the
-- specified variation-selector codepoint, in the specified Font.
fontVarGlyph :: Font -> Word32 -> Word32 -> Maybe Word32
-- | Fetches the "synthetic slant" of a font.
fontSyntheticSlant :: Font -> Float
-- | Fetches the list of normalized variation coordinates currently set on
-- a font. Note that this returned list may only contain values for some
-- (or none) of the axes; ommitted axes effectively have default values.
fontVarCoordsNormalized :: Font -> [Int]
-- | Fetches the glyph ID from given Font that matches the specified
-- string. Strings of the format gidDDD or uniUUUU are parsed
-- automatically.
fontTxt2Glyph :: Font -> String -> Maybe Word32
-- | Fetches the name of the specified glyph ID in given Font as a
-- string. If the glyph ID has no name in the Font, a string of
-- the form gidDDD is generated with DDD being the glyph ID.
fontGlyph2Str :: Font -> Word32 -> Int -> String
-- | Fetches the list of variation coordinates (in design-space units)
-- currently set on a Font. Note that this returned list may only
-- contain values for some (or none) of the axes; ommitted axes
-- effectively have their default values.
fontVarCoordsDesign :: Font -> [Float]
-- | Glyph extent values, measured in font units. Note that height is
-- negative, in coordinate systems that grow up.
data GlyphExtents
GlyphExtents :: Word32 -> Word32 -> Word32 -> Word32 -> GlyphExtents
-- | Distance from the x-origin to the left extremum of the glyph.
[xBearing] :: GlyphExtents -> Word32
-- | Distance from the top extremum of the glyph to the y-origin.
[yBearing] :: GlyphExtents -> Word32
-- | Distance from the left extremum of the glyph to the right extremum.
[width] :: GlyphExtents -> Word32
-- | Distance from the top extremum of the glyph to the right extremum.
[height] :: GlyphExtents -> Word32
-- | Fetches the GlyphExtents data for a glyph ID in the specified
-- Font.
fontGlyphExtents :: Font -> Word32 -> Maybe GlyphExtents
-- | Fetches the GlyphExtents data for a glyph ID in the specified
-- Font, with respect to the origin in a text segment in the
-- specified direction. Calls the appropriate direction-specific variant
-- (horizontal or vertical) depending on the value of given
-- Direction.
fontGlyphExtentsForOrigin :: Font -> Word32 -> Maybe Direction -> Maybe GlyphExtents
-- | Font-wide extent values, measured in font units. Note that typically
-- ascender is positive and descender is negative, in coordinate systems
-- that grow up. Note: Due to presence of 9 additional private fields,
-- arrays of font extents will not decode correctly. So far this doesn't
-- matter.
data FontExtents
FontExtents :: Int32 -> Int32 -> Int32 -> FontExtents
-- | The height of typographic ascenders.
[ascender] :: FontExtents -> Int32
-- | The depth of typographic descenders.
[descender] :: FontExtents -> Int32
-- | The suggested line-spacing gap.
[lineGap] :: FontExtents -> Int32
-- | Fetches the extents for a font in a text segment of the specified
-- direction. Calls the appropriate direction-specific variant
-- (horizontal or vertical) depending on the value of direction .
fontExtentsForDir :: Font -> Maybe Direction -> FontExtents
-- | Fetches the extents for a specified font, for horizontal text
-- segments.
fontHExtents :: ForeignPtr Font' -> Maybe FontExtents
-- | Fetches the extents for a specified font, for vertical text segments.
fontVExtents :: ForeignPtr Font' -> Maybe FontExtents
-- | Allows configuring properties on a Font when creating it.
data FontOptions
FontOptions :: Maybe (Word, Word) -> Maybe Float -> Maybe (Int, Int) -> Maybe Face -> Maybe Font -> Maybe Float -> [Variation] -> [Float] -> [Int] -> Maybe Word -> FontOptions
-- | Sets the horizontal and vertical pixels-per-em (ppem) of the
-- newly-created Font.
[optionPPEm] :: FontOptions -> Maybe (Word, Word)
-- | Sets the "point size" of a newly-created Font. Used in CoreText
-- to implement optical sizing. Note: There are 72 points in an inch.
[optionPtEm] :: FontOptions -> Maybe Float
-- | Sets the horizontal and vertical scale of a newly-created Font.
[optionScale] :: FontOptions -> Maybe (Int, Int)
-- | Sets the font-face value of the newly-created Font.
[optionFace] :: FontOptions -> Maybe Face
-- | Sets the parent Font of the newly-created Font.
[optionParent] :: FontOptions -> Maybe Font
-- | Sets the "synthetic slant" of a newly-created Font. By default
-- is zero. Synthetic slant is the graphical skew applied to the font at
-- rendering time. Harfbuzz needs to know this value to adjust shaping
-- results, metrics, and style valuesto match the slanted rendering.
-- Note: The slant value is a ratio. For example, a 20% slant would be
-- represented as a 0.2 value.
[optionSynthSlant] :: FontOptions -> Maybe Float
-- | Applies a list of font-variation settings to a font. Axes not included
-- will be effectively set to their default values.
[optionVariations] :: FontOptions -> [Variation]
-- | Applies a list of variation coordinates (in design-space units) to a
-- newly-created Font. Axes not included in coords will be
-- effectively set to their default values.
[optionVarCoordsDesign] :: FontOptions -> [Float]
-- | Applies a list of variation coordinates (in normalized units) to a
-- newly-created Font. Axes not included in coords will be
-- effectively set to their default values.
[optionVarCoordsNormalized] :: FontOptions -> [Int]
-- | Sets design coords of a font from a named instance index.
[optionVarNamedInstance] :: FontOptions -> Maybe Word
-- | FontOptions which has no effect on the newly-created
-- Font.
defaultFontOptions :: FontOptions
-- | Variant of createFont which applies the given
-- FontOptions.
createFontWithOptions :: FontOptions -> Face -> Font
-- | Variant of ftCreateFont which applies the given
-- FontOptions.
ftCreateFontWithOptions :: FontOptions -> FT_Face -> Font