{-# LANGUAGE DeriveDataTypeable, TypeSynonymInstances, OverloadedStrings #-}
{-
Copyright (C) 2009 John MacFarlane <jgm@berkeley.edu>

This program is free software; you can redistribute it and/or modify
it under the terms of the GNU General Public License as published by
the Free Software Foundation; either version 2 of the License, or
(at your option) any later version.

This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
GNU General Public License for more details.

You should have received a copy of the GNU General Public License
along with this program; if not, write to the Free Software
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
-}

{- | Types for representing a structured formula.
-}

module Text.TeXMath.Types (Exp(..), TeXSymbolType(..), ArrayLine,
                           FractionType(..), TextType(..),
                           Alignment(..), DisplayType(..),
                           Operator(..), FormType(..), Record(..),
                           Property, Position(..), Env, defaultEnv,
                           InEDelimited)
where

import Data.Generics
import qualified Data.Text as T

data TeXSymbolType = Ord | Op | Bin | Rel | Open | Close | Pun | Accent
                     | Fence | TOver | TUnder | Alpha | BotAccent | Rad
                     deriving (Int -> TeXSymbolType -> ShowS
[TeXSymbolType] -> ShowS
TeXSymbolType -> String
(Int -> TeXSymbolType -> ShowS)
-> (TeXSymbolType -> String)
-> ([TeXSymbolType] -> ShowS)
-> Show TeXSymbolType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TeXSymbolType] -> ShowS
$cshowList :: [TeXSymbolType] -> ShowS
show :: TeXSymbolType -> String
$cshow :: TeXSymbolType -> String
showsPrec :: Int -> TeXSymbolType -> ShowS
$cshowsPrec :: Int -> TeXSymbolType -> ShowS
Show, ReadPrec [TeXSymbolType]
ReadPrec TeXSymbolType
Int -> ReadS TeXSymbolType
ReadS [TeXSymbolType]
(Int -> ReadS TeXSymbolType)
-> ReadS [TeXSymbolType]
-> ReadPrec TeXSymbolType
-> ReadPrec [TeXSymbolType]
-> Read TeXSymbolType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TeXSymbolType]
$creadListPrec :: ReadPrec [TeXSymbolType]
readPrec :: ReadPrec TeXSymbolType
$creadPrec :: ReadPrec TeXSymbolType
readList :: ReadS [TeXSymbolType]
$creadList :: ReadS [TeXSymbolType]
readsPrec :: Int -> ReadS TeXSymbolType
$creadsPrec :: Int -> ReadS TeXSymbolType
Read, TeXSymbolType -> TeXSymbolType -> Bool
(TeXSymbolType -> TeXSymbolType -> Bool)
-> (TeXSymbolType -> TeXSymbolType -> Bool) -> Eq TeXSymbolType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TeXSymbolType -> TeXSymbolType -> Bool
$c/= :: TeXSymbolType -> TeXSymbolType -> Bool
== :: TeXSymbolType -> TeXSymbolType -> Bool
$c== :: TeXSymbolType -> TeXSymbolType -> Bool
Eq, Eq TeXSymbolType
Eq TeXSymbolType
-> (TeXSymbolType -> TeXSymbolType -> Ordering)
-> (TeXSymbolType -> TeXSymbolType -> Bool)
-> (TeXSymbolType -> TeXSymbolType -> Bool)
-> (TeXSymbolType -> TeXSymbolType -> Bool)
-> (TeXSymbolType -> TeXSymbolType -> Bool)
-> (TeXSymbolType -> TeXSymbolType -> TeXSymbolType)
-> (TeXSymbolType -> TeXSymbolType -> TeXSymbolType)
-> Ord TeXSymbolType
TeXSymbolType -> TeXSymbolType -> Bool
TeXSymbolType -> TeXSymbolType -> Ordering
TeXSymbolType -> TeXSymbolType -> TeXSymbolType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TeXSymbolType -> TeXSymbolType -> TeXSymbolType
$cmin :: TeXSymbolType -> TeXSymbolType -> TeXSymbolType
max :: TeXSymbolType -> TeXSymbolType -> TeXSymbolType
$cmax :: TeXSymbolType -> TeXSymbolType -> TeXSymbolType
>= :: TeXSymbolType -> TeXSymbolType -> Bool
$c>= :: TeXSymbolType -> TeXSymbolType -> Bool
> :: TeXSymbolType -> TeXSymbolType -> Bool
$c> :: TeXSymbolType -> TeXSymbolType -> Bool
<= :: TeXSymbolType -> TeXSymbolType -> Bool
$c<= :: TeXSymbolType -> TeXSymbolType -> Bool
< :: TeXSymbolType -> TeXSymbolType -> Bool
$c< :: TeXSymbolType -> TeXSymbolType -> Bool
compare :: TeXSymbolType -> TeXSymbolType -> Ordering
$ccompare :: TeXSymbolType -> TeXSymbolType -> Ordering
$cp1Ord :: Eq TeXSymbolType
Ord, Typeable TeXSymbolType
DataType
Constr
Typeable TeXSymbolType
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> TeXSymbolType -> c TeXSymbolType)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c TeXSymbolType)
-> (TeXSymbolType -> Constr)
-> (TeXSymbolType -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c TeXSymbolType))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c TeXSymbolType))
-> ((forall b. Data b => b -> b) -> TeXSymbolType -> TeXSymbolType)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> TeXSymbolType -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> TeXSymbolType -> r)
-> (forall u. (forall d. Data d => d -> u) -> TeXSymbolType -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> TeXSymbolType -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> TeXSymbolType -> m TeXSymbolType)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> TeXSymbolType -> m TeXSymbolType)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> TeXSymbolType -> m TeXSymbolType)
-> Data TeXSymbolType
TeXSymbolType -> DataType
TeXSymbolType -> Constr
(forall b. Data b => b -> b) -> TeXSymbolType -> TeXSymbolType
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TeXSymbolType -> c TeXSymbolType
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TeXSymbolType
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> TeXSymbolType -> u
forall u. (forall d. Data d => d -> u) -> TeXSymbolType -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TeXSymbolType -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TeXSymbolType -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TeXSymbolType -> m TeXSymbolType
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TeXSymbolType -> m TeXSymbolType
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TeXSymbolType
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TeXSymbolType -> c TeXSymbolType
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TeXSymbolType)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TeXSymbolType)
$cRad :: Constr
$cBotAccent :: Constr
$cAlpha :: Constr
$cTUnder :: Constr
$cTOver :: Constr
$cFence :: Constr
$cAccent :: Constr
$cPun :: Constr
$cClose :: Constr
$cOpen :: Constr
$cRel :: Constr
$cBin :: Constr
$cOp :: Constr
$cOrd :: Constr
$tTeXSymbolType :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> TeXSymbolType -> m TeXSymbolType
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TeXSymbolType -> m TeXSymbolType
gmapMp :: (forall d. Data d => d -> m d) -> TeXSymbolType -> m TeXSymbolType
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TeXSymbolType -> m TeXSymbolType
gmapM :: (forall d. Data d => d -> m d) -> TeXSymbolType -> m TeXSymbolType
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TeXSymbolType -> m TeXSymbolType
gmapQi :: Int -> (forall d. Data d => d -> u) -> TeXSymbolType -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TeXSymbolType -> u
gmapQ :: (forall d. Data d => d -> u) -> TeXSymbolType -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> TeXSymbolType -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TeXSymbolType -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TeXSymbolType -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TeXSymbolType -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TeXSymbolType -> r
gmapT :: (forall b. Data b => b -> b) -> TeXSymbolType -> TeXSymbolType
$cgmapT :: (forall b. Data b => b -> b) -> TeXSymbolType -> TeXSymbolType
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TeXSymbolType)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TeXSymbolType)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c TeXSymbolType)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TeXSymbolType)
dataTypeOf :: TeXSymbolType -> DataType
$cdataTypeOf :: TeXSymbolType -> DataType
toConstr :: TeXSymbolType -> Constr
$ctoConstr :: TeXSymbolType -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TeXSymbolType
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TeXSymbolType
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TeXSymbolType -> c TeXSymbolType
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TeXSymbolType -> c TeXSymbolType
$cp1Data :: Typeable TeXSymbolType
Data, Typeable)

