sdl2-ttf-2.1.0: Bindings to SDL2_ttf.

Copyright(c) 2015 Siniša Biđin
LicenseMIT
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

SDL.Font

Contents

Description

Bindings to the SDL2_ttf library http://www.libsdl.org/projects/SDL_ttf/docs/SDL_ttf.html which itself is a wrapper around the FreeType library. The bindings should allow you to load fonts and render Text in various styles to an SDL Surface.

You can safely assume that any monadic function listed here is capable of throwing an SDLException in case it encounters an error.

Synopsis

General

initialize :: MonadIO m => m () Source #

Initializes the library.

Unless noted otherwise, this must be called before any other part of the library is used.

You may call this multiple times.

version :: (Integral a, MonadIO m) => m (a, a, a) Source #

Gets the major, minor, patch versions of the linked SDL2_ttf library.

You may call this without initializing the library with initialize.

quit :: MonadIO m => m () Source #

Cleans up any resources still in use by the library.

If called, you must call initialize again before using any other parts of the library.

Loading

Use the following functions to load TTF and FON file formats.

newtype Font Source #

Represents a loaded font.

Constructors

Font 

Fields

Instances

Eq Font Source # 

Methods

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

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

Show Font Source # 

Methods

showsPrec :: Int -> Font -> ShowS #

show :: Font -> String #

showList :: [Font] -> ShowS #

type PointSize = Int Source #

Point size (based on 72DPI) to load font as. Translates to pixel height.

load :: MonadIO m => FilePath -> PointSize -> m Font Source #

Given a path to a font file, loads it for use as a Font at a certain PointSize.

type Index = Int Source #

Designates a font face, the default and first one being 0.

loadIndex :: MonadIO m => FilePath -> PointSize -> Index -> m Font Source #

Given a path to a font file, loads one of its font faces (designated by the given index) for use as a Font at a certain PointSize.

The first face is always index 0, and is the one chosen by default when using load.

decode :: MonadIO m => ByteString -> PointSize -> m Font Source #

Same as load, but accepts a ByteString containing a font instead.

decodeIndex :: MonadIO m => ByteString -> PointSize -> Index -> m Font Source #

Same as loadIndex, but accepts a ByteString containing a font instead.

free :: MonadIO m => Font -> m () Source #

Frees a loaded Font.

Rendering

Use the following functions to render text to a Surface.

The methods available are described in more detail in the original SDL2_ttf documentation here.

type Color = V4 Word8 Source #

Color as an RGBA byte vector.

solid :: MonadIO m => Font -> Color -> Text -> m Surface Source #

Renders Text using the quick and dirty method.

Is the fastest of the rendering methods, but results in text that isn't as smooth.

shaded :: MonadIO m => Font -> Color -> Color -> Text -> m Surface Source #

Uses the slow and nice, but with a solid box method.

Renders slower than solid, but in about the same time as blended.

Results in a Surface containing antialiased text of a foreground color surrounded by a box of a background color. This Surface will blit as fast as the one from solid.

blended :: MonadIO m => Font -> Color -> Text -> m Surface Source #

The slow slow slow, but ultra nice over another image method, blended renders text at high quality.

The text is antialiased and surrounded by a transparent box. Renders slower than solid, but in about the same time as shaded.

The resulting Surface will blit slower than the ones from solid or shaded.

size :: MonadIO m => Font -> Text -> m (Int, Int) Source #

Use this function to discover how wide and tall a Surface needs to be in order to accommodate a given text when it is rendered.

Note that no actual rendering takes place.

The values returned are the width and height, respectively, in pixels. The height returned is the same one returned by height.

Attributes

data Style Source #

Possible styles that can be applied to a Font.

Instances

Bounded Style Source # 
Enum Style Source # 
Eq Style Source # 

Methods

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

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

Ord Style Source # 

Methods

compare :: Style -> Style -> Ordering #

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

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

(>) :: Style -> Style -> Bool #

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

max :: Style -> Style -> Style #

min :: Style -> Style -> Style #

Read Style Source # 
Show Style Source # 

Methods

showsPrec :: Int -> Style -> ShowS #

show :: Style -> String #

showList :: [Style] -> ShowS #

Generic Style Source # 

Associated Types

type Rep Style :: * -> * #

Methods

from :: Style -> Rep Style x #

to :: Rep Style x -> Style #

type Rep Style Source # 
type Rep Style = D1 * (MetaData "Style" "SDL.Font" "sdl2-ttf-2.1.0-5LcWINvqecN7OfLBSF03B" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Bold" PrefixI False) (U1 *)) (C1 * (MetaCons "Italic" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Underline" PrefixI False) (U1 *)) (C1 * (MetaCons "Strikethrough" PrefixI False) (U1 *))))

