| Copyright | (c) Daan Leijen 1999-2001, (c) Paolo Martini 2007 | 
|---|---|
| License | BSD-style (see the LICENSE file) | 
| Maintainer | [email protected] | 
| Stability | provisional | 
| Portability | non-portable (uses local universal quantification: PolymorphicComponents) | 
| Safe Haskell | Safe | 
| Language | Haskell98 | 
Text.Parsec.Token
Description
A helper module to parse lexical elements (tokens). See makeTokenParser
 for a description of how to use it.
- type LanguageDef st = GenLanguageDef String st Identity
- data GenLanguageDef s u m = LanguageDef {- commentStart :: String
- commentEnd :: String
- commentLine :: String
- nestedComments :: Bool
- identStart :: ParsecT s u m Char
- identLetter :: ParsecT s u m Char
- opStart :: ParsecT s u m Char
- opLetter :: ParsecT s u m Char
- reservedNames :: [String]
- reservedOpNames :: [String]
- caseSensitive :: Bool
 
- type TokenParser st = GenTokenParser String st Identity
- data GenTokenParser s u m = TokenParser {- identifier :: ParsecT s u m String
- reserved :: String -> ParsecT s u m ()
- operator :: ParsecT s u m String
- reservedOp :: String -> ParsecT s u m ()
- charLiteral :: ParsecT s u m Char
- stringLiteral :: ParsecT s u m String
- natural :: ParsecT s u m Integer
- integer :: ParsecT s u m Integer
- float :: ParsecT s u m Double
- naturalOrFloat :: ParsecT s u m (Either Integer Double)
- decimal :: ParsecT s u m Integer
- hexadecimal :: ParsecT s u m Integer
- octal :: ParsecT s u m Integer
- symbol :: String -> ParsecT s u m String
- lexeme :: forall a. ParsecT s u m a -> ParsecT s u m a
- whiteSpace :: ParsecT s u m ()
- parens :: forall a. ParsecT s u m a -> ParsecT s u m a
- braces :: forall a. ParsecT s u m a -> ParsecT s u m a
- angles :: forall a. ParsecT s u m a -> ParsecT s u m a
- brackets :: forall a. ParsecT s u m a -> ParsecT s u m a
- squares :: forall a. ParsecT s u m a -> ParsecT s u m a
- semi :: ParsecT s u m String
- comma :: ParsecT s u m String
- colon :: ParsecT s u m String
- dot :: ParsecT s u m String
- semiSep :: forall a. ParsecT s u m a -> ParsecT s u m [a]
- semiSep1 :: forall a. ParsecT s u m a -> ParsecT s u m [a]
- commaSep :: forall a. ParsecT s u m a -> ParsecT s u m [a]
- commaSep1 :: forall a. ParsecT s u m a -> ParsecT s u m [a]
 
- makeTokenParser :: Stream s m Char => GenLanguageDef s u m -> GenTokenParser s u m
Documentation
type LanguageDef st = GenLanguageDef String st Identity Source #
data GenLanguageDef s u m Source #
The GenLanguageDef type is a record that contains all parameterizable
 features of the Text.Parsec.Token module. The module Text.Parsec.Language
 contains some default definitions.
Constructors
| LanguageDef | |
| Fields 
 | |
type TokenParser st = GenTokenParser String st Identity Source #
data GenTokenParser s u m Source #
The type of the record that holds lexical parsers that work on
 s streams with state u over a monad m.
Constructors
| TokenParser | |
| Fields 
 | |
makeTokenParser :: Stream s m Char => GenLanguageDef s u m -> GenTokenParser s u m Source #
The expression makeTokenParser language creates a GenTokenParser
 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 GenTokenParser.
 module Main where
 import Text.Parsec
 import qualified Text.Parsec.Token as P
 import Text.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
 ...