Copyright | © 2019 Vincent Archambault |
---|---|
License | 0BSD |
Maintainer | Vincent Archambault <archambault.v@gmail.com> |
Stability | experimental |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Definition of S-expression
Synopsis
- data SExpr b a
- type Sexp a = SExpr () a
- pattern A :: a -> SExpr b a
- pattern L :: [SExpr b a] -> SExpr b a
- pattern Sexp :: [Sexp a] -> Sexp a
- pattern (:::) :: SExpr b a -> SExpr b a -> SExpr b a
- pattern Nil :: SExpr b a
- isAtom :: SExpr b a -> Bool
- sAtom :: SExpr b a -> Maybe a
- isList :: SExpr b a -> Bool
- sList :: SExpr b a -> Maybe [SExpr b a]
Documentation
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.
Instances
Bifoldable SExpr Source # | |
Bifunctor SExpr Source # | |
Bitraversable SExpr Source # | |
Defined in Data.SExpresso.SExpr bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> SExpr a b -> f (SExpr c d) # | |
Foldable (SExpr b) Source # | |
Defined in Data.SExpresso.SExpr 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 # elem :: Eq a => a -> SExpr b a -> Bool # maximum :: Ord a => SExpr b a -> a # minimum :: Ord a => SExpr b a -> a # | |
Traversable (SExpr b) Source # | |
Functor (SExpr b) Source # | |
(Data b, Data a) => Data (SExpr b a) Source # | |
Defined in Data.SExpresso.SExpr 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 # | |
(Eq b, Eq a) => Eq (SExpr b a) Source # | |
Corecursive (SExpr b a) Source # | |
Defined in Data.SExpresso.SExpr 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 # | |
Recursive (SExpr b a) Source # | |
Defined in Data.SExpresso.SExpr 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 # | |
type Base (SExpr b a) Source # | |
Defined in Data.SExpresso.SExpr |
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 (:::) :: 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 :::