typograffiti-0.2.0.0: Just let me draw nice text already

Copyright(c) 2018 Schell Scivally 2023 Adrian Cochrane
LicenseMIT
MaintainerSchell Scivally <schell@takt.com> & Adrian Cochrane <alcinnz@argonaut-constellation.org>
Safe HaskellNone
LanguageHaskell2010

Typograffiti

Description

This module provides easy freetype2 & Harfbuzz based font rendering with a nice Haskell interface, whilst exposing low-level APIs for those who need it.

Synopsis

Documentation

data TypograffitiError Source #

Represents a failure to render text.

Constructors

TypograffitiErrorNoMetricsForGlyph Int

The are no glyph metrics for this character. This probably means the character has not been loaded into the atlas.

TypograffitiErrorFreetype String Int32

There was a problem while interacting with the freetype2 library.

TypograffitiErrorGL String

There was a problem while interacting with OpenGL.

allocAtlas :: (MonadIO m, MonadFail m, MonadError TypograffitiError m) => GlyphRetriever m -> [Word32] -> m Atlas Source #

Allocate a new Atlas. When creating a new Atlas you must pass all the characters that you might need during the life of the Atlas. Character texturization only happens once.

freeAtlas :: MonadIO m => Atlas -> m () Source #

Releases all resources associated with the given Atlas.

stringTris :: (MonadIO m, MonadError TypograffitiError m) => Atlas -> [(GlyphInfo, GlyphPos)] -> m Quads Source #

Generate the geometry of the given string, with next-glyph position.

data Atlas Source #

Cache of rendered glyphs to be composited into place on the GPU.

Constructors

Atlas 

Fields

Instances
Show Atlas Source # 
Instance details

Defined in Typograffiti.Atlas

Methods

showsPrec :: Int -> Atlas -> ShowS #

show :: Atlas -> String #

showList :: [Atlas] -> ShowS #

data GlyphMetrics Source #

Size & position of a Glyph in the Atlas.

Constructors

GlyphMetrics 

Fields

Instances
Eq GlyphMetrics Source # 
Instance details

Defined in Typograffiti.Atlas

Show GlyphMetrics Source # 
Instance details

Defined in Typograffiti.Atlas

makeDrawGlyphs :: (MonadIO m, MonadError TypograffitiError m, MonadIO n, MonadFail n, MonadError TypograffitiError n) => m (Atlas -> [(GlyphInfo, GlyphPos)] -> n (AllocatedRendering [TextTransform])) Source #

Constructs a callback for for computing the geometry for rendering given glyphs out of the given texture.

data AllocatedRendering t Source #

Holds an allocated draw function for some amount of text. The function takes one parameter that can be used to transform the text in various ways. This type is generic and can be used to take advantage of your own font rendering shaders.

Constructors

AllocatedRendering 

Fields

  • arDraw :: t -> V2 Int -> IO ()

    Draw the text with some transformation in some monad.

  • arRelease :: IO ()

    Release the allocated draw function in some monad.

  • arSize :: V2 Int

    The size (in pixels) of the drawn text.

class Layout t where Source #

Generic operations for text layout.

Methods

translate :: t -> V2 Float -> t Source #

Instances
Layout [TextTransform] Source # 
Instance details

Defined in Typograffiti.Cache

data SpatialTransform Source #

Geometrically transform the text.

Constructors

SpatialTransformTranslate (V2 Float)

Shift the text horizontally or vertically.

SpatialTransformScale (V2 Float)

Resize the text.

SpatialTransformRotate Float

Enlarge the text.

SpatialTransformSkew Float

Skew the text, approximating italics (or rather obliques).

SpatialTransform (M44 Float)

Apply an arbitrary matrix transform to the text.

data TextTransform Source #

Modify the rendered text.

Constructors

TextTransformMultiply (V4 Float)

Adjust the colour of the rendered text.

TextTransformSpatial SpatialTransform

Adjust the position of the rendered text.

Instances
Layout [TextTransform] Source # 
Instance details

