HaTeX-3.17.3.0: The Haskell LaTeX library.

Safe HaskellSafe
LanguageHaskell2010

Text.LaTeX.Base.Parser

Contents

Description

The LaTeX parser.

Use parseLaTeX to parse a Text containing LaTeX code. If the Text is in a file, you may want to use parseLaTeXFile. Use this module together with Text.LaTeX.Base.Syntax to perform analysis and transformations of LaTeX code. The parser (parseLaTeX) is related with the renderer (render) by the following property:

If t :: Text is a syntactically valid LaTeX block, then:

fmap render (parseLaTeX t) == Right t

This property says two things:

  • Given a valid LaTeX input, parseLaTeX returns a LaTeX value.
  • If the parsed value is again rendered, you get the initial input.

In other words, parseLaTeX is a partial function defined over the set of valid LaTeX files, and render is its left inverse.

Synopsis

The parser

parseLaTeX :: Text -> Either ParseError LaTeX Source #

Parse a Text sequence as a LaTeX block. If it fails, it returns an error string.

parseLaTeXFile :: FilePath -> IO (Either ParseError LaTeX) Source #

Read a file and parse it as LaTeX.

Parsing errors

data ParseError :: * #

The abstract data type ParseError represents parse errors. It provides the source position (SourcePos) of the error and a list of error messages (Message). A ParseError can be returned by the function parse. ParseError is an instance of the Show and Eq classes.

errorPos :: ParseError -> SourcePos #

Extracts the source position from the parse error

errorMessages :: ParseError -> [Message] #

Extracts the list of error messages from the parse error

Error messages

data Message :: * #

This abstract data type represents parse error messages. There are four kinds of messages:

 data Message = SysUnExpect String
              | UnExpect String
              | Expect String
              | Message String

The fine distinction between different kinds of parse errors allows the system to generate quite good error messages for the user. It also allows error messages that are formatted in different languages. Each kind of message is generated by different combinators:

  • A SysUnExpect message is automatically generated by the satisfy combinator. The argument is the unexpected input.
  • A UnExpect message is generated by the unexpected combinator. The argument describes the unexpected item.
  • A Expect message is generated by the <?> combinator. The argument describes the expected item.
  • A Message message is generated by the fail combinator. The argument is some general parser message.

messageString :: Message -> String #

Extract the message string from an error message

Source positions

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

Eq SourcePos 
Data SourcePos 

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 :: (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 
Show SourcePos 

sourceLine :: SourcePos -> Line #

Extracts the line number from a source position.

sourceColumn :: SourcePos -> Column #

Extracts the column number from a source position.

sourceName :: SourcePos -> SourceName #

Extracts the name of the source from a source position.

Configuring your parser

data ParserConf Source #

Configuration for the LaTeX parser.

Constructors

ParserConf 

Fields

defaultParserConf :: ParserConf Source #

Default parser configuration, used by parseLaTeX and parseLaTeXFile.

Defaults:

verbatimEnvironments = ["verbatim"]

Parser combinators

type Parser = Parsec Text ParserConf Source #

Parser with Text input and ParserConf environment.

latexBlockParser :: Parser LaTeX Source #

Parser of a single LaTeX constructor, no appending blocks.