HaTeX-3.18.0.0: The Haskell LaTeX library.

Safe HaskellSafe
LanguageHaskell2010

Text.LaTeX.Base.Syntax

Contents

Description

LaTeX syntax description in the definition of the LaTeX datatype. If you want to add new commands or environments not defined in the library, import this module and use LaTeX data constructors.

Synopsis

LaTeX datatype

data Measure #

Measure units defined in LaTeX. Use CustomMeasure to use commands like textwidth. For instance:

rule Nothing (CustomMeasure linewidth) (Pt 2)

This will create a black box (see rule) as wide as the text and two points tall.

Constructors

Pt Double

A point is 1/72.27 inch, that means about 0.0138 inch or 0.3515 mm.

Mm Double

Millimeter.

Cm Double

Centimeter.

In Double

Inch.

Ex Double

The height of an "x" in the current font.

Em Double

The width of an "M" in the current font.

CustomMeasure LaTeX

You can introduce a LaTeX expression as a measure.

Instances

Eq Measure # 

Methods

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

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

Data Measure # 

Methods

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

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

toConstr :: Measure -> Constr #

dataTypeOf :: Measure -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Measure # 
Generic Measure # 

Associated Types

type Rep Measure :: * -> * #

Methods

from :: Measure -> Rep Measure x #

to :: Rep Measure x -> Measure #

Arbitrary Measure # 
Hashable Measure # 

Methods

hashWithSalt :: Int -> Measure -> Int #

hash :: Measure -> Int #

Render Measure # 

Methods

render :: Measure -> Text #

Texy Measure # 

Methods

texy :: LaTeXC l => Measure -> l #

type Rep Measure # 

data MathType #

Different types of syntax for mathematical expressions.

Instances

Eq MathType # 
Data MathType # 

Methods

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

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

toConstr :: MathType -> Constr #

dataTypeOf :: MathType -> DataType #

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

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

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

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

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

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

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

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

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

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

Show MathType # 
Generic MathType # 

Associated Types

type Rep MathType :: * -> * #

Methods

from :: MathType -> Rep MathType x #

to :: Rep MathType x -> MathType #

Hashable MathType # 

Methods

hashWithSalt :: Int -> MathType -> Int #

hash :: MathType -> Int #

type Rep MathType # 
type Rep MathType = D1 * (MetaData "MathType" "Text.LaTeX.Base.Syntax" "HaTeX-3.18.0.0-IxcyMPasLxl1v0AMAPYPyW" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Parentheses" PrefixI False) (U1 *)) (C1 * (MetaCons "Square" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Dollar" PrefixI False) (U1 *)) (C1 * (MetaCons "DoubleDollar" PrefixI False) (U1 *))))

data LaTeX #

Type of LaTeX blocks.

Constructors

TeXRaw Text

Raw text.

TeXComm String [TeXArg]

Constructor for commands. First argument is the name of the command. Second, its arguments.

TeXCommS String

Constructor for commands with no arguments. When rendering, no space or {} will be added at the end.

TeXEnv String [TeXArg] LaTeX

Constructor for environments. First argument is the name of the environment. Second, its arguments. Third, its content.

TeXMath MathType LaTeX

Mathematical expressions.

TeXLineBreak (Maybe Measure) Bool

Line break command.

TeXBraces LaTeX

A expression between braces.

TeXComment Text

Comments.

TeXSeq LaTeX LaTeX

Sequencing of LaTeX expressions. Use <> preferably.

TeXEmpty

An empty block. Neutral element of <>.

Instances

Eq LaTeX # 

Methods

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

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

Data LaTeX # 

Methods

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

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

toConstr :: LaTeX -> Constr #

dataTypeOf :: LaTeX -> DataType #

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

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

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

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

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

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

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

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

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

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

Show LaTeX # 

Methods

showsPrec :: Int -> LaTeX -> ShowS #

show :: LaTeX -> String #

showList :: [LaTeX] -> ShowS #

IsString LaTeX #

Method fromString escapes LaTeX reserved characters using protectString.

Methods

fromString :: String -> LaTeX #

Generic LaTeX # 

Associated Types

type Rep LaTeX :: * -> * #

Methods

from :: LaTeX -> Rep LaTeX x #

to :: Rep LaTeX x -> LaTeX #

Semigroup LaTeX # 

Methods

(<>) :: LaTeX -> LaTeX -> LaTeX #

sconcat :: NonEmpty LaTeX -> LaTeX #

stimes :: Integral b => b -> LaTeX -> LaTeX #

Monoid LaTeX #

Method mappend is strict in both arguments (except in the case when the first argument is TeXEmpty).

Methods

mempty :: LaTeX #

mappend :: LaTeX -> LaTeX -> LaTeX #

mconcat :: [LaTeX] -> LaTeX #

Arbitrary LaTeX # 

Methods

arbitrary :: Gen LaTeX #

shrink :: LaTeX -> [LaTeX] #

Hashable LaTeX # 

Methods

hashWithSalt :: Int -> LaTeX -> Int #

hash :: LaTeX -> Int #