data Alignment = AlignLeft | AlignCenter | AlignRight
                 deriving (Int -> Alignment -> ShowS
[Alignment] -> ShowS
Alignment -> String
(Int -> Alignment -> ShowS)
-> (Alignment -> String)
-> ([Alignment] -> ShowS)
-> Show Alignment
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Alignment] -> ShowS
$cshowList :: [Alignment] -> ShowS
show :: Alignment -> String
$cshow :: Alignment -> String
showsPrec :: Int -> Alignment -> ShowS
$cshowsPrec :: Int -> Alignment -> ShowS
Show, ReadPrec [Alignment]
ReadPrec Alignment
Int -> ReadS Alignment
ReadS [Alignment]
(Int -> ReadS Alignment)
-> ReadS [Alignment]
-> ReadPrec Alignment
-> ReadPrec [Alignment]
-> Read Alignment
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Alignment]
$creadListPrec :: ReadPrec [Alignment]
readPrec :: ReadPrec Alignment
$creadPrec :: ReadPrec Alignment
readList :: ReadS [Alignment]
$creadList :: ReadS [Alignment]
readsPrec :: Int -> ReadS Alignment
$creadsPrec :: Int -> ReadS Alignment
Read, Alignment -> Alignment -> Bool
(Alignment -> Alignment -> Bool)
-> (Alignment -> Alignment -> Bool) -> Eq Alignment
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Alignment -> Alignment -> Bool
$c/= :: Alignment -> Alignment -> Bool
== :: Alignment -> Alignment -> Bool
$c== :: Alignment -> Alignment -> Bool
Eq, Eq Alignment
Eq Alignment
-> (Alignment -> Alignment -> Ordering)
-> (Alignment -> Alignment -> Bool)
-> (Alignment -> Alignment -> Bool)
-> (Alignment -> Alignment -> Bool)
-> (Alignment -> Alignment -> Bool)
-> (Alignment -> Alignment -> Alignment)
-> (Alignment -> Alignment -> Alignment)
-> Ord Alignment
Alignment -> Alignment -> Bool
Alignment -> Alignment -> Ordering
Alignment -> Alignment -> Alignment
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Alignment -> Alignment -> Alignment
$cmin :: Alignment -> Alignment -> Alignment
max :: Alignment -> Alignment -> Alignment
$cmax :: Alignment -> Alignment -> Alignment
>= :: Alignment -> Alignment -> Bool
$c>= :: Alignment -> Alignment -> Bool
> :: Alignment -> Alignment -> Bool
$c> :: Alignment -> Alignment -> Bool
<= :: Alignment -> Alignment -> Bool
$c<= :: Alignment -> Alignment -> Bool
< :: Alignment -> Alignment -> Bool
$c< :: Alignment -> Alignment -> Bool
compare :: Alignment -> Alignment -> Ordering
$ccompare :: Alignment -> Alignment -> Ordering
$cp1Ord :: Eq Alignment
Ord, Typeable Alignment
DataType
Constr
Typeable Alignment
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Alignment -> c Alignment)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Alignment)
-> (Alignment -> Constr)
-> (Alignment -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Alignment))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Alignment))
-> ((forall b. Data b => b -> b) -> Alignment -> Alignment)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Alignment -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Alignment -> r)
-> (forall u. (forall d. Data d => d -> u) -> Alignment -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> Alignment -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Alignment -> m Alignment)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Alignment -> m Alignment)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Alignment -> m Alignment)
-> Data Alignment
Alignment -> DataType
Alignment -> Constr
(forall b. Data b => b -> b) -> Alignment -> Alignment
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Alignment -> c Alignment
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Alignment
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Alignment -> u
forall u. (forall d. Data d => d -> u) -> Alignment -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Alignment -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Alignment -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Alignment -> m Alignment
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Alignment -> m Alignment
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Alignment
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Alignment -> c Alignment
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Alignment)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Alignment)
$cAlignRight :: Constr
$cAlignCenter :: Constr
$cAlignLeft :: Constr
$tAlignment :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Alignment -> m Alignment
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Alignment -> m Alignment
gmapMp :: (forall d. Data d => d -> m d) -> Alignment -> m Alignment
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Alignment -> m Alignment
gmapM :: (forall d. Data d => d -> m d) -> Alignment -> m Alignment
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Alignment -> m Alignment
gmapQi :: Int -> (forall d. Data d => d -> u) -> Alignment -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Alignment -> u
gmapQ :: (forall d. Data d => d -> u) -> Alignment -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Alignment -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Alignment -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Alignment -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Alignment -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Alignment -> r
gmapT :: (forall b. Data b => b -> b) -> Alignment -> Alignment
$cgmapT :: (forall b. Data b => b -> b) -> Alignment -> Alignment
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Alignment)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Alignment)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Alignment)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Alignment)
dataTypeOf :: Alignment -> DataType
$cdataTypeOf :: Alignment -> DataType
toConstr :: Alignment -> Constr
$ctoConstr :: Alignment -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Alignment
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Alignment
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Alignment -> c Alignment
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Alignment -> c Alignment
$cp1Data :: Typeable Alignment
Data, Typeable)

