pandoc-2.11.3.1: Conversion between markup formats
CopyrightCopyright (C) 2017-2020 John MacFarlane
LicenseGNU GPL, version 2 or above
MaintainerJohn MacFarlane <jgm@berkeley.edu>
Stabilityalpha
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Text.Pandoc.Readers.LaTeX.Types

Description

Types for LaTeX tokens and macros.

Synopsis

Documentation

data Tok Source #

Constructors

Tok SourcePos TokType Text 

Instances

Instances details
Eq Tok Source # 
Instance details

Defined in Text.Pandoc.Readers.LaTeX.Types

Methods

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

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

Ord Tok Source # 
Instance details

Defined in Text.Pandoc.Readers.LaTeX.Types

Methods

compare :: Tok -> Tok -> Ordering #

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

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

(>) :: Tok -> Tok -> Bool #

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

max :: Tok -> Tok -> Tok #

min :: Tok -> Tok -> Tok #

Show Tok Source # 
Instance details

Defined in Text.Pandoc.Readers.LaTeX.Types

Methods

showsPrec :: Int -> Tok -> ShowS #

show :: Tok -> String #

showList :: [Tok] -> ShowS #

data TokType Source #

Instances

Instances details
Eq TokType Source # 
Instance details

Defined in Text.Pandoc.Readers.LaTeX.Types

Methods

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

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

Ord TokType Source # 
Instance details

Defined in Text.Pandoc.Readers.LaTeX.Types

Show TokType Source # 
Instance details

Defined in Text.Pandoc.Readers.LaTeX.Types

data Macro Source #

Constructors

Macro ExpansionPoint [ArgSpec] (Maybe [Tok]) [Tok] 

Instances

Instances details
Show Macro Source # 
Instance details

Defined in Text.Pandoc.Readers.LaTeX.Types

Methods

showsPrec :: Int -> Macro -> ShowS #

show :: Macro -> String #

showList :: [Macro] -> ShowS #

data ArgSpec Source #

Constructors

ArgNum Int 
Pattern [Tok] 

Instances

Instances details
Show ArgSpec Source # 
Instance details

Defined in Text.Pandoc.Readers.LaTeX.Types

data SourcePos #

The abstract data type SourcePos represents source positions. It contains the name of the source (i.e. file name), a line number and a column number. SourcePos is an instance of the Show, Eq and Ord class.

Instances

Instances details
Eq SourcePos 
Instance details

Defined in Text.Parsec.Pos

Data SourcePos 
Instance details

Defined in Text.Parsec.Pos

Methods

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

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

toConstr :: SourcePos -> Constr #

dataTypeOf :: SourcePos -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SourcePos 
Instance details

Defined in Text.Parsec.Pos

Show SourcePos 
Instance details

Defined in Text.Parsec.Pos