FontyFruity-0.5.2: A true type file format loader

Safe HaskellNone
LanguageHaskell2010

Graphics.Text.TrueType

Contents

Description

Module in charge of loading fonts.

Synopsis

Functions

decodeFont :: ByteString -> Either String Font Source

Decode a in-memory true type file.

loadFontFile :: FilePath -> IO (Either String Font) Source

Load a font file, the file path must be pointing to the true type file (.ttf)

getStringCurveAtPoint Source

Arguments

:: Dpi

Dot per inch of the output.

-> (Float, Float)

Initial position of the baseline.

-> [(Font, PointSize, String)]

Text to draw

-> [[Vector (Float, Float)]]

List of contours for each char

Extract a list of outlines for every char in the string. The given curves are in an image like coordinate system, with the origin point in the upper left corner.

unitsPerEm :: Font -> Word16 Source

Return the number of pixels relative to the point size.

isPlaceholder :: Font -> Char -> Bool Source

True if the character is not present in the font, therefore it will appear as a placeholder in renderings.

getCharacterGlyphsAndMetrics Source

Arguments

:: Font 
-> Char 
-> (Float, Vector RawGlyph)

Advance and glyph information.

Retrive the glyph contours and associated transformations. The coordinate system is assumed to be the TTF one (y upward). No transformation is performed.

getGlyphForStrings :: Dpi -> [(Font, PointSize, String)] -> [[Vector (Float, Float)]] Source

This function return the list of all contour for all char with the given font in a string. All glyph are at the same position, they are not placed like with getStringCurveAtPoint. It is a function helpful to extract the glyph geometry for further external manipulation.

stringBoundingBox :: Font -> Dpi -> PointSize -> String -> BoundingBox Source

Compute the bounding box of a string displayed with a font at a given size. The resulting coordinate represent the width and the height in pixels.

findFontOfFamily :: String -> FontStyle -> IO (Maybe FilePath) Source

This function will scan the system's font folder to find a font with the desired properties. Favor using a FontCache to speed up the lookup process.

Font cache

data FontCache Source

A font cache is a cache listing all the found fonts on the system, allowing faster font lookup once created

FontCache is an instance of binary, to get okish performance you should save it in a file somewhere instead of rebuilding it everytime!

The font cache is dependent on the version of rasterific, you must rebuild it for every version.

data FontDescriptor Source

A font descriptor is a key used to find a font in a font cache.

Constructors

FontDescriptor 

Fields

_descriptorFamilyName :: Text

The family name of the font

_descriptorStyle :: FontStyle

The desired style

emptyFontCache :: FontCache Source

Font cache with no pre-existing fonts in it.

findFontInCache :: FontCache -> FontDescriptor -> Maybe FilePath Source

Try to find a font with the given properties in the font cache.

buildCache :: IO FontCache Source

This function will search in the system for truetype files and index them in a cache for further fast search.

enumerateFonts :: FontCache -> [FontDescriptor] Source

Returns a list of descriptors of fonts stored in the given cache.

Types

data Font Source

Type representing a font.

Instances

data FontStyle Source

Describe the basic stylistic properties of a font.

Constructors

FontStyle 

Fields

_fontStyleBold :: !Bool

If the font is bold.

_fontStyleItalic :: !Bool

If the font is italic.

data RawGlyph Source

This type represent unscaled glyph information, everything is still in its raw form.

Constructors

RawGlyph 

Fields

_rawGlyphCompositionScale :: ![CompositeScaling]

List of transformations to apply to the contour in order to get their correct placement.

_rawGlyphIndex :: !Int

Glyph index in the current font.

_rawGlyphContour :: ![Vector (Int16, Int16)]

Real Geometry of glyph, each vector contain one contour.

type Dpi = Int Source

Express device resolution in dot per inch.

newtype PointSize Source

Font size expressed in points. You must convert size expressed in pixels to point using the DPI information. See pixelSizeInPointAtDpi

Constructors

PointSize 

Fields

getPointSize :: Float
 

data CompositeScaling Source

Transformation matrix used to transform composite glyph

  | a b c |
  | d e f |

Constructors

CompositeScaling 

Fields

_a :: !Int16

a coeff.

_b :: !Int16

b coeff.

_c :: !Int16

c coeff.

_d :: !Int16

d coeff.

_e :: !Int16

e coeff.

_f :: !Int16

f coeff.

data BoundingBox Source

String bounding box. with value for min/max.

Constructors

BoundingBox 

Fields

_xMin :: !Float
 
_yMin :: !Float
 
_xMax :: !Float
 
_yMax :: !Float
 
_baselineHeight :: !Float

Should be 0 most of the times.

Instances