Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Graphics.Rendering.MiniTypeset.Document
Contents
Description
The document type, which expresses the intent of the user about what to render.
We support general layouting / formatting, and also construction specific to mathematical documents (similar to LaTeX).
TODO: fractions, brackets, mathemetical accents, compound symbols
Synopsis
- data Document ident
- = Symbol !Char
- | String !String
- | Space
- | HorzCat !VAlign [Document ident]
- | VertCat !HAlign [Document ident]
- | Overlay !(HAlign, VAlign) [Document ident]
- | SubSupScript !(SubSup ident) !(Document ident)
- | AboveBelow !(AboveBelow ident) !(Document ident)
- | WithColor !Col !(Document ident)
- | WithStyle !BasicStyle !(Document ident)
- | Decorated !TextDecoration !(Document ident)
- | Identified !ident !(Document ident)
- | AddMargin !Margin !(Document ident)
- | Realign !WhichQuad !(Document ident)
- | EmptyDoc
- data TextDecoration
- data SubSup ident
- = Subscript !(Document ident)
- | Superscript !(Document ident)
- | SubAndSupscript !(Document ident) !(Document ident)
- subSupDocs :: SubSup ident -> (Document ident, Document ident)
- data AboveBelow ident
- aboveBelowDocs :: AboveBelow ident -> (Document ident, Document ident)
- string :: String -> Document a
- char :: Char -> Document a
- space :: Document a
- zeroWidthSpace :: Document a
- (<|>) :: Document a -> Document a -> Document a
- (<->) :: Document a -> Document a -> Document a
- (<#>) :: Document a -> Document a -> Document a
- hcat :: [Document a] -> Document a
- vcat :: [Document a] -> Document a
- overlay :: [Document a] -> Document a
- hcatB :: [Document a] -> Document a
- hcatT :: [Document a] -> Document a
- vcatL :: [Document a] -> Document a
- vcatR :: [Document a] -> Document a
- subscript :: Document a -> Document a -> Document a
- supscript :: Document a -> Document a -> Document a
- subSup :: Document a -> (Document a, Document a) -> Document a
- above :: Document a -> Document a -> Document a
- below :: Document a -> Document a -> Document a
- aboveBelow :: Document a -> (Document a, Document a) -> Document a
- underline :: Document a -> Document a
- overline :: Document a -> Document a
- strike :: Document a -> Document a
- regular :: Document a -> Document a
- bold :: Document a -> Document a
- italic :: Document a -> Document a
- boldItalic :: Document a -> Document a
- white :: Document a -> Document a
- black :: Document a -> Document a
- red :: Document a -> Document a
- green :: Document a -> Document a
- blue :: Document a -> Document a
- rgb :: Float -> Float -> Float -> Document a -> Document a
- margin :: Double -> Document a -> Document a
- hmargin :: Double -> Document a -> Document a
- vmargin :: Double -> Document a -> Document a
- margin' :: Double -> Double -> Double -> Double -> Document a -> Document a
- data Bracket
- = Paren
- | Square
- | Brace
- | Angle
- | Ceil
- | Floor
- | Top
- | Bottom
- | AngleQuote
- | FrenchQuote
- bracketChars :: Bracket -> (Char, Char)
The document data type
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 | a single character or symbol |
String !String | a string |
Space | a space character (do we need this to be separate?) |
HorzCat !VAlign [Document ident] | horizontal concatenation |
VertCat !HAlign [Document ident] | vertical concatenation |
Overlay !(HAlign, VAlign) [Document ident] | overlaying on the top of each other |
SubSupScript !(SubSup ident) !(Document ident) | add subscript and/or superscript |
AboveBelow !(AboveBelow ident) !(Document ident) | above/below (like in a summation or limit) |
WithColor !Col !(Document ident) | change color |
WithStyle !BasicStyle !(Document ident) | change font family |
Decorated !TextDecoration !(Document ident) | add text decoration |
Identified !ident !(Document ident) | user identifier so that the layout engine can return position information |
AddMargin !Margin !(Document ident) | an extra margin around the document |
Realign !WhichQuad !(Document ident) | change the alignment box |
EmptyDoc | the empty document |
Instances
Eq ident => Eq (Document ident) Source # | |
Ord ident => Ord (Document ident) Source # | |
Defined in Graphics.Rendering.MiniTypeset.Document 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 # | |
IsString (Document ident) Source # | |
Defined in Graphics.Rendering.MiniTypeset.Document Methods fromString :: String -> Document ident # |
data TextDecoration Source #
A text decoration
Constructors
Underline | |
Overline | |
StrikeThrough |
Instances
Eq TextDecoration Source # | |
Defined in Graphics.Rendering.MiniTypeset.Document Methods (==) :: TextDecoration -> TextDecoration -> Bool # (/=) :: TextDecoration -> TextDecoration -> Bool # | |
Ord TextDecoration Source # | |
Defined in Graphics.Rendering.MiniTypeset.Document Methods compare :: TextDecoration -> TextDecoration -> Ordering # (<) :: TextDecoration -> TextDecoration -> Bool # (<=) :: TextDecoration -> TextDecoration -> Bool # (>) :: TextDecoration -> TextDecoration -> Bool # (>=) :: TextDecoration -> TextDecoration -> Bool # max :: TextDecoration -> TextDecoration -> TextDecoration # min :: TextDecoration -> TextDecoration -> TextDecoration # | |
Show TextDecoration Source # | |
Defined in Graphics.Rendering.MiniTypeset.Document Methods showsPrec :: Int -> TextDecoration -> ShowS # show :: TextDecoration -> String # showList :: [TextDecoration] -> ShowS # |
A subscript or a superscript, or both
Constructors
Subscript !(Document ident) | |
Superscript !(Document ident) | |
SubAndSupscript !(Document ident) !(Document ident) | first is the subscript, second the superscript |
Instances
Eq ident => Eq (SubSup ident) Source # | |
Ord ident => Ord (SubSup ident) Source # | |
Defined in Graphics.Rendering.MiniTypeset.Document | |
Show ident => Show (SubSup ident) Source # | |
data AboveBelow ident Source #
Limits of summations and similar things.
Constructors
Above !(Document ident) | |
Below !(Document ident) | |
AboveAndBelow !(Document ident) !(Document ident) | first is the above, second is below |
Instances
Eq ident => Eq (AboveBelow ident) Source # | |
Defined in Graphics.Rendering.MiniTypeset.Document Methods (==) :: AboveBelow ident -> AboveBelow ident -> Bool # (/=) :: AboveBelow ident -> AboveBelow ident -> Bool # | |
Ord ident => Ord (AboveBelow ident) Source # | |
Defined in Graphics.Rendering.MiniTypeset.Document Methods compare :: AboveBelow ident -> AboveBelow ident -> Ordering # (<) :: AboveBelow ident -> AboveBelow ident -> Bool # (<=) :: AboveBelow ident -> AboveBelow ident -> Bool # (>) :: AboveBelow ident -> AboveBelow ident -> Bool # (>=) :: AboveBelow ident -> AboveBelow ident -> Bool # max :: AboveBelow ident -> AboveBelow ident -> AboveBelow ident # min :: AboveBelow ident -> AboveBelow ident -> AboveBelow ident # | |
Show ident => Show (AboveBelow ident) Source # | |
Defined in Graphics.Rendering.MiniTypeset.Document Methods showsPrec :: Int -> AboveBelow ident -> ShowS # show :: AboveBelow ident -> String # showList :: [AboveBelow ident] -> ShowS # |
aboveBelowDocs :: AboveBelow ident -> (Document ident, Document ident) Source #
Atomic documents
zeroWidthSpace :: Document a Source #
A zero-width space (hopefully your chosen unicode font supports it)
Document combinators
overlay :: [Document a] -> Document a Source #
Overlay of several document fragments on top of each other
Subscript and superscript
Above and below
above :: Document a -> Document a -> Document a Source #
Used for "big" mathematical operators (like summation)
Text decoration
Font variations
boldItalic :: Document a -> Document a Source #