texmath-0.12.2: Conversion between formats used to represent mathematics.
Safe HaskellNone
LanguageHaskell2010

Text.TeXMath

Description

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

Documentation

readMathML :: Text -> Either Text [Exp] Source #

Parse a MathML expression to a list of Exp.

readTeX :: Text -> Either Text [Exp] Source #

Parse a formula, returning a list of Exp.

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

writeEqn :: DisplayType -> [Exp] -> Text Source #

Transforms an expression tree to equivalent Eqn with the default packages (amsmath and amssymb)

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 #

Constructors

DisplayBlock

A displayed formula.

DisplayInline

A formula rendered inline in text.

data Exp Source #

Instances

Instances details
Eq Exp Source # 
Instance details

Defined in Text.TeXMath.Types

Methods

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

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

Data Exp Source # 
Instance details

Defined in Text.TeXMath.Types

Methods

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

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

toConstr :: Exp -> Constr #

dataTypeOf :: Exp -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Exp Source # 
Instance details

Defined in Text.TeXMath.Types

Methods

compare :: Exp -> Exp -> Ordering #

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

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

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

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

max :: Exp -> Exp -> Exp #

min :: Exp -> Exp -> Exp #

Read Exp Source # 
Instance details

Defined in Text.TeXMath.Types

Show Exp Source # 
Instance details

Defined in Text.TeXMath.Types

Methods

showsPrec :: Int -> Exp -> ShowS #

show :: Exp -> String #

showList :: [Exp] -> ShowS #