harfbuzz-pure-1.0.1.0: Pure-functional Harfbuzz language bindings

Safe HaskellNone
LanguageHaskell2010

Data.Text.Glyphize

Description

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 any writing system and language. See shape for the central function all other datatypes serves to support.

Synopsis

Documentation

shape :: Font -> Buffer -> [Feature] -> [(GlyphInfo, GlyphPos)] Source #

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.

version :: (Int, Int, Int) Source #

Returns the library version as 3 integer components.

versionAtLeast :: Int -> Int -> Int -> Bool Source #

Tests the library version against a minimum value, as 3 integer components.

versionString :: String Source #

Returns library version as a string with 3 integer components.

data Buffer Source #

Text to be shaped or the resulting glyphs, for which languagescriptdirection/etc.

Constructors

Buffer 

Fields

  • text :: Text

    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.

  • contentType :: Maybe ContentType

    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`.

  • direction :: Maybe Direction

    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.

  • script :: Maybe String

    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.

  • language :: 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.

  • beginsText :: Bool

    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.

  • endsText :: Bool

    special handling of the end of text paragraph can be applied to this buffer.

  • preserveDefaultIgnorables :: 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.

  • removeDefaultIgnorables :: 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.)

  • don'tInsertDottedCircle :: Bool

    a dotted circle should not be inserted in the rendering of incorrect character sequences (such as 093E).

  • clusterLevel :: ClusterLevel

    dictates one aspect of how HarfBuzz will treat non-base characters during shaping.

  • invisibleGlyph :: Char

    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.

  • replacementCodepoint :: Char

    the glyph number that replaces invalid entries for a given encoding when adding text to buffer.

  • notFoundGlyph :: Char

    the glyph number that replaces replaces characters not found in the font.

Instances
Eq Buffer Source # 
Instance details

Defined in Data.Text.Glyphize.Buffer

Methods

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

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

Ord Buffer Source # 
Instance details

Defined in Data.Text.Glyphize.Buffer

Read Buffer Source # 
Instance details

Defined in Data.Text.Glyphize.Buffer

Show Buffer Source # 
Instance details

Defined in Data.Text.Glyphize.Buffer

defaultBuffer :: Buffer Source #

An empty buffer with sensible default properties.

dirFromStr :: [Char] -> Maybe Direction Source #

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.

dirToStr :: Direction -> [Char] Source #

Converts an Direction to a string.

dirReverse :: Direction -> Direction Source #

Reverses a text direction.

dirBackward :: Direction -> Bool Source #

Tests whether a text direction moves backward (from right to left, or from bottom to top).

dirForward :: Direction -> Bool Source #

Tests whether a text direction moves forward (from left to right, or from top to bottom).

dirHorizontal :: Direction -> Bool Source #

Tests whether a text direction is horizontal.

dirVertical :: Direction -> Bool Source #

Tests whether a text direction is vertical.

scriptHorizontalDir :: String -> Maybe Direction Source #

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.

languageDefault :: IO String Source #

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.

tag_from_string :: String -> Word32 Source #

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_to_string :: Word32 -> String Source #

Converts a "tag" Word32 into a 4 Char String.

guessSegmentProperties :: Buffer -> Buffer Source #

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.

data GlyphInfo Source #

Holds information about the glyphs & their relation to input text.

Constructors

GlyphInfo 

Fields

  • codepoint :: Word32

    Glyph index (or unicode codepoint)

  • cluster :: 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.

  • unsafeToBreak :: Bool

    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.

  • unsafeToConcat :: 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.

  • safeToInsertTatweel :: 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.

data GlyphPos Source #

Holds positions of the glyph in both horizontal & vertical directions. All positions are relative to current point.

Constructors

GlyphPos 

Fields

  • x_advance :: Int32

    How much the line advances after drawing this glyph when setting text in horizontal direction.

  • y_advance :: Int32

    How much the line advances after drawing this glyph when setting text in vertical direction.

  • x_offset :: Int32

    How much the glyph moves on the X-axis before drawing it, this should not effect how much the line advances.

  • y_offset :: Int32

    How much the glyph moves on the Y-axis before drawing it, this should not effect how much the line advances.

Instances
Eq GlyphPos Source # 
Instance details

Defined in Data.Text.Glyphize.Buffer

Read GlyphPos Source # 
Instance details

Defined in Data.Text.Glyphize.Buffer

Show GlyphPos Source # 
Instance details

Defined in Data.Text.Glyphize.Buffer

Generic GlyphPos Source # 
Instance details

Defined in Data.Text.Glyphize.Buffer

Associated Types

type Rep GlyphPos :: Type -> Type #

Methods

from :: GlyphPos -> Rep GlyphPos x #

to :: Rep GlyphPos x -> GlyphPos #

Storable GlyphPos Source # 
Instance details

Defined in Data.Text.Glyphize.Buffer

type Rep GlyphPos Source # 
Instance details

Defined in Data.Text.Glyphize.Buffer

data Feature Source #

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.

Constructors

Feature 

Fields

  • featTag' :: Word32

    Tag of the feature. Use featTag to decode as an ASCII string.

  • featValue :: 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.

  • featStart :: Word

    The cluster to start applying this feature setting (inclusive).

  • featEnd :: Word

    The cluster to end applying this feature setting (exclusive).

Instances
Read Feature Source # 
Instance details

Defined in Data.Text.Glyphize.Font

Show Feature Source # 
Instance details

Defined in Data.Text.Glyphize.Font

Generic Feature Source # 
Instance details

Defined in Data.Text.Glyphize.Font

Associated Types

type Rep Feature :: Type -> Type #

Methods

from :: Feature -> Rep Feature x #

to :: Rep Feature x -> Feature #

GStorable Feature Source # 
Instance details

Defined in Data.Text.Glyphize.Font

type Rep Feature Source # 
Instance details

Defined in Data.Text.Glyphize.Font

featTag :: Feature -> String Source #

Tag of the feature.

data Variation Source #

Data type for holding variation data. Registered OpenType variation-axis tags are listed in OpenType Axis Tag Registry.

Constructors

Variation 

Fields

Instances
Read Variation Source # 
Instance details

Defined in Data.Text.Glyphize.Font

Show Variation Source # 
Instance details

Defined in Data.Text.Glyphize.Font

Generic Variation Source # 
Instance details

Defined in Data.Text.Glyphize.Font

Associated Types

type Rep Variation :: Type -> Type #

GStorable Variation Source # 
Instance details

Defined in Data.Text.Glyphize.Font

type Rep Variation Source # 
Instance details

Defined in Data.Text.Glyphize.Font

type Rep Variation = D1 (MetaData "Variation" "Data.Text.Glyphize.Font" "harfbuzz-pure-1.0.1.0-inplace" False) (C1 (MetaCons "Variation" PrefixI True) (S1 (MetaSel (Just "varTag'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word32) :*: S1 (MetaSel (Just "varValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float)))

varTag :: Variation -> String Source #

Tag of the variation-axis.

parseFeature :: String -> Maybe Feature Source #

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.

unparseFeature :: Feature -> String Source #

Converts a Feature into a String in the format understood by parseFeature.

parseVariation :: String -> Maybe Variation Source #

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.

unparseVariation :: Variation -> String Source #

Converts a Variation into a String in the format understood by parseVariation.

globalStart :: Word Source #

Special setting for featStart to apply the feature from the start of the buffer.

globalEnd :: Word Source #

Special setting for featEnd to apply the feature to the end of the buffer.

countFace :: ByteString -> Word Source #

Fetches the number of Faces in a ByteString.

type Face = ForeignPtr Face' Source #

A Font face.

createFace :: ByteString -> Word -> Face Source #

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.

ftCreateFace :: FT_Face -> IO Face Source #

Creates aFace object from the specified FT_Face. Not thread-safe due to FreeType dependency.

emptyFace :: Face Source #

Fetches the singleton empty Face object.

faceTableTags :: Face -> Word -> Word -> (Word, [String]) Source #

Fetches a list of all table tags for a face, if possible. The list returned will begin at the offset provided

faceGlyphCount :: Face -> Word Source #

Fetches the glyph-count value of the specified face object.

faceCollectUnicodes :: Face -> [Word32] Source #

Collects all of the Unicode characters covered by Face into a list of unique values.

faceCollectVarSels :: Face -> [Word32] Source #

Collects all Unicode "Variation Selector" characters covered by Face into a list of unique values.

faceCollectVarUnicodes :: Face -> Word32 -> [Word32] Source #

Collects all Unicode characters for variation_selector covered by Face into a list of unique values.

faceIndex :: Face -> Word Source #

Fetches the face-index corresponding to the given Face.

faceUpem :: Face -> Word Source #

Fetches the units-per-em (upem) value of the specified Face object.

faceBlob :: Face -> ByteString Source #

Fetches the binary blob that contains the specified Face. Returns an empty ByteString if referencing face data is not possible.

faceTable :: Face -> String -> ByteString Source #

Fetches the specified table within the specified face.

type Font = ForeignPtr Font' Source #

Data type for holding fonts

createFont :: Face -> Font Source #

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.

ftCreateFont :: FT_Face -> IO Font Source #

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.

emptyFont :: Font Source #

Fetches the empty Font object.

fontFace :: Font -> Face Source #

Fetches the Face associated with the specified Font object.

fontGlyph :: Font -> Char -> Maybe Char -> Maybe Word32 Source #

Fetches the glyph ID for a Unicode codepoint in the specified Font, with an optional variation selector.

fontGlyphAdvance :: Font -> Word32 -> Maybe Direction -> (Int32, Int32) Source #

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 .

fontGlyphContourPoint :: Font -> Word32 -> Int -> Maybe (Int32, Int32) Source #

Fetches the (x,y) coordinates of a specified contour-point index in the specified glyph, within the specified font.

fontGlyphContourPointForOrigin :: Font -> Word32 -> Int -> Maybe Direction -> Maybe (Int32, Int32) Source #

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 .

fontGlyphFromName :: Font -> String -> Maybe Word32 Source #

Fetches the glyph ID that corresponds to a name string in the specified Font.

fontGlyphHAdvance :: Font -> Word32 -> Int32 Source #

Fetches the advance for a glyph ID in the specified Font, for horizontal text segments.

fontGlyphVAdvance :: Font -> Word32 -> Int32 Source #

Fetches the advance for a glyph ID in the specified Font, for vertical text segments.

fontGlyphHKerning :: Font -> Word32 -> Word32 -> Int32 Source #

Fetches the kerning-adjustment value for a glyph-pair in the specified Font, for horizontal text segments.

fontGlyphHOrigin :: Font -> Word32 -> Maybe (Int32, Int32) Source #

Fetches the (X,Y) coordinate of the origin for a glyph ID in the specified Font, for horizontal text segments.

fontGlyphVOrigin :: Font -> Word32 -> Maybe (Int32, Int32) Source #

Fetches the (X,Y) coordinates of the origin for a glyph ID in the specified Font, for vertical text segments.

fontGlyphKerningForDir :: Font -> Word32 -> Word32 -> Maybe Direction -> (Int32, Int32) Source #

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.

fontGlyphName :: Font -> Word32 -> Maybe String Source #

Fetches the glyph-name string for a glyph ID in the specified Font.

fontGlyphName_ :: Font -> Word32 -> Int -> Maybe String Source #

Variant of fontGlyphName which lets you specify the maximum of the return value. Defaults to 32.

fontGlyphOriginForDir :: Font -> Word32 -> Maybe Direction -> (Int32, Int32) Source #

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.

fontNominalGlyph :: Font -> Char -> Maybe Word32 Source #

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.

fontPPEm :: Font -> (Word32, Word32) Source #

Fetches the horizontal & vertical points-per-em (ppem) of a Font.

fontPtEm :: Font -> Float Source #

Fetches the "point size" of a Font. Used in CoreText to implement optical sizing.

fontScale :: Font -> (Int, Int) Source #

Fetches the horizontal and vertical scale of a Font.

fontVarGlyph :: Font -> Word32 -> Word32 -> Maybe Word32 Source #

Fetches the glyph ID for a Unicode codepoint when followed by the specified variation-selector codepoint, in the specified Font.

fontSyntheticSlant :: Font -> Float Source #

Fetches the "synthetic slant" of a font.

fontVarCoordsNormalized :: Font -> [Int] Source #

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.

fontTxt2Glyph :: Font -> String -> Maybe Word32 Source #

Fetches the glyph ID from given Font that matches the specified string. Strings of the format gidDDD or uniUUUU are parsed automatically.

fontGlyph2Str :: Font -> Word32 -> Int -> String Source #

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.

fontVarCoordsDesign :: Font -> [Float] Source #

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.

data GlyphExtents Source #

Glyph extent values, measured in font units. Note that height is negative, in coordinate systems that grow up.

Constructors

GlyphExtents 

Fields

  • xBearing :: Word32

    Distance from the x-origin to the left extremum of the glyph.

  • yBearing :: Word32

    Distance from the top extremum of the glyph to the y-origin.

  • width :: Word32

    Distance from the left extremum of the glyph to the right extremum.

  • height :: Word32

    Distance from the top extremum of the glyph to the right extremum.

fontGlyphExtents :: Font -> Word32 -> Maybe GlyphExtents Source #

Fetches the GlyphExtents data for a glyph ID in the specified Font.

fontGlyphExtentsForOrigin :: Font -> Word32 -> Maybe Direction -> Maybe GlyphExtents Source #

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.

data FontExtents Source #

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.

Constructors

FontExtents 

Fields

Instances
Generic FontExtents Source # 
Instance details

Defined in Data.Text.Glyphize.Font

Associated Types

type Rep FontExtents :: Type -> Type #

GStorable FontExtents Source # 
Instance details

Defined in Data.Text.Glyphize.Font

type Rep FontExtents Source # 
Instance details

Defined in Data.Text.Glyphize.Font

type Rep FontExtents = D1 (MetaData "FontExtents" "Data.Text.Glyphize.Font" "harfbuzz-pure-1.0.1.0-inplace" False) (C1 (MetaCons "FontExtents" PrefixI True) (S1 (MetaSel (Just "ascender") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32) :*: (S1 (MetaSel (Just "descender") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32) :*: S1 (MetaSel (Just "lineGap") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32))))

fontExtentsForDir :: Font -> Maybe Direction -> FontExtents Source #

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 .

fontHExtents :: ForeignPtr Font' -> Maybe FontExtents Source #

Fetches the extents for a specified font, for horizontal text segments.

fontVExtents :: ForeignPtr Font' -> Maybe FontExtents Source #

Fetches the extents for a specified font, for vertical text segments.

data FontOptions Source #

Allows configuring properties on a Font when creating it.

Constructors

FontOptions 

Fields

  • optionPPEm :: Maybe (Word, Word)

    Sets the horizontal and vertical pixels-per-em (ppem) of the newly-created Font.

  • optionPtEm :: Maybe Float

    Sets the "point size" of a newly-created Font. Used in CoreText to implement optical sizing. Note: There are 72 points in an inch.

  • optionScale :: Maybe (Int, Int)

    Sets the horizontal and vertical scale of a newly-created Font.

  • optionFace :: Maybe Face

    Sets the font-face value of the newly-created Font.

  • optionParent :: Maybe Font

    Sets the parent Font of the newly-created Font.

  • optionSynthSlant :: Maybe Float

    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.

  • optionVariations :: [Variation]

    Applies a list of font-variation settings to a font. Axes not included will be effectively set to their default values.

  • optionVarCoordsDesign :: [Float]

    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.

  • optionVarCoordsNormalized :: [Int]

    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.

  • optionVarNamedInstance :: Maybe Word

    Sets design coords of a font from a named instance index.

defaultFontOptions :: FontOptions Source #

FontOptions which has no effect on the newly-created Font.

createFontWithOptions :: FontOptions -> Face -> Font Source #

Variant of createFont which applies the given FontOptions.

ftCreateFontWithOptions :: FontOptions -> FT_Face -> Font Source #

Variant of ftCreateFont which applies the given FontOptions.