LaTeXC LaTeX #

This instance just sets liftListL = id.

Methods

liftListL :: ([LaTeX] -> LaTeX) -> [LaTeX] -> LaTeX #

Render LaTeX # 

Methods

render :: LaTeX -> Text #

Texy LaTeX # 

Methods

texy :: LaTeXC l => LaTeX -> l #

type Rep LaTeX # 
type Rep LaTeX = D1 * (MetaData "LaTeX" "Text.LaTeX.Base.Syntax" "HaTeX-3.18.0.0-IxcyMPasLxl1v0AMAPYPyW" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "TeXRaw" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text))) (C1 * (MetaCons "TeXComm" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [TeXArg]))))) ((:+:) * (C1 * (MetaCons "TeXCommS" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))) ((:+:) * (C1 * (MetaCons "TeXEnv" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [TeXArg])) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * LaTeX))))) (C1 * (MetaCons "TeXMath" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MathType)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * LaTeX))))))) ((:+:) * ((:+:) * (C1 * (MetaCons "TeXLineBreak" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Measure))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)))) (C1 * (MetaCons "TeXBraces" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * LaTeX)))) ((:+:) * (C1 * (MetaCons "TeXComment" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text))) ((:+:) * (C1 * (MetaCons "TeXSeq" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * LaTeX)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * LaTeX)))) (C1 * (MetaCons "TeXEmpty" PrefixI False) (U1 *))))))

data TeXArg #

An argument for a LaTeX command or environment.

Constructors

FixArg LaTeX

Fixed argument.

OptArg LaTeX

Optional argument.

MOptArg [LaTeX]

Multiple optional argument.

SymArg LaTeX

An argument enclosed between < and >.

MSymArg [LaTeX]

Version of SymArg with multiple options.

ParArg LaTeX

An argument enclosed between ( and ).

MParArg [LaTeX]

Version of ParArg with multiple options.

Instances

Eq TeXArg # 

Methods

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

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

Data TeXArg # 

Methods

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

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

toConstr :: TeXArg -> Constr #

dataTypeOf :: TeXArg -> DataType #

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

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

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

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

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

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

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

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

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

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

Show TeXArg # 
Generic TeXArg # 

Associated Types

type Rep TeXArg :: * -> * #

Methods

from :: TeXArg -> Rep TeXArg x #

to :: Rep TeXArg x -> TeXArg #

Arbitrary TeXArg # 
Hashable TeXArg # 

Methods

hashWithSalt :: Int -> TeXArg -> Int #

hash :: TeXArg -> Int #

Render TeXArg # 

Methods

render :: TeXArg -> Text #

type Rep TeXArg # 

(<>) :: Monoid m => m -> m -> m infixr 6 #

An infix synonym for mappend.

Since: 4.5.0.0

Escaping reserved characters

protectString :: String -> String #

Escape LaTeX reserved characters in a String.

protectText :: Text -> Text #

Escape LaTeX reserved characters in a Text.

Syntax analysis

matchCommand :: (String -> Bool) -> LaTeX -> [(String, [TeXArg])] #

Traverse a LaTeX syntax tree and returns the commands (see TeXComm and TeXCommS) that matches the condition and their arguments in each call.

lookForCommand #

Arguments

:: String

Name of the command.

-> LaTeX

LaTeX syntax tree.

-> [[TeXArg]]

List of arguments passed to the command.

Look into a LaTeX syntax tree to find any call to the command with the given name. It returns a list of arguments with which this command is called.

lookForCommand = (fmap snd .) . matchCommand . (==)

If the returned list is empty, the command was not found. However, if the list contains empty lists, those are callings to the command with no arguments.

For example

lookForCommand "author" l

would look for the argument passed to the \author command in l.

matchEnv :: (String -> Bool) -> LaTeX -> [(String, [TeXArg], LaTeX)] #

Traverse a LaTeX syntax tree and returns the environments (see TeXEnv) that matches the condition, their arguments and their content in each call.

lookForEnv :: String -> LaTeX -> [([TeXArg], LaTeX)] #

Similar to lookForCommand, but applied to environments. It returns a list with arguments passed and content of the environment in each call.

lookForEnv = (fmap (\(_,as,l) -> (as,l)) .) . matchEnv . (==)

texmap #

Arguments

:: (LaTeX -> Bool)

Condition.

-> (LaTeX -> LaTeX)

Function to apply when the condition matches.

-> LaTeX 
-> LaTeX 

The function texmap looks for subexpressions that match a given condition and applies a function to them.

texmap c f = runIdentity . texmapM c (pure . f)

texmapM #

Arguments

:: (Applicative m, Monad m) 
=> (LaTeX -> Bool)

Condition.

-> (LaTeX -> m LaTeX)

Function to apply when the condition matches.

-> LaTeX 
-> m LaTeX 

Version of texmap where the function returns values in a Monad.

Utils

getBody :: LaTeX -> Maybe LaTeX #

Extract the content of the document environment, if present.

getPreamble :: LaTeX -> LaTeX #

Extract the preamble of a LaTeX document (everything before the document environment). It could be empty.