parsec2-1.0.0: Monadic parser combinators

Portabilitynon-portable (uses non-portable module Text.ParserCombinators.Parsec.Token)
Stabilityprovisional
MaintainerAntoine Latter <aslatter@gmail.com>

Text.ParserCombinators.Parsec.Language

Description

A helper module that defines some language definitions that can be used to instantiate a token parser (see Text.ParserCombinators.Parsec.Token).

Synopsis

Documentation

haskellDef :: LanguageDef stSource

The language definition for the Haskell language.

haskell :: TokenParser stSource

A lexer for the haskell language.

mondrianDef :: LanguageDef stSource

The language definition for the language Mondrian.

mondrian :: TokenParser stSource

A lexer for the mondrian language.

haskellStyle :: LanguageDef stSource

This is a minimal token definition for Haskell style languages. It defines the style of comments, valid identifiers and case sensitivity. It does not define any reserved words or operators.

javaStyle :: LanguageDef stSource

This is a minimal token definition for Java style languages. It defines the style of comments, valid identifiers and case sensitivity. It does not define any reserved words or operators.

data LanguageDef st Source

The LanguageDef type is a record that contains all parameterizable features of the Text.ParserCombinators.Parsec.Token module. The module Text.ParserCombinators.Parsec.Language contains some default definitions.

Constructors

LanguageDef 

Fields

commentStart :: String

Describes the start of a block comment. Use the empty string if the language doesn't support block comments. For example "/*".

commentEnd :: String

Describes the end of a block comment. Use the empty string if the language doesn't support block comments. For example "*/".

commentLine :: String

Describes the start of a line comment. Use the empty string if the language doesn't support line comments. For example "//".

nestedComments :: Bool

Set to True if the language supports nested block comments.

identStart :: CharParser st Char

This parser should accept any start characters of identifiers. For example letter <|> char "_".

identLetter :: CharParser st Char

This parser should accept any legal tail characters of identifiers. For example alphaNum <|> char "_".

opStart :: CharParser st Char

This parser should accept any start characters of operators. For example oneOf ":!#$%&*+./<=>?@\\^|-~"

opLetter :: CharParser st Char

This parser should accept any legal tail characters of operators. Note that this parser should even be defined if the language doesn't support user-defined operators, or otherwise the reservedOp parser won't work correctly.

reservedNames :: [String]

The list of reserved identifiers.

reservedOpNames :: [String]

The list of reserved operators.

caseSensitive :: Bool

Set to True if the language is case sensitive.