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

Safe HaskellNone
LanguageHaskell2010

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 v1.19.

This is a very low-level library; if you just want to render text using OpenGL, look at the the higher-level library minitypeset-opengl

Note: the glyph coordinate system uses te is the mathematical convention, that is, the Y coordinate increases upwards; unlike the screen and/or bitmap coordinate system, where Y increases downwards.

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
Eq Offset Source # 
Instance details

Defined in Graphics.Rendering.TrueType.STB

Methods

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

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

Ord Offset Source # 
Instance details

Defined in Graphics.Rendering.TrueType.STB

Show Offset Source # 
Instance details

Defined in Graphics.Rendering.TrueType.STB

data Glyph Source #

A glyph inside a font.

Instances
Eq Glyph Source # 
Instance details

Defined in Graphics.Rendering.TrueType.STB

Methods

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

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

Ord Glyph Source # 
Instance details

Defined in Graphics.Rendering.TrueType.STB

Methods

compare :: Glyph -> Glyph -> Ordering #

(<) :: Glyph -> Glyph -> Bool #

(<=) :: Glyph -> Glyph -> Bool #

(>) :: Glyph -> Glyph -> Bool #

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

max :: Glyph -> Glyph -> Glyph #

min :: Glyph -> Glyph -> Glyph #

Show Glyph Source # 
Instance details

Defined in Graphics.Rendering.TrueType.STB

Methods

showsPrec :: Int -> Glyph -> ShowS #

show :: Glyph -> String #

showList :: [Glyph] -> ShowS #

Initialization

withTTF :: FilePath -> (TrueType -> IO a) -> IO a Source #

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 #

Maps unicode characters to glyphs. As a hack, we map 0xffff (which is not a valid unicode code point) to the "not defined glyph" (glyph #0), which has no character counterpart.

Note: this is cached, so you can call it many times if necessary.

notDefinedGlyphChar :: Char Source #

The character 0xffff (which is not a valid unicode code point) which maps to the "not defined glyph"

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

data BoundingBox a Source #

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

Constructors

BBox (a, a) (a, a) 
Instances
Show a => Show (BoundingBox a) Source # 
Instance details

Defined in Graphics.Rendering.TrueType.STB

lineAdvance :: Num a => VerticalMetrics a -> a Source #

As calculated by (ascent - descent + lineGap).

verticalSize :: Num a => VerticalMetrics a -> a Source #

As calculated by (ascent - descent).

getGlyphKernAdvance :: Font -> Glyph -> Glyph -> IO Unscaled Source #

An additional amount to add to the 'advance' value between two glyphs

Bitmaps

data Bitmap Source #

A 8-bit grayscale bitmap.

Constructors

Bitmap 

Fields

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

flipBitmap :: Bitmap -> IO Bitmap Source #

Flips the bitmap vertically (leaving the original unchanged)

type BitmapOfs = (Int, Int) Source #

An offset (for example the pivot of the glyph)

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.

Vanilla (non-subpixel) rendering

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!

Subpixel rendering

type SubpixelShift = (Float, Float) Source #

The subpixel version of the rendering functions accept an additional fractional shift

getGlyphBitmapBoxSubpixel :: Font -> Glyph -> Scaling -> SubpixelShift -> 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.

newGlyphBitmapSubpixel :: Font -> Glyph -> Scaling -> SubpixelShift -> 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).

renderGlyphIntoBitmapSubpixel' :: Font -> Glyph -> Scaling -> SubpixelShift -> 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).

renderGlyphIntoBitmapSubpixel :: Font -> Glyph -> Scaling -> SubpixelShift -> 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!

Cached glyph storage

data CachedBitmap Source #

Note: the metrics are scaled!

bmcVerticalMetrics :: BitmapCache -> VerticalMetrics Float Source #

Note: these metrics are scaled!

newBitmapCache :: Font -> Bool -> (Float, Float) -> IO BitmapCache Source #

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

Unicode tables

data UnicodeCache a Source #

A table indexed by unicode code points.

Organized into small continous blocks (say 128 characters) so lookup should be pretty fast