Safe Haskell | None |
---|---|
Language | Haskell2010 |
Graphics.Rendering.MiniTypeset
Description
A text rendering and typesetting library for OpenGL.
It is enough to import this module to use the library.
To render text, first initialize your fonts with newMultiFont
;
then build a Document
describing what you want to render;
after that, create a Layout
out of it using createLayout
;
finally render it with renderLayout
. Optionally you can also
query the screen location of identified parts of the document,
and do something with them.
There is an example program (example-STIX.hs
) in the example subdirectory
illustrating how to use it.
Synopsis
- data Margin = Margin {
- _leftMargin :: !Double
- _rightMargin :: !Double
- _topMargin :: !Double
- _bottomMargin :: !Double
- class Translate a where
- data Pos = Pos !Double !Double
- data Delimiter
- = Paren
- | Square
- | Brace
- | Angle
- | Ceil
- | Floor
- | Top
- | Bottom
- | Guillemet
- | AngleQuote
- | VertSingle
- | VertDouble
- | Tortoise
- data WhichDelim
- data VAlign
- data HAlign
- data Col = Col !Float !Float !Float
- newtype Height = Height Int
- data BasicStyle
- = Regular
- | Bold
- | Italic
- | BoldItalic
- colToTriple :: Col -> (Float, Float, Float)
- tripleToCol :: (Float, Float, Float) -> Col
- delimiterChars :: Delimiter -> (Char, Char)
- posToPair :: Pos -> (Double, Double)
- pairToPos :: (Double, Double) -> Pos
- module Graphics.Rendering.MiniTypeset.Document
- module Graphics.Rendering.MiniTypeset.Box
- data UserFontConfig fontfile style = UserFontConfig {
- _ufcFontFiles :: fontfile -> FilePath
- _ufcCharMap :: style -> Char -> fontfile
- _ufcStyleMap :: BasicStyle -> style
- _ufcLineGapFactor :: !Double
- data MultiFont fontfile style
- newMultiFont :: Ord fontfile => UserFontConfig fontfile style -> IO (MultiFont fontfile style)
- data MultiFontGlyph
- 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
Common types
A margin definition
Constructors
Margin | |
Fields
|
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.
A delimiter type
Constructors
Paren | parentheses (can stretch) |
Square | square brackets (can stretch) |
Brace | curly braces (can stretch) |
Angle | angle brackets |
Ceil | ceiling |
Floor | floor |
Top | top corners |
Bottom | bottom corners |
Guillemet | guillemet or french quote |
AngleQuote | single quillemet or angle quote |
VertSingle | vertical line (can stretch) |
VertDouble | double vertical line (can stretch) |
Tortoise | tortoise brackets |
Instances
Eq Delimiter Source # | |
Ord Delimiter Source # | |
Defined in Graphics.Rendering.MiniTypeset.Common | |
Show Delimiter Source # | |
data WhichDelim Source #
Constructors
LeftDelim | |
RightDelim |
Instances
Eq WhichDelim Source # | |
Defined in Graphics.Rendering.MiniTypeset.Common | |
Ord WhichDelim Source # | |
Defined in Graphics.Rendering.MiniTypeset.Common Methods compare :: WhichDelim -> WhichDelim -> Ordering # (<) :: WhichDelim -> WhichDelim -> Bool # (<=) :: WhichDelim -> WhichDelim -> Bool # (>) :: WhichDelim -> WhichDelim -> Bool # (>=) :: WhichDelim -> WhichDelim -> Bool # max :: WhichDelim -> WhichDelim -> WhichDelim # min :: WhichDelim -> WhichDelim -> WhichDelim # | |
Show WhichDelim Source # | |
Defined in Graphics.Rendering.MiniTypeset.Common Methods showsPrec :: Int -> WhichDelim -> ShowS # show :: WhichDelim -> String # showList :: [WhichDelim] -> ShowS # |
Vertical alignment
Constructors
AlignTop | |
AlignBottom |
Horizontal alignment
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 # |
Documents
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
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
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.