typograffiti-0.2.0.1: Just let me draw nice text already
Copyright(c) 2018 Schell Scivally
LicenseMIT
MaintainerSchell Scivally <schell@takt.com> & Adrian Cochrane <alcinnz@argonaut-constellation.org>
Safe HaskellSafe-Inferred
LanguageHaskell2010

Typograffiti.Text

Description

Text rendering abstraction, hiding the details of the Atlas, Cache, and the Harfbuzz library.

Synopsis

Documentation

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.

Instances

Instances details
Show GlyphSize Source # 
Instance details

Defined in Typograffiti.Text

Methods

showsPrec :: Int -> GlyphSize -> ShowS

show :: GlyphSize -> String

showList :: [GlyphSize] -> ShowS

Eq GlyphSize Source # 
Instance details

Defined in Typograffiti.Text

Methods

(==) :: GlyphSize -> GlyphSize -> Bool

(/=) :: GlyphSize -> GlyphSize -> Bool

Ord GlyphSize Source # 
Instance details

Defined in Typograffiti.Text

Methods

compare :: GlyphSize -> GlyphSize -> Ordering

(<) :: GlyphSize -> GlyphSize -> Bool

(<=) :: GlyphSize -> GlyphSize -> Bool

(>) :: GlyphSize -> GlyphSize -> Bool

(>=) :: GlyphSize -> GlyphSize -> Bool

max :: GlyphSize -> GlyphSize -> GlyphSize

min :: GlyphSize -> GlyphSize -> GlyphSize

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 0 indicate to use the font's default lineheight.

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 :: String Source #

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

varOptSize :: String Source #

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

varSlant :: String Source #

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

varWidth :: String Source #

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

varWeight :: String Source #

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

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.

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

Variant of makeDrawText which initializes FreeType itself.

type TextRenderer m = RichText -> m (AllocatedRendering [TextTransform]) Source #

Internal utility for rendering multiple lines of text & expanding tabs as configured.

drawLinesWrapper :: (MonadIO m, MonadFail m) => Int -> Float -> TextRenderer m -> TextRenderer m Source #