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

Safe HaskellNone
LanguageHaskell2010

Data.SCargot.Repr.WellFormed

Contents

Synopsis

WellFormedSExpr representation

data WellFormedSExpr atom Source

A well-formed s-expression is one which does not contain any dotted lists. This means that not every value of SExpr a can be converted to a WellFormedSExpr a, although the opposite is fine.

Constructors

WFSList [WellFormedSExpr atom] 
WFSAtom atom 

toWellFormed :: SExpr atom -> Either String (WellFormedSExpr atom) Source

This will be Nothing if the argument contains an improper list. It should hold that

toWellFormed (fromWellFormed x) == Right x

and also (more tediously) that

case toWellFormed x of
  Left _  -> True
  Right y -> x == fromWellFormed y

fromWellFormed :: WellFormedSExpr atom -> SExpr atom Source

Convert a WellFormedSExpr back into a SExpr.

Constructing and Deconstructing

cons :: WellFormedSExpr a -> WellFormedSExpr a -> Maybe (WellFormedSExpr a) Source

Combine the two-expressions into a new one. This will return Nothing if the resulting s-expression is not well-formed.

>>> cons (A "el") (L [A "eph", A "ant"])
Just (WFSList [WFSAtom "el",WFSAtom "eph",WFSAtom "ant"])
>>> cons (A "pachy") (A "derm"))
Nothing

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

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

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

Useful pattern synonyms

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

A shorter infix alias to grab the head and tail of a WFSList. This pattern is unidirectional, because it cannot be guaranteed that it is used to construct well-formed s-expressions; use the function "cons" instead.

>>> let sum (x ::: xs) = x + sum xs; sum Nil = 0

pattern L :: [WellFormedSExpr t] -> WellFormedSExpr t Source

A shorter alias for WFSList

>>> L [A "pachy", A "derm"]
WFSList [WFSAtom "pachy",WFSAtom "derm"]

pattern A :: t -> WellFormedSExpr t Source

A shorter alias for WFSAtom

>>> A "elephant"
WFSAtom "elephant"

pattern Nil :: WellFormedSExpr t Source

A shorter alias for WFSList []

>>> Nil
WFSList []

Useful processing functions

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

Utility function for parsing a pair of things.

>>> 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 :: (WellFormedSExpr t -> Either String a) -> WellFormedSExpr t -> Either String [a] Source

Utility function for parsing a list of things.

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

fromAtom :: WellFormedSExpr 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 :: ((WellFormedSExpr t, WellFormedSExpr t) -> Either String a) -> WellFormedSExpr 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 :: ([WellFormedSExpr t] -> Either String a) -> WellFormedSExpr 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 (A "pachyderm")
Left "asList: expected list; found atom"

isAtom :: Eq t => t -> WellFormedSExpr 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 :: WellFormedSExpr 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) -> WellFormedSExpr 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 :: ([(WellFormedSExpr t, WellFormedSExpr t)] -> Either String a) -> WellFormedSExpr 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"

car :: (WellFormedSExpr t -> Either String t') -> [WellFormedSExpr t] -> Either String t' Source

Run the parser on the first element of a Haskell list of WellFormedSExpr values, failing if the list is empty. This is useful in conjunction with the asList function.

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

Run the parser on all but the first element of a Haskell list of WellFormedSExpr values, failing if the list is empty. This is useful in conjunction with the asList function.