Defined in Typograffiti.Cache

move :: Float -> Float -> TextTransform Source #

Shift the text horizontally or vertically.

scale :: Float -> Float -> TextTransform Source #

Resize the text.

rotate :: Float -> TextTransform Source #

Rotate the text.

color :: Float -> Float -> Float -> Float -> TextTransform Source #

Recolour the text.

alpha :: Float -> TextTransform Source #

Make the text semi-transparant.

withFontStore :: (MonadIO n, MonadError TypograffitiError n, MonadFail n) => (FontStore n -> ExceptT TypograffitiError IO a) -> IO (Either TypograffitiError a) Source #

Runs the given callback with a new FontStore. Due to FreeType limitations this font store should not persist outside the callback.

newFontStore :: (MonadIO m, MonadError TypograffitiError m, MonadIO n, MonadError TypograffitiError n, MonadFail n) => FT_Library -> m (FontStore n) Source #

Allocates a new FontStore wrapping given FreeType state.

data FontStore n Source #

Stored fonts at specific sizes.

Constructors

FontStore 

Fields

data Font Source #

An opened font. In Harfbuzz, FreeType, & Atlas formats.

Constructors

Font 

Fields

data SampleText Source #

Extra parameters for constructing a font atlas, and determining which glyphs should be in it.

Constructors

SampleText 

Fields

  • sampleFeatures :: [Feature]

    Which OpenType Features you want available to be used in the rendered text. Defaults to none.

  • sampleText :: Text

    Indicates which characters & ligatures will be in the text to be rendered. Defaults to ASCII, no ligatures.

  • tabwidth :: Int

    How many spaces wide should a tab be rendered? Defaults to 4 spaces.

  • fontOptions :: FontOptions

    Additional font options offered by Harfbuzz.

  • minLineHeight :: Float

    Number of pixels tall each line should be at minimum. Defaults to 10px.

defaultSample :: SampleText Source #

Constructs a SampleText with default values.

addSampleFeature :: String -> Word32 -> SampleText -> SampleText Source #

Appends an OpenType feature callers may use to the Sample ensuring its glyphs are available. Call after setting sampleText.

parseSampleFeature :: String -> SampleText -> SampleText Source #

Parse an OpenType feature into this font using syntax akin to CSS font-feature-settings.

parseSampleFeatures :: [String] -> SampleText -> SampleText Source #

Parse multiple OpenType features into this font.

addFontVariant :: String -> Float -> SampleText -> SampleText Source #

Alter which OpenType variant of this font will be rendered. Please check your font which variants are supported.

parseFontVariant :: String -> SampleText -> SampleText Source #

Parse a OpenType variant into the configured font using syntax akin to CSS font-variant-settings.

parseFontVariants :: [String] -> SampleText -> SampleText Source #

Parse multiple OpenType variants into this font.

varItalic :: [Char] Source #

Standard italic font variant. Please check if your font supports this.

varOptSize :: [Char] Source #

Standard optical size font variant. Please check if your font supports this.

varSlant :: [Char] Source #

Standard slant (oblique) font variant. Please check if your font supports this.

varWidth :: [Char] Source #

Standard width font variant. Please check if your font supports this.

varWeight :: [Char] Source #

Standard weight (boldness) font variant. Please check if your font supports this.

data RichText Source #

Styled text to be rendered.

Constructors

RichText 

Fields

Instances
IsString RichText Source # 
Instance details

Defined in Typograffiti.Rich

str :: String -> RichText Source #

Converts a String to renderable RichText.

txt :: Text -> RichText Source #

Converts Text to renderable RichText.

($$) :: RichText -> RichText -> RichText Source #

Concatenate richtext data.

style :: String -> Word32 -> RichText -> RichText Source #

Applies the given OpenType Feature to the given RichText. Check your font for details on which OpenType features are supported. Or see https://learn.microsoft.com/en-us/typography/opentype/spec/featurelist/ (from which much of this documentation is taken).

