hedn-0.1.8.2: EDN parsing and encoding

Safe HaskellNone
LanguageHaskell98

Data.EDN

Contents

Synopsis

Encoding and decoding

decode :: FromEDN a => ByteString -> Maybe a Source #

Deserializes a EDN value from a lazy ByteString. If this fails to to incomplete or invalid input, Nothing is returned.

encode :: ToEDN a => a -> ByteString Source #

Serialize a value as a lazy ByteString.

Core EDN types

data Value Source #

A "raw" EDN value represented as a Haskell value.

data Tagged a Source #

Abstract namespaced tag.

Constructors

NoTag !a 
Tagged !a !ByteString !ByteString 

Instances

Functor Tagged Source # 

Methods

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

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

FromEDN TaggedValue Source # 
ToEDN TaggedValue Source # 
Eq a => Eq (Tagged a) Source # 

Methods

(==) :: Tagged a -> Tagged a -> Bool #

(/=) :: Tagged a -> Tagged a -> Bool #

Ord a => Ord (Tagged a) Source # 

Methods

compare :: Tagged a -> Tagged a -> Ordering #

(<) :: Tagged a -> Tagged a -> Bool #

(<=) :: Tagged a -> Tagged a -> Bool #

(>) :: Tagged a -> Tagged a -> Bool #

(>=) :: Tagged a -> Tagged a -> Bool #

max :: Tagged a -> Tagged a -> Tagged a #

min :: Tagged a -> Tagged a -> Tagged a #

Show a => Show (Tagged a) Source # 

Methods

showsPrec :: Int -> Tagged a -> ShowS #

show :: Tagged a -> String #

showList :: [Tagged a] -> ShowS #

IsString (Tagged Value) Source #

Strings will become an tagless EDN strings.

NFData a => NFData (Tagged a) Source # 

Methods

rnf :: Tagged a -> () #

FromEDN a => FromEDN (Tagged a) Source # 
ToEDN a => ToEDN (Tagged a) Source # 

Type conversion

class ToEDN a where Source #

A type that can be converted to JSON.

Methods

toEDN :: a -> TaggedValue Source #

Instances

ToEDN Bool Source # 
ToEDN Char Source # 
ToEDN Double Source # 
ToEDN Int Source # 
ToEDN Integer Source # 
ToEDN () Source # 

Methods

toEDN :: () -> TaggedValue Source #

toEDNv :: () -> Value Source #

ToEDN ByteString Source # 
ToEDN ByteString Source # 
ToEDN Text Source # 
ToEDN Text Source # 
ToEDN UTCTime Source # 
ToEDN Value Source # 
ToEDN TaggedValue Source # 
ToEDN [Char] Source # 
ToEDN a => ToEDN [a] Source # 

Methods

toEDN :: [a] -> TaggedValue Source #

toEDNv :: [a] -> Value Source #

ToEDN a => ToEDN (Maybe a) Source # 
(Ord a, ToEDN a) => ToEDN (Set a) Source # 
ToEDN a => ToEDN (Vector a) Source # 
ToEDN a => ToEDN (Tagged a) Source # 
(ToEDN a, ToEDN b) => ToEDN (Either a b) Source # 
(ToEDN a, ToEDN b) => ToEDN (a, b) Source # 

Methods

toEDN :: (a, b) -> TaggedValue Source #

toEDNv :: (a, b) -> Value Source #

(ToEDN a, ToEDN b) => ToEDN (Map a b) Source # 

Methods

toEDN :: Map a b -> TaggedValue Source #

toEDNv :: Map a b -> Value Source #

(ToEDN a, ToEDN b, ToEDN c) => ToEDN (a, b, c) Source # 

Methods

toEDN :: (a, b, c) -> TaggedValue Source #

toEDNv :: (a, b, c) -> Value Source #

(ToEDN a, ToEDN b, ToEDN c, ToEDN d) => ToEDN (a, b, c, d) Source # 

Methods

toEDN :: (a, b, c, d) -> TaggedValue Source #

toEDNv :: (a, b, c, d) -> Value Source #

(ToEDN a, ToEDN b, ToEDN c, ToEDN d, ToEDN e) => ToEDN (a, b, c, d, e) Source # 

