Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- data Bracket
- = Paren
- | Square
- | Brace
- | Angle
- | Ceil
- | Floor
- | Top
- | Bottom
- | AngleQuote
- | FrenchQuote
- class Translate a where
- data Pos = Pos !Double !Double
- data VAlign
- data HAlign
- data Col = Col !Double !Double !Double
- newtype Height = Height Int
- data BasicStyle
- = Regular
- | Bold
- | Italic
- | BoldItalic
- colToTriple :: Col -> (Double, Double, Double)
- tripleToCol :: (Double, Double, Double) -> Col
- black :: Col
- white :: Col
- red :: Col
- green :: Col
- blue :: Col
- yellow :: Col
- cyan :: Col
- magenta :: Col
- posToPair :: Pos -> (Double, Double)
- bracketChars :: Bracket -> (Char, Char)
- module Graphics.Rendering.MiniTypeset.Box
- data UserFontConfig fontfile style = UserFontConfig {
- _ufcFontFiles :: fontfile -> FilePath
- _ufcCharMap :: style -> Char -> fontfile
- _ufcStyleMap :: BasicStyle -> style
- data MultiFont fontfile style
- newMultiFont :: Ord fontfile => UserFontConfig fontfile style -> IO (MultiFont fontfile style)
- data MultiFontGlyph
- data Document ident
- data Layout ident style
- createLayout :: forall fontfile style ident. (Ord fontfile, Ord ident) => MultiFont fontfile style -> Height -> Document ident -> IO (Layout ident style)
- createLayout' :: forall fontfile style ident. (Ord fontfile, Ord ident) => MultiFont fontfile style -> Height -> Document ident -> IO (Box, Layout ident style)
- dryrunLayout :: Ord ident => Layout ident style -> Pos -> IO (Map ident AbsBox)
- renderLayout :: Ord ident => Layout ident style -> Pos -> IO ()
- renderLayout' :: forall ident style. Ord ident => Bool -> Layout ident style -> Pos -> IO (Map ident AbsBox)
- module Graphics.Rendering.MiniTypeset.Render
Documentation
Constructors
Paren | |
Square | |
Brace | |
Angle | |
Ceil | |
Floor | |
Top | |
Bottom | |
AngleQuote | |
FrenchQuote |
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
AlignBottom | |
AlignTop |
Constructors
AlignLeft | |
AlignRight |
Font height in pixels
data BasicStyle Source #
Basic variations in a typeface (font family)
Constructors
Regular | |
Bold | |
Italic | |
BoldItalic |
Instances
Eq BasicStyle Source # | |
Defined in Graphics.Rendering.MiniTypeset.Common | |
Ord BasicStyle Source # | |
Defined in Graphics.Rendering.MiniTypeset.Common Methods compare :: BasicStyle -> BasicStyle -> Ordering # (<) :: BasicStyle -> BasicStyle -> Bool # (<=) :: BasicStyle -> BasicStyle -> Bool # (>) :: BasicStyle -> BasicStyle -> Bool # (>=) :: BasicStyle -> BasicStyle -> Bool # max :: BasicStyle -> BasicStyle -> BasicStyle # min :: BasicStyle -> BasicStyle -> BasicStyle # | |
Show BasicStyle Source # | |
Defined in Graphics.Rendering.MiniTypeset.Common Methods showsPrec :: Int -> BasicStyle -> ShowS # show :: BasicStyle -> String # showList :: [BasicStyle] -> ShowS # |
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
|
newMultiFont :: Ord fontfile => UserFontConfig fontfile style -> IO (MultiFont fontfile style) Source #
data MultiFontGlyph Source #
Instances
Show MultiFontGlyph Source # | |
Defined in Graphics.Rendering.MiniTypeset.MultiFont Methods showsPrec :: Int -> MultiFontGlyph -> ShowS # show :: MultiFontGlyph -> String # showList :: [MultiFontGlyph] -> ShowS # |
Layout
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 # | |
Ord ident => Ord (Document ident) Source # | |
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 # | |
Show ident => Show (Document ident) Source # | |
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 |
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.