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

Description

This module provides a font-character atlas to use in font rendering with opengl.

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.

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

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 #

emptyAtlas :: GLuint -> Atlas Source #

Initializes an empty atlas.

data AtlasMeasure Source #

Precomputed positioning of glyphs in an Atlas texture.

Constructors

AM 

Fields

  • amWH :: V2 Int

    Current size of the atlas as it has been laid out so far.

  • amXY :: V2 Int

    Tentative position for the next glyph added to the atlas.

  • rowHeight :: Int

    Height of the current row, for the sake of line wrapping.

  • amMap :: IntMap (V2 Int)

    Position of each glyph in the atlas.

Instances
Eq AtlasMeasure Source # 
Instance details

Defined in Typograffiti.Atlas

Show AtlasMeasure Source # 
Instance details

Defined in Typograffiti.Atlas

spacing :: Int Source #

The amount of spacing between glyphs rendered into the atlas's texture.

type GlyphRetriever m = Word32 -> m (FT_Bitmap, FT_Glyph_Metrics) Source #

Callback for looking up a glyph from an atlas. Useful for applying synthetic styles to fonts which lack them, when calling the low-level APIs.

glyphRetriever :: (MonadIO m, MonadError TypograffitiError m) => FT_Face -> GlyphRetriever m Source #

Default callback for glyph lookups, with no modifications.

measure :: (MonadIO m, MonadError TypograffitiError m) => GlyphRetriever m -> Int -> AtlasMeasure -> Word32 -> m AtlasMeasure Source #

Extract the measurements of a character in the FT_Face and append it to the given AtlasMeasure.

texturize :: (MonadIO m, MonadError TypograffitiError m) => GlyphRetriever m -> IntMap (V2 Int) -> Atlas -> Word32 -> m Atlas Source #

Uploads glyphs into an Atlas texture for the GPU to composite.

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.

type Quads = (Float, Float, [Vector (V2 Float, V2 Float)]) Source #

The geometry needed to render some text, with the position for the next glyph.

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

Construct the geometry needed to render the given character.

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

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

stringTris' :: (MonadIO m, MonadError TypograffitiError m) => Atlas -> [(GlyphInfo, GlyphPos)] -> m (Vector (V2 Float, V2 Float)) Source #

Generate the geometry of the given string.

liftFreetype :: (MonadIO m, MonadError TypograffitiError m) => IO a -> m a Source #

Internal utility to propagate FreeType errors into Typograffiti errors.