sexpresso-1.2.1.0: A flexible library for parsing and printing S-expression
Copyright© 2019 Vincent Archambault
License0BSD
MaintainerVincent Archambault <archambault.v@gmail.com>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Data.SExpresso.SExpr

Description

Definition of S-expression

Synopsis

Documentation

data SExpr b a Source #

The datatype SExpr is the definition of an S-expression for the library S-expresso.

The parameter a allows you to specify the datatype of atoms and the parameter b is usefull for keeping metadata about S-expression like source position for example.

Constructors

SList b [SExpr b a] 
SAtom a 

Instances

Instances details
Bitraversable SExpr Source # 
Instance details

Defined in Data.SExpresso.SExpr

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> SExpr a b -> f (SExpr c d) #

Bifoldable SExpr Source # 
Instance details

Defined in Data.SExpresso.SExpr

Methods

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

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> SExpr a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> SExpr a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> SExpr a b -> c #

Bifunctor SExpr Source # 
Instance details

Defined in Data.SExpresso.SExpr

Methods

bimap :: (a -> b) -> (c -> d) -> SExpr a c -> SExpr b d #

first :: (a -> b) -> SExpr a c -> SExpr b c #

second :: (b -> c) -> SExpr a b -> SExpr a c #

Functor (SExpr b) Source # 
Instance details

Defined in Data.SExpresso.SExpr

Methods

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

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

Foldable (SExpr b) Source # 
Instance details

Defined in Data.SExpresso.SExpr

Methods

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

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

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

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

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

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

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

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

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

toList :: SExpr b a -> [a] #

null :: SExpr b a -> Bool #

length :: SExpr b a -> Int #

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

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

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

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

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

Traversable (SExpr b) Source # 
Instance details

Defined in Data.SExpresso.SExpr

Methods

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

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

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

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

(Eq b, Eq a) => Eq (SExpr b a) Source # 
Instance details

Defined in Data.SExpresso.SExpr

Methods

(==) :: SExpr b a -> SExpr b a -> Bool #

(/=) :: SExpr b a -> SExpr b a -> Bool #

(Data b, Data a) => Data (SExpr b a) Source # 
Instance details

Defined in Data.SExpresso.SExpr

Methods

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

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

toConstr :: SExpr b a -> Constr #

dataTypeOf :: SExpr b a -> DataType #

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

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

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

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

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

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

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

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

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

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

(Show b, Show a) => Show (SExpr b a) Source # 
Instance details

Defined in Data.SExpresso.SExpr

Methods

showsPrec :: Int -> SExpr b a -> ShowS #

show :: SExpr b a -> String #

showList :: [SExpr b a] -> ShowS #

Recursive (SExpr b a) Source # 
Instance details

Defined in Data.SExpresso.SExpr

Methods

project :: SExpr b a -> Base (SExpr b a) (SExpr b a) #

cata :: (Base (SExpr b a) a0 -> a0) -> SExpr b a -> a0 #

para :: (Base (SExpr b a) (SExpr b a, a0) -> a0) -> SExpr b a -> a0 #

gpara :: (Corecursive (SExpr b a), Comonad w) => (forall b0. Base (SExpr b a) (w b0) -> w (Base (SExpr b a) b0)) -> (Base (SExpr b a) (EnvT (SExpr b a) w a0) -> a0) -> SExpr b a -> a0 #

prepro :: Corecursive (SExpr b a) => (forall b0. Base (SExpr b a) b0 -> Base (SExpr b a) b0) -> (Base (SExpr b a) a0 -> a0) -> SExpr b a -> a0 #

gprepro :: (Corecursive (SExpr b a), Comonad w) => (forall b0. Base (SExpr b a) (w b0) -> w (Base (SExpr b a) b0)) -> (forall c. Base (SExpr b a) c -> Base (SExpr b a) c) -> (Base (SExpr b a) (w a0) -> a0) -> SExpr b a -> a0 #

Corecursive (SExpr b a) Source # 
Instance details

Defined in Data.SExpresso.SExpr

Methods

embed :: Base (SExpr b a) (SExpr b a) -> SExpr b a #

ana :: (a0 -> Base (SExpr b a) a0) -> a0 -> SExpr b a #

apo :: (a0 -> Base (SExpr b a) (Either (SExpr b a) a0)) -> a0 -> SExpr b a #

postpro :: Recursive (SExpr b a) => (forall b0. Base (SExpr b a) b0 -> Base (SExpr b a) b0) -> (a0 -> Base (SExpr b a) a0) -> a0 -> SExpr b a #

gpostpro :: (Recursive (SExpr b a), Monad m) => (forall b0. m (Base (SExpr b a) b0) -> Base (SExpr b a) (m b0)) -> (forall c. Base (SExpr b a) c -> Base (SExpr b a) c) -> (a0 -> Base (SExpr b a) (m a0)) -> a0 -> SExpr b a #

type Base (SExpr b a) Source # 
Instance details

Defined in Data.SExpresso.SExpr

type Base (SExpr b a)

type Sexp a = SExpr () a Source #

The type synonym Sexp is a variant of the more general SExpr datatype with no data for the SList constructor.

pattern A :: a -> SExpr b a Source #

Shorthand for SAtom.

foo (A x) = x -- Equivalent to foo (SAtom x) = x
 a = A 3      -- Equivalent to a = SAtom 3

pattern L :: [SExpr b a] -> SExpr b a Source #

Pattern for matching only the sublist of the SList constructor. See also the Sexp pattern synonym.

foo (L xs) = xs -- Equivalent to foo (SList _ xs) = xs

pattern Sexp :: [Sexp a] -> Sexp a Source #

Bidirectional pattern synonym for the type synonym Sexp. See also the L pattern synonym.

foo (Sexp x) = x -- Equivalent to foo (SList () x) = x
s = Sexp []      -- Equivalent to s = SList () []

pattern (:::) :: SExpr b a -> SExpr b a -> SExpr b a infixr 5 Source #

Pattern specifying the shape of the sublist of the SList constructor. See also Nil.

Although it aims to mimic the behavior of the cons (:) constructor for list, this pattern behavior is a little bit different. Indeed its signature is SExpr b a -> SExpr b a -> SExpr b a while the cons (:) constructor signature is a -> [a] -> [a]. The first argument type is different in the case of the cons constructor but all the types are identical for the pattern :::.

This implies that the following code

foo (x ::: xs) = ...

is equivalent to

foo (SList b (x : rest)) = let xs = SList b rest
                           in ...

If you wish for the xs above to match the remaining of the list, you need to use the L pattern

foo (A x ::: L xs)

which is equivalent to

foo (SList b (x : rest)) = let (SList _ xs) = SList b rest
                           in ...

Other examples :

foo (A x1 ::: A x2 ::: Nil)   -- Equivalent to foo (SList _ [SAtom x1, SAtom x2])
foo (L ys ::: A x ::: L xs)   -- Equivalent to foo (SList _ (SList _ ys : SAtom x : xs))

pattern Nil :: SExpr b a Source #

Pattern to mark the end of the list when using the pattern synonym :::

isAtom :: SExpr b a -> Bool Source #

The isAtom function returns True iff its argument is of the form SAtom _.

sAtom :: SExpr b a -> Maybe a Source #

The sAtom function returns Nothing if its argument is of the form SList _ _ and Just a if its argument is of the form SAtom _..

isList :: SExpr b a -> Bool Source #

The isList function returns True iff its argument is of the form SList _ _.

sList :: SExpr b a -> Maybe [SExpr b a] Source #

The sList function returns Nothing if its argument is of the form SAtom _ and the sublist xs if its argument is of the form SList _ xs.