data FractionType = NormalFrac   -- ^ Displayed or textual, acc to 'DisplayType'
                  | DisplayFrac  -- ^ Force display mode
                  | InlineFrac   -- ^ Force inline mode (textual)
                  | NoLineFrac   -- ^ No line between top and bottom
                  deriving (Int -> FractionType -> ShowS
[FractionType] -> ShowS
FractionType -> String
(Int -> FractionType -> ShowS)
-> (FractionType -> String)
-> ([FractionType] -> ShowS)
-> Show FractionType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FractionType] -> ShowS
$cshowList :: [FractionType] -> ShowS
show :: FractionType -> String
$cshow :: FractionType -> String
showsPrec :: Int -> FractionType -> ShowS
$cshowsPrec :: Int -> FractionType -> ShowS
Show, ReadPrec [FractionType]
ReadPrec FractionType
Int -> ReadS FractionType
ReadS [FractionType]
(Int -> ReadS FractionType)
-> ReadS [FractionType]
-> ReadPrec FractionType
-> ReadPrec [FractionType]
-> Read FractionType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FractionType]
$creadListPrec :: ReadPrec [FractionType]
readPrec :: ReadPrec FractionType
$creadPrec :: ReadPrec FractionType
readList :: ReadS [FractionType]
$creadList :: ReadS [FractionType]
readsPrec :: Int -> ReadS FractionType
$creadsPrec :: Int -> ReadS FractionType
Read, FractionType -> FractionType -> Bool
(FractionType -> FractionType -> Bool)
-> (FractionType -> FractionType -> Bool) -> Eq FractionType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FractionType -> FractionType -> Bool
$c/= :: FractionType -> FractionType -> Bool
== :: FractionType -> FractionType -> Bool
$c== :: FractionType -> FractionType -> Bool
Eq, Eq FractionType
Eq FractionType
-> (FractionType -> FractionType -> Ordering)
-> (FractionType -> FractionType -> Bool)
-> (FractionType -> FractionType -> Bool)
-> (FractionType -> FractionType -> Bool)
-> (FractionType -> FractionType -> Bool)
-> (FractionType -> FractionType -> FractionType)
-> (FractionType -> FractionType -> FractionType)
-> Ord FractionType
FractionType -> FractionType -> Bool
FractionType -> FractionType -> Ordering
FractionType -> FractionType -> FractionType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FractionType -> FractionType -> FractionType
$cmin :: FractionType -> FractionType -> FractionType
max :: FractionType -> FractionType -> FractionType
$cmax :: FractionType -> FractionType -> FractionType
>= :: FractionType -> FractionType -> Bool
$c>= :: FractionType -> FractionType -> Bool
> :: FractionType -> FractionType -> Bool
$c> :: FractionType -> FractionType -> Bool
<= :: FractionType -> FractionType -> Bool
$c<= :: FractionType -> FractionType -> Bool
< :: FractionType -> FractionType -> Bool
$c< :: FractionType -> FractionType -> Bool
compare :: FractionType -> FractionType -> Ordering
$ccompare :: FractionType -> FractionType -> Ordering
$cp1Ord :: Eq FractionType
Ord, Typeable FractionType
DataType
Constr
Typeable FractionType
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> FractionType -> c FractionType)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c FractionType)
-> (FractionType -> Constr)
-> (FractionType -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c FractionType))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c FractionType))
-> ((forall b. Data b => b -> b) -> FractionType -> FractionType)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> FractionType -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> FractionType -> r)
-> (forall u. (forall d. Data d => d -> u) -> FractionType -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> FractionType -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> FractionType -> m FractionType)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> FractionType -> m FractionType)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> FractionType -> m FractionType)
-> Data FractionType
FractionType -> DataType
FractionType -> Constr
(forall b. Data b => b -> b) -> FractionType -> FractionType
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FractionType -> c FractionType
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FractionType
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> FractionType -> u
forall u. (forall d. Data d => d -> u) -> FractionType -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FractionType -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FractionType -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FractionType -> m FractionType
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FractionType -> m FractionType
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FractionType
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FractionType -> c FractionType
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FractionType)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FractionType)
$cNoLineFrac :: Constr
$cInlineFrac :: Constr
$cDisplayFrac :: Constr
$cNormalFrac :: Constr
$tFractionType :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> FractionType -> m FractionType
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FractionType -> m FractionType
gmapMp :: (forall d. Data d => d -> m d) -> FractionType -> m FractionType
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FractionType -> m FractionType
gmapM :: (forall d. Data d => d -> m d) -> FractionType -> m FractionType
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FractionType -> m FractionType
gmapQi :: Int -> (forall d. Data d => d -> u) -> FractionType -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> FractionType -> u
gmapQ :: (forall d. Data d => d -> u) -> FractionType -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> FractionType -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FractionType -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FractionType -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FractionType -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FractionType -> r
gmapT :: (forall b. Data b => b -> b) -> FractionType -> FractionType
$cgmapT :: (forall b. Data b => b -> b) -> FractionType -> FractionType
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FractionType)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FractionType)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c FractionType)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FractionType)
dataTypeOf :: FractionType -> DataType
$cdataTypeOf :: FractionType -> DataType
toConstr :: FractionType -> Constr
$ctoConstr :: FractionType -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FractionType
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FractionType
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FractionType -> c FractionType
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FractionType -> c FractionType
$cp1Data :: Typeable FractionType
Data, Typeable)

