Safe Haskell | None |
---|---|
Language | Haskell2010 |
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.
Synopsis
- shape :: Font -> Buffer -> [Feature] -> [(GlyphInfo, GlyphPos)]
- version :: (Int, Int, Int)
- versionAtLeast :: Int -> Int -> Int -> Bool
- versionString :: String
- data HarfbuzzError = OutOfMemory
- data Buffer = Buffer {
- text :: Text
- contentType :: Maybe ContentType
- direction :: Maybe Direction
- script :: Maybe String
- language :: Maybe String
- beginsText :: Bool
- endsText :: Bool
- preserveDefaultIgnorables :: Bool
- removeDefaultIgnorables :: Bool
- don'tInsertDottedCircle :: Bool
- clusterLevel :: ClusterLevel
- invisibleGlyph :: Char
- replacementCodepoint :: Char
- notFoundGlyph :: Char
- data ContentType
- data ClusterLevel
- data Direction
- defaultBuffer :: Buffer
- dirFromStr :: [Char] -> Maybe Direction
- dirToStr :: Direction -> [Char]
- dirReverse :: Direction -> Direction
- dirBackward :: Direction -> Bool
- dirForward :: Direction -> Bool
- dirHorizontal :: Direction -> Bool
- dirVertical :: Direction -> Bool
- scriptHorizontalDir :: String -> Maybe Direction
- languageDefault :: IO String
- tag_from_string :: String -> Word32
- tag_to_string :: Word32 -> String
- guessSegmentProperties :: Buffer -> Buffer
- data GlyphInfo = GlyphInfo {
- codepoint :: Word32
- cluster :: Word32
- unsafeToBreak :: Bool
- unsafeToConcat :: Bool
- safeToInsertTatweel :: Bool
- data GlyphPos = GlyphPos {}
- data Feature = Feature {}
- featTag :: Feature -> String
- data Variation = Variation {}
- varTag :: Variation -> String
- parseFeature :: String -> Maybe Feature
- unparseFeature :: Feature -> String
- parseVariation :: String -> Maybe Variation
- unparseVariation :: Variation -> String
- globalStart :: Word
- globalEnd :: Word
- countFace :: ByteString -> Word
- type Face = ForeignPtr Face'
- createFace :: ByteString -> Word -> Face
- ftCreateFace :: FT_Face -> IO Face
- emptyFace :: Face
- faceTableTags :: Face -> Word -> Word -> (Word, [String])
- faceGlyphCount :: Face -> Word
- faceCollectUnicodes :: Face -> [Word32]
- faceCollectVarSels :: Face -> [Word32]
- faceCollectVarUnicodes :: Face -> Word32 -> [Word32]
- faceIndex :: Face -> Word
- faceUpem :: Face -> Word
- faceBlob :: Face -> ByteString
- faceTable :: Face -> String -> ByteString
- type Font = ForeignPtr Font'
- createFont :: Face -> Font
- ftCreateFont :: FT_Face -> IO Font
- emptyFont :: Font
- fontFace :: Font -> Face
- fontGlyph :: Font -> Char -> Maybe Char -> Maybe Word32
- fontGlyphAdvance :: Font -> Word32 -> Maybe Direction -> (Int32, Int32)
- fontGlyphContourPoint :: Font -> Word32 -> Int -> Maybe (Int32, Int32)
- fontGlyphContourPointForOrigin :: Font -> Word32 -> Int -> Maybe Direction -> Maybe (Int32, Int32)
- fontGlyphFromName :: Font -> String -> Maybe Word32
- fontGlyphHAdvance :: Font -> Word32 -> Int32
- fontGlyphVAdvance :: Font -> Word32 -> Int32
- fontGlyphHKerning :: Font -> Word32 -> Word32 -> Int32
- fontGlyphHOrigin :: Font -> Word32 -> Maybe (Int32, Int32)
- fontGlyphVOrigin :: Font -> Word32 -> Maybe (Int32, Int32)
- fontGlyphKerningForDir :: Font -> Word32 -> Word32 -> Maybe Direction -> (Int32, Int32)
- fontGlyphName :: Font -> Word32 -> Maybe String
- fontGlyphName_ :: Font -> Word32 -> Int -> Maybe String
- fontGlyphOriginForDir :: Font -> Word32 -> Maybe Direction -> (Int32, Int32)
- fontNominalGlyph :: Font -> Char -> Maybe Word32
- fontPPEm :: Font -> (Word32, Word32)
- fontPtEm :: Font -> Float
- fontScale :: Font -> (Int, Int)
- fontVarGlyph :: Font -> Word32 -> Word32 -> Maybe Word32
- fontSyntheticSlant :: Font -> Float
- fontVarCoordsNormalized :: Font -> [Int]
- fontTxt2Glyph :: Font -> String -> Maybe Word32
- fontGlyph2Str :: Font -> Word32 -> Int -> String
- fontVarCoordsDesign :: Font -> [Float]
- data GlyphExtents = GlyphExtents {}
- fontGlyphExtents :: Font -> Word32 -> Maybe GlyphExtents
- fontGlyphExtentsForOrigin :: Font -> Word32 -> Maybe Direction -> Maybe GlyphExtents
- data FontExtents = FontExtents {}
- fontExtentsForDir :: Font -> Maybe Direction -> FontExtents
- fontHExtents :: ForeignPtr Font' -> Maybe FontExtents
- fontVExtents :: ForeignPtr Font' -> Maybe FontExtents
- data FontOptions = FontOptions {
- optionPPEm :: Maybe (Word, Word)
- optionPtEm :: Maybe Float
- optionScale :: Maybe (Int, Int)
- optionFace :: Maybe Face
- optionParent :: Maybe Font
- optionSynthSlant :: Maybe Float
- optionVariations :: [Variation]
- optionVarCoordsDesign :: [Float]
- optionVarCoordsNormalized :: [Int]
- optionVarNamedInstance :: Maybe Word
- defaultFontOptions :: FontOptions
- createFontWithOptions :: FontOptions -> Face -> Font
- ftCreateFontWithOptions :: FontOptions -> FT_Face -> Font
Documentation
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 HarfbuzzError Source #
Indicates that Harfbuzz has ran out of memory during a computation. Should be extremely rare!
Instances
Show HarfbuzzError Source # | |
Defined in Data.Text.Glyphize.Oom showsPrec :: Int -> HarfbuzzError -> ShowS show :: HarfbuzzError -> String showList :: [HarfbuzzError] -> ShowS | |
Exception HarfbuzzError Source # | |
Defined in Data.Text.Glyphize.Oom toException :: HarfbuzzError -> SomeException fromException :: SomeException -> Maybe HarfbuzzError displayException :: HarfbuzzError -> String |
Text to be shaped or the resulting glyphs, for which languagescriptdirection/etc.
Buffer | |
|
data ContentType Source #
Whether the given text is Unicode or font-specific "glyphs".
Instances
Eq ContentType Source # | |
Defined in Data.Text.Glyphize.Buffer (==) :: ContentType -> ContentType -> Bool (/=) :: ContentType -> ContentType -> Bool | |
Ord ContentType Source # | |
Defined in Data.Text.Glyphize.Buffer compare :: ContentType -> ContentType -> Ordering (<) :: ContentType -> ContentType -> Bool (<=) :: ContentType -> ContentType -> Bool (>) :: ContentType -> ContentType -> Bool (>=) :: ContentType -> ContentType -> Bool max :: ContentType -> ContentType -> ContentType min :: ContentType -> ContentType -> ContentType | |
Read ContentType Source # | |
Defined in Data.Text.Glyphize.Buffer readsPrec :: Int -> ReadS ContentType readList :: ReadS [ContentType] readPrec :: ReadPrec ContentType readListPrec :: ReadPrec [ContentType] | |
Show ContentType Source # | |
Defined in Data.Text.Glyphize.Buffer showsPrec :: Int -> ContentType -> ShowS show :: ContentType -> String showList :: [ContentType] -> ShowS |
data ClusterLevel Source #
Instances
Eq ClusterLevel Source # | |
Defined in Data.Text.Glyphize.Buffer (==) :: ClusterLevel -> ClusterLevel -> Bool (/=) :: ClusterLevel -> ClusterLevel -> Bool | |
Ord ClusterLevel Source # | |
Defined in Data.Text.Glyphize.Buffer compare :: ClusterLevel -> ClusterLevel -> Ordering (<) :: ClusterLevel -> ClusterLevel -> Bool (<=) :: ClusterLevel -> ClusterLevel -> Bool (>) :: ClusterLevel -> ClusterLevel -> Bool (>=) :: ClusterLevel -> ClusterLevel -> Bool max :: ClusterLevel -> ClusterLevel -> ClusterLevel min :: ClusterLevel -> ClusterLevel -> ClusterLevel | |
Read ClusterLevel Source # | |
Defined in Data.Text.Glyphize.Buffer readsPrec :: Int -> ReadS ClusterLevel readList :: ReadS [ClusterLevel] readPrec :: ReadPrec ClusterLevel readListPrec :: ReadPrec [ClusterLevel] | |
Show ClusterLevel Source # | |
Defined in Data.Text.Glyphize.Buffer showsPrec :: Int -> ClusterLevel -> ShowS show :: ClusterLevel -> String showList :: [ClusterLevel] -> ShowS |
The direction of a text segment or buffer.
defaultBuffer :: Buffer Source #
An empty buffer with sensible default properties.
dirFromStr :: [Char] -> Maybe Direction Source #
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 #
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 Char
s.
Shorter input String
s 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.
Holds information about the glyphs & their relation to input text.
GlyphInfo | |
|
Instances
Eq GlyphInfo Source # | |
Read GlyphInfo Source # | |
Defined in Data.Text.Glyphize.Buffer | |
Show GlyphInfo Source # | |
Storable GlyphInfo Source # | |
Defined in Data.Text.Glyphize.Buffer |
Holds positions of the glyph in both horizontal & vertical directions. All positions are relative to current point.
GlyphPos | |
|
Instances
Eq GlyphPos Source # | |
Read GlyphPos Source # | |
Defined in Data.Text.Glyphize.Buffer | |
Show GlyphPos Source # | |
Generic GlyphPos Source # | |
Storable GlyphPos Source # | |
Defined in Data.Text.Glyphize.Buffer | |
type Rep GlyphPos Source # | |
Defined in Data.Text.Glyphize.Buffer type Rep GlyphPos = D1 ('MetaData "GlyphPos" "Data.Text.Glyphize.Buffer" "harfbuzz-pure-1.0.3.2-inplace" 'False) (C1 ('MetaCons "GlyphPos" 'PrefixI 'True) ((S1 ('MetaSel ('Just "x_advance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int32) :*: S1 ('MetaSel ('Just "y_advance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int32)) :*: (S1 ('MetaSel ('Just "x_offset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int32) :*: S1 ('MetaSel ('Just "y_offset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 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.
Feature | |
|
Instances
Eq Feature Source # | |
Ord Feature Source # | |
Read Feature Source # | |
Defined in Data.Text.Glyphize.Font | |
Show Feature Source # | |
Generic Feature Source # | |
GStorable Feature Source # | |
Defined in Data.Text.Glyphize.Font galignment :: Feature -> Int # gpeekByteOff :: Ptr b -> Int -> IO Feature # gpokeByteOff :: Ptr b -> Int -> Feature -> IO () # | |
type Rep Feature Source # | |
Defined in Data.Text.Glyphize.Font type Rep Feature = D1 ('MetaData "Feature" "Data.Text.Glyphize.Font" "harfbuzz-pure-1.0.3.2-inplace" 'False) (C1 ('MetaCons "Feature" 'PrefixI 'True) ((S1 ('MetaSel ('Just "featTag'") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32) :*: S1 ('MetaSel ('Just "featValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32)) :*: (S1 ('MetaSel ('Just "featStart") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word) :*: S1 ('MetaSel ('Just "featEnd") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word)))) |
Data type for holding variation data. Registered OpenType variation-axis tags are listed in OpenType Axis Tag Registry.
Instances
Eq Variation Source # | |
Ord Variation Source # | |
Defined in Data.Text.Glyphize.Font | |
Read Variation Source # | |
Defined in Data.Text.Glyphize.Font | |
Show Variation Source # | |
Generic Variation Source # | |
GStorable Variation Source # | |
Defined in Data.Text.Glyphize.Font galignment :: Variation -> Int # gpeekByteOff :: Ptr b -> Int -> IO Variation # gpokeByteOff :: Ptr b -> Int -> Variation -> IO () # | |
type Rep Variation Source # | |
Defined in Data.Text.Glyphize.Font type Rep Variation = D1 ('MetaData "Variation" "Data.Text.Glyphize.Font" "harfbuzz-pure-1.0.3.2-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))) |
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.
Special setting for featEnd
to apply the feature to the end of the buffer.
countFace :: ByteString -> Word Source #
Fetches the number of Face
s in a ByteString
.
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 #
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.
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.
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.
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 #
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 #
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.
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 #
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.
GlyphExtents | |
|
Instances
Eq GlyphExtents Source # | |
Defined in Data.Text.Glyphize.Font (==) :: GlyphExtents -> GlyphExtents -> Bool (/=) :: GlyphExtents -> GlyphExtents -> Bool | |
Ord GlyphExtents Source # | |
Defined in Data.Text.Glyphize.Font compare :: GlyphExtents -> GlyphExtents -> Ordering (<) :: GlyphExtents -> GlyphExtents -> Bool (<=) :: GlyphExtents -> GlyphExtents -> Bool (>) :: GlyphExtents -> GlyphExtents -> Bool (>=) :: GlyphExtents -> GlyphExtents -> Bool max :: GlyphExtents -> GlyphExtents -> GlyphExtents min :: GlyphExtents -> GlyphExtents -> GlyphExtents | |
Read GlyphExtents Source # | |
Defined in Data.Text.Glyphize.Font readsPrec :: Int -> ReadS GlyphExtents readList :: ReadS [GlyphExtents] readPrec :: ReadPrec GlyphExtents readListPrec :: ReadPrec [GlyphExtents] | |
Show GlyphExtents Source # | |
Defined in Data.Text.Glyphize.Font showsPrec :: Int -> GlyphExtents -> ShowS show :: GlyphExtents -> String showList :: [GlyphExtents] -> ShowS | |
Generic GlyphExtents Source # | |
Defined in Data.Text.Glyphize.Font type Rep GlyphExtents :: Type -> Type from :: GlyphExtents -> Rep GlyphExtents x to :: Rep GlyphExtents x -> GlyphExtents | |
GStorable GlyphExtents Source # | |
Defined in Data.Text.Glyphize.Font gsizeOf :: GlyphExtents -> Int # galignment :: GlyphExtents -> Int # gpeekByteOff :: Ptr b -> Int -> IO GlyphExtents # gpokeByteOff :: Ptr b -> Int -> GlyphExtents -> IO () # | |
type Rep GlyphExtents Source # | |
Defined in Data.Text.Glyphize.Font type Rep GlyphExtents = D1 ('MetaData "GlyphExtents" "Data.Text.Glyphize.Font" "harfbuzz-pure-1.0.3.2-inplace" 'False) (C1 ('MetaCons "GlyphExtents" 'PrefixI 'True) ((S1 ('MetaSel ('Just "xBearing") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32) :*: S1 ('MetaSel ('Just "yBearing") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32)) :*: (S1 ('MetaSel ('Just "width") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32) :*: S1 ('MetaSel ('Just "height") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32)))) |
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.
Instances
Eq FontExtents Source # | |
Defined in Data.Text.Glyphize.Font (==) :: FontExtents -> FontExtents -> Bool (/=) :: FontExtents -> FontExtents -> Bool | |
Ord FontExtents Source # | |
Defined in Data.Text.Glyphize.Font compare :: FontExtents -> FontExtents -> Ordering (<) :: FontExtents -> FontExtents -> Bool (<=) :: FontExtents -> FontExtents -> Bool (>) :: FontExtents -> FontExtents -> Bool (>=) :: FontExtents -> FontExtents -> Bool max :: FontExtents -> FontExtents -> FontExtents min :: FontExtents -> FontExtents -> FontExtents | |
Read FontExtents Source # | |
Defined in Data.Text.Glyphize.Font readsPrec :: Int -> ReadS FontExtents readList :: ReadS [FontExtents] readPrec :: ReadPrec FontExtents readListPrec :: ReadPrec [FontExtents] | |
Show FontExtents Source # | |
Defined in Data.Text.Glyphize.Font showsPrec :: Int -> FontExtents -> ShowS show :: FontExtents -> String showList :: [FontExtents] -> ShowS | |
Generic FontExtents Source # | |
Defined in Data.Text.Glyphize.Font type Rep FontExtents :: Type -> Type from :: FontExtents -> Rep FontExtents x to :: Rep FontExtents x -> FontExtents | |
GStorable FontExtents Source # | |
Defined in Data.Text.Glyphize.Font gsizeOf :: FontExtents -> Int # galignment :: FontExtents -> Int # gpeekByteOff :: Ptr b -> Int -> IO FontExtents # gpokeByteOff :: Ptr b -> Int -> FontExtents -> IO () # | |
type Rep FontExtents Source # | |
Defined in Data.Text.Glyphize.Font type Rep FontExtents = D1 ('MetaData "FontExtents" "Data.Text.Glyphize.Font" "harfbuzz-pure-1.0.3.2-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.
FontOptions | |
|
Instances
Eq FontOptions Source # | |
Defined in Data.Text.Glyphize.Font (==) :: FontOptions -> FontOptions -> Bool (/=) :: FontOptions -> FontOptions -> Bool | |
Ord FontOptions Source # | |
Defined in Data.Text.Glyphize.Font compare :: FontOptions -> FontOptions -> Ordering (<) :: FontOptions -> FontOptions -> Bool (<=) :: FontOptions -> FontOptions -> Bool (>) :: FontOptions -> FontOptions -> Bool (>=) :: FontOptions -> FontOptions -> Bool max :: FontOptions -> FontOptions -> FontOptions min :: FontOptions -> FontOptions -> FontOptions | |
Show FontOptions Source # | |
Defined in Data.Text.Glyphize.Font showsPrec :: Int -> FontOptions -> ShowS show :: FontOptions -> String showList :: [FontOptions] -> ShowS |
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
.