apply :: String -> RichText -> RichText Source #

Parses the given syntax akin to CSS font-feature-settings & apply to The given RichText.

on :: Word32 Source #

Typical word to turn a font-feature on

off :: Word32 Source #

Typical word to turn a font-feature off.

alternate :: Word32 Source #

Typical word to switch to the alternate setting for a font-feature.

alt :: Word32 -> RichText -> RichText Source #

This feature makes all variations of a selected character accessible. This serves several purposes: An application may not support the feature by which the desired glyph would normally be accessed; the user may need a glyph outside the context supported by the normal substitution, or the user may not know what feature produces the desired glyph. Since many-to-one substitutions are not covered, ligatures would not appear in this table unless they were variant forms of another ligature.

case_ :: Word32 -> RichText -> RichText Source #

Shifts various punctuation marks up to a position that works better with all-capital sequences or sets of lining figures; also changes oldstyle figures to lining figures. By default, glyphs in a text face are designed to work with lowercase characters. Some characters should be shifted vertically to fit the higher visual center of all-capital or lining text. Also, lining figures are the same height (or close to it) as capitals, and fit much better with all-capital text.

centerCJKPunct :: Word32 -> RichText -> RichText Source #

Centers specific punctuation marks for those fonts that do not include centered and non-centered forms.

capSpace :: Word32 -> RichText -> RichText Source #

Globally adjusts inter-glyph spacing for all-capital text. Most typefaces contain capitals and lowercase characters, and the capitals are positioned to work with the lowercase. When capitals are used for words, they need more space between them for legibility and esthetics. This feature would not apply to monospaced designs. Of course the user may want to override this behavior in order to do more pronounced letterspacing for esthetic reasons.

ctxtSwash :: Word32 -> RichText -> RichText Source #

This feature replaces default character glyphs with corresponding swash glyphs in a specified context. Note that there may be more than one swash alternate for a given character.

petiteCaps' :: Word32 -> RichText -> RichText Source #

This feature turns capital characters into petite capitals. It is generally used for words which would otherwise be set in all caps, such as acronyms, but which are desired in petite-cap form to avoid disrupting the flow of text. See the pcap feature description for notes on the relationship of caps, smallcaps and petite caps.

smallCaps' :: Word32 -> RichText -> RichText Source #

This feature turns capital characters into small capitals. It is generally used for words which would otherwise be set in all caps, such as acronyms, but which are desired in small-cap form to avoid disrupting the flow of text.

expertJ :: Word32 -> RichText -> RichText Source #

Like the JIS78 Forms feature, this feature replaces standard forms in Japanese fonts with corresponding forms preferred by typographers. Although most of the JIS78 substitutions are included, the expert substitution goes on to handle many more characters.

finGlyph :: Word32 -> RichText -> RichText Source #

Replaces line final glyphs with alternate forms specifically designed for this purpose (they would have less or more advance width as need may be), to help justification of text.

fract :: Word32 -> RichText -> RichText Source #

Replaces figures (digits) separated by a slash (U+002F or U+2044) with “common” (diagonal) fractions.

fullWidth :: Word32 -> RichText -> RichText Source #

Replaces glyphs set on other widths with glyphs set on full (usually em) widths. In a CJKV font, this may include “lower ASCII” Latin characters and various symbols. In a European font, this feature replaces proportionally-spaced glyphs with monospaced glyphs, which are generally set on widths of 0.6 em.

hist :: Word32 -> RichText -> RichText Source #

Some letterforms were in common use in the past, but appear anachronistic today. The best-known example is the long form of s; others would include the old Fraktur k. Some fonts include the historical forms as alternates, so they can be used for a “period” effect. This feature replaces the default (current) forms with the historical alternates. While some ligatures are also used for historical effect, this feature deals only with single characters.

hkana :: Word32 -> RichText -> RichText Source #

Replaces standard kana with forms that have been specially designed for only horizontal writing. This is a typographic optimization for improved fit and more even color. Also see vkana.

