Copyright | (c) 1999 - 2004 Wolfgang Lux 2012 - 2013 Björn Peemöller 2016 Jan Tikovsky |
---|---|
License | BSD-3-clause |
Maintainer | bjp@informatik.uni-kiel.de |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
This module provides the basic types and combinators to implement the lexers. The combinators use continuation passing code in a monadic style.
The first argument of the continuation function is the current span, and the second is the string to be parsed. The third argument is a flag which signals the lexer that it is lexing the beginning of a line and therefore has to check for layout tokens. The fourth argument is a stack of indentations that is used to handle nested layout groups.
Synopsis
- class (Ord s, Show s) => Symbol s where
- type Indent = Int
- type Context = [Indent]
- type P a = Span -> String -> Bool -> Context -> CYM a
- type CYM a = CYT Identity a
- type SuccessP s a = Span -> s -> P a
- type FailP a = Span -> String -> P a
- type Lexer s a = SuccessP s a -> FailP a -> P a
- parse :: P a -> FilePath -> String -> CYM a
- applyLexer :: Symbol s => Lexer s [(Span, s)] -> P [(Span, s)]
- returnP :: a -> P a
- thenP :: P a -> (a -> P b) -> P b
- thenP_ :: P a -> P b -> P b
- failP :: Span -> String -> P a
- warnP :: Span -> String -> P a -> P a
- liftP :: (a -> b) -> P a -> P b
- closeP0 :: P a -> P (P a)
- closeP1 :: (a -> P b) -> P (a -> P b)
- pushContext :: Indent -> P a -> P a
- popContext :: P a -> P a
- convertSignedIntegral :: Num a => a -> String -> a
- convertSignedFloating :: Fractional a => String -> String -> Int -> a
- convertIntegral :: Num a => a -> String -> a
- convertFloating :: Fractional a => String -> String -> Int -> a
Types
class (Ord s, Show s) => Symbol s where Source #
Type class for symbols
= Span | Current source code span |
-> String |
|
-> Bool | Flag whether the beginning of a line should be parsed, which requires layout checking |
-> Context | context as a stack of |
-> CYM a |
Basic lexer function
Monadic functions
thenP :: P a -> (a -> P b) -> P b infixl 1 Source #
Apply the first lexer and then apply the second one, based on the result of the first lexer.
thenP_ :: P a -> P b -> P b infixl 1 Source #
Apply the first lexer and then apply the second one, ignoring the first result.
closeP0 :: P a -> P (P a) Source #
Lift a lexer into the P
monad, returning the lexer when evaluated.
closeP1 :: (a -> P b) -> P (a -> P b) Source #
Lift a lexer-generating function into the P
monad, returning the
function when evaluated.
Combinators for layout handling
pushContext :: Indent -> P a -> P a Source #
Push an Indent
to the context, increasing the levels of indentation
popContext :: P a -> P a Source #
Pop an Indent
from the context, decreasing the levels of indentation
Conversion of numbers
convertSignedIntegral :: Num a => a -> String -> a Source #
Convert a String into a signed intergral using a given base
convertSignedFloating :: Fractional a => String -> String -> Int -> a Source #
Convert a mantissa, a fraction part and an exponent into a signed floating value
convertIntegral :: Num a => a -> String -> a Source #
Convert a String into an unsigned intergral using a given base
convertFloating :: Fractional a => String -> String -> Int -> a Source #
Convert a mantissa, a fraction part and an exponent into an unsigned floating value