gdritter repos s-cargot / f5c0fe8
Working on Common Lisp repr Getty Ritter 9 years ago
2 changed file(s) with 58 addition(s) and 20 deletion(s). Collapse all Expand all
66
77 module Data.SCargot.CommonLisp where
88
9 data Atom
10 = Symbol Text
11 | String Text
12 | Integer Int
13 | True
9 data CLAtom
10 = CLSymbol Text
11 | CLString Text
12 | CLInteger Integer
13 | CLRatio Integer Integer
14 | CLFloat Double
1415 deriving (Eq, Show, Read)
1516
16 parseSexpr :: Text -> Either SExprError
17 type CommonLispSpec carrier = SExprSpec CLAtom carrier
18
19 withComments :: CommonLispSpec c -> CommonLispSpec c
20 withComments = addCommentType (const () <$> (char ';' *> restOfLine))
21
22 withQuote :: CommonLispSpec (SCons CLAtom) -> CommonLispSpec (SCons CLAtom)
23 withQuote = addReader '\'' (go <$> parse)
24 where go v = SCons q (SCons v SNil)
25
26 -- | Adds support for the '#(...)' sugar for vectors. (This will be
27 -- parsed as '(vector ...)', and
28 withVectors :: CommonLispSpec c -> CommonLispSpec c
29 withVectors = addReader '#' (go <$> parse)
30
31 parse :: CommonLispSpec c -> Text -> Either String c
32 serialize :: CommonLispSpec c -> c -> Text
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
217
318 import Control.Applicative
419 import Data.Attoparsec.Text
823 import Data.SCargot.Repr
924
1025 type ReaderMacroMap atom = Map Char (Reader atom)
26 type CommentMap = Map Char (Parser ())
1127 type Reader atom = (Parser (SExpr atom) -> Parser (SExpr atom))
1228 type Serializer atom = atom -> Text
1329
1430 -- | A 'SExprSpec' describes a parser and emitter for a particular
1531 -- variant of S-Expressions. The @atom@ type corresponds to a
1632 -- 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.
2036 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
2643 }
2744
2845 -- | This creates a basic 'SExprSpec' when given a parser and serializer
5370 addReader :: Char -> Reader a -> SExprSpec a c -> SExprSpec a c
5471 addReader c reader spec = spec { rmMap = insert c reader (rmMap spec) }
5572
73 addCommentType :: Char -> Comment -> SExprSpec a c -> SExprSpec a c
74 addCommentType c comment spec = spec { }
75
5676 quote :: atom -> Reader atom
5777 quote q parse = go <$> parse
5878 where go v = SCons q (SCons v SNil)
5979
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
6282
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
6585
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 '(' *>
6789
6890 -- |
6991 parseSExpr :: SExprSpec atom carrier -> Text -> Either String carrier