type ArrayLine = [[Exp]]

data Exp =
    ENumber T.Text  -- ^ 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 T.Text T.Text [InEDelimited] -- ^ A group of expressions inside
                    -- paired open and close delimiters (which may in some
                    -- cases be null).
  | EIdentifier T.Text  -- ^ 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 T.Text  -- ^ A spelled-out operator like @lim@ or @sin@.
  | ESymbol TeXSymbolType T.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 @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 T.Text  -- ^ Some normal text, possibly styled.
  | EStyled TextType [Exp] -- ^  A group of styled expressions.
  deriving (Int -> Exp -> ShowS
[Exp] -> ShowS
Exp -> String
(Int -> Exp -> ShowS)
-> (Exp -> String) -> ([Exp] -> ShowS) -> Show Exp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Exp] -> ShowS
$cshowList :: [Exp] -> ShowS
show :: Exp -> String
$cshow :: Exp -> String
showsPrec :: Int -> Exp -> ShowS
$cshowsPrec :: Int -> Exp -> ShowS
Show, ReadPrec [Exp]
ReadPrec Exp
Int -> ReadS Exp
ReadS [Exp]
(Int -> ReadS Exp)
-> ReadS [Exp] -> ReadPrec Exp -> ReadPrec [Exp] -> Read Exp
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Exp]
$creadListPrec :: ReadPrec [Exp]
readPrec :: ReadPrec Exp
$creadPrec :: ReadPrec Exp
readList :: ReadS [Exp]
$creadList :: ReadS [Exp]
readsPrec :: Int -> ReadS Exp
$creadsPrec :: Int -> ReadS Exp
Read, Exp -> Exp -> Bool
(Exp -> Exp -> Bool) -> (Exp -> Exp -> Bool) -> Eq Exp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Exp -> Exp -> Bool
$c/= :: Exp -> Exp -> Bool
== :: Exp -> Exp -> Bool
$c== :: Exp -> Exp -> Bool
Eq, Eq Exp
Eq Exp
-> (Exp -> Exp -> Ordering)
-> (Exp -> Exp -> Bool)
-> (Exp -> Exp -> Bool)
-> (Exp -> Exp -> Bool)
-> (Exp -> Exp -> Bool)
-> (Exp -> Exp -> Exp)
-> (Exp -> Exp -> Exp)
-> Ord Exp
Exp -> Exp -> Bool
Exp -> Exp -> Ordering
Exp -> Exp -> Exp
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Exp -> Exp -> Exp
$cmin :: Exp -> Exp -> Exp
max :: Exp -> Exp -> Exp
$cmax :: Exp -> Exp -> Exp
>= :: Exp -> Exp -> Bool
$c>= :: Exp -> Exp -> Bool
> :: Exp -> Exp -> Bool
$c> :: Exp -> Exp -> Bool
<= :: Exp -> Exp -> Bool
$c<= :: Exp -> Exp -> Bool
< :: Exp -> Exp -> Bool
$c< :: Exp -> Exp -> Bool
compare :: Exp -> Exp -> Ordering
$ccompare :: Exp -> Exp -> Ordering
$cp1Ord :: Eq Exp
Ord, Typeable Exp
DataType
Constr
Typeable Exp
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Exp -> c Exp)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Exp)
-> (Exp -> Constr)
-> (Exp -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Exp))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Exp))
-> ((forall b. Data b => b -> b) -> Exp -> Exp)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Exp -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Exp -> r)
-> (forall u. (forall d. Data d => d -> u) -> Exp -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Exp -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Exp -> m Exp)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Exp -> m Exp)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Exp -> m Exp)
-> Data Exp
Exp -> DataType
Exp -> Constr
(forall b. Data b => b -> b) -> Exp -> Exp
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Exp -> c Exp
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Exp
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Exp -> u
forall u. (forall d. Data d => d -> u) -> Exp -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Exp -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Exp -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Exp -> m Exp
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Exp -> m Exp
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Exp
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Exp -> c Exp
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Exp)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Exp)
$cEStyled :: Constr
$cEText :: Constr
$cEArray :: Constr
$cEScaled :: Constr
$cESqrt :: Constr
$cERoot :: Constr
$cEFraction :: Constr
$cEBoxed :: Constr
$cEPhantom :: Constr
$cEUnderover :: Constr
$cEUnder :: Constr
$cEOver :: Constr
$cESubsup :: Constr
$cESuper :: Constr
$cESub :: Constr
$cESpace :: Constr
$cESymbol :: Constr
$cEMathOperator :: Constr
$cEIdentifier :: Constr
$cEDelimited :: Constr
$cEGrouped :: Constr
$cENumber :: Constr
$tExp :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Exp -> m Exp
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Exp -> m Exp
gmapMp :: (forall d. Data d => d -> m d) -> Exp -> m Exp
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Exp -> m Exp
gmapM :: (forall d. Data d => d -> m d) -> Exp -> m Exp
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Exp -> m Exp
gmapQi :: Int -> (forall d. Data d => d -> u) -> Exp -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Exp -> u
gmapQ :: (forall d. Data d => d -> u) -> Exp -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Exp -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Exp -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Exp -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Exp -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Exp -> r
gmapT :: (forall b. Data b => b -> b) -> Exp -> Exp
$cgmapT :: (forall b. Data b => b -> b) -> Exp -> Exp
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Exp)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Exp)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Exp)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Exp)
dataTypeOf :: Exp -> DataType
$cdataTypeOf :: Exp -> DataType
toConstr :: Exp -> Constr
$ctoConstr :: Exp -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Exp
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Exp
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Exp -> c Exp
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Exp -> c Exp
$cp1Data :: Typeable Exp
Data, Typeable)