histLig :: Word32 -> RichText -> RichText Source #

Some ligatures were in common use in the past, but appear anachronistic today. Some fonts include the historical forms as alternates, so they can be used for a “period” effect. This feature replaces the default (current) forms with the historical alternates.

hojo :: Word32 -> RichText -> RichText Source #

The JIS X 0212-1990 (aka, “Hojo Kanji”) and JIS X 0213:2004 character sets overlap significantly. In some cases their prototypical glyphs differ. When building fonts that support both JIS X 0212-1990 and JIS X 0213:2004 (such as those supporting the Adobe-Japan 1-6 character collection), it is recommended that JIS X 0213:2004 forms be preferred as the encoded form. The hojo feature is used to access the JIS X 0212-1990 glyphs for the cases when the JIS X 0213:2004 form is encoded.

halfWidth :: Word32 -> RichText -> RichText Source #

Replaces glyphs on proportional widths, or fixed widths other than half an em, with glyphs on half-em (en) widths. Many CJKV fonts have glyphs which are set on multiple widths; this feature selects the half-em version. There are various contexts in which this is the preferred behavior, including compatibility with older desktop documents.

italic :: Word32 -> RichText -> RichText Source #

Some fonts (such as Adobe’s Pro Japanese fonts) will have both Roman and Italic forms of some characters in a single font. This feature replaces the Roman glyphs with the corresponding Italic glyphs.

justifyAlt :: Word32 -> RichText -> RichText Source #

Improves justification of text by replacing glyphs with alternate forms specifically designed for this purpose (they would have less or more advance width as need may be).

jap78 :: Word32 -> RichText -> RichText Source #

This feature replaces default (JIS90) Japanese glyphs with the corresponding forms from the JIS C 6226-1978 (JIS78) specification.

jap83 :: Word32 -> RichText -> RichText Source #

This feature replaces default (JIS90) Japanese glyphs with the corresponding forms from the JIS X 0208-1983 (JIS83) specification.

jap90 :: Word32 -> RichText -> RichText Source #

This feature replaces Japanese glyphs from the JIS78 or JIS83 specifications with the corresponding forms from the JIS X 0208-1990 (JIS90) specification.

jap04 :: Word32 -> RichText -> RichText Source #

The National Language Council (NLC) of Japan has defined new glyph shapes for a number of JIS characters, which were incorporated into JIS X 0213:2004 as new prototypical forms. The jp04 feature is a subset of the nlck feature, and is used to access these prototypical glyphs in a manner that maintains the integrity of JIS X 0213:2004.

kerning :: Word32 -> RichText -> RichText Source #

Adjusts amount of space between glyphs, generally to provide optically consistent spacing between glyphs. Although a well-designed typeface has consistent inter-glyph spacing overall, some glyph combinations require adjustment for improved legibility. Besides standard adjustment in the horizontal direction, this feature can supply size-dependent kerning data via device tables, “cross-stream” kerning in the Y text direction, and adjustment of glyph placement independent of the advance adjustment. Note that this feature may apply to runs of more than two glyphs, and would not be used in monospaced fonts. Also note that this feature does not apply to text set vertically.

lBounds :: Word32 -> RichText -> RichText Source #

Aligns glyphs by their apparent left extents at the left ends of horizontal lines of text, replacing the default behavior of aligning glyphs by their origins.

liningFig :: Word32 -> RichText -> RichText Source #

This feature changes selected non-lining figures (digits) to lining figures.

localized :: Word32 -> RichText -> RichText Source #

Many scripts used to write multiple languages over wide geographical areas have developed localized variant forms of specific letters, which are used by individual literary communities. For example, a number of letters in the Bulgarian and Serbian alphabets have forms distinct from their Russian counterparts and from each other. In some cases the localized form differs only subtly from the script “norm”, in others the forms are radically distinct. This feature enables localized forms of glyphs to be substituted for default forms.

mathGreek :: Word32 -> RichText -> RichText Source #

