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

Safe HaskellNone
LanguageHaskell2010

Data.SCargot.Repr

Contents

Synopsis

Documentation

This module contains several different representations for s-expressions. The s-cargot library underlying uses the SExpr type as its representation type, which is a binary tree representation with an arbitrary type for its leaves.

This type is not always convenient to manipulate in Haskell code, this module defines two alternate representations which turn a sequence of nested right-branching cons pairs into Haskell lists: that is to say, they transform between

SCons a (SCons b (SCons c SNil))  <=>  RSList [a, b, c]

These two types differ in how they handle non-well-formed lists, i.e. lists that end with an atom. The RichSExpr format handles this with a special constructor for lists that end in an atom:

SCons a (SCons b (SAtom c))  <=>  RSDotted [a, b] c

On the other hand, the WellFormedSExpr type elects not to handle this case. This is unusual for Lisp source code, but is a reasonable choice for configuration or data storage formats that use s-expressions, where non-well-formed lists would be an unnecessary complication.

To make working with these types less verbose, there are other modules that export pattern aliases and helper functions: these can be found at Data.SCargot.Repr.Basic, Data.SCargot.Repr.Rich, and Data.SCargot.Repr.WellFormed.

data SExpr atom Source #

All S-Expressions can be understood as a sequence of cons cells (represented here by SCons), the empty list nil (represented by SNil) or an atom.

Constructors

SCons (SExpr atom) (SExpr atom) 
SAtom atom 
SNil 

Instances

Functor SExpr Source # 

Methods

fmap :: (a -> b) -> SExpr a -> SExpr b #

(<$) :: a -> SExpr b -> SExpr a #

Foldable SExpr Source # 

Methods

fold :: Monoid m => SExpr m -> m #

foldMap :: Monoid m => (a -> m) -> SExpr a -> m #

foldr :: (a -> b -> b) -> b -> SExpr a -> b #

foldr' :: (a -> b -> b) -> b -> SExpr a -> b #

foldl :: (b -> a -> b) -> b -> SExpr a -> b #

foldl' :: (b -> a -> b) -> b -> SExpr a -> b #

foldr1 :: (a -> a -> a) -> SExpr a -> a #

foldl1 :: (a -> a -> a) -> SExpr a -> a #

toList :: SExpr a -> [a] #

null :: SExpr a -> Bool #

length :: SExpr a -> Int #

elem :: Eq a => a -> SExpr a -> Bool #

maximum :: Ord a => SExpr a -> a #

minimum :: Ord a => SExpr a -> a #

sum :: Num a => SExpr a -> a #

product :: Num a => SExpr a -> a #

Traversable SExpr Source # 

Methods

traverse :: Applicative f => (a -> f b) -> SExpr a -> f (SExpr b) #

sequenceA :: Applicative f => SExpr (f a) -> f (SExpr a) #

mapM :: Monad m => (a -> m b) -> SExpr a -> m (SExpr b) #

sequence :: Monad m => SExpr (m a) -> m (SExpr a) #

IsList (SExpr atom) Source # 

Associated Types

type Item (SExpr atom) :: * #

Methods

fromList :: [Item (SExpr atom)] -> SExpr atom #

fromListN :: Int -> [Item (SExpr atom)] -> SExpr atom #

toList :: SExpr atom -> [Item (SExpr atom)] #

Eq atom => Eq (SExpr atom) Source # 

Methods

(==) :: SExpr atom -> SExpr atom -> Bool #

(/=) :: SExpr atom -> SExpr atom -> Bool #

Data atom => Data (SExpr atom) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SExpr atom -> c (SExpr atom) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SExpr atom) #

toConstr :: SExpr atom -> Constr #

dataTypeOf :: SExpr atom -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (SExpr atom)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SExpr atom)) #

gmapT :: (forall b. Data b => b -> b) -> SExpr atom -> SExpr atom #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SExpr atom -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SExpr atom -> r #