-- | 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@).
type InEDelimited = Either Middle Exp
type Middle = T.Text

data DisplayType = DisplayBlock  -- ^ A displayed formula.
                 | DisplayInline  -- ^ A formula rendered inline in text.
                 deriving (Int -> DisplayType -> ShowS
[DisplayType] -> ShowS
DisplayType -> String
(Int -> DisplayType -> ShowS)
-> (DisplayType -> String)
-> ([DisplayType] -> ShowS)
-> Show DisplayType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisplayType] -> ShowS
$cshowList :: [DisplayType] -> ShowS
show :: DisplayType -> String
$cshow :: DisplayType -> String
showsPrec :: Int -> DisplayType -> ShowS
$cshowsPrec :: Int -> DisplayType -> ShowS
Show, DisplayType -> DisplayType -> Bool
(DisplayType -> DisplayType -> Bool)
-> (DisplayType -> DisplayType -> Bool) -> Eq DisplayType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisplayType -> DisplayType -> Bool
$c/= :: DisplayType -> DisplayType -> Bool
== :: DisplayType -> DisplayType -> Bool
$c== :: DisplayType -> DisplayType -> Bool
Eq, Eq DisplayType
Eq DisplayType
-> (DisplayType -> DisplayType -> Ordering)
-> (DisplayType -> DisplayType -> Bool)
-> (DisplayType -> DisplayType -> Bool)
-> (DisplayType -> DisplayType -> Bool)
-> (DisplayType -> DisplayType -> Bool)
-> (DisplayType -> DisplayType -> DisplayType)
-> (DisplayType -> DisplayType -> DisplayType)
-> Ord DisplayType
DisplayType -> DisplayType -> Bool
DisplayType -> DisplayType -> Ordering
DisplayType -> DisplayType -> DisplayType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DisplayType -> DisplayType -> DisplayType
$cmin :: DisplayType -> DisplayType -> DisplayType
max :: DisplayType -> DisplayType -> DisplayType
$cmax :: DisplayType -> DisplayType -> DisplayType
>= :: DisplayType -> DisplayType -> Bool
$c>= :: DisplayType -> DisplayType -> Bool
> :: DisplayType -> DisplayType -> Bool
$c> :: DisplayType -> DisplayType -> Bool
<= :: DisplayType -> DisplayType -> Bool
$c<= :: DisplayType -> DisplayType -> Bool
< :: DisplayType -> DisplayType -> Bool
$c< :: DisplayType -> DisplayType -> Bool
compare :: DisplayType -> DisplayType -> Ordering
$ccompare :: DisplayType -> DisplayType -> Ordering
$cp1Ord :: Eq DisplayType
Ord)

