Copyright | (c) Daan Leijen 1999-2001 |
---|---|
License | BSD-style (see the file libraries/parsec/LICENSE) |
Maintainer | Antoine Latter <aslatter@gmail.com> |
Stability | provisional |
Portability | non-portable (uses existentially quantified data constructors) |
Safe Haskell | Safe |
Language | Haskell98 |
Text.ParserCombinators.Parsec.Token
Description
A helper module to parse lexical elements (tokens).
- data LanguageDef st = LanguageDef {
- commentStart :: String
- commentEnd :: String
- commentLine :: String
- nestedComments :: Bool
- identStart :: CharParser st Char
- identLetter :: CharParser st Char
- opStart :: CharParser st Char
- opLetter :: CharParser st Char
- reservedNames :: [String]
- reservedOpNames :: [String]
- caseSensitive :: Bool
- data TokenParser st = TokenParser {
- identifier :: CharParser st String
- reserved :: String -> CharParser st ()
- operator :: CharParser st String
- reservedOp :: String -> CharParser st ()
- charLiteral :: CharParser st Char
- stringLiteral :: CharParser st String
- natural :: CharParser st Integer
- integer :: CharParser st Integer
- float :: CharParser st Double
- naturalOrFloat :: CharParser st (Either Integer Double)
- decimal :: CharParser st Integer
- hexadecimal :: CharParser st Integer
- octal :: CharParser st Integer
- symbol :: String -> CharParser st String
- lexeme :: forall a. CharParser st a -> CharParser st a
- whiteSpace :: CharParser st ()
- parens :: forall a. CharParser st a -> CharParser st a
- braces :: forall a. CharParser st a -> CharParser st a
- angles :: forall a. CharParser st a -> CharParser st a
- brackets :: forall a. CharParser st a -> CharParser st a
- squares :: forall a. CharParser st a -> CharParser st a
- semi :: CharParser st String
- comma :: CharParser st String
- colon :: CharParser st String
- dot :: CharParser st String
- semiSep :: forall a. CharParser st a -> CharParser st [a]
- semiSep1 :: forall a. CharParser st a -> CharParser st [a]
- commaSep :: forall a. CharParser st a -> CharParser st [a]
- commaSep1 :: forall a. CharParser st a -> CharParser st [a]
- makeTokenParser :: LanguageDef st -> TokenParser st
Documentation
data LanguageDef st Source
The LanguageDef
type is a record that contains all parameterizable
features of the Token
module. The module
Language
contains some default definitions.
Constructors
LanguageDef | |
Fields
|
data TokenParser st Source
The type of the record that holds lexical parsers.
Constructors
TokenParser | |
Fields
|
makeTokenParser :: LanguageDef st -> TokenParser st Source
The expression makeTokenParser language
creates a TokenParser
record that contains lexical parsers that are
defined using the definitions in the language
record.
The use of this function is quite stylized - one imports the
appropiate language definition and selects the lexical parsers that
are needed from the resulting TokenParser
.
module Main where import Text.ParserCombinators.Parsec import qualified Text.ParserCombinators.Parsec.Token as P import Text.ParserCombinators.Parsec.Language (haskellDef) -- The parser ... expr = parens expr <|> identifier <|> ... -- The lexer lexer = P.makeTokenParser haskellDef parens = P.parens lexer braces = P.braces lexer identifier = P.identifier lexer reserved = P.reserved lexer ...