gmapQ :: (forall d. Data d => d -> u) -> SExpr atom -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SExpr atom -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SExpr atom -> m (SExpr atom) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SExpr atom -> m (SExpr atom) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SExpr atom -> m (SExpr atom) #

Read atom => Read (SExpr atom) Source # 

Methods

readsPrec :: Int -> ReadS (SExpr atom) #

readList :: ReadS [SExpr atom] #

readPrec :: ReadPrec (SExpr atom) #

readListPrec :: ReadPrec [SExpr atom] #

Show atom => Show (SExpr atom) Source # 

Methods

showsPrec :: Int -> SExpr atom -> ShowS #

show :: SExpr atom -> String #

showList :: [SExpr atom] -> ShowS #

IsString atom => IsString (SExpr atom) Source # 

Methods

fromString :: String -> SExpr atom #

type Item (SExpr atom) Source # 
type Item (SExpr atom) = SExpr atom

Rich SExpr 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 

Instances

Functor RichSExpr Source # 

Methods

fmap :: (a -> b) -> RichSExpr a -> RichSExpr b #

(<$) :: a -> RichSExpr b -> RichSExpr a #

Foldable RichSExpr Source # 

Methods

fold :: Monoid m => RichSExpr m -> m #

foldMap :: Monoid m => (a -> m) -> RichSExpr a -> m #

foldr :: (a -> b -> b) -> b -> RichSExpr a -> b #

foldr' :: (a -> b -> b) -> b -> RichSExpr a -> b #

foldl :: (b -> a -> b) -> b -> RichSExpr a -> b #

foldl' :: (b -> a -> b) -> b -> RichSExpr a -> b #

foldr1 :: (a -> a -> a) -> RichSExpr a -> a #

foldl1 :: (a -> a -> a) -> RichSExpr a -> a #

toList :: RichSExpr a -> [a] #

null :: RichSExpr a -> Bool #

length :: RichSExpr a -> Int #

elem :: Eq a => a -> RichSExpr a -> Bool #

maximum :: Ord a => RichSExpr a -> a #

minimum :: Ord a => RichSExpr a -> a #

sum :: Num a => RichSExpr a -> a #

product :: Num a => RichSExpr a -> a #

Traversable RichSExpr Source # 

Methods

traverse :: Applicative f => (a -> f b) -> RichSExpr a -> f (RichSExpr b) #

sequenceA :: Applicative f => RichSExpr (f a) -> f (RichSExpr a) #

mapM :: Monad m => (a -> m b) -> RichSExpr a -> m (RichSExpr b) #

sequence :: Monad m => RichSExpr (m a) -> m (RichSExpr a) #

IsList (RichSExpr atom) Source # 

Associated Types

type Item (RichSExpr atom) :: * #

Methods

fromList :: [Item (RichSExpr atom)] -> RichSExpr atom #

fromListN :: Int -> [Item (RichSExpr atom)] -> RichSExpr atom #

toList :: RichSExpr atom -> [Item (RichSExpr atom)] #

Eq atom => Eq (RichSExpr atom) Source # 

Methods

(==) :: RichSExpr atom -> RichSExpr atom -> Bool #

(/=) :: RichSExpr atom -> RichSExpr atom -> Bool #

Data atom => Data (RichSExpr atom) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RichSExpr atom -> c (RichSExpr atom) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RichSExpr atom) #

toConstr :: RichSExpr atom -> Constr #

dataTypeOf :: RichSExpr atom -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (RichSExpr atom)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RichSExpr atom)) #

gmapT :: (forall b. Data b => b -> b) -> RichSExpr atom -> RichSExpr atom #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RichSExpr atom -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RichSExpr atom -> r #

gmapQ :: (forall d. Data d => d -> u) -> RichSExpr atom -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RichSExpr atom -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RichSExpr atom -> m (RichSExpr atom) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RichSExpr atom -> m (RichSExpr atom) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RichSExpr atom -> m (RichSExpr atom) #

