HaTeX-3.9.1.0: The Haskell LaTeX library.

Safe HaskellNone

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 Source

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.

data MathType Source

Different types of syntax for mathematical expressions.

Constructors

Parentheses 
Square 
Dollar 

Instances

data LaTeX Source

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.

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.

TeXOp String LaTeX LaTeX

Operators.

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 
Floating LaTeX

Undefined methods: asinh, atanh and acosh. This instance is defined in the Text.LaTeX.Packages.AMSMath module.

Fractional LaTeX

Division uses the LaTeX frac command. This instance is defined in the Text.LaTeX.Packages.AMSMath module.

Num LaTeX

Careful! Method signum is undefined. Don't use it! This instance is defined in the Text.LaTeX.Packages.AMSMath module.

Show LaTeX 
Typeable LaTeX 
IsString LaTeX

Method fromString escapes LaTeX reserved characters using protectString.

Monoid LaTeX

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

LaTeXC LaTeX

This instance just sets liftListL = id.

Render LaTeX 
Texy LaTeX 

data TeXArg Source

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.

(<>) :: Monoid m => m -> m -> m

An infix synonym for mappend.

Escaping reserved characters

protectString :: String -> StringSource

Escape LaTeX reserved characters in a String.

protectText :: Text -> TextSource

Escape LaTeX reserved characters in a Text.

Syntax analysis

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

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

lookForCommandSource

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)]Source

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)]Source

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 . (==)

texmapSource

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)

texmapMSource

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 LaTeXSource

Extract the content of the document environment, if present.

getPreamble :: LaTeX -> LaTeXSource

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