| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Text.TeXMath.Types
Description
Types for representing a structured formula.
Synopsis
- data Exp
- = ENumber Text
 - | EGrouped [Exp]
 - | EDelimited Text Text [InEDelimited]
 - | EIdentifier Text
 - | EMathOperator Text
 - | ESymbol TeXSymbolType Text
 - | ESpace Rational
 - | ESub Exp Exp
 - | ESuper Exp Exp
 - | ESubsup Exp Exp Exp
 - | EOver Bool Exp Exp
 - | EUnder Bool Exp Exp
 - | EUnderover Bool Exp Exp Exp
 - | EPhantom Exp
 - | EBoxed Exp
 - | EFraction FractionType Exp Exp
 - | ERoot Exp Exp
 - | ESqrt Exp
 - | EScaled Rational Exp
 - | EArray [Alignment] [ArrayLine]
 - | EText TextType Text
 - | EStyled TextType [Exp]
 
 - data TeXSymbolType
 - type ArrayLine = [[Exp]]
 - data FractionType
 - data TextType
 - data Alignment
 - data DisplayType
 - data Operator = Operator {}
 - data FormType
 - data Record = Record {}
 - type Property = Text
 - data Position
 - type Env = [Text]
 - defaultEnv :: [Text]
 - type InEDelimited = Either Middle Exp
 
Documentation
Constructors
| ENumber Text | A number (  | 
| EGrouped [Exp] | A group of expressions that function as a unit
 (e.g.   | 
| EDelimited Text Text [InEDelimited] | A group of expressions inside paired open and close delimiters (which may in some cases be null).  | 
| EIdentifier Text | An identifier, e.g. a variable (  | 
| EMathOperator Text | A spelled-out operator like   | 
| ESymbol TeXSymbolType Text | A symbol.  | 
| ESpace Rational | A space, with the width specified in em.  | 
| ESub Exp Exp | An expression with a subscript. First argument is base, second subscript.  | 
| ESuper Exp Exp | An expresion with a superscript. First argument is base, second subscript.  | 
| ESubsup Exp Exp Exp | An expression with both a sub and a superscript. First argument is base, second subscript, third superscript.  | 
| EOver Bool Exp Exp | An expression with something over it. The first argument is True if the formula is "convertible:" that is, if the material over the formula should appear as a regular superscript in inline math. The second argument is the base, the third the expression that goes over it.  | 
| EUnder Bool Exp Exp | An expression with something under it.
 The arguments work as in   | 
| EUnderover Bool Exp Exp Exp | An expression with something over and something under it.  | 
| EPhantom Exp | A "phantom" operator that takes space but doesn't display.  | 
| EBoxed Exp | A boxed expression.  | 
| EFraction FractionType Exp Exp | A fraction. First argument is numerator, second denominator.  | 
| ERoot Exp Exp | An nth root. First argument is index, second is base.  | 
| ESqrt Exp | A square root.  | 
| EScaled Rational Exp | An expression that is scaled to some factor of its normal size.  | 
| EArray [Alignment] [ArrayLine] | An array or matrix. The first argument specifies the alignments of the columns; the second gives the contents of the lines. All of these lists should be the same length.  | 
| EText TextType Text | Some normal text, possibly styled.  | 
| EStyled TextType [Exp] | A group of styled expressions.  | 
Instances
| Eq Exp Source # | |
| Data Exp Source # | |
Defined in Text.TeXMath.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Exp -> c Exp # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Exp # dataTypeOf :: Exp -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Exp) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Exp) # gmapT :: (forall b. Data b => b -> b) -> Exp -> Exp # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Exp -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Exp -> r # gmapQ :: (forall d. Data d => d -> u) -> Exp -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Exp -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Exp -> m Exp # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Exp -> m Exp # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Exp -> m Exp #  | |
| Ord Exp Source # | |
| Read Exp Source # | |
| Show Exp Source # | |
data TeXSymbolType Source #
Instances
data FractionType Source #
Constructors
| NormalFrac | Displayed or textual, acc to   | 
| DisplayFrac | Force display mode  | 
| InlineFrac | Force inline mode (textual)  | 
| NoLineFrac | No line between top and bottom  | 
Instances
Constructors
Instances
| Eq TextType Source # | |
| Data TextType Source # | |
Defined in Text.TeXMath.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TextType -> c TextType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TextType # toConstr :: TextType -> Constr # dataTypeOf :: TextType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TextType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TextType) # gmapT :: (forall b. Data b => b -> b) -> TextType -> TextType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TextType -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TextType -> r # gmapQ :: (forall d. Data d => d -> u) -> TextType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TextType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TextType -> m TextType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TextType -> m TextType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TextType -> m TextType #  | |
| Ord TextType Source # | |
Defined in Text.TeXMath.Types  | |
| Read TextType Source # | |
| Show TextType Source # | |
Constructors
| AlignLeft | |
| AlignCenter | |
| AlignRight | 
Instances
| Eq Alignment Source # | |
| Data Alignment Source # | |
Defined in Text.TeXMath.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Alignment -> c Alignment # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Alignment # toConstr :: Alignment -> Constr # dataTypeOf :: Alignment -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Alignment) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Alignment) # gmapT :: (forall b. Data b => b -> b) -> Alignment -> Alignment # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Alignment -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Alignment -> r # gmapQ :: (forall d. Data d => d -> u) -> Alignment -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Alignment -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Alignment -> m Alignment # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Alignment -> m Alignment # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Alignment -> m Alignment #  | |
| Ord Alignment Source # | |
| Read Alignment Source # | |
| Show Alignment Source # | |
data DisplayType Source #
Constructors
| DisplayBlock | A displayed formula.  | 
| DisplayInline | A formula rendered inline in text.  | 
Instances
| Eq DisplayType Source # | |
Defined in Text.TeXMath.Types  | |
| Ord DisplayType Source # | |
Defined in Text.TeXMath.Types Methods compare :: DisplayType -> DisplayType -> Ordering # (<) :: DisplayType -> DisplayType -> Bool # (<=) :: DisplayType -> DisplayType -> Bool # (>) :: DisplayType -> DisplayType -> Bool # (>=) :: DisplayType -> DisplayType -> Bool # max :: DisplayType -> DisplayType -> DisplayType # min :: DisplayType -> DisplayType -> DisplayType #  | |
| Show DisplayType Source # | |
Defined in Text.TeXMath.Types Methods showsPrec :: Int -> DisplayType -> ShowS # show :: DisplayType -> String # showList :: [DisplayType] -> ShowS #  | |
A record of the MathML dictionary as defined in the specification
Constructors
| Operator | |
A record of the Unicode to LaTeX lookup table a full descripton can be seen <http://milde.users.sourceforge.net/LUCR/Math/data/unimathsymbols.txt here>
Constructors
| Record | |
defaultEnv :: [Text] Source #
Contains amsmath and amssymbol
type InEDelimited = Either Middle Exp Source #
An EDelimited element contains a string of ordinary expressions
 (represented here as Right values) or fences (represented here as
 Left, and in LaTeX using mid).