stb-truetype-0.1.2: A wrapper around Sean Barrett's TrueType rasterizer library.

Graphics.Rendering.TrueType.STB

Contents

Description

This is a wrapper around Sean Barrett's TrueType font rasterizer code. The original can be found at http://nothings.org/stb/stb_truetype.h. The version of stb-truetype used here is 0.3.

Synopsis

Documentation

newtype TrueType Source

A TrueType font file (containing maybe multiple font sets) loaded into memory.

Constructors

TrueType ByteString 

data Offset Source

A font offset inside a TrueType font file.

Instances

data Glyph Source

A glyph inside a font.

Instances

Initialization

withTTF :: FilePath -> (TrueType -> IO a) -> IO aSource

enumerateFonts :: TrueType -> IO [Offset]Source

Enumerates the fonts found in a TrueType file. Often there is only one, but there may be more.

findGlyph :: Font -> Char -> IO (Maybe Glyph)Source

Note: this is cached.

Font metrics

data VerticalMetrics a Source

ascent is the coordinate above the baseline the font extends; descent is the coordinate below the baseline the font extends (i.e. it is typically negative) lineGap is the spacing between one row's descent and the next row's ascent... so you should advance the vertical position by ascent - descent + lineGap

Constructors

VMetrics 

Fields

ascent :: a
 
descent :: a
 
lineGap :: a
 

data BoundingBox a Source

The convention is BBox (x0,y0) (x1,y1).

Constructors

BBox (a, a) (a, a) 

Instances

Show a => Show (BoundingBox a) 

lineAdvance :: Num a => VerticalMetrics a -> aSource

As calculated by (ascent - descent + lineGap).

verticalSize :: Num a => VerticalMetrics a -> aSource

As calculated by (ascent - descent).

getGlyphKernAdvance :: Font -> Glyph -> Glyph -> IO UnscaledSource

This is not yet implemented in stb_truetype; it always returns 0.

Bitmaps

data Bitmap Source

A 8-bit grayscale bitmap.

Constructors

Bitmap 

withBitmap :: Bitmap -> (Int -> Int -> Ptr Word8 -> IO a) -> IO aSource

flipBitmap :: Bitmap -> IO BitmapSource

Flips the bitmap vertically (leaving the original unchanged)

type BitmapOfs = (Int, Int)Source

An offset (for example the pivot of the glyph)

getGlyphBitmapBox :: Font -> Glyph -> Scaling -> IO (BoundingBox Int)Source

Returns the size of the bitmap (in pixels) needed to render the glyph with the given scaling.

The box is centered around the glyph origin; so the bitmap width is x1-x0, height is y1-y0, and location to place the bitmap top left is (leftSideBearing*scale,y0). Note that the bitmap uses y-increases-down, but the shape uses y-increases-up, so the results of getGlyphBitmapBox and getGlyphBoundingBox are inverted.

newGlyphBitmap :: Font -> Glyph -> Scaling -> IO (Bitmap, BitmapOfs)Source

Creates a new bitmap just enough to fit the glyph with the given scaling, and renders the glyph into it. The offset returned is the offset in pixel space from the glyph origin to the top-left of the bitmap (so it's almost always negative).

renderGlyphIntoBitmap' :: Font -> Glyph -> Scaling -> Bitmap -> BitmapOfs -> IO ()Source

The offset is the top-left corner of the bounding box of the glyph, and must be nonnegative (otherwise nothing will happen).

renderGlyphIntoBitmap :: Font -> Glyph -> Scaling -> Bitmap -> BitmapOfs -> IO ()Source

The offset is the origin of the glyph. If the glyph extends from the bitmap in the positive direction, it is clipped; however, if it extends in the negative direction, no drawing will happen!

bitmapArray :: Bitmap -> IO (UArray (Int, Int) Word8)Source

NOTE: because of the way Haskell indexes rectangular arrays, the resulting array is indexed with (y,x), as opposed to what you would expect.

Cached glyph storage

data CachedBitmap Source

Note: the metrics are scaled!

data BitmapCache Source

A "bitmap cache".

bmcVerticalMetrics :: BitmapCache -> VerticalMetrics FloatSource

Note: these metrics are scaled!

newBitmapCache :: Font -> Bool -> (Float, Float) -> IO BitmapCacheSource

Creates a new cache where glyph bitmaps with the given scaling will be stored. The second argument is whether the resulting bitmaps should be flipped vertically or not (this is useful with OpenGL).

getCachedBitmap :: BitmapCache -> Char -> IO (Maybe CachedBitmap)Source

Fetches a rendered glyph bitmap from the cache (rendering it first if it was not present in the cache before).