Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Functions for converting between different representations of mathematical formulas.
Also note that in general writeLaTeX . readLaTeX /= id
.
A typical use is to combine together a reader and writer.
import Control.Applicative ((<$>)) import Data.Text (Text) import Text.TeXMath (writeMathML, readTeX) texMathToMathML :: DisplayType -> Text -> Either Text Element texMathToMathML dt s = writeMathML dt <$> readTeX s
It is also possible to manipulate the AST using Generics
. For
example, if you wanted to replace all occurences of the identifier
x in your expression, you do could do so with the following
script.
{-# LANGUAGE OverloadedStrings -#} import Control.Applicative ((<$>)) import Data.Text (Text) import Data.Generics (everywhere, mkT) import Text.TeXMath (writeMathML, readTeX) import Text.TeXMath.Types import Text.XML.Light (Element) changeIdent :: Exp -> Exp changeIdent (EIdentifier "x") = EIdentifier "y" changeIdent e = e texToMMLWithChangeIdent :: DisplayType -> Text -> Either Text Element texToMMLWithChangeIdent dt s = writeMathML dt . everywhere (mkT changeIdent) <$> readTeX s
Synopsis
- readMathML :: Text -> Either Text [Exp]
- readOMML :: Text -> Either Text [Exp]
- readTeX :: Text -> Either Text [Exp]
- writeTeX :: [Exp] -> Text
- writeTeXWith :: Env -> [Exp] -> Text
- addLaTeXEnvironment :: DisplayType -> Text -> Text
- writeEqn :: DisplayType -> [Exp] -> Text
- writeTypst :: DisplayType -> [Exp] -> Text
- writeOMML :: DisplayType -> [Exp] -> Element
- writeMathML :: DisplayType -> [Exp] -> Element
- writePandoc :: DisplayType -> [Exp] -> Maybe [Inline]
- data DisplayType
- data Exp
Documentation
writeTeX :: [Exp] -> Text Source #
Transforms an expression tree to equivalent LaTeX with the default packages (amsmath and amssymb)
writeTeXWith :: Env -> [Exp] -> Text Source #
Transforms an expression tree to equivalent LaTeX with the specified packages
addLaTeXEnvironment :: DisplayType -> Text -> Text Source #
Adds the correct LaTeX environment around a TeXMath fragment
writeTypst :: DisplayType -> [Exp] -> Text Source #
Transforms an expression tree to equivalent Typst
writeOMML :: DisplayType -> [Exp] -> Element Source #
Transforms an expression tree to an OMML XML Tree
writeMathML :: DisplayType -> [Exp] -> Element Source #
Transforms an expression tree to a MathML XML tree
writePandoc :: DisplayType -> [Exp] -> Maybe [Inline] Source #
Attempts to convert a formula to a list of Pandoc
inlines.
data DisplayType Source #
DisplayBlock | A displayed formula. |
DisplayInline | A formula rendered inline in text. |
Instances
Show DisplayType Source # | |
Defined in Text.TeXMath.Types showsPrec :: Int -> DisplayType -> ShowS # show :: DisplayType -> String # showList :: [DisplayType] -> ShowS # | |
Eq DisplayType Source # | |
Defined in Text.TeXMath.Types (==) :: DisplayType -> DisplayType -> Bool # (/=) :: DisplayType -> DisplayType -> Bool # | |
Ord DisplayType Source # | |
Defined in Text.TeXMath.Types compare :: DisplayType -> DisplayType -> Ordering # (<) :: DisplayType -> DisplayType -> Bool # (<=) :: DisplayType -> DisplayType -> Bool # (>) :: DisplayType -> DisplayType -> Bool # (>=) :: DisplayType -> DisplayType -> Bool # max :: DisplayType -> DisplayType -> DisplayType # min :: DisplayType -> DisplayType -> DisplayType # |
Instances
Data Exp Source # | |
Defined in Text.TeXMath.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Exp -> c Exp # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Exp # dataTypeOf :: Exp -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Exp) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Exp) # gmapT :: (forall b. Data b => b -> b) -> Exp -> Exp # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Exp -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Exp -> r # gmapQ :: (forall d. Data d => d -> u) -> Exp -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Exp -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Exp -> m Exp # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Exp -> m Exp # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Exp -> m Exp # | |
Read Exp Source # | |
Show Exp Source # | |
Eq Exp Source # | |
Ord Exp Source # | |