A Sexpr is an S-expressionin the style of Rivest's Canonical S-expressions. Atoms may be of any type, but String and ByteString have special support. Rivest's implementation of S-expressions is unusual in supporting MIME type hints for each atom. See http:people.csail.mit.edurivestSexp.txt
- data Sexpr s
- isAtom :: Sexpr a -> Bool
- isList :: Sexpr a -> Bool
- atom :: a -> Sexpr a
- list :: [Sexpr a] -> Sexpr a
- unAtom :: Sexpr s -> s
- unList :: Sexpr s -> [Sexpr s]
- hintedAtom :: String -> a -> Sexpr a
- hint :: Sexpr a -> Maybe String
- defaultHint :: String
- isTokenChar :: Char -> Bool
- isInitialTokenChar :: Char -> Bool
- isQuoteableChar :: Char -> Bool
- fold :: (Sexpr t -> Sexpr t) -> Sexpr t -> Sexpr t
- canonicalString :: Sexpr String -> String
- basicString :: Sexpr String -> String
- advancedString :: Sexpr String -> String
- canonical :: Sexpr String -> ShowS
- basic :: Sexpr String -> Doc
- advanced :: Sexpr String -> Doc
- putCanonical :: Sexpr String -> Put
- putCanonicalBS :: Sexpr ByteString -> Put
- readSexpr :: Read a => String -> Sexpr a
- readSexprString :: String -> Sexpr String
- readCanonicalSexprString :: String -> Sexpr String
- advancedSexpr :: ReadP (Sexpr String)
- canonicalSexpr :: ReadP (Sexpr String)
Basics
Functor Sexpr | The |
Foldable Sexpr | |
Traversable Sexpr | |
Eq s => Eq (Sexpr s) | |
Read s => Read (Sexpr s) | |
Show (Sexpr String) | |
Show s => Show (Sexpr s) | |
Arbitrary a => Arbitrary (Sexpr a) |
isAtom :: Sexpr a -> BoolSource
A predicate for identifying atoms, whether or not they have explicit hints.
unList :: Sexpr s -> [Sexpr s]Source
Extract the sub-S-expressions of a List. If all you intend to do is traverse or map over that list, the Functor instance of S-expressions may work just fine.
Hinted Atoms
hintedAtom :: String -> a -> Sexpr aSource
Construct an atom with a MIME type hint.
hintedAtom
defaultHint
== atom
hint :: Sexpr a -> Maybe StringSource
Extract the hint of an atom. Lists do not have hints, but all atoms have hints.
Any atom whose hint is not specified is assumed to be text/plain; charset=iso-8859-1. This is that default value.
Character predicates to support encoding
isTokenChar :: Char -> BoolSource
Tokens may internally contain any of the characters legitimate to begin tokens, or any numeral.
isInitialTokenChar :: Char -> BoolSource
Tokens may begin with any alphabetic character or the characters
in -./_:*+=
;
isQuoteableChar :: Char -> BoolSource
Only token characters and spaces don't need to be escaped when shown in the quoted syntax.
Transformations
fold :: (Sexpr t -> Sexpr t) -> Sexpr t -> Sexpr tSource
fold f s
applies f to each sub-S-expression of s, from each leaf
to the root. f
need not preserve the shape of s
, in contrast
to the shape-preserving Traversable
instance.
String printers
basicString :: Sexpr String -> StringSource
ShowS printers
Doc pretty printers
Put binary printers
putCanonical :: Sexpr String -> PutSource
Parsers
canonicalSexpr :: ReadP (Sexpr String)Source
For some applications it is wise to accept only very carefully specified input. This is useful when you know you are receiving exactly a Canonical S-Expression. It will read only a Canonical S-expression (and optional terminating NUL), but not the Basic or Advanced encodings.