| Safe Haskell | None | 
|---|
Text.ParserCombinators.UU.Demo.Examples
Description
This module contains a lot of examples of the typical use of our parser combinator library. 
   We strongly encourage you to take a look at the source code.
   At the end you find a mainrun
- type Parser a = P (Str Char String LineColPos) a
- justamessage :: [Char]
- show_demos :: IO ()
- run :: Show t => Parser t -> String -> IO ()
- run' :: (Show a, Show a1, ListLike s a) => P (Str a s LineColPos) a1 -> s -> IO ()
- pa :: Parser String
- pb :: Parser String
- pc :: Parser String
- lift :: t -> [t]
- (<++>) :: Parser String -> Parser String -> Parser String
- pa2 :: Parser String
- pa3 :: Parser String
- paz :: Parser String
- wfp :: Parser Int
- test11 :: IO ()
- expr :: Parser Int
- operators :: Integral a => [[(Char, a -> a -> a)]]
- same_prio :: (Eq b, Show b, ListLike state b, IsLocationUpdatedBy loc b) => [(b, a)] -> P (Str b state loc) a
- test16 :: IO ()
- ident :: P (Str Char String LineColPos) [Char]
- idents :: P (Str Char String LineColPos) [[Char]]
- pKey :: [Char] -> P (Str Char String LineColPos) [Char]
- spaces :: Parser String
- takes_second_alt :: P (Str Char String LineColPos) [[Char]]
- test13 :: IO ()
- test14 :: IO ()
- pManyTill :: P st a -> P st b -> P st [a]
- simpleComment :: (ListLike state Char, IsLocationUpdatedBy loc Char) => P (Str Char state loc) [Char]
- string :: (IsLocationUpdatedBy loc Char, ListLike state Char) => String -> P (Str Char state loc) String
- pVarId :: (ListLike state Char, IsLocationUpdatedBy loc Char) => P (Str Char state loc) [Char]
- pConId :: (ListLike state Char, IsLocationUpdatedBy loc Char) => P (Str Char state loc) [Char]
- pIdChar :: (ListLike state Char, IsLocationUpdatedBy loc Char) => P (Str Char state loc) Char
- pAnyToken :: (IsLocationUpdatedBy loc Char, ListLike state Char) => [String] -> P (Str Char state loc) String
- pIntList :: Parser [Int]
- parseIntString :: Parser [String]
- demo :: Show r => String -> String -> P (Str Char String LineColPos) r -> IO ()
Documentation
justamessage :: [Char]Source
show_demos :: IO ()Source
Running the function show_demos should give the following output:
>>>run pa "a"Result: "a"
>>>run pa ""Result: "a" Correcting steps: Inserted 'a' at position LineColPos 0 0 0 expecting 'a'
>>>run pa "b"Result: "a" Correcting steps: Deleted 'b' at position LineColPos 0 0 0 expecting 'a' Inserted 'a' at position LineColPos 0 1 1 expecting 'a'
>>>run ((++) <$> pa <*> pa) "bbab"Result: "aa" Correcting steps: Deleted 'b' at position LineColPos 0 0 0 expecting 'a' Deleted 'b' at position LineColPos 0 1 1 expecting 'a' Deleted 'b' at position LineColPos 0 3 3 expecting 'a' Inserted 'a' at position LineColPos 0 4 4 expecting 'a'
>>>run pa "ba"Result: "a" Correcting steps: Deleted 'b' at position LineColPos 0 0 0 expecting 'a'
>>>run pa "aa"Result: "a" Correcting steps: The token 'a' was not consumed by the parsing process.
>>>run (pCount pa :: Parser Int) "aaa"Result: 3
>>>run (do {l <- pCount pa; pExact l pb}) "aaacabbbbb"Result: ["b","b","b","b"] Correcting steps: Deleted 'c' at position LineColPos 0 3 3 expecting one of ['b', 'a'] The token 'b' was not consumed by the parsing process.
>>>run (amb ( (++) <$> pa2 <*> pa3 <|> (++) <$> pa3 <*> pa2)) "aaaaa"Result: ["aaaaa","aaaaa"]
>>>run (pList pLower) "doaitse"Result: "doaitse"
>>>run paz "abc2ez"Result: "abcez" Correcting steps: Deleted '2' at position LineColPos 0 3 3 expecting 'a'..'z'
>>>run (max <$> pParens ((+1) <$> wfp) <*> wfp `opt` 0) "((()))()(())"Result: 3
>>>run (pa <|> pb <?> justamessage) "c"Result: "b" Correcting steps: Deleted 'c' at position LineColPos 0 0 0 expecting justamessage Inserted 'b' at position LineColPos 0 1 1 expecting 'b'
>>>run (amb (pEither parseIntString pIntList)) "(123;456;789)"Result: [Left ["123","456","789"],Right [123,456,789]]
run :: Show t => Parser t -> String -> IO ()Source
The fuction run
Our first two parsers are simple; one recognises a single a character and the other one a single b. Since we will use them later we 
   convert the recognised character into String so they can be easily combined.
