Added IsList instance for s-cargot lists
Getty Ritter
9 years ago
16 | 16 | import Text.Parsec.Char (satisfy) |
17 | 17 | import Text.Parsec.Text (Parser) |
18 | 18 | |
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. | |
19 | 25 | parseR5RSIdent :: Parser Text |
20 | 26 | parseR5RSIdent = |
21 | 27 | T.pack <$> ((:) <$> initial <*> many subsequent <|> peculiar) |
26 | 32 | hasCategory :: Char -> [GeneralCategory] -> Bool |
27 | 33 | hasCategory c cs = generalCategory c `elem` cs |
28 | 34 | |
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. | |
29 | 40 | parseR6RSIdent :: Parser Text |
30 | 41 | parseR6RSIdent = |
31 | 42 | T.pack <$> ((:) <$> initial <*> many subsequent <|> peculiar) |
54 | 65 | uniClass :: (Char -> Bool) -> Parser Char |
55 | 66 | uniClass sp = satisfy (\ c -> c > '\x7f' && sp c) |
56 | 67 | |
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. | |
57 | 74 | parseR7RSIdent :: Parser Text |
58 | 75 | parseR7RSIdent = T.pack <$> |
59 | 76 | ( (:) <$> initial <*> many subsequent |
1 | 1 | {-# LANGUAGE DeriveFunctor #-} |
2 | {-# LANGUAGE TypeFamilies #-} | |
2 | 3 | |
3 | 4 | module Data.SCargot.Repr |
4 | 5 | ( -- * Elementary SExpr representation |
13 | 14 | , fromWellFormed |
14 | 15 | ) where |
15 | 16 | |
16 |
|
|
17 | --import Data.String (IsString(..)) | |
18 | import GHC.Exts (IsList(..), IsString(..)) | |
17 | 19 | |
18 | 20 | -- | All S-Expressions can be understood as a sequence |
19 | 21 | -- of @cons@ cells (represented here by 'SCons'), the |
28 | 30 | instance IsString atom => IsString (SExpr atom) where |
29 | 31 | fromString = SAtom . fromString |
30 | 32 | |
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 | |
32 | 39 | -- level, and we'd rather have the lists themselves |
33 | 40 | -- exposed. In this case, we have 'RSList' to |
34 | 41 | -- represent a well-formed cons list, and 'RSDotted' |
47 | 54 | |
48 | 55 | instance IsString atom => IsString (RichSExpr atom) where |
49 | 56 | 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" | |
50 | 64 | |
51 | 65 | -- | It should always be true that |
52 | 66 | -- |
78 | 92 | | WFSAtom atom |
79 | 93 | deriving (Eq, Show, Read, Functor) |
80 | 94 | |
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 | ||
81 | 101 | instance IsString atom => IsString (WellFormedSExpr atom) where |
82 | 102 | fromString = WFSAtom . fromString |
83 | 103 |
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 | -} |