Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data HaskLikeAtom
- haskLikeParser :: SExprParser HaskLikeAtom (SExpr HaskLikeAtom)
- haskLikePrinter :: SExprPrinter HaskLikeAtom (SExpr HaskLikeAtom)
- locatedHaskLikeParser :: SExprParser (Located HaskLikeAtom) (SExpr (Located HaskLikeAtom))
- locatedHaskLikePrinter :: SExprPrinter (Located HaskLikeAtom) (SExpr (Located HaskLikeAtom))
- parseHaskellString :: Parser Text
- parseHaskellFloat :: Parser Double
- parseHaskellInt :: Parser Integer
Documentation
This module is intended for simple, ad-hoc configuration or data
formats that might not need their on rich structure but might benefit
from a few various kinds of literals. The haskLikeParser
understands
identifiers as defined by R5RS, as well as string, integer, and
floating-point literals as defined by the Haskell 2010 spec. It does
not natively understand other data types, such as booleans,
vectors, bitstrings.
data HaskLikeAtom Source #
An atom type that understands Haskell-like values as well as Scheme-like identifiers.
HSIdent Text | An identifier, parsed according to the R5RS Scheme standard |
HSString Text | A string, parsed according to the syntax for string literals in the Haskell report |
HSInt Integer | An arbitrary-sized integer value, parsed according to the syntax for integer literals in the Haskell report |
HSFloat Double | A double-precision floating-point value, parsed according to the syntax for floats in the Haskell report |
haskLikeParser :: SExprParser HaskLikeAtom (SExpr HaskLikeAtom) Source #
This SExprParser
understands s-expressions that contain
Scheme-like tokens, as well as string literals, integer
literals, and floating-point literals. Each of these values
is parsed according to the lexical rules in the Haskell
report, so the same set of string escapes, numeric bases,
and floating-point options are available. This spec does
not parse comments and does not understand any reader
macros.
>>>
decode haskLikeParser "(0x01 \"\\x65lephant\")"
Right [SCons (SAtom (HSInt 1)) (SCons (SAtom (HSString "elephant")) SNil)]
haskLikePrinter :: SExprPrinter HaskLikeAtom (SExpr HaskLikeAtom) Source #
This SExprPrinter
emits s-expressions that contain Scheme-like
tokens as well as string literals, integer literals, and floating-point
literals, which will be emitted as the literals produced by Haskell's
show
function. This printer will produce a flat s-expression with
no indentation of any kind.
>>>
encode haskLikePrinter [L [A (HSInt 1), A (HSString "elephant")]]
"(1 \"elephant\")"
locatedHaskLikeParser :: SExprParser (Located HaskLikeAtom) (SExpr (Located HaskLikeAtom)) Source #
A haskLikeParser
which produces Located
values
>>>
decode locatedHaskLikeParser $ pack "(0x01 \"\\x65lephant\")"
Right [SCons (SAtom (At (Span (line 1, column 2) (line 1, column 6)) (HSInt 1))) (SCons (SAtom (At (Span (line 1, column 7) (line 1, column 20)) (HSString "elephant"))) SNil)]
>>>
decode locatedHaskLikeParser $ pack "(1 elephant)"
Right [SCons (SAtom (At (Span (line 1, column 2) (line 1, column 3)) (HSInt 1))) (SCons (SAtom (At (Span (line 1, column 4) (line 1, column 12)) (HSIdent "elephant"))) SNil)]
locatedHaskLikePrinter :: SExprPrinter (Located HaskLikeAtom) (SExpr (Located HaskLikeAtom)) Source #
A SExprPrinter
for Located
values. Works exactly like haskLikePrinter
It ignores the location tags when printing the result.
>>>
let (Right dec) = decode locatedHaskLikeParser $ pack "(1 elephant)"
[SCons (SAtom (At (Span (line 1, column 2) (line 1, column 3)) (HSInt 1))) (SCons (SAtom (At (Span (line 1, column 4) (line 1, column 12)) (HSIdent "elephant"))) SNil)]
>>>
encode locatedHaskLikePrinter dec
"(1 elephant)"
Individual Parsers
parseHaskellString :: Parser Text Source #
Parse a Haskell string literal as defined by the Haskell 2010 language specification.
parseHaskellFloat :: Parser Double Source #
Parse a Haskell floating-point number as defined by the Haskell 2010 language specification.
parseHaskellInt :: Parser Integer Source #
Parse a Haskell integer literal as defined by the Haskell 2010 language specification.