Replaces standard typographic forms of Greek glyphs with corresponding forms commonly used in mathematical notation (which are a subset of the Greek alphabet).

altAnnotation :: Word32 -> RichText -> RichText Source #

Replaces default glyphs with various notational forms (e.g. glyphs placed in open or solid circles, squares, parentheses, diamonds or rounded boxes). In some cases an annotation form may already be present, but the user may want a different one.

nlcKanji :: Word32 -> RichText -> RichText Source #

The National Language Council (NLC) of Japan has defined new glyph shapes for a number of JIS characters in 2000.

oldFig :: Word32 -> RichText -> RichText Source #

This feature changes selected figures from the default or lining style to oldstyle form.

ordinals :: Word32 -> RichText -> RichText Source #

Replaces default alphabetic glyphs with the corresponding ordinal forms for use after figures. One exception to the follows-a-figure rule is the numero character (U+2116), which is actually a ligature substitution, but is best accessed through this feature.

ornament :: Word32 -> RichText -> RichText Source #

This is a dual-function feature, which uses two input methods to give the user access to ornament glyphs (e.g. fleurons, dingbats and border elements) in the font. One method replaces the bullet character with a selection from the full set of available ornaments; the other replaces specific “lower ASCII” characters with ornaments assigned to them. The first approach supports the general or browsing user; the second supports the power user.

propAltWidth :: Word32 -> RichText -> RichText Source #

Re-spaces glyphs designed to be set on full-em widths, fitting them onto individual (more or less proportional) horizontal widths. This differs from pwid in that it does not substitute new glyphs (GPOS, not GSUB feature). The user may prefer the monospaced form, or may simply want to ensure that the glyph is well-fit and not rotated in vertical setting (Latin forms designed for proportional spacing would be rotated).

petiteCaps :: Word32 -> RichText -> RichText Source #

Some fonts contain an additional size of capital letters, shorter than the regular smallcaps and whimsically referred to as petite caps. Such forms are most likely to be found in designs with a small lowercase x-height, where they better harmonise with lowercase text than the taller smallcaps (for examples of petite caps, see the Emigre type families Mrs Eaves and Filosofia). This feature turns glyphs for lowercase characters into petite capitals. Forms related to petite capitals, such as specially designed figures, may be included.

propKana :: Word32 -> RichText -> RichText Source #

Replaces glyphs, kana and kana-related, set on uniform widths (half or full-width) with proportional glyphs.

propFig :: Word32 -> RichText -> RichText Source #

Replaces figure glyphs set on uniform (tabular) widths with corresponding glyphs set on glyph-specific (proportional) widths. Tabular widths will generally be the default, but this cannot be safely assumed. Of course this feature would not be present in monospaced designs.

propWidth :: Word32 -> RichText -> RichText Source #

Replaces glyphs set on uniform widths (typically full or half-em) with proportionally spaced glyphs. The proportional variants are often used for the Latin characters in CJKV fonts, but may also be used for Kana in Japanese fonts.

quarterWidth :: Word32 -> RichText -> RichText Source #

Replaces glyphs on other widths with glyphs set on widths of one quarter of an em (half an en). The characters involved are normally figures and some forms of punctuation.

rBounds :: Word32 -> RichText -> RichText Source #

Aligns glyphs by their apparent right extents at the right ends of horizontal lines of text, replacing the default behavior of aligning glyphs by their origins.

ruby :: Word32 -> RichText -> RichText Source #

Japanese typesetting often uses smaller kana glyphs, generally in superscripted form, to clarify the meaning of kanji which may be unfamiliar to the reader. These are called “ruby”, from the old typesetting term for four-point-sized type. This feature identifies glyphs in the font which have been designed for this use, substituting them for the default designs.

styleAlt :: Word32 -> RichText -> RichText Source #

Many fonts contain alternate glyph designs for a purely esthetic effect; these don’t always fit into a clear category like swash or historical. As in the case of swash glyphs, there may be more than one alternate form. This feature replaces the default forms with the stylistic alternates.