getStyle :: MonadIO m => Font -> m [Style] Source #

Gets the rendering styles of a given Font.

If none were ever set, this will be an empty list.

setStyle :: MonadIO m => Font -> [Style] -> m () Source #

Sets the rendering style of a Font.

Use an empty list to reset the style.

type Outline = Int Source #

The size of the Font outline, in pixels.

Use 0 to turn off outlining.

getOutline :: MonadIO m => Font -> m Outline Source #

Gets the current outline size of a given Font.

setOutline :: MonadIO m => Font -> Outline -> m () Source #

Sets the outline size for a given Font.

Use 0 to turn off outlining.

data Hinting Source #

The hinting setting of a Font.

Constructors

Normal 
Light 
Mono 
None 

Instances

Bounded Hinting Source # 
Enum Hinting Source # 
Eq Hinting Source # 

Methods

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

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

Ord Hinting Source # 
Read Hinting Source # 
Show Hinting Source # 
Generic Hinting Source # 

Associated Types

type Rep Hinting :: * -> * #

Methods

from :: Hinting -> Rep Hinting x #

to :: Rep Hinting x -> Hinting #

type Rep Hinting Source # 
type Rep Hinting = D1 * (MetaData "Hinting" "SDL.Font" "sdl2-ttf-2.1.0-5LcWINvqecN7OfLBSF03B" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Normal" PrefixI False) (U1 *)) (C1 * (MetaCons "Light" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Mono" PrefixI False) (U1 *)) (C1 * (MetaCons "None" PrefixI False) (U1 *))))

getHinting :: MonadIO m => Font -> m Hinting Source #

Gets the hinting setting of a given Font.

setHinting :: MonadIO m => Font -> Hinting -> m () Source #

Sets the hinting setting of a font.

type Kerning = Bool Source #

Whether kerning is enabled or not.

The default for a newly-loaded Font is enabled.

getKerning :: MonadIO m => Font -> m Kerning Source #

Gets the current kerning setting of a given Font.

setKerning :: MonadIO m => Font -> Kerning -> m () Source #

Sets the kerning setting for a given Font.

Use False to turn off kerning.

isMonospace :: MonadIO m => Font -> m Bool Source #

Tests whether the current face of a Font is a fixed width font or not.

familyName :: MonadIO m => Font -> m (Maybe Text) Source #

Gets the current font face family name, if any.

styleName :: MonadIO m => Font -> m (Maybe Text) Source #

Gets the current font face style name, if any.

height :: MonadIO m => Font -> m Int Source #

Gets the maximum pixel height of all glyphs of a given Font.

ascent :: MonadIO m => Font -> m Int Source #

Gets the maximum pixel ascent of all glyphs of a given Font.

This can be interpreted as the distance from the top of the font to the baseline.

descent :: MonadIO m => Font -> m Int Source #

Gets the maximum pixel descent of all glyphs of a given Font.

Also interpreted as the distance from the baseline to the bottom of the font.

lineSkip :: MonadIO m => Font -> m Int Source #

Gets the recommended pixel height of a rendered line of text of a given Font.

This is usually larger than what height would return.

getKerningSize :: MonadIO m => Font -> Index -> Index -> m Int Source #

From a given Font get the kerning size of two glyphs.

Glyphs

Functions that work with individual glyphs.

glyphProvided :: MonadIO m => Font -> Char -> m Bool Source #

Does a Font provide a certain unicode character?

glyphIndex :: MonadIO m => Font -> Char -> m (Maybe Int) Source #

Same as glyphProvided, but returns an index of the glyph for the given character instead, if one is provided.

glyphMetrics :: MonadIO m => Font -> Char -> m (Maybe (Int, Int, Int, Int, Int)) Source #

Get glyph metrics for a given unicode character. The values returned are:

  1. minimum x offset
  2. maximum x offset
  3. minimum y offset
  4. maximum y offset
  5. advance offset

You can see more information about these values in the original SDL2_ttf documentation here.

solidGlyph :: MonadIO m => Font -> Color -> Char -> m Surface Source #

Same as solid, but renders a single glyph instead.

shadedGlyph :: MonadIO m => Font -> Color -> Color -> Char -> m Surface Source #

Same as shaded, but renders a single glyph instead.

blendedGlyph :: MonadIO m => Font -> Color -> Char -> m Surface Source #

Same as blended, but renders a single glyph instead.

blendedWrapped :: MonadIO m => Font -> Color -> Int -> Text -> m Surface Source #

Same as blended, but renders across multiple lines. Text is wrapped to multiple lines on line endings and on word boundaries if it extends beyond wrapLength in pixels.