data TextType = TextNormal
              | TextBold
              | TextItalic
              | TextMonospace
              | TextSansSerif
              | TextDoubleStruck
              | TextScript
              | TextFraktur
              | TextBoldItalic
              | TextSansSerifBold
              | TextSansSerifBoldItalic
              | TextBoldScript
              | TextBoldFraktur
              | TextSansSerifItalic
              deriving (Int -> TextType -> ShowS
[TextType] -> ShowS
TextType -> String
(Int -> TextType -> ShowS)
-> (TextType -> String) -> ([TextType] -> ShowS) -> Show TextType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TextType] -> ShowS
$cshowList :: [TextType] -> ShowS
show :: TextType -> String
$cshow :: TextType -> String
showsPrec :: Int -> TextType -> ShowS
$cshowsPrec :: Int -> TextType -> ShowS
Show, ReadPrec [TextType]
ReadPrec TextType
Int -> ReadS TextType
ReadS [TextType]
(Int -> ReadS TextType)
-> ReadS [TextType]
-> ReadPrec TextType
-> ReadPrec [TextType]
-> Read TextType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TextType]
$creadListPrec :: ReadPrec [TextType]
readPrec :: ReadPrec TextType
$creadPrec :: ReadPrec TextType
readList :: ReadS [TextType]
$creadList :: ReadS [TextType]
readsPrec :: Int -> ReadS TextType
$creadsPrec :: Int -> ReadS TextType
Read, TextType -> TextType -> Bool
(TextType -> TextType -> Bool)
-> (TextType -> TextType -> Bool) -> Eq TextType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextType -> TextType -> Bool
$c/= :: TextType -> TextType -> Bool
== :: TextType -> TextType -> Bool
$c== :: TextType -> TextType -> Bool
Eq, Eq TextType
Eq TextType
-> (TextType -> TextType -> Ordering)
-> (TextType -> TextType -> Bool)
-> (TextType -> TextType -> Bool)
-> (TextType -> TextType -> Bool)
-> (TextType -> TextType -> Bool)
-> (TextType -> TextType -> TextType)
-> (TextType -> TextType -> TextType)
-> Ord TextType
TextType -> TextType -> Bool
TextType -> TextType -> Ordering
TextType -> TextType -> TextType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TextType -> TextType -> TextType
$cmin :: TextType -> TextType -> TextType
max :: TextType -> TextType -> TextType
$cmax :: TextType -> TextType -> TextType
>= :: TextType -> TextType -> Bool
$c>= :: TextType -> TextType -> Bool
> :: TextType -> TextType -> Bool
$c> :: TextType -> TextType -> Bool
<= :: TextType -> TextType -> Bool
$c<= :: TextType -> TextType -> Bool
< :: TextType -> TextType -> Bool
$c< :: TextType -> TextType -> Bool
compare :: TextType -> TextType -> Ordering
$ccompare :: TextType -> TextType -> Ordering
$cp1Ord :: Eq TextType
Ord, Typeable TextType
DataType
Constr
Typeable TextType
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> TextType -> c TextType)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c TextType)
-> (TextType -> Constr)
-> (TextType -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c TextType))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TextType))
-> ((forall b. Data b => b -> b) -> TextType -> TextType)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> TextType -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> TextType -> r)
-> (forall u. (forall d. Data d => d -> u) -> TextType -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> TextType -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> TextType -> m TextType)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> TextType -> m TextType)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> TextType -> m TextType)
-> Data TextType
TextType -> DataType
TextType -> Constr
(forall b. Data b => b -> b) -> TextType -> TextType
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TextType -> c TextType
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TextType
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> TextType -> u
forall u. (forall d. Data d => d -> u) -> TextType -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TextType -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TextType -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TextType -> m TextType
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TextType -> m TextType
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TextType
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TextType -> c TextType
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TextType)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TextType)
$cTextSansSerifItalic :: Constr
$cTextBoldFraktur :: Constr
$cTextBoldScript :: Constr
$cTextSansSerifBoldItalic :: Constr
$cTextSansSerifBold :: Constr
$cTextBoldItalic :: Constr
$cTextFraktur :: Constr
$cTextScript :: Constr
$cTextDoubleStruck :: Constr
$cTextSansSerif :: Constr
$cTextMonospace :: Constr
$cTextItalic :: Constr
$cTextBold :: Constr
$cTextNormal :: Constr
$tTextType :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> TextType -> m TextType
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TextType -> m TextType
gmapMp :: (forall d. Data d => d -> m d) -> TextType -> m TextType
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TextType -> m TextType
gmapM :: (forall d. Data d => d -> m d) -> TextType -> m TextType
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TextType -> m TextType
gmapQi :: Int -> (forall d. Data d => d -> u) -> TextType -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TextType -> u
gmapQ :: (forall d. Data d => d -> u) -> TextType -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> TextType -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TextType -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TextType -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TextType -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TextType -> r
gmapT :: (forall b. Data b => b -> b) -> TextType -> TextType
$cgmapT :: (forall b. Data b => b -> b) -> TextType -> TextType
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TextType)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TextType)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c TextType)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TextType)
dataTypeOf :: TextType -> DataType
$cdataTypeOf :: TextType -> DataType
toConstr :: TextType -> Constr
$ctoConstr :: TextType -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TextType
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TextType
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TextType -> c TextType
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TextType -> c TextType
$cp1Data :: Typeable TextType
Data, Typeable)

