gdritter repos s-cargot / d51c85a
Added IsList instance for s-cargot lists Getty Ritter 8 years ago
3 changed file(s) with 39 addition(s) and 37 deletion(s). Collapse all Expand all
1616 import Text.Parsec.Char (satisfy)
1717 import Text.Parsec.Text (Parser)
1818
19 -- | Parse an identifier according to the R5RS Scheme standard. This
20 -- will not normalize case, even though the R5RS standard specifies
21 -- that all identifiers be normalized to lower case first.
22 --
23 -- An R5RS identifier is, broadly speaking, alphabetic or numeric
24 -- and may include various symbols, but no escapes.
1925 parseR5RSIdent :: Parser Text
2026 parseR5RSIdent =
2127 T.pack <$> ((:) <$> initial <*> many subsequent <|> peculiar)
2632 hasCategory :: Char -> [GeneralCategory] -> Bool
2733 hasCategory c cs = generalCategory c `elem` cs
2834
35 -- | Parse an identifier according to the R6RS Scheme standard. An
36 -- R6RS identifier may include inline hexadecimal escape sequences
37 -- so that, for example, 'foo' is equivalent to 'f\x6f;o', and is
38 -- more liberal than R5RS as to which Unicode characters it may
39 -- accept.
2940 parseR6RSIdent :: Parser Text
3041 parseR6RSIdent =
3142 T.pack <$> ((:) <$> initial <*> many subsequent <|> peculiar)
5465 uniClass :: (Char -> Bool) -> Parser Char
5566 uniClass sp = satisfy (\ c -> c > '\x7f' && sp c)
5667
68 -- | Parse an identifier according to the R7RS Scheme standard. An
69 -- R7RS identifier, in addition to a typical identifier format,
70 -- can also be a chunk of text surrounded by vertical bars that
71 -- can contain spaces and other characters. Unlike R6RS, it does
72 -- not allow escapes to be included in identifiers that are not
73 -- surrounded by vertical bars.
5774 parseR7RSIdent :: Parser Text
5875 parseR7RSIdent = T.pack <$>
5976 ( (:) <$> initial <*> many subsequent
11 {-# LANGUAGE DeriveFunctor #-}
2 {-# LANGUAGE TypeFamilies #-}
23
34 module Data.SCargot.Repr
45 ( -- * Elementary SExpr representation
1314 , fromWellFormed
1415 ) where
1516
16 import Data.String (IsString(..))
17 --import Data.String (IsString(..))
18 import GHC.Exts (IsList(..), IsString(..))
1719
1820 -- | All S-Expressions can be understood as a sequence
1921 -- of @cons@ cells (represented here by 'SCons'), the
2830 instance IsString atom => IsString (SExpr atom) where
2931 fromString = SAtom . fromString
3032
31 -- | Sometimes, the cons-based interface is too low
33 instance IsList (SExpr atom) where
34 type Item (SExpr atom) = SExpr atom
35 fromList = foldr SCons SNil
36 toList = undefined
37
38 -- | sometimes, the cons-based interface is too low
3239 -- level, and we'd rather have the lists themselves
3340 -- exposed. In this case, we have 'RSList' to
3441 -- represent a well-formed cons list, and 'RSDotted'
4754
4855 instance IsString atom => IsString (RichSExpr atom) where
4956 fromString = RSAtom . fromString
57
58 instance IsList (RichSExpr atom) where
59 type Item (RichSExpr atom) = RichSExpr atom
60 fromList = RSList
61 toList (RSList xs) = xs
62 toList (RSDotted {}) = error "Unable to turn dotted list into haskell list"
63 toList (RSAtom {}) = error "Unable to turn atom into Haskell list"
5064
5165 -- | It should always be true that
5266 --
7892 | WFSAtom atom
7993 deriving (Eq, Show, Read, Functor)
8094
95 instance IsList (WellFormedSExpr atom) where
96 type Item (WellFormedSExpr atom) = WellFormedSExpr atom
97 fromList = WFSList
98 toList (WFSList xs) = xs
99 toList (WFSAtom {}) = error "Unable to turn atom into Haskell list"
100
81101 instance IsString atom => IsString (WellFormedSExpr atom) where
82102 fromString = WFSAtom . fromString
83103
+0
-35
Data/SCargot/Tutorial.hs less more
1 {-| The "s-cargot" library attempts to be as general as possible, and
2 to support a wide range of use-cases for s-expressions. It is built
3 around a core of primitives which are then exposed in various
4 ways, and can be easily and flexibly extended. This tutorial
5 describes particular use-cases, and then shows how to adapt this
6 library to that use-case.
7 -}
8
9 module Data.SCargot.Tutorial
10 ( -- * Basic Usage and Organization
11 -- $usage
12 -- * Building a Custom Config Format
13 -- $config
14 -- * Analyzing Scheme code
15 -- $scheme
16 -- * Building a Custom Lisp
17 -- $lisp
18 ) where
19
20 {- $usage
21 When people talk about s-expressions, they're really talking about
22 a _family_ of formats that have in common a rough structure and
23 the fact that -}
24
25 {- $config
26
27 -}
28
29 {- $scheme
30
31 -}
32
33 {- $lisp
34
35 -}