1 | |
module Data.SCargot.General where
|
| 1 |
module Data.SCargot.General
|
| 2 |
( -- * SExprSpec
|
| 3 |
SExprSpec
|
| 4 |
, mkSpec
|
| 5 |
, convertSpec
|
| 6 |
, addReader
|
| 7 |
, addCommentType
|
| 8 |
, asRich
|
| 9 |
, asWellFormed
|
| 10 |
-- * A Few Standard Reader Macros
|
| 11 |
, quote
|
| 12 |
, vector
|
| 13 |
-- * Using a SExprSpec
|
| 14 |
, parseSExpr
|
| 15 |
, serializeSExpr
|
| 16 |
) where
|
2 | 17 |
|
3 | 18 |
import Control.Applicative
|
4 | 19 |
import Data.Attoparsec.Text
|
|
8 | 23 |
import Data.SCargot.Repr
|
9 | 24 |
|
10 | 25 |
type ReaderMacroMap atom = Map Char (Reader atom)
|
| 26 |
type CommentMap = Map Char (Parser ())
|
11 | 27 |
type Reader atom = (Parser (SExpr atom) -> Parser (SExpr atom))
|
12 | 28 |
type Serializer atom = atom -> Text
|
13 | 29 |
|
14 | 30 |
-- | A 'SExprSpec' describes a parser and emitter for a particular
|
15 | 31 |
-- variant of S-Expressions. The @atom@ type corresponds to a
|
16 | 32 |
-- Haskell type used to represent the atoms, and the @carrier@
|
17 | |
-- type corresponds to the parsed S-Expression structure. This
|
18 | |
-- is deliberately opaque so that it must be constructed and
|
19 | |
-- modified with other helper functions.
|
| 33 |
-- type corresponds to the parsed S-Expression structure. The
|
| 34 |
-- 'SExprSpec' type is deliberately opaque so that it must be
|
| 35 |
-- constructed and modified with other helper functions.
|
20 | 36 |
data SExprSpec atom carrier = SExprSpec
|
21 | |
{ sesPAtom :: Parser atom
|
22 | |
, sesSAtom :: Serializer atom
|
23 | |
, rmMap :: ReaderMacroMap atom
|
24 | |
, postparse :: SExpr atom -> Either String carrier
|
25 | |
, preserial :: carrier -> SExpr atom
|
| 37 |
{ sesPAtom :: Parser atom
|
| 38 |
, sesSAtom :: Serializer atom
|
| 39 |
, readerMap :: ReaderMacroMap atom
|
| 40 |
, commentMap :: CommentMap
|
| 41 |
, postparse :: SExpr atom -> Either String carrier
|
| 42 |
, preserial :: carrier -> SExpr atom
|
26 | 43 |
}
|
27 | 44 |
|
28 | 45 |
-- | This creates a basic 'SExprSpec' when given a parser and serializer
|
|
53 | 70 |
addReader :: Char -> Reader a -> SExprSpec a c -> SExprSpec a c
|
54 | 71 |
addReader c reader spec = spec { rmMap = insert c reader (rmMap spec) }
|
55 | 72 |
|
| 73 |
addCommentType :: Char -> Comment -> SExprSpec a c -> SExprSpec a c
|
| 74 |
addCommentType c comment spec = spec { }
|
| 75 |
|
56 | 76 |
quote :: atom -> Reader atom
|
57 | 77 |
quote q parse = go <$> parse
|
58 | 78 |
where go v = SCons q (SCons v SNil)
|
59 | 79 |
|
60 | |
toRich :: SExprSpec a (SExpr b) -> SExprSpec a (RichSExpr b)
|
61 | |
toRich = convertSpec (return . toRich) fromRich
|
| 80 |
asRich :: SExprSpec a (SExpr b) -> SExprSpec a (RichSExpr b)
|
| 81 |
asRich = convertSpec (return . toRich) fromRich
|
62 | 82 |
|
63 | |
toWellFormed :: SExprSpec a (SExpr b) -> SExprSpec a (WellFormedSExpr b)
|
64 | |
toWellFormed = convertSpec toWellFormed fromWellFormed
|
| 83 |
asWellFormed :: SExprSpec a (SExpr b) -> SExprSpec a (WellFormedSExpr b)
|
| 84 |
asWellFormed = convertSpec toWellFormed fromWellFormed
|
65 | 85 |
|
66 | |
parseGenericSExpr :: Parser atom -> ReaderMacroMap atom -> Parser (SExpr atom)
|
| 86 |
parseGenericSExpr :: Parser atom -> ReaderMacroMap atom -> CommentMap -> Parser (SExpr atom)
|
| 87 |
parseGenericSExpr atom reader comment =
|
| 88 |
char '(' *>
|
67 | 89 |
|
68 | 90 |
-- |
|
69 | 91 |
parseSExpr :: SExprSpec atom carrier -> Text -> Either String carrier
|