gdritter repos s-cargot / 6b055f0
Big example + some detail on the pattern aliases Getty Ritter 9 years ago
1 changed file(s) with 83 addition(s) and 0 deletion(s). Collapse all Expand all
8282 Left "Found atom in cdr position"
8383 ~~~~
8484
85 These names and patterns can be quite long, so S-Cargot also exports
86 several pattern synonyms that can be used both as expressions and
87 in pattern-matches to make working with these types less verbose.
88 These are each contained in their own module, as their names conflict
89 with each other, so it's recommended to only import the type that
90 you plan on working with:
91
92 ~~~~.haskell
93 *Data.SCargot.Repr.Basic> A 2 ::: A 3 ::: A 4 ::: Nil
94 SCons (SCons (SCons (SAtom 2) (SAtom 3)) (SAtom 4)) SNil
95 ~~~~
96
97 ~~~~.haskell
98 *Data.SCargot.Repr.WellFormed> L [A 1,A 2,A 3]
99 WFSList [WFSAtom 1,WFSAtom 2,WFSAtom 3]
100 *Data.SCargot.Repr.WellFormed> let sexprSum (L xs) = sum (map sexprSum xs); sexprSum (A n) = n
101 *Data.SCargot.Repr Data.SCargot.Repr.WellFormed> :t sexprSum
102 sexprSum :: Num a => WellFormedSExpr a -> a
103 *Data.SCargot.Repr.WellFormed> sexprSum (L [A 2, L [A 3, A 4]])
104 9
105 ~~~~
106
85107 ## Atom Types
86108
87109 Any type can serve as an underlying atom type provided that it has
142164
143165 ~~~~.haskell
144166 import Data.Char (isDigit)
167 import Data.SCargot.General
145168 import Data.Text (Text)
146169 import qualified Data.Text as T
170
147171
148172 data Expr = Add Expr Expr | Num Int deriving (Eq, Show)
149173
240264 *Data.SCargot.General> decode (asRich (vec mySpec)) "(1 [2 3])"
241265 Right [RSList [RSAtom "1",RSList [RSAtom "2",RSAtom "3"]]]
242266 ~~~~
267
268 ## Putting It All Together
269
270 Here is a final example which implements a limited arithmetic language
271 with Haskell-style line comments and a special reader to understand hex
272 literals:
273
274 ~~~~.haskell
275 data Op = Add | Sub | Mul
276 data Atom = AOp Op | ANum Int
277 data Expr = EOp Op Expr Expr | ENum Int deriving (Eq, Show)
278
279 -- Conversions for our Expr type
280 toExpr :: SExpr Atom -> Either String Expr
281 toExpr (A (AOp op) ::: l ::: r ::: Nil) = EOp op <$> l <*> r
282 toExpr (A (ANum n)) = pure (ENum n)
283 toExpr sexpr = Left ("Invalid parse: " ++ show sexpr)
284
285 fromExpr :: Expr -> SExpr Atom
286 fromExpr (EOp op l r) = A (AOp op) ::: fromExpr l ::: fromExpr r ::: Nil
287 fromExpr (ENum n) = ANum n
288
289 -- Parser and serializer for our Atom type
290 pAtom :: Parser Atom
291 pAtom = ((ANum . read . T.unpack) <$> takeWhile1 isDigit)
292 <|> (char "+" *> pure (AOp Add))
293 <|> (char "-" *> pure (AOp Sub))
294 <|> (char "*" *> pure (AOp Mul))
295
296 sAtom :: Atom -> Text
297 sAtom (AOp Add) = "+"
298 sAtom (AOp Sub) = "-"
299 sAtom (AOp Mul) = "*"
300 sAtom (ANum n) = T.pack (show n)
301
302 -- Our comment syntax
303 hsComment :: Parser ()
304 hsComment = string "--" >> takeWhile (/= '\n') >> return ()
305
306 -- Our custom reader macro
307 hexReader :: Reader Atom
308 hexReader _ = (Num . readHex . T.unpack) <$> takeWhile1 isHexDigit
309 where isHexDigit c = isDigit c || c `elem` "AaBbCcDdEeFf"
310 rd = readHex . head . fst
311
312 -- Our final s-expression family
313 myLangSpec :: SExprSpec Atom Expr
314 myLangSpec
315 = setComment hsComment -- set comment syntax to be Haskell-style
316 $ addReader '#' hexReader -- add hex reader
317 $ convertSpec toExpr fromExpr -- convert final repr to Expr
318 $ mkSpec pAtom sAtom -- create spec with Atom type
319 ~~~~
320
321 Keep in mind that you often won't need to write all this by hand,
322 as you can often use a variety of built-in atom types, reader
323 macros, comment types, and representations, but it's a useful
324 illustration of all the options that are available to you should
325 you need them!