Safe Haskell | None |
---|---|
Language | Haskell2010 |
A simple layout engine to render text (and later also mathematics).
Synopsis
- subSupSize :: Double
- supPos :: Double
- subPos :: Double
- underlinePos :: Double
- overlinePos :: Double
- strikeThroughPos :: Double
- horizLineWidth :: Double
- abovePos :: Double
- belowPos :: Double
- fractionSize :: Double
- fracLinePos :: Double
- fracYMargin :: Double
- data SizeIndex
- scriptSuccSizeIndex :: SizeIndex -> SizeIndex
- fracSuccSizeIndex :: SizeIndex -> SizeIndex
- calculateSizeXHeight :: Height -> SizeIndex -> Int
- calculateSizeYHeight :: Height -> SizeIndex -> Int
- data Layout ident style
- data LayoutDecoration = HorizLine {
- _hlineCol :: !Col
- _hlineWhichQuad :: !WhichQuad
- _hlineVAlign :: !VAlign
- _hlineVPos :: !Double
- _hlineLineWidth :: !Double
- translateLayout :: Pos -> Layout ident style -> Layout ident style
- reboxLayout :: Box -> Layout ident style -> Layout ident style
- mfgRelBox :: MultiFontGlyph -> Box
- renderLayout :: Ord ident => Layout ident style -> Pos -> IO ()
- dryrunLayout :: Ord ident => Layout ident style -> Pos -> IO (Map ident AbsBox)
- renderLayout' :: forall ident style. Ord ident => Bool -> Layout ident style -> Pos -> IO (Map ident AbsBox)
- renderLayoutDecoration :: AbsBox -> LayoutDecoration -> IO ()
- createLayout :: forall fontfile style ident. (Ord fontfile, Ord ident) => MultiFont fontfile style -> Height -> Document ident -> IO (Layout ident style)
- data Cfg = Cfg {
- _currentSize :: !SizeIndex
- _currentStyle :: !BasicStyle
- _currentColor :: !Col
- defaultCfg :: Cfg
- createLayout' :: forall fontfile style ident. (Ord fontfile, Ord ident) => MultiFont fontfile style -> Height -> Document ident -> IO (Box, Layout ident style)
Relative position and size constants (mathematical coordinate system!)
subSupSize :: Double Source #
overlinePos :: Double Source #
fracLinePos :: Double Source #
fracYMargin :: Double Source #
Subscript size indexing
0 is the default size, 1 is smaller, 2 is even smaller, etc (each subscript
NormalSize | normal text size |
FractionSize | first-level fraction |
ScriptSize1 | first-level subscript |
ScriptSize2 | second-level subscript |
ScriptSize3 | third-level subscript |
CustomSize !(Double, Double) !SizeIndex | temporary hack |
The layout data type
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
LoutGlyph !Pos !style !Col !Char !MultiFontGlyph | |
LoutGroup !Box [Layout ident style] | |
LoutBox !Box (Layout ident style) | |
LoutOfs !Pos (Layout ident style) | |
LoutIdent !ident (Layout ident style) | |
LoutDecor !LayoutDecoration (Layout ident style) | |
LoutEmpty |
data LayoutDecoration Source #
HorizLine | |
|
Instances
Show LayoutDecoration Source # | |
Defined in Graphics.Rendering.MiniTypeset.Layout showsPrec :: Int -> LayoutDecoration -> ShowS # show :: LayoutDecoration -> String # showList :: [LayoutDecoration] -> ShowS # |
The box of a glyph
mfgRelBox :: MultiFontGlyph -> Box Source #
Rendering a 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.
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.
renderLayoutDecoration :: AbsBox -> LayoutDecoration -> IO () Source #
Creating a layouting
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
A type used by createLayout
Cfg | |
|
defaultCfg :: Cfg Source #