sciInferior :: Word32 -> RichText -> RichText Source #

Replaces lining or oldstyle figures (digits) with inferior figures (smaller glyphs which sit lower than the standard baseline, primarily for chemical or mathematical notation). May also replace glyphs for lowercase characters with alphabetic inferiors.

smallCaps :: Word32 -> RichText -> RichText Source #

This feature turns glyphs for lowercase characters into small capitals. It is generally used for display lines set in Large & small caps, such as titles. Forms related to small capitals, such as oldstyle figures, may be included.

simpleCJ :: Word32 -> RichText -> RichText Source #

Replaces “traditional” Chinese or Japanese forms with the corresponding “simplified” forms.

subscript :: Word32 -> RichText -> RichText Source #

The subs feature may replace a default glyph with a subscript glyph, or it may combine a glyph substitution with positioning adjustments for proper placement.

superscript :: Word32 -> RichText -> RichText Source #

Replaces lining or oldstyle figures with superior figures (primarily for footnote indication), and replaces lowercase letters with superior letters (primarily for abbreviated French titles).

swash :: Word32 -> RichText -> RichText Source #

This feature replaces default character glyphs with corresponding swash glyphs. Note that there may be more than one swash alternate for a given character.

titling :: Word32 -> RichText -> RichText Source #

This feature replaces the default glyphs with corresponding forms designed specifically for titling. These may be all-capital and/or larger on the body, and adjusted for viewing at larger sizes.

traditionNameJ :: Word32 -> RichText -> RichText Source #

Replaces “simplified” Japanese kanji forms with the corresponding “traditional” forms. This is equivalent to the Traditional Forms feature, but explicitly limited to the traditional forms considered proper for use in personal names (as many as 205 glyphs in some fonts).

tabularFig :: Word32 -> RichText -> RichText Source #

Replaces figure glyphs set on proportional widths with corresponding glyphs set on uniform (tabular) widths. Tabular widths will generally be the default, but this cannot be safely assumed. Of course this feature would not be present in monospaced designs.

traditionCJ :: Word32 -> RichText -> RichText Source #

Replaces simplified Chinese hanzi or Japanese kanji forms with the corresponding traditional forms.

thirdWidth :: Word32 -> RichText -> RichText Source #

Replaces glyphs on other widths with glyphs set on widths of one third of an em. The characters involved are normally figures and some forms of punctuation.

unicase :: Word32 -> RichText -> RichText Source #

This feature maps upper- and lowercase letters to a mixed set of lowercase and small capital forms, resulting in a single case alphabet (for an example of unicase, see the Emigre type family Filosofia). The letters substituted may vary from font to font, as appropriate to the design. If aligning to the x-height, smallcap glyphs may be substituted, or specially designed unicase forms might be used. Substitutions might also include specially designed figures.

vAlt :: Word32 -> RichText -> RichText Source #

Repositions glyphs to visually center them within full-height metrics, for use in vertical setting. Applies to full-width Latin, Greek, or Cyrillic glyphs, which are typically included in East Asian fonts, and whose glyphs are aligned on a common horizontal baseline and not rotated relative to the page or text frame.

vert :: Word32 -> RichText -> RichText Source #

Transforms default glyphs into glyphs that are appropriate for upright presentation in vertical writing mode. While the glyphs for most characters in East Asian writing systems remain upright when set in vertical writing mode, some must be transformed — usually by rotation, shifting, or different component ordering — for vertical writing mode.

vHalfAlt :: Word32 -> RichText -> RichText Source #

Re-spaces glyphs designed to be set on full-em heights, fitting them onto half-em heights. This differs from valt, which repositions a glyph but does not affect its advance.

vKanaAlt :: Word32 -> RichText -> RichText Source #

Replaces standard kana with forms that have been specially designed for only vertical writing. This is a typographic optimization for improved fit and more even color. Also see hkna.

vKerning :: Word32 -> RichText -> RichText Source #

