texmath-0.10.1: Conversion between formats used to represent mathematics.

Safe HaskellNone
LanguageHaskell2010

Text.TeXMath.Types

Description

Types for representing a structured formula.

Synopsis

Documentation

data Exp Source #

Constructors

ENumber String

A number (<mn> in MathML).

EGrouped [Exp]

A group of expressions that function as a unit (e.g. {...}) in TeX, <mrow>...</mrow> in MathML.

EDelimited String String [InEDelimited]

A group of expressions inside paired open and close delimiters (which may in some cases be null).

EIdentifier String

An identifier, e.g. a variable (<mi>...</mi> in MathML. Note that MathML tends to use <mi> tags for "sin" and other mathematical operators; these are represented as EMathOperator in TeXMath.

EMathOperator String

A spelled-out operator like lim or sin.

ESymbol TeXSymbolType String

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 EOver.

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 String

Some normal text, possibly styled.

EStyled TextType [Exp]

A group of styled expressions.

Instances

Eq Exp Source # 

Methods

(==) :: Exp -> Exp -> Bool #

(/=) :: Exp -> Exp -> Bool #

Data Exp Source # 

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 #

toConstr :: Exp -> Constr #

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 :: (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 # 

Methods

compare :: Exp -> Exp -> Ordering #

(<) :: Exp -> Exp -> Bool #

(<=) :: Exp -> Exp -> Bool #

(>) :: Exp -> Exp -> Bool #

(>=) :: Exp -> Exp -> Bool #

max :: Exp -> Exp -> Exp #

min :: Exp -> Exp -> Exp #

Read Exp Source # 
Show Exp Source # 

Methods

showsPrec :: Int -> Exp -> ShowS #

show :: Exp -> String #

showList :: [Exp] -> ShowS #

data TeXSymbolType Source #

Instances

Eq TeXSymbolType Source # 
Data TeXSymbolType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TeXSymbolType -> c TeXSymbolType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TeXSymbolType #

toConstr :: TeXSymbolType -> Constr #

dataTypeOf :: TeXSymbolType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TeXSymbolType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TeXSymbolType) #

gmapT :: (forall b. Data b => b -> b) -> TeXSymbolType -> TeXSymbolType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TeXSymbolType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TeXSymbolType -> r #

gmapQ :: (forall d. Data d => d -> u) -> TeXSymbolType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TeXSymbolType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TeXSymbolType -> m TeXSymbolType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TeXSymbolType -> m TeXSymbolType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TeXSymbolType -> m TeXSymbolType #

Ord TeXSymbolType Source # 
Read TeXSymbolType Source # 
Show TeXSymbolType Source # 

type ArrayLine = [[Exp]] Source #

data FractionType Source #

Constructors

NormalFrac

Displayed or textual, acc to DisplayType

DisplayFrac

Force display mode

InlineFrac

Force inline mode (textual)

NoLineFrac

No line between top and bottom

Instances

Eq FractionType Source # 
Data FractionType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FractionType -> c FractionType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FractionType #

toConstr :: FractionType -> Constr #

dataTypeOf :: FractionType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FractionType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FractionType) #

gmapT :: (forall b. Data b => b -> b) -> FractionType -> FractionType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FractionType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FractionType -> r #

gmapQ :: (forall d. Data d => d -> u) -> FractionType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FractionType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FractionType -> m FractionType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FractionType -> m FractionType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FractionType -> m FractionType #

Ord FractionType Source # 
Read FractionType Source # 
Show FractionType Source # 

data TextType Source #

Instances

Eq TextType Source # 
Data TextType Source # 

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 :: (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 # 
Read TextType Source # 
Show TextType Source # 

data Alignment Source #

Instances

Eq Alignment Source # 
Data Alignment Source # 

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 :: (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 Operator Source #

A record of the MathML dictionary as defined in the specification

Constructors

Operator 

Fields

data Record Source #

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 

Fields

Instances

data Position Source #

Constructors

Under 
Over 

type Env = [String] Source #

List of available packages

defaultEnv :: [String] 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).