data FormType = FPrefix | FPostfix | FInfix deriving (Int -> FormType -> ShowS
[FormType] -> ShowS
FormType -> String
(Int -> FormType -> ShowS)
-> (FormType -> String) -> ([FormType] -> ShowS) -> Show FormType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FormType] -> ShowS
$cshowList :: [FormType] -> ShowS
show :: FormType -> String
$cshow :: FormType -> String
showsPrec :: Int -> FormType -> ShowS
$cshowsPrec :: Int -> FormType -> ShowS
Show, Eq FormType
Eq FormType
-> (FormType -> FormType -> Ordering)
-> (FormType -> FormType -> Bool)
-> (FormType -> FormType -> Bool)
-> (FormType -> FormType -> Bool)
-> (FormType -> FormType -> Bool)
-> (FormType -> FormType -> FormType)
-> (FormType -> FormType -> FormType)
-> Ord FormType
FormType -> FormType -> Bool
FormType -> FormType -> Ordering
FormType -> FormType -> FormType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FormType -> FormType -> FormType
$cmin :: FormType -> FormType -> FormType
max :: FormType -> FormType -> FormType
$cmax :: FormType -> FormType -> FormType
>= :: FormType -> FormType -> Bool
$c>= :: FormType -> FormType -> Bool
> :: FormType -> FormType -> Bool
$c> :: FormType -> FormType -> Bool
<= :: FormType -> FormType -> Bool
$c<= :: FormType -> FormType -> Bool
< :: FormType -> FormType -> Bool
$c< :: FormType -> FormType -> Bool
compare :: FormType -> FormType -> Ordering
$ccompare :: FormType -> FormType -> Ordering
$cp1Ord :: Eq FormType
Ord, FormType -> FormType -> Bool
(FormType -> FormType -> Bool)
-> (FormType -> FormType -> Bool) -> Eq FormType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FormType -> FormType -> Bool
$c/= :: FormType -> FormType -> Bool
== :: FormType -> FormType -> Bool
$c== :: FormType -> FormType -> Bool
Eq)

