HaTeX-3.22.3.2: The Haskell LaTeX library.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Text.LaTeX.Base.Syntax

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.

Instances

Instances details
Render Measure Source # 
Instance details

Defined in Text.LaTeX.Base.Render

Texy Measure Source # 
Instance details

Defined in Text.LaTeX.Base.Texy

Methods

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

Arbitrary Measure Source # 
Instance details

Defined in Text.LaTeX.Base.Syntax

Data Measure Source # 
Instance details

Defined in Text.LaTeX.Base.Syntax

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 :: forall r r'. (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 #

Generic Measure Source # 
Instance details

Defined in Text.LaTeX.Base.Syntax

Associated Types

type Rep Measure :: Type -> Type #

Methods

from :: Measure -> Rep Measure x #

to :: Rep Measure x -> Measure #

Show Measure Source # 
Instance details

Defined in Text.LaTeX.Base.Syntax

Eq Measure Source # 
Instance details

Defined in Text.LaTeX.Base.Syntax

Methods

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

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

Hashable Measure Source # 
Instance details

Defined in Text.LaTeX.Base.Syntax

Methods

hashWithSalt :: Int -> Measure -> Int #

hash :: Measure -> Int #

type Rep Measure Source # 
Instance details

Defined in Text.LaTeX.Base.Syntax

data MathType Source #

Different types of syntax for mathematical expressions.

Instances

Instances details
Data MathType Source # 
Instance details

Defined in Text.LaTeX.Base.Syntax

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 :: forall r r'. (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 #

Generic MathType Source # 
Instance details

Defined in Text.LaTeX.Base.Syntax

Associated Types

type Rep MathType :: Type -> Type #

Methods

from :: MathType -> Rep MathType x #

to :: Rep MathType x -> MathType #

Show MathType Source # 
Instance details

Defined in Text.LaTeX.Base.Syntax

Eq MathType Source # 
Instance details

Defined in Text.LaTeX.Base.Syntax

Hashable MathType Source # 
Instance details

Defined in Text.LaTeX.Base.Syntax

Methods

hashWithSalt :: Int -> MathType -> Int #

hash :: MathType -> Int #

type Rep MathType Source # 
Instance details

Defined in Text.LaTeX.Base.Syntax

type Rep MathType = D1 ('MetaData "MathType" "Text.LaTeX.Base.Syntax" "HaTeX-3.22.3.2-HZvUhlnm8H82ymAYOfPoYP" 'False) ((C1 ('MetaCons "Parentheses" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Square" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Dollar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DoubleDollar" 'PrefixI 'False) (U1 :: Type -> Type)))

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. 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

Instances details
LaTeXC LaTeX Source #

This instance just sets liftListL = id.

Instance details

Defined in Text.LaTeX.Base.Class

Methods

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

Render LaTeX Source # 
Instance details

Defined in Text.LaTeX.Base.Render

Texy LaTeX Source # 
Instance details

Defined in Text.LaTeX.Base.Texy

Methods

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

Arbitrary LaTeX Source # 
Instance details

Defined in Text.LaTeX.Base.Syntax

Methods

arbitrary :: Gen LaTeX #

shrink :: LaTeX -> [LaTeX] #

Data LaTeX Source # 
Instance details

Defined in Text.LaTeX.Base.Syntax

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 :: forall r r'. (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 #

IsString LaTeX Source #

Method fromString escapes LaTeX reserved characters using protectString.

Instance details

Defined in Text.LaTeX.Base.Syntax

Methods

fromString :: String -> LaTeX #

Monoid LaTeX Source #

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

Instance details

Defined in Text.LaTeX.Base.Syntax

Methods

mempty :: LaTeX #

mappend :: LaTeX -> LaTeX -> LaTeX #

mconcat :: [LaTeX] -> LaTeX #

Semigroup LaTeX Source # 
Instance details

Defined in Text.LaTeX.Base.Syntax

Methods

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

sconcat :: NonEmpty LaTeX -> LaTeX #

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

Floating LaTeX Source #

The asinh, atanh and acosh methods use custom operatornames and will not be automatically translated by babel. This instance is defined in the Text.LaTeX.Packages.AMSMath module.

Instance details

Defined in Text.LaTeX.Base.Math

Generic LaTeX Source # 
Instance details

Defined in Text.LaTeX.Base.Syntax

Associated Types

type Rep LaTeX :: Type -> Type #

Methods

from :: LaTeX -> Rep LaTeX x #

to :: Rep LaTeX x -> LaTeX #

Num LaTeX Source #

The signum method uses a custom operatorname and will not be automatically translated by babel. This instance is defined in the Text.LaTeX.Packages.AMSMath module.

Instance details

Defined in Text.LaTeX.Base.Math

Fractional LaTeX Source #

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

Instance details

Defined in Text.LaTeX.Base.Math

Show LaTeX Source # 
Instance details

Defined in Text.LaTeX.Base.Syntax

Methods

showsPrec :: Int -> LaTeX -> ShowS #

show :: LaTeX -> String #

showList :: [LaTeX] -> ShowS #

Eq LaTeX Source # 
Instance details

Defined in Text.LaTeX.Base.Syntax

Methods

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

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

Hashable LaTeX Source # 
Instance details

Defined in Text.LaTeX.Base.Syntax

Methods

hashWithSalt :: Int -> LaTeX -> Int #

hash :: LaTeX -> Int #

type Rep LaTeX Source # 
Instance details

Defined in Text.LaTeX.Base.Syntax

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

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.

ParArg LaTeX

An argument enclosed between ( and ).

MParArg [LaTeX]

Version of ParArg with multiple options.

Instances

Instances details
Render TeXArg Source # 
Instance details

Defined in Text.LaTeX.Base.Render

Arbitrary TeXArg Source # 
Instance details

Defined in Text.LaTeX.Base.Syntax

Data TeXArg Source # 
Instance details

Defined in Text.LaTeX.Base.Syntax

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 :: forall r r'. (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 #

Generic TeXArg Source # 
Instance details

Defined in Text.LaTeX.Base.Syntax

Associated Types

type Rep TeXArg :: Type -> Type #

Methods

from :: TeXArg -> Rep TeXArg x #

to :: Rep TeXArg x -> TeXArg #

Show TeXArg Source # 
Instance details

Defined in Text.LaTeX.Base.Syntax

Eq TeXArg Source # 
Instance details

Defined in Text.LaTeX.Base.Syntax

Methods

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

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

Hashable TeXArg Source # 
Instance details

Defined in Text.LaTeX.Base.Syntax

Methods

hashWithSalt :: Int -> TeXArg -> Int #

hash :: TeXArg -> Int #

type Rep TeXArg Source # 
Instance details

Defined in Text.LaTeX.Base.Syntax

(<>) :: Semigroup a => a -> a -> a infixr 6 #

An associative operation.

>>> [1,2,3] <> [4,5,6]
[1,2,3,4,5,6]

between :: Monoid m => m -> m -> m -> m Source #

Calling between c l1 l2 puts c between l1 and l2 and appends them.

between c l1 l2 = l1 <> c <> l2

Escaping reserved characters

protectString :: String -> String Source #

Escape LaTeX reserved characters in a String.

protectText :: Text -> Text Source #

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.

lookForCommand Source #

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

texmap Source #

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 Source #

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 Source #

Extract the content of the document environment, if present.

getPreamble :: LaTeX -> LaTeX Source #

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