Adjusts amount of space between glyphs, generally to provide optically consistent spacing between glyphs. Although a well-designed typeface has consistent inter-glyph spacing overall, some glyph combinations require adjustment for improved legibility. Besides standard adjustment in the vertical direction, this feature can supply size-dependent kerning data via device tables, “cross-stream” kerning in the X text direction, and adjustment of glyph placement independent of the advance adjustment. Note that this feature may apply to runs of more than two glyphs, and would not be used in monospaced fonts. Also note that this feature applies only to text set vertically.

vPropAlt :: Word32 -> RichText -> RichText Source #

Re-spaces glyphs designed to be set on full-em heights, fitting them onto individual (more or less proportional) vertical heights. This differs from valt, which repositions a glyph but does not affect its advance.

vRotAlt :: Word32 -> RichText -> RichText Source #

Replaces some fixed-width (half-, third- or quarter-width) or proportional-width glyphs (mostly Latin or katakana) with forms suitable for vertical writing (that is, rotated 90 degrees clockwise). Note that these are a superset of the glyphs covered in the vert table.

vrot :: Word32 -> RichText -> RichText Source #

Transforms default glyphs into glyphs that are appropriate for sideways presentation in vertical writing mode. While the glyphs for most characters in East Asian writing systems remain upright when set in vertical writing mode, glyphs for other characters — such as those of other scripts or for particular Western-style punctuation — are expected to be presented sideways in vertical writing.

slash0 :: Word32 -> RichText -> RichText Source #

Some fonts contain both a default form of zero, and an alternative form which uses a diagonal slash through the counter. Especially in condensed designs, it can be difficult to distinguish between 0 and O (zero and capital O) in any situation where capitals and lining figures may be arbitrarily mixed. This feature allows the user to change from the default 0 to a slashed form.

altFrac :: Bool -> RichText -> RichText Source #

Replaces figures separated by a slash with an alternative form.

ctxtAlt :: Bool -> RichText -> RichText Source #

n specified situations, replaces default glyphs with alternate forms which provide better joining behavior. Used in script typefaces which are designed to have some or all of their glyphs join.

ctxtLig :: Bool -> RichText -> RichText Source #

Replaces a sequence of glyphs with a single glyph which is preferred for typographic purposes. Unlike other ligature features, clig specifies the context in which the ligature is recommended. This capability is important in some script designs and for swash ligatures.

optLigs :: Bool -> RichText -> RichText Source #

Replaces a sequence of glyphs with a single glyph which is preferred for typographic purposes. This feature covers those ligatures which may be used for special effect, at the user’s preference.

lig :: Bool -> RichText -> RichText Source #

Replaces a sequence of glyphs with a single glyph which is preferred for typographic purposes. This feature covers the ligatures which the designer or manufacturer judges should be used in normal conditions.

rand :: Word32 -> RichText -> RichText Source #

In order to emulate the irregularity and variety of handwritten text, this feature allows multiple alternate forms to be used.

data GlyphSize Source #

How large the text should be rendered.

Constructors

CharSize Float Float Int Int

Size in Pts at given DPI.

PixelSize Int Int

Size in device pixels.

makeDrawTextCached :: (MonadIO m, MonadFail m, MonadError TypograffitiError m, MonadIO n, MonadFail n, MonadError TypograffitiError n) => FontStore n -> FilePath -> Int -> GlyphSize -> SampleText -> m (RichText -> n (AllocatedRendering [TextTransform])) Source #

Opens a font sized to given value & prepare to render text in it. The fonts are cached for later reuse.

makeDrawText :: (MonadIO m, MonadFail m, MonadError TypograffitiError m, MonadIO n, MonadFail n, MonadError TypograffitiError n) => FT_Library -> FilePath -> Int -> GlyphSize -> SampleText -> m (RichText -> n (AllocatedRendering [TextTransform])) Source #

Opens a font sized to the given value & prepare to render text in it. There is no need to keep the given FT_Library live before rendering the text.