type Property = T.Text

-- | A record of the MathML dictionary as defined
-- <http://www.w3.org/TR/MathML3/appendixc.html in the specification>
data Operator = Operator
                  { Operator -> Text
oper :: T.Text -- ^ Operator
                  , Operator -> Text
description :: T.Text -- ^ Plain English Description
                  , Operator -> FormType
form :: FormType -- ^ Whether Prefix, Postfix or Infix
                  , Operator -> Int
priority :: Int -- ^ Default priority for implicit
                                    --   nesting
                  , Operator -> Int
lspace :: Int -- ^ Default Left Spacing
                  , Operator -> Int
rspace :: Int -- ^ Default Right Spacing
                  , Operator -> [Text]
properties :: [Property] -- ^ List of MathML properties
                  }
                  deriving (Int -> Operator -> ShowS
[Operator] -> ShowS
Operator -> String
(Int -> Operator -> ShowS)
-> (Operator -> String) -> ([Operator] -> ShowS) -> Show Operator
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Operator] -> ShowS
$cshowList :: [Operator] -> ShowS
show :: Operator -> String
$cshow :: Operator -> String
showsPrec :: Int -> Operator -> ShowS
$cshowsPrec :: Int -> Operator -> ShowS
Show)

-- | 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>
data Record = Record { Record -> Char
uchar :: Char -- ^ Unicode Character
                     , Record -> [(Text, Text)]
commands :: [(T.Text, T.Text)] -- ^ LaTeX commands (package, command)
                     , Record -> TeXSymbolType
category :: TeXSymbolType -- ^ TeX math category
                     , Record -> Text
comments :: T.Text -- ^ Plain english description
                     } deriving (Int -> Record -> ShowS
[Record] -> ShowS
Record -> String
(Int -> Record -> ShowS)
-> (Record -> String) -> ([Record] -> ShowS) -> Show Record
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Record] -> ShowS
$cshowList :: [Record] -> ShowS
show :: Record -> String
$cshow :: Record -> String
showsPrec :: Int -> Record -> ShowS
$cshowsPrec :: Int -> Record -> ShowS
Show)

data Position = Under | Over

-- | List of available packages
type Env = [T.Text]

-- | Contains @amsmath@ and @amssymbol@
defaultEnv :: [T.Text]
defaultEnv :: [Text]
defaultEnv = [Text
"amsmath", Text
"amssymb"]