hedn-0.1.8.1: EDN parsing and encoding

Safe HaskellNone

Data.EDN

Contents

Synopsis

Encoding and decoding

decode :: FromEDN a => ByteString -> Maybe aSource

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

encode :: ToEDN a => a -> ByteStringSource

Serialize a value as a lazy ByteString.

Core EDN types

data Value Source

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

Instances

Eq Value 
Ord Value 
Show Value 
IsString Value

Strings starting with ":" will become keywords.

NFData Value 
FromEDN Value 
FromEDN TaggedValue 
ToEDN Value 
ToEDN TaggedValue 
IsString (Tagged Value)

Strings will become an tagless EDN strings.

data Tagged a Source

Abstract namespaced tag.

Constructors

NoTag !a 
Tagged !a !ByteString !ByteString 

Instances

Functor Tagged 
FromEDN TaggedValue 
ToEDN TaggedValue 
Eq a => Eq (Tagged a) 
Ord a => Ord (Tagged a) 
Show a => Show (Tagged a) 
IsString (Tagged Value)

Strings will become an tagless EDN strings.

NFData a => NFData (Tagged a) 
FromEDN a => FromEDN (Tagged a) 
ToEDN a => ToEDN (Tagged a) 

Type conversion

class ToEDN a whereSource

A type that can be converted to JSON.

Methods

toEDN :: a -> TaggedValueSource

Instances

ToEDN Bool 
ToEDN Char 
ToEDN Double 
ToEDN Int 
ToEDN Integer 
ToEDN () 
ToEDN ByteString 
ToEDN ByteString 
ToEDN Text 
ToEDN Text 
ToEDN UTCTime 
ToEDN Value 
ToEDN TaggedValue 
ToEDN [Char] 
ToEDN a => ToEDN [a] 
ToEDN a => ToEDN (Maybe a) 
(Ord a, ToEDN a) => ToEDN (Set a) 
ToEDN a => ToEDN (Vector a) 
ToEDN a => ToEDN (Tagged a) 
(ToEDN a, ToEDN b) => ToEDN (Either a b) 
(ToEDN a, ToEDN b) => ToEDN (a, b) 
(ToEDN a, ToEDN b) => ToEDN (Map a b) 
(ToEDN a, ToEDN b, ToEDN c) => ToEDN (a, b, c) 
(ToEDN a, ToEDN b, ToEDN c, ToEDN d) => ToEDN (a, b, c, d) 
(ToEDN a, ToEDN b, ToEDN c, ToEDN d, ToEDN e) => ToEDN (a, b, c, d, e) 
(ToEDN a, ToEDN b, ToEDN c, ToEDN d, ToEDN e, ToEDN f) => ToEDN (a, b, c, d, e, f) 
(ToEDN a, ToEDN b, ToEDN c, ToEDN d, ToEDN e, ToEDN f, ToEDN g) => ToEDN (a, b, c, d, e, f, g) 
(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) 

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 
FromEDN Char 
FromEDN Double 
FromEDN Int 
FromEDN Integer 
FromEDN () 
FromEDN ByteString 
FromEDN ByteString 
FromEDN Text 
FromEDN Text 
FromEDN UTCTime 
FromEDN Value 
FromEDN TaggedValue 
FromEDN [Char] 
FromEDN a => FromEDN [a] 
FromEDN a => FromEDN (Maybe a) 
(Ord a, FromEDN a) => FromEDN (Set a) 
FromEDN a => FromEDN (Vector a) 
FromEDN a => FromEDN (Tagged a) 
(FromEDN a, FromEDN b) => FromEDN (Either a b) 
(FromEDN a, FromEDN b) => FromEDN (a, b) 
(Ord a, FromEDN a, FromEDN b) => FromEDN (Map a b) 
(FromEDN a, FromEDN b, FromEDN c) => FromEDN (a, b, c) 
(FromEDN a, FromEDN b, FromEDN c, FromEDN d) => FromEDN (a, b, c, d) 
(FromEDN a, FromEDN b, FromEDN c, FromEDN d, FromEDN e) => FromEDN (a, b, c, d, e) 
(FromEDN a, FromEDN b, FromEDN c, FromEDN d, FromEDN e, FromEDN f) => FromEDN (a, b, c, d, e, f) 
(FromEDN a, FromEDN b, FromEDN c, FromEDN d, FromEDN e, FromEDN f, FromEDN g) => FromEDN (a, b, c, d, e, f, g) 
(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) 

fromEDN :: FromEDN a => TaggedValue -> Result aSource

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

fromEDNv :: FromEDN a => Value -> Result aSource

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

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

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 aSource

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 aSource

Attach a namespaced tag to a value.

notag :: a -> Tagged aSource

Wrap a value into tagless container.

Basic values

nil :: TaggedValueSource

Basic EDN nil.

bool :: Bool -> TaggedValueSource

Basic EDN boolean.

true :: TaggedValueSource

Const EDN True.

false :: TaggedValueSource

Const EDN False.

char :: Char -> TaggedValueSource

Basic EDN character.

string :: Text -> TaggedValueSource

Basic EDN string.

symbol :: ByteString -> TaggedValueSource

"Bare" symbol.

symbolNS :: ByteString -> ByteString -> TaggedValueSource

A namespaced symbol.

keyword :: ByteString -> TaggedValueSource

Basic EDN keyword.

integer :: Integer -> TaggedValueSource

Basic EDN integer.

floating :: Double -> TaggedValueSource

Basic EDN fp number.

Containers

makeList :: [TaggedValue] -> ValueSource

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

makeVec :: [TaggedValue] -> ValueSource

Create an EDN Vector from a TaggedValue list.

makeSet :: [TaggedValue] -> ValueSource

Create an EDN Set from a TaggedValue list.

makeMap :: [Pair] -> ValueSource

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 -> PairSource

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

Tag manipulation

setTag :: ByteString -> ByteString -> Tagged a -> Tagged aSource

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 -> aSource

Extract bare value from a tagged or tagless container.

Parsing

parseMaybe :: ByteString -> Maybe TaggedValueSource

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