minitypeset-opengl-0.1.0.0: Layout and render text with TrueType fonts using OpenGL

Safe HaskellNone
LanguageHaskell2010

Graphics.Rendering.MiniTypeset

Contents

Description

A text rendering and typesetting library for OpenGL.

It is enough to import this module to use the library.

There is an example program (example-STIX.hs) in the example subdirectory illustrating how to use it.

Synopsis

Documentation

class Translate a where Source #

Methods

translate :: Pos -> a -> a Source #

Instances
Translate Pos Source # 
Instance details

Defined in Graphics.Rendering.MiniTypeset.Common

Methods

translate :: Pos -> Pos -> Pos Source #

Translate AbsBox Source # 
Instance details

Defined in Graphics.Rendering.MiniTypeset.Box

Methods

translate :: Pos -> AbsBox -> AbsBox Source #

Translate (Layout ident style) Source # 
Instance details

Defined in Graphics.Rendering.MiniTypeset.Layout

Methods

translate :: Pos -> Layout ident style -> Layout ident style Source #

data Pos Source #

A position. We use screen-space coordinates here (so the top-left corner of the screen is the origin, and the vertical coordinate increases downwards).

It is monomorphic so that GHC can optimize it better.

Constructors

Pos !Double !Double 
Instances
Eq Pos Source # 
Instance details

Defined in Graphics.Rendering.MiniTypeset.Common

Methods

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

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

Num Pos Source # 
Instance details

Defined in Graphics.Rendering.MiniTypeset.Common

Methods

(+) :: Pos -> Pos -> Pos #

(-) :: Pos -> Pos -> Pos #

(*) :: Pos -> Pos -> Pos #

negate :: Pos -> Pos #

abs :: Pos -> Pos #

signum :: Pos -> Pos #

fromInteger :: Integer -> Pos #

Ord Pos Source # 
Instance details

Defined in Graphics.Rendering.MiniTypeset.Common

Methods

compare :: Pos -> Pos -> Ordering #

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

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

(>) :: Pos -> Pos -> Bool #

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

max :: Pos -> Pos -> Pos #

min :: Pos -> Pos -> Pos #

Show Pos Source # 
Instance details

Defined in Graphics.Rendering.MiniTypeset.Common

Methods

showsPrec :: Int -> Pos -> ShowS #

show :: Pos -> String #

showList :: [Pos] -> ShowS #

Translate Pos Source # 
Instance details

Defined in Graphics.Rendering.MiniTypeset.Common

Methods

translate :: Pos -> Pos -> Pos Source #

data VAlign Source #

Constructors

AlignBottom 
AlignTop 
Instances
Eq VAlign Source # 
Instance details

Defined in Graphics.Rendering.MiniTypeset.Common

Methods

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

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

Ord VAlign Source # 
Instance details

Defined in Graphics.Rendering.MiniTypeset.Common

Show VAlign Source # 
Instance details

Defined in Graphics.Rendering.MiniTypeset.Common

data HAlign Source #

Constructors

AlignLeft 
AlignRight 
Instances
Eq HAlign Source # 
Instance details

Defined in Graphics.Rendering.MiniTypeset.Common

Methods

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

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

Ord HAlign Source # 
Instance details

Defined in Graphics.Rendering.MiniTypeset.Common

Show HAlign Source # 
Instance details

Defined in Graphics.Rendering.MiniTypeset.Common

data Col Source #

Constructors

Col !Double !Double !Double 
Instances
Eq Col Source # 
Instance details

Defined in Graphics.Rendering.MiniTypeset.Common

Methods

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

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

Ord Col Source # 
Instance details

Defined in Graphics.Rendering.MiniTypeset.Common

Methods

compare :: Col -> Col -> Ordering #

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

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

(>) :: Col -> Col -> Bool #

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

max :: Col -> Col -> Col #

min :: Col -> Col -> Col #

Show Col Source # 
Instance details

Defined in Graphics.Rendering.MiniTypeset.Common

Methods

showsPrec :: Int -> Col -> ShowS #

show :: Col -> String #

showList :: [Col] -> ShowS #

newtype Height Source #

Font height in pixels

Constructors

Height Int 
Instances
Eq Height Source # 
Instance details

Defined in Graphics.Rendering.MiniTypeset.Common

Methods

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

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

Ord Height Source # 
Instance details

