{-# LANGUAGE DeriveDataTypeable, TypeSynonymInstances, OverloadedStrings #-}
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
$cshowsPrec :: Int -> TeXSymbolType -> ShowS
showsPrec :: Int -> TeXSymbolType -> ShowS
$cshow :: TeXSymbolType -> String
show :: TeXSymbolType -> String
$cshowList :: [TeXSymbolType] -> ShowS
showList :: [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
$creadsPrec :: Int -> ReadS TeXSymbolType
readsPrec :: Int -> ReadS TeXSymbolType
$creadList :: ReadS [TeXSymbolType]
readList :: ReadS [TeXSymbolType]
$creadPrec :: ReadPrec TeXSymbolType
readPrec :: ReadPrec TeXSymbolType
$creadListPrec :: ReadPrec [TeXSymbolType]
readListPrec :: ReadPrec [TeXSymbolType]
Read, TeXSymbolType -> TeXSymbolType -> Bool
(TeXSymbolType -> TeXSymbolType -> Bool)
-> (TeXSymbolType -> TeXSymbolType -> Bool) -> Eq TeXSymbolType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TeXSymbolType -> TeXSymbolType -> Bool
== :: TeXSymbolType -> TeXSymbolType -> Bool
$c/= :: TeXSymbolType -> TeXSymbolType -> Bool
/= :: 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
$ccompare :: TeXSymbolType -> TeXSymbolType -> Ordering
compare :: TeXSymbolType -> TeXSymbolType -> Ordering
$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
>= :: TeXSymbolType -> TeXSymbolType -> Bool
$cmax :: TeXSymbolType -> TeXSymbolType -> TeXSymbolType
max :: TeXSymbolType -> TeXSymbolType -> TeXSymbolType
$cmin :: TeXSymbolType -> TeXSymbolType -> TeXSymbolType
min :: TeXSymbolType -> TeXSymbolType -> TeXSymbolType
Ord, Typeable TeXSymbolType
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 -> Constr
TeXSymbolType -> DataType
(forall b. Data b => b -> b) -> TeXSymbolType -> 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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TeXSymbolType -> c TeXSymbolType
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TeXSymbolType -> c TeXSymbolType
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TeXSymbolType
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TeXSymbolType
$ctoConstr :: TeXSymbolType -> Constr
toConstr :: TeXSymbolType -> Constr
$cdataTypeOf :: TeXSymbolType -> DataType
dataTypeOf :: TeXSymbolType -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TeXSymbolType)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TeXSymbolType)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TeXSymbolType)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TeXSymbolType)
$cgmapT :: (forall b. Data b => b -> b) -> TeXSymbolType -> TeXSymbolType
gmapT :: (forall b. Data b => b -> b) -> TeXSymbolType -> TeXSymbolType
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TeXSymbolType -> r
gmapQl :: forall r r'.
(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
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TeXSymbolType -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> TeXSymbolType -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> TeXSymbolType -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TeXSymbolType -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TeXSymbolType -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TeXSymbolType -> m TeXSymbolType
gmapM :: forall (m :: * -> *).
Monad m =>
(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
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(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
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TeXSymbolType -> m 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
$cshowsPrec :: Int -> Alignment -> ShowS
showsPrec :: Int -> Alignment -> ShowS
$cshow :: Alignment -> String
show :: Alignment -> String
$cshowList :: [Alignment] -> ShowS
showList :: [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
$creadsPrec :: Int -> ReadS Alignment
readsPrec :: Int -> ReadS Alignment
$creadList :: ReadS [Alignment]
readList :: ReadS [Alignment]
$creadPrec :: ReadPrec Alignment
readPrec :: ReadPrec Alignment
$creadListPrec :: ReadPrec [Alignment]
readListPrec :: ReadPrec [Alignment]
Read, Alignment -> Alignment -> Bool
(Alignment -> Alignment -> Bool)
-> (Alignment -> Alignment -> Bool) -> Eq Alignment
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Alignment -> Alignment -> Bool
== :: Alignment -> Alignment -> Bool
$c/= :: Alignment -> Alignment -> Bool
/= :: 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
$ccompare :: Alignment -> Alignment -> Ordering
compare :: Alignment -> Alignment -> Ordering
$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
>= :: Alignment -> Alignment -> Bool
$cmax :: Alignment -> Alignment -> Alignment
max :: Alignment -> Alignment -> Alignment
$cmin :: Alignment -> Alignment -> Alignment
min :: Alignment -> Alignment -> Alignment
Ord, Typeable Alignment
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 -> Constr
Alignment -> DataType
(forall b. Data b => b -> b) -> Alignment -> 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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Alignment -> c Alignment
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Alignment -> c Alignment
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Alignment
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Alignment
$ctoConstr :: Alignment -> Constr
toConstr :: Alignment -> Constr
$cdataTypeOf :: Alignment -> DataType
dataTypeOf :: Alignment -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Alignment)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Alignment)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Alignment)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Alignment)
$cgmapT :: (forall b. Data b => b -> b) -> Alignment -> Alignment
gmapT :: (forall b. Data b => b -> b) -> Alignment -> Alignment
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Alignment -> r
gmapQl :: forall r r'.
(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
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Alignment -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Alignment -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Alignment -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Alignment -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Alignment -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Alignment -> m Alignment
gmapM :: forall (m :: * -> *).
Monad m =>
(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
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(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
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Alignment -> m Alignment
Data, Typeable)
data FractionType = NormalFrac
| DisplayFrac
| InlineFrac
| NoLineFrac
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
$cshowsPrec :: Int -> FractionType -> ShowS
showsPrec :: Int -> FractionType -> ShowS
$cshow :: FractionType -> String
show :: FractionType -> String
$cshowList :: [FractionType] -> ShowS
showList :: [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
$creadsPrec :: Int -> ReadS FractionType
readsPrec :: Int -> ReadS FractionType
$creadList :: ReadS [FractionType]
readList :: ReadS [FractionType]
$creadPrec :: ReadPrec FractionType
readPrec :: ReadPrec FractionType
$creadListPrec :: ReadPrec [FractionType]
readListPrec :: ReadPrec [FractionType]
Read, FractionType -> FractionType -> Bool
(FractionType -> FractionType -> Bool)
-> (FractionType -> FractionType -> Bool) -> Eq FractionType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FractionType -> FractionType -> Bool
== :: FractionType -> FractionType -> Bool
$c/= :: FractionType -> FractionType -> Bool
/= :: 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
$ccompare :: FractionType -> FractionType -> Ordering
compare :: FractionType -> FractionType -> Ordering
$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
>= :: FractionType -> FractionType -> Bool
$cmax :: FractionType -> FractionType -> FractionType
max :: FractionType -> FractionType -> FractionType
$cmin :: FractionType -> FractionType -> FractionType
min :: FractionType -> FractionType -> FractionType
Ord, Typeable FractionType
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 -> Constr
FractionType -> DataType
(forall b. Data b => b -> b) -> FractionType -> 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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FractionType -> c FractionType
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FractionType -> c FractionType
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FractionType
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FractionType
$ctoConstr :: FractionType -> Constr
toConstr :: FractionType -> Constr
$cdataTypeOf :: FractionType -> DataType
dataTypeOf :: FractionType -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FractionType)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FractionType)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FractionType)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FractionType)
$cgmapT :: (forall b. Data b => b -> b) -> FractionType -> FractionType
gmapT :: (forall b. Data b => b -> b) -> FractionType -> FractionType
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FractionType -> r
gmapQl :: forall r r'.
(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
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FractionType -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> FractionType -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> FractionType -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> FractionType -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> FractionType -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FractionType -> m FractionType
gmapM :: forall (m :: * -> *).
Monad m =>
(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
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(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
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FractionType -> m FractionType
Data, Typeable)
type ArrayLine = [[Exp]]
data Exp =
ENumber T.Text
| EGrouped [Exp]
| EDelimited T.Text T.Text [InEDelimited]
| EIdentifier T.Text
| EMathOperator T.Text
| ESymbol TeXSymbolType T.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 T.Text
| EStyled TextType [Exp]
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
$cshowsPrec :: Int -> Exp -> ShowS
showsPrec :: Int -> Exp -> ShowS
$cshow :: Exp -> String
show :: Exp -> String
$cshowList :: [Exp] -> ShowS
showList :: [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
$creadsPrec :: Int -> ReadS Exp
readsPrec :: Int -> ReadS Exp
$creadList :: ReadS [Exp]
readList :: ReadS [Exp]
$creadPrec :: ReadPrec Exp
readPrec :: ReadPrec Exp
$creadListPrec :: ReadPrec [Exp]
readListPrec :: ReadPrec [Exp]
Read, Exp -> Exp -> Bool
(Exp -> Exp -> Bool) -> (Exp -> Exp -> Bool) -> Eq Exp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Exp -> Exp -> Bool
== :: Exp -> Exp -> Bool
$c/= :: Exp -> Exp -> Bool
/= :: 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
$ccompare :: Exp -> Exp -> Ordering
compare :: Exp -> Exp -> Ordering
$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
>= :: Exp -> Exp -> Bool
$cmax :: Exp -> Exp -> Exp
max :: Exp -> Exp -> Exp
$cmin :: Exp -> Exp -> Exp
min :: Exp -> Exp -> Exp
Ord, Typeable Exp
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 -> Constr
Exp -> DataType
(forall b. Data b => b -> b) -> Exp -> 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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Exp -> c Exp
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Exp -> c Exp
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Exp
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Exp
$ctoConstr :: Exp -> Constr
toConstr :: Exp -> Constr
$cdataTypeOf :: Exp -> DataType
dataTypeOf :: Exp -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Exp)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Exp)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Exp)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Exp)
$cgmapT :: (forall b. Data b => b -> b) -> Exp -> Exp
gmapT :: (forall b. Data b => b -> b) -> Exp -> Exp
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Exp -> r
gmapQl :: forall r r'.
(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
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Exp -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Exp -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Exp -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Exp -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Exp -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Exp -> m Exp
gmapM :: forall (m :: * -> *).
Monad m =>
(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
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(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
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Exp -> m Exp
Data, Typeable)
type InEDelimited = Either Middle Exp
type Middle = T.Text
data DisplayType = DisplayBlock
| DisplayInline
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
$cshowsPrec :: Int -> DisplayType -> ShowS
showsPrec :: Int -> DisplayType -> ShowS
$cshow :: DisplayType -> String
show :: DisplayType -> String
$cshowList :: [DisplayType] -> ShowS
showList :: [DisplayType] -> ShowS
Show, DisplayType -> DisplayType -> Bool
(DisplayType -> DisplayType -> Bool)
-> (DisplayType -> DisplayType -> Bool) -> Eq DisplayType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DisplayType -> DisplayType -> Bool
== :: DisplayType -> DisplayType -> Bool
$c/= :: DisplayType -> DisplayType -> Bool
/= :: 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
$ccompare :: DisplayType -> DisplayType -> Ordering
compare :: DisplayType -> DisplayType -> Ordering
$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
>= :: DisplayType -> DisplayType -> Bool
$cmax :: DisplayType -> DisplayType -> DisplayType
max :: DisplayType -> DisplayType -> DisplayType
$cmin :: DisplayType -> DisplayType -> DisplayType
min :: DisplayType -> DisplayType -> 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
$cshowsPrec :: Int -> TextType -> ShowS
showsPrec :: Int -> TextType -> ShowS
$cshow :: TextType -> String
show :: TextType -> String
$cshowList :: [TextType] -> ShowS
showList :: [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
$creadsPrec :: Int -> ReadS TextType
readsPrec :: Int -> ReadS TextType
$creadList :: ReadS [TextType]
readList :: ReadS [TextType]
$creadPrec :: ReadPrec TextType
readPrec :: ReadPrec TextType
$creadListPrec :: ReadPrec [TextType]
readListPrec :: ReadPrec [TextType]
Read, TextType -> TextType -> Bool
(TextType -> TextType -> Bool)
-> (TextType -> TextType -> Bool) -> Eq TextType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TextType -> TextType -> Bool
== :: TextType -> TextType -> Bool
$c/= :: TextType -> TextType -> Bool
/= :: 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
$ccompare :: TextType -> TextType -> Ordering
compare :: TextType -> TextType -> Ordering
$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
>= :: TextType -> TextType -> Bool
$cmax :: TextType -> TextType -> TextType
max :: TextType -> TextType -> TextType
$cmin :: TextType -> TextType -> TextType
min :: TextType -> TextType -> TextType
Ord, Typeable TextType
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 -> Constr
TextType -> DataType
(forall b. Data b => b -> b) -> TextType -> 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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TextType -> c TextType
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TextType -> c TextType
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TextType
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TextType
$ctoConstr :: TextType -> Constr
toConstr :: TextType -> Constr
$cdataTypeOf :: TextType -> DataType
dataTypeOf :: TextType -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TextType)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TextType)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TextType)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TextType)
$cgmapT :: (forall b. Data b => b -> b) -> TextType -> TextType
gmapT :: (forall b. Data b => b -> b) -> TextType -> TextType
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TextType -> r
gmapQl :: forall r r'.
(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
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TextType -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> TextType -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> TextType -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TextType -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TextType -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TextType -> m TextType
gmapM :: forall (m :: * -> *).
Monad m =>
(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
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(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
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TextType -> m 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
$cshowsPrec :: Int -> FormType -> ShowS
showsPrec :: Int -> FormType -> ShowS
$cshow :: FormType -> String
show :: FormType -> String
$cshowList :: [FormType] -> ShowS
showList :: [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
$ccompare :: FormType -> FormType -> Ordering
compare :: FormType -> FormType -> Ordering
$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
>= :: FormType -> FormType -> Bool
$cmax :: FormType -> FormType -> FormType
max :: FormType -> FormType -> FormType
$cmin :: FormType -> FormType -> FormType
min :: FormType -> FormType -> FormType
Ord, FormType -> FormType -> Bool
(FormType -> FormType -> Bool)
-> (FormType -> FormType -> Bool) -> Eq FormType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FormType -> FormType -> Bool
== :: FormType -> FormType -> Bool
$c/= :: FormType -> FormType -> Bool
/= :: FormType -> FormType -> Bool
Eq)
type Property = T.Text
data Operator = Operator
{ Operator -> Text
oper :: T.Text
, Operator -> Text
description :: T.Text
, Operator -> FormType
form :: FormType
, Operator -> Int
priority :: Int
, Operator -> Int
lspace :: Int
, Operator -> Int
rspace :: Int
, Operator -> [Text]
properties :: [Property]
}
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
$cshowsPrec :: Int -> Operator -> ShowS
showsPrec :: Int -> Operator -> ShowS
$cshow :: Operator -> String
show :: Operator -> String
$cshowList :: [Operator] -> ShowS
showList :: [Operator] -> ShowS
Show)
data Record = Record { Record -> Char
uchar :: Char
, Record -> [(Text, Text)]
commands :: [(T.Text, T.Text)]
, Record -> TeXSymbolType
category :: TeXSymbolType
, :: T.Text
} 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
$cshowsPrec :: Int -> Record -> ShowS
showsPrec :: Int -> Record -> ShowS
$cshow :: Record -> String
show :: Record -> String
$cshowList :: [Record] -> ShowS
showList :: [Record] -> ShowS
Show)
data Position = Under | Over
type Env = [T.Text]
defaultEnv :: [T.Text]
defaultEnv :: [Text]
defaultEnv = [Text
"amsmath", Text
"amssymb"]