Methods

toEDN :: (a, b, c, d, e) -> TaggedValue Source #

toEDNv :: (a, b, c, d, e) -> Value Source #

(ToEDN a, ToEDN b, ToEDN c, ToEDN d, ToEDN e, ToEDN f) => ToEDN (a, b, c, d, e, f) Source # 

Methods

toEDN :: (a, b, c, d, e, f) -> TaggedValue Source #

toEDNv :: (a, b, c, d, e, f) -> Value Source #

(ToEDN a, ToEDN b, ToEDN c, ToEDN d, ToEDN e, ToEDN f, ToEDN g) => ToEDN (a, b, c, d, e, f, g) Source # 

Methods

toEDN :: (a, b, c, d, e, f, g) -> TaggedValue Source #

toEDNv :: (a, b, c, d, e, f, g) -> Value Source #

(ToEDN a, ToEDN b, ToEDN c, ToEDN d, ToEDN e, ToEDN f, ToEDN g, ToEDN h) => ToEDN (a, b, c, d, e, f, g, h) Source # 

Methods

toEDN :: (a, b, c, d, e, f, g, h) -> TaggedValue Source #

toEDNv :: (a, b, c, d, e, f, g, h) -> Value Source #

class FromEDN a Source #

A type that can be converted from EDN, with a possibility of failure.

When writing an instance, use empty, mzero, or fail to make a conversion fail, e.g. if an Map is missing a required key, or the value is of the wrong type.

Instances

FromEDN Bool Source # 
FromEDN Char Source # 
FromEDN Double Source # 
FromEDN Int Source # 
FromEDN Integer Source # 
FromEDN () Source # 
FromEDN ByteString Source # 
FromEDN ByteString Source # 
FromEDN Text Source # 
FromEDN Text Source # 
FromEDN UTCTime Source # 
FromEDN Value Source # 
FromEDN TaggedValue Source # 
FromEDN [Char] Source # 
FromEDN a => FromEDN [a] Source # 
FromEDN a => FromEDN (Maybe a) Source # 
(Ord a, FromEDN a) => FromEDN (Set a) Source # 
FromEDN a => FromEDN (Vector a) Source # 
FromEDN a => FromEDN (Tagged a) Source # 
(FromEDN a, FromEDN b) => FromEDN (Either a b) Source # 
(FromEDN a, FromEDN b) => FromEDN (a, b) Source # 

Methods

parseEDN :: TaggedValue -> Parser (a, b) Source #

parseEDNv :: Value -> Parser (a, b) Source #

(Ord a, FromEDN a, FromEDN b) => FromEDN (Map a b) Source # 
(FromEDN a, FromEDN b, FromEDN c) => FromEDN (a, b, c) Source # 

Methods

parseEDN :: TaggedValue -> Parser (a, b, c) Source #

parseEDNv :: Value -> Parser (a, b, c) Source #

(FromEDN a, FromEDN b, FromEDN c, FromEDN d) => FromEDN (a, b, c, d) Source # 

Methods

parseEDN :: TaggedValue -> Parser (a, b, c, d) Source #

parseEDNv :: Value -> Parser (a, b, c, d) Source #

(FromEDN a, FromEDN b, FromEDN c, FromEDN d, FromEDN e) => FromEDN (a, b, c, d, e) Source # 

Methods

parseEDN :: TaggedValue -> Parser (a, b, c, d, e) Source #

parseEDNv :: Value -> Parser (a, b, c, d, e) Source #

(FromEDN a, FromEDN b, FromEDN c, FromEDN d, FromEDN e, FromEDN f) => FromEDN (a, b, c, d, e, f) Source # 

Methods

parseEDN :: TaggedValue -> Parser (a, b, c, d, e, f) Source #

parseEDNv :: Value -> Parser (a, b, c, d, e, f) Source #

(FromEDN a, FromEDN b, FromEDN c, FromEDN d, FromEDN e, FromEDN f, FromEDN g) => FromEDN (a, b, c, d, e, f, g) Source # 

Methods

parseEDN :: TaggedValue -> Parser (a, b, c, d, e, f, g) Source #

