sexp-grammar-2.0.0: Invertible grammar combinators for S-expressions

Safe HaskellNone
LanguageHaskell2010

Language.Sexp

Contents

Synopsis

Parse and print

decode :: ByteString -> Either String Sexp Source #

Deserialise a Sexp from a string

decodeMany :: ByteString -> Either String [Sexp] Source #

Deserialise potentially multiple Sexp from a string

encode :: Sexp -> ByteString Source #

Serialise a Sexp into a compact string

format :: Sexp -> ByteString Source #

Serialise a Sexp into a pretty-printed string

Type

pattern Atom :: Atom -> Sexp Source #

pattern Number :: Scientific -> Sexp Source #

pattern Symbol :: Text -> Sexp Source #

pattern String :: Text -> Sexp Source #

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

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

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

pattern Modified :: Prefix -> Sexp -> Sexp Source #

Internal types

data SexpF e Source #

S-expression functor

Constructors

AtomF !Atom 
ParenListF [e] 
BracketListF [e] 
BraceListF [e] 
ModifiedF !Prefix e 

Instances

Functor SexpF Source # 

Methods

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

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

Foldable SexpF Source # 

Methods

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

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

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

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

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

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

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

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

toList :: SexpF a -> [a] #

null :: SexpF a -> Bool #

length :: SexpF a -> Int #

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

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

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

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

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

Traversable SexpF Source # 

Methods

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

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

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

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

Eq1 SexpF Source # 

Methods

liftEq :: (a -> b -> Bool) -> SexpF a -> SexpF b -> Bool #

Generic (SexpF e) Source # 

Associated Types

type Rep (SexpF e) :: * -> * #

Methods

from :: SexpF e -> Rep (SexpF e) x #

to :: Rep (SexpF e) x -> SexpF e #

NFData (Fix (Compose * * (LocatedBy Position) SexpF)) Source # 

Methods

rnf :: Fix (Compose * * (LocatedBy Position) SexpF) -> () #

NFData (Fix SexpF) Source # 

Methods

rnf :: Fix SexpF -> () #

type Rep (SexpF e) Source # 

data Atom Source #

S-expression atom type

Instances

Eq Atom Source # 

Methods

(==) :: Atom -> Atom -> Bool #

(/=) :: Atom -> Atom -> Bool #

Ord Atom Source # 

Methods

compare :: Atom -> Atom -> Ordering #

(<) :: Atom -> Atom -> Bool #

(<=) :: Atom -> Atom -> Bool #

(>) :: Atom -> Atom -> Bool #

(>=) :: Atom -> Atom -> Bool #

max :: Atom -> Atom -> Atom #

min :: Atom -> Atom -> Atom #

Show Atom Source # 

Methods

showsPrec :: Int -> Atom -> ShowS #

show :: Atom -> String #

showList :: [Atom] -> ShowS #

Generic Atom Source # 

Associated Types

type Rep Atom :: * -> * #

Methods

from :: Atom -> Rep Atom x #

to :: Rep Atom x -> Atom #

NFData Atom Source # 

Methods

rnf :: Atom -> () #

type Rep Atom Source # 
type Rep Atom = D1 * (MetaData "Atom" "Language.Sexp.Types" "sexp-grammar-2.0.0-7H6WbiqRhQHGwWvTncrSQw" False) ((:+:) * (C1 * (MetaCons "AtomNumber" PrefixI False) (S1 * (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 * Scientific))) ((:+:) * (C1 * (MetaCons "AtomString" PrefixI False) (S1 * (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 * Text))) (C1 * (MetaCons "AtomSymbol" PrefixI False) (S1 * (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 * Text)))))

data Prefix Source #

S-expression quotation type

Constructors

Quote 
Backtick 
Comma 
CommaAt 
Hash 

Instances

Eq Prefix Source # 

Methods

(==) :: Prefix -> Prefix -> Bool #

(/=) :: Prefix -> Prefix -> Bool #

Ord Prefix Source # 
Show Prefix Source # 
Generic Prefix Source # 

Associated Types

type Rep Prefix :: * -> * #

Methods

from :: Prefix -> Rep Prefix x #

to :: Rep Prefix x -> Prefix #

NFData Prefix Source # 

Methods

rnf :: Prefix -> () #

type Rep Prefix Source # 
type Rep Prefix = D1 * (MetaData "Prefix" "Language.Sexp.Types" "sexp-grammar-2.0.0-7H6WbiqRhQHGwWvTncrSQw" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Quote" PrefixI False) (U1 *)) (C1 * (MetaCons "Backtick" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Comma" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "CommaAt" PrefixI False) (U1 *)) (C1 * (MetaCons "Hash" PrefixI False) (U1 *)))))

Orphan instances