Copyright | (c) 2008 Utrecht University |
---|---|
License | All rights reserved |
Maintainer | stefan@cs.uu.nl |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell98 |
CCO.Lexing
Description
A library of lexer combinators that expose their functionality through an
Applicative
interface.
- data Lexer a
- satisfy :: (Char -> Bool) -> Lexer Char
- message :: String -> Lexer a
- anyChar :: Lexer Char
- anyCharFrom :: [Char] -> Lexer Char
- anyCharBut :: [Char] -> Lexer Char
- range :: (Char, Char) -> Lexer Char
- notInRange :: (Char, Char) -> Lexer Char
- char :: Char -> Lexer Char
- string :: String -> Lexer String
- space :: Lexer Char
- lower :: Lexer Char
- upper :: Lexer Char
- letter :: Lexer Char
- alpha :: Lexer Char
- alphaNum :: Lexer Char
- digit :: Lexer Char
- digit_ :: Lexer Int
- binDigit :: Lexer Char
- binDigit_ :: Lexer Int
- octDigit :: Lexer Char
- octDigit_ :: Lexer Int
- hexDigit :: Lexer Char
- hexDigit_ :: Lexer Int
- ignore :: Lexer a -> Lexer b
- data LexicalUnit a
- data Symbols a = Symbols Source [LexicalUnit a]
- lex :: Lexer a -> Source -> String -> Symbols a
- tokens :: Symbols a -> [(SourcePos, a)]
- tokens_ :: Symbols a -> [a]
Lexers
Type of lexers that produce tokens of type a
.
Instances
satisfy :: (Char -> Bool) -> Lexer Char Source
A Lexer
that recognises any character that satisfies a specified
predicate.
Derived lexers
anyCharFrom :: [Char] -> Lexer Char Source
A Lexer
that recognises any character that appears in a given list.
anyCharBut :: [Char] -> Lexer Char Source
A Lexer
that recognises any character that does not appear in a given
list.
range :: (Char, Char) -> Lexer Char Source
A Lexer
that recognises any character that appears in a given range.
More efficent than \(low, up) -> anyCharFrom [low .. up]
.
notInRange :: (Char, Char) -> Lexer Char Source
A Lexer
that recognises any character that does not appear in a given
range.
Ignoring recognised input
ignore :: Lexer a -> Lexer b Source
Produces a Lexer
that recognises the same inputs as a given underlying
Lexer
, but that does not result in any tokenisation.
The input recognised by a Lexer
constructed with ignore
is simply
ignored when the Lexer
is used to turn a stream of characters into a
stream of LexicalUnit
s.
Mainly used to suppress the generation of tokens for lexemes that constitute-- lexical units like comments and whitespace.
Symbols
data LexicalUnit a Source
The type of lexical units.
Constructors
Token a Pos String String | A tokenised lexeme: its token, its position, the characters it consists of, and its its trailing characters in the input stream. |
Error Pos String String | An invalid lexeme: its position, the characters it consists of, and its trailing characters in the input stream. |
Msg String Pos String String | An invalid lexeme, labeled by a custom error message: the message, its position, the characters it consists of, and its trailing characters in the input stream. |
The type of streams of symbols described by tokens of type a
.
Constructors
Symbols Source [LexicalUnit a] |