parseEDNv :: Value -> Parser (a, b, c, d, e, f, g) Source #

(FromEDN a, FromEDN b, FromEDN c, FromEDN d, FromEDN e, FromEDN f, FromEDN g, FromEDN h) => FromEDN (a, b, c, d, e, f, g, h) Source # 

Methods

parseEDN :: TaggedValue -> Parser (a, b, c, d, e, f, g, h) Source #

parseEDNv :: Value -> Parser (a, b, c, d, e, f, g, h) Source #

fromEDN :: FromEDN a => TaggedValue -> Result a Source #

Convert a value from TaggedValue, failing if the types do not match.

fromEDNv :: FromEDN a => Value -> Result a Source #

Convert a value from Value, failing if the types do not match.

(.:) :: (Show k, ToEDN k, FromEDN a) => EDNMap -> k -> Parser a Source #

Retrieve the value associated with the given key of an EDNMap. The result is empty if the key is not present or the value cannot be converted to the desired type.

This accessor is appropriate if the key and value must be present in an object for it to be valid. If the key and value are optional, use '(.:?)' instead.

(.:?) :: (ToEDN k, FromEDN a) => EDNMap -> k -> Parser (Maybe a) Source #

Retrieve the value associated with the given key of an EDNMap. The result is Nothing if the key is not present, or empty if the value cannot be converted to the desired type.

This accessor is most useful if the key and value can be absent from an object without affecting its validity. If the key and value are mandatory, use '(.:)' instead.

(.!=) :: Parser (Maybe a) -> a -> Parser a Source #

Helper for use in combination with .:? to provide default values for optional JSON object fields.

This combinator is most useful if the key and value can be absent from an object without affecting its validity and we know a default value to assign in that case. If the key and value are mandatory, use '(.:)' instead.

Example usage:

 v1 <- o .:? "opt_field_with_dfl" .!= "default_val"
 v2 <- o .:  "mandatory_field"
 v3 <- o .:? "opt_field2"

Constructors

tag :: ByteString -> ByteString -> a -> Tagged a Source #

Attach a namespaced tag to a value.

notag :: a -> Tagged a Source #

Wrap a value into tagless container.

Basic values

nil :: TaggedValue Source #

Basic EDN nil.

bool :: Bool -> TaggedValue Source #

Basic EDN boolean.

true :: TaggedValue Source #

Const EDN True.

false :: TaggedValue Source #

Const EDN False.

char :: Char -> TaggedValue Source #

Basic EDN character.

string :: Text -> TaggedValue Source #

Basic EDN string.

symbol :: ByteString -> TaggedValue Source #

"Bare" symbol.

symbolNS :: ByteString -> ByteString -> TaggedValue Source #

A namespaced symbol.

keyword :: ByteString -> TaggedValue Source #

Basic EDN keyword.

integer :: Integer -> TaggedValue Source #

Basic EDN integer.

floating :: Double -> TaggedValue Source #

Basic EDN fp number.

Containers

makeList :: [TaggedValue] -> Value Source #

Create an EDN List from a Value list wrapping them into empty tags.

makeVec :: [TaggedValue] -> Value Source #

Create an EDN Vector from a TaggedValue list.

makeSet :: [TaggedValue] -> Value Source #

Create an EDN Set from a TaggedValue list.

makeMap :: [Pair] -> Value Source #

Create an EDN Map from a assoc list with untagged keys and tagged values.

type Pair = (Value, TaggedValue) Source #

A key/value pair for a EDN Map

(.=) :: ToEDN a => ByteString -> a -> Pair Source #

Construct a Pair from a key (as EDN keyword) and a value.

Tag manipulation

setTag :: ByteString -> ByteString -> Tagged a -> Tagged a Source #

Replace a tag on a Tagged value.

getTag :: TaggedValue -> (ByteString, ByteString) Source #

Extract namespace and tag from a tagged container. Will be a pair of empty for tagless containers.

stripTag :: Tagged a -> a Source #

Extract bare value from a tagged or tagless container.

Parsing

parseMaybe :: ByteString -> Maybe TaggedValue Source #

Parse a lazy ByteString into a TaggedValue. If fails due to incomplete or invalid input, Nothing is returned.