Defined in Graphics.Rendering.MiniTypeset.Common

Show Height Source # 
Instance details

Defined in Graphics.Rendering.MiniTypeset.Common

Boxes

"Multifonts"

data UserFontConfig fontfile style Source #

The user-defined types fontfile and style should encode the available font files and styles. They should be an enumerated type for efficiency. fontfile must have Eq and Ord instances, too.

Constructors

UserFontConfig 

Fields

data MultiFont fontfile style Source #

newMultiFont :: Ord fontfile => UserFontConfig fontfile style -> IO (MultiFont fontfile style) Source #

Layout

data Document ident Source #

This data type describes what the user want to render.

The type parameter ident is used when the user want to know positions (bounding boxes) of different parts of the rendered text. It must have an Ord instance.

Constructors

Symbol !Char 
String !String 
Space 
HorzCat !VAlign [Document ident] 
VertCat !HAlign [Document ident] 
WithColor !Col !(Document ident) 
WithStyle !BasicStyle !(Document ident) 
Identified !ident !(Document ident)

user identifier so that the layout engine can return position information

Instances
Eq ident => Eq (Document ident) Source # 
Instance details

Defined in Graphics.Rendering.MiniTypeset.Layout

Methods

(==) :: Document ident -> Document ident -> Bool #

(/=) :: Document ident -> Document ident -> Bool #

Ord ident => Ord (Document ident) Source # 
Instance details

Defined in Graphics.Rendering.MiniTypeset.Layout

Methods

compare :: Document ident -> Document ident -> Ordering #

(<) :: Document ident -> Document ident -> Bool #

(<=) :: Document ident -> Document ident -> Bool #

(>) :: Document ident -> Document ident -> Bool #

(>=) :: Document ident -> Document ident -> Bool #

max :: Document ident -> Document ident -> Document ident #

min :: Document ident -> Document ident -> Document ident #

Show ident => Show (Document ident) Source # 
Instance details

Defined in Graphics.Rendering.MiniTypeset.Layout

Methods

showsPrec :: Int -> Document ident -> ShowS #

show :: Document ident -> String #

showList :: [Document ident] -> ShowS #

data Layout ident style Source #

This data type is the output of the layout engine. The `identifying' part is retained, because everything is still relative, and only during the rendering will positions become absolute. See dryrunLayout

Constructors

LoutGlyph Pos style Col Char MultiFontGlyph 
LoutGroup Box [Layout ident style] 
LoutOfs Pos (Layout ident style) 
LoutIdent ident (Layout ident style) 
LoutEmpty 
Instances
(Show style, Show ident) => Show (Layout ident style) Source # 
Instance details

Defined in Graphics.Rendering.MiniTypeset.Layout

Methods

showsPrec :: Int -> Layout ident style -> ShowS #

show :: Layout ident style -> String #

showList :: [Layout ident style] -> ShowS #

Translate (Layout ident style) Source # 
Instance details

Defined in Graphics.Rendering.MiniTypeset.Layout

Methods

translate :: Pos -> Layout ident style -> Layout ident style Source #

createLayout :: forall fontfile style ident. (Ord fontfile, Ord ident) => MultiFont fontfile style -> Height -> Document ident -> IO (Layout ident style) Source #

Creates a layout from a document. Then you can render the resulting layout with renderLayout

createLayout' :: forall fontfile style ident. (Ord fontfile, Ord ident) => MultiFont fontfile style -> Height -> Document ident -> IO (Box, Layout ident style) Source #

dryrunLayout :: Ord ident => Layout ident style -> Pos -> IO (Map ident AbsBox) Source #

Does not actually render, but computes the bounding boxes of the identified parts of the layout.

renderLayout :: Ord ident => Layout ident style -> Pos -> IO () Source #

Renders the layout to the OpenGL framebuffer.

Note: you should set up the OpenGL coordinate transformation matrices so that the coordinate system is screen-space, measured in pixels. For example something like

matrixMode $= Projection
loadIdentity
ortho 0 xres yres 0 (-1) 1 
matrixMode $= Modelview 0
loadIdentity

should do.

renderLayout' Source #

Arguments

:: Ord ident 
=> Bool

True = dryrun (do not render); False = do the rendering

-> Layout ident style 
-> Pos 
-> IO (Map ident AbsBox) 

Rendering