Read atom => Read (RichSExpr atom) Source # 
Show atom => Show (RichSExpr atom) Source # 

Methods

showsPrec :: Int -> RichSExpr atom -> ShowS #

show :: RichSExpr atom -> String #

showList :: [RichSExpr atom] -> ShowS #

IsString atom => IsString (RichSExpr atom) Source # 

Methods

fromString :: String -> RichSExpr atom #

type Item (RichSExpr atom) Source # 
type Item (RichSExpr atom) = RichSExpr 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.

Well-Formed SExpr 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 

Instances

Functor WellFormedSExpr Source # 

Methods

fmap :: (a -> b) -> WellFormedSExpr a -> WellFormedSExpr b #

(<$) :: a -> WellFormedSExpr b -> WellFormedSExpr a #

Foldable WellFormedSExpr Source # 

Methods

fold :: Monoid m => WellFormedSExpr m -> m #

foldMap :: Monoid m => (a -> m) -> WellFormedSExpr a -> m #

foldr :: (a -> b -> b) -> b -> WellFormedSExpr a -> b #

foldr' :: (a -> b -> b) -> b -> WellFormedSExpr a -> b #

foldl :: (b -> a -> b) -> b -> WellFormedSExpr a -> b #

foldl' :: (b -> a -> b) -> b -> WellFormedSExpr a -> b #

foldr1 :: (a -> a -> a) -> WellFormedSExpr a -> a #

foldl1 :: (a -> a -> a) -> WellFormedSExpr a -> a #

toList :: WellFormedSExpr a -> [a] #

null :: WellFormedSExpr a -> Bool #

length :: WellFormedSExpr a -> Int #

elem :: Eq a => a -> WellFormedSExpr a -> Bool #

maximum :: Ord a => WellFormedSExpr a -> a #

minimum :: Ord a => WellFormedSExpr a -> a #

sum :: Num a => WellFormedSExpr a -> a #

product :: Num a => WellFormedSExpr a -> a #

Traversable WellFormedSExpr Source # 

Methods

traverse :: Applicative f => (a -> f b) -> WellFormedSExpr a -> f (WellFormedSExpr b) #

sequenceA :: Applicative f => WellFormedSExpr (f a) -> f (WellFormedSExpr a) #

mapM :: Monad m => (a -> m b) -> WellFormedSExpr a -> m (WellFormedSExpr b) #

sequence :: Monad m => WellFormedSExpr (m a) -> m (WellFormedSExpr a) #

IsList (WellFormedSExpr atom) Source # 

Associated Types

type Item (WellFormedSExpr atom) :: * #

Eq atom => Eq (WellFormedSExpr atom) Source # 

Methods

(==) :: WellFormedSExpr atom -> WellFormedSExpr atom -> Bool #

(/=) :: WellFormedSExpr atom -> WellFormedSExpr atom -> Bool #

Data atom => Data (WellFormedSExpr atom) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WellFormedSExpr atom -> c (WellFormedSExpr atom) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WellFormedSExpr atom) #

toConstr :: WellFormedSExpr atom -> Constr #

dataTypeOf :: WellFormedSExpr atom -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (WellFormedSExpr atom)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WellFormedSExpr atom)) #

gmapT :: (forall b. Data b => b -> b) -> WellFormedSExpr atom -> WellFormedSExpr atom #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WellFormedSExpr atom -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WellFormedSExpr atom -> r #

gmapQ :: (forall d. Data d => d -> u) -> WellFormedSExpr atom -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WellFormedSExpr atom -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WellFormedSExpr atom -> m (WellFormedSExpr atom) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WellFormedSExpr atom -> m (WellFormedSExpr atom) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WellFormedSExpr atom -> m (WellFormedSExpr atom) #

Read atom => Read (WellFormedSExpr atom) Source # 
Show atom => Show (WellFormedSExpr atom) Source # 
IsString atom => IsString (WellFormedSExpr atom) Source # 
type Item (WellFormedSExpr atom) Source # 

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.