The applicative style makes it very easy to merge recogition and computing a result. 
   As an example we parse a sequence of nested well formed parentheses pairs and
   compute the maximum nesting depth with wfp
It is very easy to recognise infix expressions with any number of priorities and operators:
 operators       = [[('+', (+)), ('-', (-))],  [('*' , (*))], [('^', (^))]]
 same_prio  ops  = msum [ op <$ pSym c | (c, op) <- ops]
 expr            = foldr pChainl ( pNatural <|> pParens expr) (map same_prio operators) -- 
which we can call:
run expr "15-3*5+2^5"
Result: 32
Note that also here correction takes place:
run expr "2 + + 3 5"
 Result: 37
 Correcting steps: 
    Deleted  ' ' at position 1 expecting one of ['0'..'9', '^', '*', '-', '+']
    Deleted  ' ' at position 3 expecting one of ['(', '0'..'9']
    Inserted '0' at position 4 expecting '0'..'9'
    Deleted  ' ' at position 5 expecting one of ['(', '0'..'9']
    Deleted  ' ' at position 7 expecting one of ['0'..'9', '^', '*', '-', '+']
same_prio :: (Eq b, Show b, ListLike state b, IsLocationUpdatedBy loc b) => [(b, a)] -> P (Str b state loc) aSource
A common case where ambiguity arises is when we e.g. want to recognise identifiers, 
   but only those which are not keywords. 
   The combinator micro inserts steps with a specfied cost in the result 
   of the parser which can be used to disambiguate:
 
 ident ::  Parser String
 ident = ((:) <$> pSym ('a','z') <*> pMunch (\x -> 'a' <= x && x <= 'z') `micro` 2) <* spaces
 idents = pList1 ident
 pKey keyw = pToken keyw `micro` 1 <* spaces
 spaces :: Parser String
 spaces = pMunch (==' ')
 takes_second_alt =   pList ident 
                \<|> (\ c t e -> ["IfThenElse"] ++  c   ++  t  ++  e) 
                    \<$ pKey "if"   <*> pList_ng ident 
                    \<* pKey "then" <*> pList_ng ident
                    \<* pKey "else" <*> pList_ng ident  
A keyword is followed by a small cost 1, which makes sure that 
  identifiers which have a keyword as a prefix win over the keyword. Identifiers are however
   followed by a cost 2, with as result that in this case the keyword wins. 
   Note that a limitation of this approach is that keywords are only recognised as such when expected!
test13 = run takes_second_alt "if a then if else c" test14 = run takes_second_alt "ifx a then if else c"
with results for test13 and test14:
Result: ["IfThenElse","a","if","c"] Result: ["ifx","a","then","if", "else","c"]
A mistake which is made quite often is to construct  a parser which can recognise a sequence of elements using one of the 
  derived combinators (say pList
run (pList spaces) "" Result: *** Exception: The combinator pList requires that it's argument cannot recognise the empty string
run (pMaybe spaces) " " Result: *** Exception: The combinator pMaybe requires that it's argument cannot recognise the empty string
takes_second_alt :: P (Str Char String LineColPos) [[Char]]Source
simpleComment :: (ListLike state Char, IsLocationUpdatedBy loc Char) => P (Str Char state loc) [Char]Source
string :: (IsLocationUpdatedBy loc Char, ListLike state Char) => String -> P (Str Char state loc) StringSource
pVarId :: (ListLike state Char, IsLocationUpdatedBy loc Char) => P (Str Char state loc) [Char]Source
pConId :: (ListLike state Char, IsLocationUpdatedBy loc Char) => P (Str Char state loc) [Char]Source