s-cargot-0.1.1.1: A flexible, extensible s-expression library.

Safe HaskellNone
LanguageHaskell2010

Data.SCargot.Repr.Rich

Contents

Synopsis

RichSExpr representation

data RichSExpr atom Source

Sometimes the cons-based interface is too low level, and we'd rather have the lists themselves exposed. In this case, we have RSList to represent a well-formed cons list, and RSDotted to represent an improper list of the form (a b c . d). This representation is based on the structure of the parsed S-Expression, and not on how it was originally represented: thus, (a . (b)) is going to be represented as RSList[RSAtom a, RSAtom b] despite having been originally represented as a dotted list.

Constructors

RSList [RichSExpr atom] 
RSDotted [RichSExpr atom] atom 
RSAtom atom 

toRich :: SExpr atom -> RichSExpr atom Source

It should always be true that

fromRich (toRich x) == x

and that

toRich (fromRich x) == x

fromRich :: RichSExpr atom -> SExpr atom Source

This follows the same laws as toRich.

Constructing and Deconstructing

cons :: RichSExpr a -> RichSExpr a -> RichSExpr a Source

Combine the two s-expressions into a new one.

>>> cons (A "el") (L [A "eph", A "ant"])
L [A "el",A "eph",A "ant"]

uncons :: RichSExpr a -> Maybe (RichSExpr a, RichSExpr a) Source

Produce the head and tail of the s-expression (if possible).

>>> uncons (L [A "el", A "eph", A "ant"])
Just (A "el",L [A "eph",A "ant"])

Useful pattern synonyms

pattern (:::) :: RichSExpr a -> RichSExpr a -> RichSExpr a Source

A shorter infix alias to grab the head and tail of an RSList.

>>> A "one" ::: L [A "two", A "three"]
RSList [RSAtom "one",RSAtom "two",RSAtom "three"]

pattern A :: a -> RichSExpr a Source

A shorter alias for RSAtom

>>> A "elephant"
RSAtom "elephant"

pattern L :: [RichSExpr a] -> RichSExpr a Source

A shorter alias for RSList

>>> L [A "pachy", A "derm"]
RSList [RSAtom "pachy",RSAtom "derm"]

pattern DL :: [RichSExpr a] -> a -> RichSExpr a Source

A shorter alias for RSDotted

>>> DL [A "pachy"] "derm"
RSDotted [RSAtom "pachy"] "derm"

pattern Nil :: RichSExpr a Source

A shorter alias for RSList []

>>> Nil
RSList []

Lenses

_car :: Applicative f => (RichSExpr a -> f (RichSExpr a)) -> RichSExpr a -> f (RichSExpr a) Source

A traversal with access to the first element of a pair.

>>> import Lens.Family
>>> set _car (A "elephant") (L [A "one", A "two", A "three"])
L [A "elelphant",A "two",A "three"]
>>> set _car (L [A "two", A "three"]) (DL [A "one"] "elephant")
DL [L[A "two",A "three"]] "elephant"

_cdr :: Applicative f => (RichSExpr a -> f (RichSExpr a)) -> RichSExpr a -> f (RichSExpr a) Source

A traversal with access to the second element of a pair. Using this to modify an s-expression may result in changing the constructor used, changing a list to a dotted list or vice versa.

>>> import Lens.Family
>>> set _cdr (A "elephant") (L [A "one", A "two", A "three"])
DL [A "one"] "elephant"
>>> set _cdr (L [A "two", A "three"]) (DL [A "one"] "elephant")
L [A "one",A "two",A "three"]

Useful processing functions

fromPair :: (RichSExpr t -> Either String a) -> (RichSExpr t -> Either String b) -> RichSExpr t -> Either String (a, b) Source

Utility function for parsing a pair of things: this parses a two-element list, and not a cons pair.

>>> fromPair (isAtom "pachy") (asAtom return) (L [A "pachy", A "derm"])
Right ((), "derm")
>>> fromPair (isAtom "pachy") fromAtom (L [A "pachy"])
Left "Expected two-element list"

fromList :: (RichSExpr t -> Either String a) -> RichSExpr t -> Either String [a] Source

Utility function for parsing a proper list of things.

>>> fromList fromAtom (L [A "this", A "that", A "the-other"])
Right ["this","that","the-other"]
>>> fromList fromAtom (DL [A "this", A "that"] "the-other"])
Left "asList: expected proper list; found dotted list"

fromAtom :: RichSExpr t -> Either String t Source

Utility function for parsing a single atom

>>> fromAtom (A "elephant")
Right "elephant"
>>> fromAtom (L [A "elephant"])
Left "fromAtom: expected atom; found list"

asPair :: ((RichSExpr t, RichSExpr t) -> Either String a) -> RichSExpr t -> Either String a Source

Parses a two-element list using the provided function.

>>> let go (A l) (A r) = return (l ++ r); go _ _ = Left "expected atoms"
>>> asPair go (L [A "pachy", A "derm"])
Right "pachyderm"
>>> asPair go (L [A "elephant"])
Left "asPair: expected two-element list; found list of length 1"

asList :: ([RichSExpr t] -> Either String a) -> RichSExpr t -> Either String a Source

Parse an arbitrary-length list using the provided function.

>>> let go xs = concat <$> mapM fromAtom xs
>>> asList go (L [A "el", A "eph", A "ant"])
Right "elephant"
>>> asList go (DL [A "el", A "eph"] "ant")
Left "asList: expected list; found dotted list"

isAtom :: Eq t => t -> RichSExpr t -> Either String () Source

Match a given literal atom, failing otherwise.

>>> isAtom "elephant" (A "elephant")
Right ()
>>> isAtom "elephant" (L [A "elephant"])
Left "isAtom: expected atom; found list"

isNil :: RichSExpr t -> Either String () Source

Match an empty list, failing otherwise.

>>> isNil (L [])
Right ()
>>> isNil (A "elephant")
Left "isNil: expected nil; found atom"

asAtom :: (t -> Either String a) -> RichSExpr t -> Either String a Source

Parse an atom using the provided function.

>>> import Data.Char (toUpper)
>>> asAtom (return . map toUpper) (A "elephant")
Right "ELEPHANT"
>>> asAtom (return . map toUpper) (L [])
Left "asAtom: expected atom; found list"

asAssoc :: ([(RichSExpr t, RichSExpr t)] -> Either String a) -> RichSExpr t -> Either String a Source

Parse an assoc-list using the provided function.

>>> let def (x, y) = do { a <- fromAtom x; b <- fromAtom y; return (a ++ ": " ++ b) }
>>> let defList xs = do { defs <- mapM def xs; return (unlines defs) }
>>> asAssoc defList (L [ L [A "legs", A "four"], L [ A "trunk", A "one"] ])
Right "legs: four\ntrunk: one\n"
>>> asAssoc defList (L [ L [A "legs", A "four"], L [ A "elephant"] ])
Left "asAssoc: expected pair; found list of length 1"

cdr :: ([RichSExpr t] -> Either String t') -> [RichSExpr t] -> Either String t' Source