Copyright | (c) Dennis Gosnell 2016 |
---|---|
License | BSD-style (see LICENSE file) |
Maintainer | cdep.illabout@gmail.com |
Stability | experimental |
Portability | POSIX |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- testString1 :: String
- testString2 :: String
- expressionParse :: String -> [Expr]
- parseExpr :: String -> (Expr, String)
- parseExprs :: String -> ([Expr], String)
- parseCSep :: Char -> String -> ([[Expr]], String)
- parseStringLit :: String -> (String, String)
- parseCharLit :: String -> (String, String)
- parseNumberLit :: Char -> String -> (String, String)
- parseOther :: String -> (String, String)
Documentation
testString1 :: String Source #
testString1
and testString2
are convenient to use in GHCi when playing
around with how parsing works.
testString2 :: String Source #
See testString1
.
expressionParse :: String -> [Expr] Source #
parseExprs :: String -> ([Expr], String) Source #
Parse multiple expressions.
>>>
parseExprs "Just 'a'"
([Other "Just ",CharLit "a"],"")
Handle escaped characters correctly
>>>
parseExprs $ "Foo \"hello \\\"world!\""
([Other "Foo ",StringLit "hello \\\"world!"],"")>>>
parseExprs $ "'\\''"
([CharLit "\\'"],"")
parseStringLit :: String -> (String, String) Source #
Parse string literals until a trailing double quote.
>>>
parseStringLit "foobar\" baz"
("foobar"," baz")
Keep literal back slashes:
>>>
parseStringLit "foobar\\\" baz\" after"
("foobar\\\" baz"," after")
parseCharLit :: String -> (String, String) Source #
Parse character literals until a trailing single quote.
>>>
parseCharLit "a' foobar"
("a"," foobar")
Keep literal back slashes:
>>>
parseCharLit "\\'' hello"
("\\'"," hello")
parseNumberLit :: Char -> String -> (String, String) Source #
Parses integers and reals, like 123
and 45.67
.
To be more precise, any numbers matching the regex \d+(\.\d+)?
should
get parsed by this function.
>>>
parseNumberLit '3' "456hello world []"
("3456","hello world []")>>>
parseNumberLit '0' ".12399880 foobar"
("0.12399880"," foobar")
parseOther :: String -> (String, String) Source #
This function consumes input, stopping only when it hits a special
character or a digit. However, if the digit is in the middle of a
Haskell-style identifier (e.g. foo123
), then keep going
anyway.
This is almost the same as the function
parseOtherSimple = span $ \c -> notElem c ("{[()]}\"," :: String) && not (isDigit c) && (c /= '\'')
except parseOther
ignores digits and single quotes that appear in
Haskell-like identifiers.
>>>
parseOther "hello world []"
("hello world ","[]")>>>
parseOther "hello234 world"
("hello234 world","")>>>
parseOther "hello 234 world"
("hello ","234 world")>>>
parseOther "hello{[ 234 world"
("hello","{[ 234 world")>>>
parseOther "H3110 World"
("H3110 World","")>>>
parseOther "Node' (Leaf' 1) (Leaf' 2)"
("Node' ","(Leaf' 1) (Leaf' 2)")>>>
parseOther "I'm One"
("I'm One","")>>>
parseOther "I'm 2"
("I'm ","2")