unjson-0.15.3: Bidirectional JSON parsing and generation.

Safe HaskellNone
LanguageHaskell2010

Data.Unjson

Contents

Description

Unjson: bidirectional JSON (de)serialization with strong error reporting capabilities and automatic documentation generation.

Data.Unjson offers:

  • single definition for serialization and deserialization
  • parse and update mode
  • exact error reporting
  • required, optional and fields with default values
  • first class object, array and tuple support
  • lifting of Aeson instances
  • automatic documentation generation

Example:

data Example = Example
   { exampleName     :: Text.Text,
     exampleArray    :: [Int],
     exampleOptional :: Maybe Bool }

unjsonExample :: UnjsonDef Example
unjsonExample = objectOf $ pure Example
  <*> field "name"
          exampleName
          "Name used for example"
  <*> fieldDefBy "array_of_ints" []
          exampleArray
          "Array of integers, optional, defaults to empty list"
          (arrayOf unjsonDef)
  <*> fieldOpt "optional_bool"
          exampleOptional
          "Optional boolean"

Rendered documentation:

name (req):
    Name used for example
    Text
array_of_ints (def):
    Array of integers, optional, defaults to empty list
    array of:
        Int
optional_bool (opt):
    Optional boolean
    Bool

Documentation has some colors that could not be reproduced in haddock.

Parsing:

let Result val iss = parse unjsonExample $
                     object [ "name"          .= 123
                            , "array_of_ints" .= [toJSON 123, toJSON "abc"]
                            , "optional_bool" .= True ]

Error reporting:

mapM_ print iss
> name: "when expecting a Text, encountered Number instead"
> array_of_ints[1]: "when expecting a Integral, encountered String instead"

Partial results:

print (exampleOptional val)
> Just True

Bottom errors in partial results:

print (exampleName val)
> "*** Exception: name: "when expecting a Text, encountered Number instead"

Note: if list of issues is empty then there are not bottoms, guaranteed.

For more examples have a look at Unjson, parse, update, unjsonToJSON, unjsonToByteStringLazy, unjsonToByteStringBuilder and render.

Synopsis

Serialization to JSON

unjsonToJSON :: UnjsonDef a -> a -> Value Source #

Given a definition of a value and a value produce a Value.

Example:

let v = Thing { ... }
let json = unjsonToJSON unjsonThing v

unjsonToJSON' :: Options -> UnjsonDef a -> a -> Value Source #

Given a definition of a value and a value produce a Value. Takes Options.

Example:

let v = Thing { ... }
let json = unjsonToJSON' options unjsonThing v

unjsonToByteStringLazy :: UnjsonDef a -> a -> ByteString Source #

Given a definition of a value and a value produce a ByteString.

Example:

let v = Thing { ... }
let utf8bsrep = unjsonToByteStringLazy unjsonThing v

unjsonToByteStringLazy' :: Options -> UnjsonDef a -> a -> ByteString Source #

Given a definition of a value and a value produce a ByteString. Also takes formatting Options.

Example:

let v = Thing { ... }
let utf8bsrep = unjsonToByteStringLazy' options unjsonThing v

unjsonToByteStringBuilder :: UnjsonDef a -> a -> Builder Source #

Given a definition of a value and a value produce a Builder. Functionally it is the same as unjsonToByteStringLazy but useful if json serialization is a part of some bigger serialization function.

unjsonToByteStringBuilder' :: Options -> UnjsonDef a -> a -> Builder Source #

Given a definition of a value and a value produce a Builder. Functionally it is the same as unjsonToByteStringLazy but useful if json serialization is a part of some bigger serialization function. Also takes formatting Options.

unjsonToByteStringBuilder'' :: Int -> Options -> UnjsonDef a -> a -> Builder Source #

Given a definition of a value and a value produce a Builder. Useful when JSON serialization is a part of a bigger serialization function.

data Options Source #

Formatting options when serializing to JSON. Used in unjsonToJSON', unjsonToByteStringLazy' and unjsonToByteStringBuilder'.

Constructors

Options 

Fields

  • pretty :: Bool

    Pretty format. Use spaces and newlines.

  • indent :: Int

    Amount of spaces for indent. 4 looks good.

  • nulls :: Bool

    Output explicit nulls for absent optional fields.

Instances
Eq Options Source # 
Instance details

Defined in Data.Unjson

Methods

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

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

Ord Options Source # 
Instance details

Defined in Data.Unjson

Show Options Source # 
Instance details

Defined in Data.Unjson

Data definitions

class Unjson a where Source #

Unjson typeclass describes all types that can be parsed from JSON and JSON generated from their values.

Example declaration:

instance Unjson Thing where
    unjsonDef = objectOf $ pure Thing
        <*> field "key1"
              thingField1
              "Required field of type with Unjson instance"
        <*> fieldBy "key2"
              thingField2
              "Required field with parser given below"
              unjsonForKey2
        <*> fieldOpt "key4"
              thingField4
              "Optional field of type with Unjson instance"
        <*> fieldOptBy "key5"
              thingField5
              "Optional field with parser given below"
              unjsonForKey5
        <*> fieldDef "key7"
              thingField7
              "Optional field with default of type with Unjson instance"
        <*> fieldDefBy "key8"
              thingField8
              "Optional field with default with parser given below"
              unjsonForKey8

Methods

unjsonDef :: UnjsonDef a Source #

Definition of a bidirectional parser for a type a. See parse, update, serialize and render to see how to use UnjsonDef.

Instances
Unjson Bool Source # 
Instance details

Defined in Data.Unjson

Unjson Char Source # 
Instance details

Defined in Data.Unjson

Unjson Double Source # 
Instance details

Defined in Data.Unjson

Unjson Float Source # 
Instance details

Defined in Data.Unjson

Unjson Int Source # 
Instance details

Defined in Data.Unjson

Unjson Int8 Source # 
Instance details

Defined in Data.Unjson

Unjson Int16 Source # 
Instance details

Defined in Data.Unjson

Unjson Int32 Source # 
Instance details

Defined in Data.Unjson

Unjson Int64 Source # 
Instance details

Defined in Data.Unjson

Unjson Integer Source # 
Instance details

Defined in Data.Unjson

Unjson Word Source # 
Instance details

Defined in Data.Unjson

Unjson Word8 Source # 
Instance details

Defined in Data.Unjson

Unjson Word16 Source # 
Instance details

Defined in Data.Unjson

Unjson Word32 Source # 
Instance details

Defined in Data.Unjson

Unjson Word64 Source # 
Instance details

Defined in Data.Unjson

Unjson () Source # 
Instance details

Defined in Data.Unjson

Unjson Scientific Source # 
Instance details

Defined in Data.Unjson

Unjson Text Source # 
Instance details

Defined in Data.Unjson

Unjson UTCTime Source # 
Instance details

Defined in Data.Unjson

Unjson Value Source # 
Instance details

Defined in Data.Unjson

Unjson DotNetTime Source # 
Instance details

Defined in Data.Unjson

Unjson Text Source # 
Instance details

Defined in Data.Unjson

Unjson String Source # 
Instance details

Defined in Data.Unjson

Unjson IntSet Source # 
Instance details

Defined in Data.Unjson

Unjson ZonedTime Source # 
Instance details

Defined in Data.Unjson

(Unjson a, Typeable a) => Unjson [a] Source # 
Instance details

Defined in Data.Unjson

Methods

unjsonDef :: UnjsonDef [a] Source #

Unjson (Ratio Integer) Source # 
Instance details

Defined in Data.Unjson

(HasResolution a, Typeable a, FromJSON a, ToJSON a) => Unjson (Fixed a) Source # 
Instance details

Defined in Data.Unjson

Unjson a => Unjson (Dual a) Source # 
Instance details

Defined in Data.Unjson

(Unjson a, Typeable a) => Unjson (IntMap a) Source # 
Instance details

Defined in Data.Unjson

(Ord a, Unjson a, Typeable a) => Unjson (Set a) Source # 
Instance details

Defined in Data.Unjson

(Eq a, Hashable a, Unjson a, Typeable a) => Unjson (HashSet a) Source # 
Instance details

Defined in Data.Unjson

(Vector Vector a, Unjson a, Unbox a, Typeable a) => Unjson (Vector a) Source # 
Instance details

Defined in Data.Unjson

(Storable a, Unjson a, Typeable a) => Unjson (Vector a) Source # 
Instance details

Defined in Data.Unjson

(Prim a, Unjson a, Typeable a) => Unjson (Vector a) Source # 
Instance details

Defined in Data.Unjson

(Unjson a, Typeable a) => Unjson (Vector a) Source # 
Instance details

Defined in Data.Unjson

(Unjson a, Unjson b) => Unjson (a, b) Source # 
Instance details

Defined in Data.Unjson

Methods

unjsonDef :: UnjsonDef (a, b) Source #

(Typeable v, Unjson v) => Unjson (HashMap Text v) Source # 
Instance details

Defined in Data.Unjson

(Typeable v, Unjson v) => Unjson (HashMap Text v) Source # 
Instance details

Defined in Data.Unjson

(Typeable v, Unjson v) => Unjson (HashMap String v) Source # 
Instance details

Defined in Data.Unjson

(Typeable v, Unjson v) => Unjson (Map Text v) Source # 
Instance details

Defined in Data.Unjson

(Typeable v, Unjson v) => Unjson (Map Text v) Source # 
Instance details

Defined in Data.Unjson

(Typeable v, Unjson v) => Unjson (Map String v) Source # 
Instance details

Defined in Data.Unjson

(Unjson a, Unjson b, Unjson c) => Unjson (a, b, c) Source # 
Instance details

Defined in Data.Unjson

Methods

unjsonDef :: UnjsonDef (a, b, c) Source #

(Unjson a, Unjson b, Unjson c, Unjson d) => Unjson (a, b, c, d) Source # 
Instance details

Defined in Data.Unjson

Methods

unjsonDef :: UnjsonDef (a, b, c, d) Source #

(Unjson a, Unjson b, Unjson c, Unjson d, Unjson e) => Unjson (a, b, c, d, e) Source # 
Instance details

Defined in Data.Unjson

Methods

unjsonDef :: UnjsonDef (a, b, c, d, e) Source #

(Unjson a, Unjson b, Unjson c, Unjson d, Unjson e, Unjson f) => Unjson (a, b, c, d, e, f) Source # 
Instance details

Defined in Data.Unjson

Methods

unjsonDef :: UnjsonDef (a, b, c, d, e, f) Source #

(Unjson a, Unjson b, Unjson c, Unjson d, Unjson e, Unjson f, Unjson g) => Unjson (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Data.Unjson

Methods

unjsonDef :: UnjsonDef (a, b, c, d, e, f, g) Source #

(Unjson a, Unjson b, Unjson c, Unjson d, Unjson e, Unjson f, Unjson g, Unjson h) => Unjson (a, b, c, d, e, f, g, h) Source # 
Instance details

Defined in Data.Unjson

Methods

unjsonDef :: UnjsonDef (a, b, c, d, e, f, g, h) Source #

(Unjson a, Unjson b, Unjson c, Unjson d, Unjson e, Unjson f, Unjson g, Unjson h, Unjson i) => Unjson (a, b, c, d, e, f, g, h, i) Source # 
Instance details

Defined in Data.Unjson

Methods

unjsonDef :: UnjsonDef (a, b, c, d, e, f, g, h, i) Source #

(Unjson a, Unjson b, Unjson c, Unjson d, Unjson e, Unjson f, Unjson g, Unjson h, Unjson i, Unjson j) => Unjson (a, b, c, d, e, f, g, h, i, j) Source # 
Instance details

Defined in Data.Unjson

Methods

unjsonDef :: UnjsonDef (a, b, c, d, e, f, g, h, i, j) Source #

(Unjson a, Unjson b, Unjson c, Unjson d, Unjson e, Unjson f, Unjson g, Unjson h, Unjson i, Unjson j, Unjson k) => Unjson (a, b, c, d, e, f, g, h, i, j, k) Source # 
Instance details

Defined in Data.Unjson

Methods

unjsonDef :: UnjsonDef (a, b, c, d, e, f, g, h, i, j, k) Source #

(Unjson a, Unjson b, Unjson c, Unjson d, Unjson e, Unjson f, Unjson g, Unjson h, Unjson i, Unjson j, Unjson k, Unjson l) => Unjson (a, b, c, d, e, f, g, h, i, j, k, l) Source # 
Instance details

Defined in Data.Unjson

Methods

unjsonDef :: UnjsonDef (a, b, c, d, e, f, g, h, i, j, k, l) Source #

data UnjsonDef a where Source #

Opaque UnjsonDef defines a bidirectional JSON parser.

Constructors

SimpleUnjsonDef :: Text -> (Value -> Result k) -> (k -> Value) -> UnjsonDef k 
ArrayUnjsonDef :: Typeable k => Maybe (PrimaryKeyExtraction k) -> ArrayMode -> ([k] -> Result v) -> (v -> [k]) -> UnjsonDef k -> UnjsonDef v 
ObjectUnjsonDef :: Ap (FieldDef k) (Result k) -> UnjsonDef k 
TupleUnjsonDef :: Ap (TupleFieldDef k) (Result k) -> UnjsonDef k 
DisjointUnjsonDef :: Text -> [(Text, k -> Bool, Ap (FieldDef k) (Result k))] -> UnjsonDef k 
UnionUnjsonDef :: [(k -> Bool, Ap (FieldDef k) (Result k))] -> UnjsonDef k 
MapUnjsonDef :: Typeable k => UnjsonDef k -> (HashMap Text k -> Result v) -> (v -> HashMap Text k) -> UnjsonDef v 
Instances
Invariant UnjsonDef Source # 
Instance details

Defined in Data.Unjson

Methods

invmap :: (a -> b) -> (b -> a) -> UnjsonDef a -> UnjsonDef b #

Objects

objectOf :: Ap (FieldDef a) a -> UnjsonDef a Source #

Declare an object as bidirectional mapping from JSON object to Haskell record and back.

Example:

unjsonThing :: UnjsonDef Thing
unjsonThing = objectOf $ pure Thing
   ...field definitions go here

Use field functions to specify fields of an object: field, fieldBy, fieldOpt, fieldOptBy, fieldDef or fieldDefBy.

field :: (Unjson a, Typeable a) => Text -> (s -> a) -> Text -> Ap (FieldDef s) a Source #

Declare a required field with definition from Unjson typeclass.

Example:

unjsonThing :: UnjsonDef Thing
unjsonThing = objectOf $ pure Thing
   <*> field "credentials"
         thingCredentials
         "Credentials to use"

data Thing = Thing { thingCredentials :: Credentials, ... }
instance Unjson Credentials where ...

fieldBy :: Typeable a => Text -> (s -> a) -> Text -> UnjsonDef a -> Ap (FieldDef s) a Source #

Declare a required field with definition given inline by valuedef.

Example:

unjsonThing :: UnjsonDef Thing
unjsonThing = objectOf $ pure Thing
   <*> fieldBy "credentials"
         thingCredentials
         "Credentials to use"
         unjsonCredentials

data Thing = Thing { thingCredentials :: Credentials, ... }
unjsonCredentials :: UnjsonDef Credentials

fieldOpt :: (Unjson a, Typeable a) => Text -> (s -> Maybe a) -> Text -> Ap (FieldDef s) (Maybe a) Source #

Declare an optional field and definition by Unjson typeclass.

Example:

unjsonThing :: UnjsonDef Thing
unjsonThing = objectOf $ pure Thing
   <*> fieldOpt "credentials"
         thingCredentials
         "Optional credentials to use"

data Thing = Thing { thingCredentials :: Credentials, ... }
instance Unjson Credentials where ...

fieldOptBy :: Typeable a => Text -> (s -> Maybe a) -> Text -> UnjsonDef a -> Ap (FieldDef s) (Maybe a) Source #

Declare an optional field and definition by valuedef.

Example:

unjsonThing :: UnjsonDef Thing
unjsonThing = objectOf $ pure Thing
   <*> fieldOptBy "credentials"
         thingCredentials
         "Optional credentials to use"
         unjsonCredentials

data Thing = Thing { thingCredentials :: Credentials, ... }
unjsonCredentials :: UnjsonDef Credentials

fieldDef :: (Unjson a, Typeable a) => Text -> a -> (s -> a) -> Text -> Ap (FieldDef s) a Source #

Declare a field with default value and definition by Unjson typeclass.

Example:

unjsonThing :: UnjsonDef Thing
unjsonThing = objectOf $ pure Thing
   <*> fieldDef "port" 80
         thingPort
         "Port to listen on, defaults to 80"

data Thing = Thing { thingPort :: Int, ... }

fieldDefBy :: Typeable a => Text -> a -> (s -> a) -> Text -> UnjsonDef a -> Ap (FieldDef s) a Source #

Declare a field with default value and definition by valuedef.

Example:

unjsonThing :: UnjsonDef Thing
unjsonThing = objectOf $ pure Thing
   <*> fieldDefBy "credentials" defaultCredentials
         thingCredentials
         "Credentials to use, defaults to defaultCredentials"
         unjsonCredentials

data Thing = Thing { thingCredentials :: Credentials, ... }
unjsonCredentials :: UnjsonDef Credentials

fieldReadonly :: (Unjson a, Typeable a) => Text -> (s -> a) -> Text -> Ap (FieldDef s) () Source #

Declare a field that is readonly from the point of view of Haskell structures, it will be serialized to JSON but never read from JSON.

Example:

unjsonThing :: UnjsonDef Thing
unjsonThing = objectOf $ pure (\s -> Thing 59123 s)
   <* fieldReadonly "port"
         thingPort
         "Random port the server is listening on"
   <*> field "string"
         thingString
         "Additional string"

data Thing = Thing { thingPort :: Int, thingString :: String, ... }

fieldReadonlyBy :: Typeable a => Text -> (s -> a) -> Text -> UnjsonDef a -> Ap (FieldDef s) () Source #

Declare a field that is readonly from the point of view of Haskell structures, it will be serialized to JSON but never read from JSON. Accepts unjson parser as a parameter.

Example:

unjsonThing :: UnjsonDef Thing
unjsonThing = objectOf $ pure (\s -> Thing 59123 s)
   <* fieldReadonlyBy "port"
         thingPort
         "Random port the server is listening on"
         unjsonPort
   <*> field "string"
         thingString
         "Additional string"

data Thing = Thing { thingPort :: Port, thingString :: String, ... }

data FieldDef s a where Source #

Define a relation between a field of an object in JSON and a field in a Haskell record structure. FieldDef holds information about a documentation string, key name, Haskell data accessor and parsing definition. FieldDef has three cases for fields that are required, optional (via Maybe) or jave default value.

Constructors

FieldReqDef :: Typeable a => Text -> Text -> (s -> a) -> UnjsonDef a -> FieldDef s a 
FieldOptDef :: Typeable a => Text -> Text -> (s -> Maybe a) -> UnjsonDef a -> FieldDef s (Maybe a) 
FieldDefDef :: Typeable a => Text -> Text -> a -> (s -> a) -> UnjsonDef a -> FieldDef s a 
FieldRODef :: Typeable a => Text -> Text -> (s -> a) -> UnjsonDef a -> FieldDef s () 

Arrays

arrayOf :: Typeable a => UnjsonDef a -> UnjsonDef [a] Source #

Declare array of values where each of them is described by valuedef. Use unjsonAeson to parse.

Example:

unjsonArrayOfThings :: UnjsonDef [Thing]
unjsonArrayOfThings = arrayOf unjsonThing

unjsonThing :: UnjsonDef Thing
unjsonThing = ...

arrayWithModeOf :: Typeable a => ArrayMode -> UnjsonDef a -> UnjsonDef [a] Source #

Declare array of values where each of them is described by valuedef. Accepts mode specifier.

Example:

unjsonArrayOfThings :: UnjsonDef [Thing]
unjsonArrayOfThings = arrayOf unjsonThing

unjsonThing :: UnjsonDef Thing
unjsonThing = ...

arrayWithModeOf' :: (FromJSON a, ToJSON a, Typeable a) => ArrayMode -> UnjsonDef [a] Source #

Declare array of primitive values lifed from Aeson. Accepts mode specifier.

Example:

unjsonArrayOfIntOrSimpleInt :: UnjsonDef [Int]
unjsonArrayOfIntOrSimpleInt = arrayWithModeOf'

Since: 0.15.1.0

arrayWithPrimaryKeyOf :: (Ord pk, Typeable a) => (a -> pk) -> UnjsonDef pk -> UnjsonDef a -> UnjsonDef [a] Source #

Declare array of objects with given parsers that should be matched by a primary key. Uses ArrayModeStrict.

Primary key:

Primary keys are used to match objects in update mode. When a request to update array is issued and array has primary key specification then the following steps are used:

  1. primary keys from old array elements are extracted and a mapping from primary key to element is created. Mapping is left biased meaning that first element with specific primary key in array is used
  2. for each object in json array primary key is extracted and is looked up in old elements mapping
  3. if mapping is found then element is updated, if mapping is not found then element is parsed
  4. in all cases the order of elements in the *new* array is respected

Example:

unjsonArrayOfIntToInt :: UnjsonDef [(Int,Int)]
unjsonArrayOfIntToInt = arrayWithPrimaryKeyOf
                             (fst)
                             (objectOf $ pure id
                                <*> field "key" id "Key in mapping")
                             (objectOf $ pure (,)
                                <*> field "key" fst "Key in mapping"
                                <*> field "value" fst "Value in mapping")

arrayWithModeAndPrimaryKeyOf :: (Ord pk, Typeable a) => ArrayMode -> (a -> pk) -> UnjsonDef pk -> UnjsonDef a -> UnjsonDef [a] Source #

Declare array of objects with given parsers that should be matched by a primary key and accepts mode specifier.

For discussion of primary key see arrayWithPrimaryKeyOf. For discussion of array modes see ArrayMode.

Example:

unjsonArrayOfIntToInt :: UnjsonDef [(Int,Int)]
unjsonArrayOfIntToInt = arrayWithPrimaryKeyOf ArrayModeParseSingle
                             (fst)
                             (objectOf $ pure id
                                <*> field "key" id "Key in mapping")
                             (objectOf $ pure (,)
                                <*> field "key" fst "Key in mapping"
                                <*> field "value" fst "Value in mapping")

data ArrayMode Source #

Specify how arrays should be handled. Default is ArrayModeStrict that does not do anything special with arrays.

ArrayMode is used in arrayWithModeAndPrimaryKeyOf and arrayWithModeOf.

Constructors

ArrayModeStrict

Require JSON array. On output always output array.

ArrayModeParseSingle

Allow non-array element, in that case it will be treated as a single element array. On output always output array.

ArrayModeParseAndOutputSingle

Allow non-array element, in that case it will be treated as a single element array. On output output single element if array has one element.

Instances
Eq ArrayMode Source # 
Instance details

Defined in Data.Unjson

Ord ArrayMode Source # 
Instance details

Defined in Data.Unjson

Show ArrayMode Source # 
Instance details

Defined in Data.Unjson

Maps, enums, sums

mapOf :: Typeable x => UnjsonDef x -> UnjsonDef (HashMap Text x) Source #

Gather all keys with respective values in a map.

Example:

data X = X { xMap :: LazyHashMap.HashMap Text.Text x }

objectOf $ pure X
  <*> fieldBy "xmap" xMap
      "Map string to Y value"
      (mapOf unjsonY)

Note that overloading allows for automatic conversion to more map types, for example:

data X = X { xMap :: Map.Map String x }

objectOf $ pure X
  <*> field "xmap" xMap
      "Map string to Y value"

enumOf :: Eq k => Text -> [(Text, k)] -> UnjsonDef k Source #

Provide sum type support for parameterless constructors.

For related functionality see disjointUnionOf.

Example:

data X = A | B

unjsonX = enumOf "type_thing"
            [("a_thing", A),
             ("b_thing", B)]

enumUnjsonDef :: forall a. (Eq a, Typeable a, Enum a, Bounded a, Data a) => UnjsonDef a Source #

Automatic sum type conversion with parameterless constructors.

Basically an automatic version of enumOf.

Example:

data X = A | B deriving (Eq, Data, Enum, Bounded)

instance Unjson X where unjsonDef = enumUnjsonDef

disjointUnionOf :: Text -> [(Text, k -> Bool, Ap (FieldDef k) k)] -> UnjsonDef k Source #

Provide sum type support. Bidirectional case matching in Haskell is not good, so some obvious information needs to be given manually.

For related functionality see enumOf.

Example:

data X = A { aString :: String } | B { bInt :: Int }
            deriving (Data,Typeable)

unjsonX = disjointUnionOf "type"
            [("a_thing", unjsonIsConstrByName "A",
              pure A <*> field "string" "A string value"),
             ("b_thing", unjsonIsConstrByName "B",
              pure B <*> field "string" "An int value")]

Note that each case in the list must be able to discriminate between constructors in a data type and it has to be able to this both ways: to find out based on json contents which constructor applies and also based on data contructor which of serialization cases to use.

Note that unjsonIsConstrByName is helpful, but you may use usual case ... of if you do not like the Data typeclass.

unionOf :: [(k -> Bool, Ap (FieldDef k) k)] -> UnjsonDef k Source #

Provide sum type support, non-disjoin version. Bidirectional case matching in Haskell is not good, so some obvious information needs to be given manually.

For related functionality see enumOf.

Example:

data X = A { aString :: String } | B { bInt :: Int }
            deriving (Data,Typeable)

unjsonX = unionOf
            [(unjsonIsConstrByName "A",
              pure A <*> field "string" "A string value"),
             (unjsonIsConstrByName "B",
              pure B <*> field "int" "An int value")]

Note that each case in the list must be able to discriminate between constructors in a data type and it has to be able to this both ways: to find out based on json contents which constructor applies and also based on data contructor which of serialization cases to use. To know what constructor to use at parsing time unjson looks at fields present in json object and on list of field names required to satisfy. First constructor for which all fields are present is chosen.

Note that unjsonIsConstrByName is helpful, but you may use usual case ... of if you do not like the Data typeclass.

Helpers

unjsonAeson :: forall a. (FromJSON a, ToJSON a, Typeable a) => UnjsonDef a Source #

Use fromJSON and toJSON to create a UnjsonDef. This function is useful when lifted type is one of the primitives. Although it can be used to lift user defined instances, it is not advisable as there is too much information lost in the process and proper error infomation is not possible. Use full UnjsonDef instance whenever possible.

Example:

instance FromJSON MyType where ...
instance ToJSON MyType where ...
instance Unjson MyType where
    unjsonDef = unjsonAeson

unjsonAesonWithDoc :: (FromJSON a, ToJSON a) => Text -> UnjsonDef a Source #

Like unjsonAeson but accepts docstring as additional parameter that should identify type.

Documentation rendering

render :: UnjsonDef a -> String Source #

Renders documentation for a parser into a multiline string. It is expected that this string is a human readable representation that can go directly to console.

Example rendering:

hostname (req):
    The hostname this service is visible as
    Text
port (def):
    Port to listen on, defaults to 80
    Int
credentials (req):
    User admin credentials
    username (req):
        Name of the user
        Text
    password (req):
        Password for the user
        Text
    domain (opt):
        Domain for user credentials
        Text
comment (opt):
    Optional comment, free text
    Text
options (def):
    Additional options, defaults to empty
    array of:
        Text
alternates (opt):
    Alternate names for this server
    tuple of size 2 with elements:
    0:
        Text
    1:
        username (req):
            Name of the user
            Text
        password (req):
            Password for the user
            Text
        domain (opt):
            Domain for user credentials
            Text

renderForPath :: MonadFail m => Path -> UnjsonDef a -> m String Source #

Render only selected part of structure documentation. Path should point to a subtree, if it does not then Nothing is returned.

renderDoc :: UnjsonDef a -> Doc Source #

Renders documentation for a parser into a Doc. See render for example.

renderDocForPath :: MonadFail m => Path -> UnjsonDef a -> m Doc Source #

Render only selected part of structure documentation as Doc. Path should point to a subtree, if it does not then Nothing is returned.

Parsing and updating

parse :: UnjsonDef a -> Value -> Result a Source #

Parse JSON according to unjson definition.

Example:

let json = Aeson.object [ ... ]
let Result val iss = parse unjsonThing json
if null iss
  then putStrLn ("Parsed: " ++ show val)
  else putStrLn ("Not parsed, issues: " ++ show iss)

Error reporting is a strong side of Unjson, see Result.

For parsing of fields the following rules apply:

  • required fields generate an error if json key is missing
  • for optional fields Nothing is returned if json key is missing, Just value otherwise
  • for fields with default value, the default value is returned if key is missing, otherwise the parsed value is returned

Note that Unjson makes strong difference between missing keys and values that result in parse errors.

For discussion of update mode see update.

update :: a -> UnjsonDef a -> Value -> Result a Source #

Update object with JSON according to unjson definition.

Example:

let original = Thing { ... }
let json = Aeson.object [ ... ]
let Result val iss = update original unjsonThing (Anchored [] json)
if null iss
  then putStrLn ("Updated: " ++ show val)
  else putStrLn ("Not updated, issues: " ++ show iss)

Error reporting is a strong side of Unjson, see Result.

For updating of fields the following rules apply:

  • required fields take the original value if json key is missing
  • optional fields take the original value if json key is missing unless the value is null, then Nothing is returned (reset to Nothing)
  • fields with default value take the original value if json key is missing unless the value is null, then the default value is returned (reset to default)

Note that Unjson makes strong difference between missing keys and values that result in parse errors.

For discussion of parse mode see parse.

data Result a Source #

Parsing result. The value a is only reliable when Problems is an empty list.

Problems is list of issues encountered while parsing. Unjson parsers continue forward and are able to find many problems at once.

Note that problems are anchored to specific elements of JSON so it should be easy to find and spot an error.

Even if list of problems is not empty, the returned value may be partially usable.

Examples of list of problems:

[Anchored [PathElemKey "credentials",PathElemKey "password"] "missing key",
 Anchored [PathElemKey "tuple"] "cannot parse array of length 3 into tuple of size 4",
 Anchored [PathElemKey "text_array",PathElemIndex 0.PathElemKey "value"]
                                 "when expecting a Text, encountered Boolean instead"]

conveniently rendered as:

"credentials.password": "missing key"
"tuple": "cannot parse array of length 3 into tuple of size 4"
"text_array[0].value": "when expecting a Text, encountered Boolean instead"

Constructors

Result a Problems 
Instances
Monad Result Source # 
Instance details

Defined in Data.Unjson

Methods

(>>=) :: Result a -> (a -> Result b) -> Result b #

(>>) :: Result a -> Result b -> Result b #

return :: a -> Result a #

fail :: String -> Result a #

Functor Result Source # 
Instance details

Defined in Data.Unjson

Methods

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

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

MonadFail Result Source # 
Instance details

Defined in Data.Unjson

Methods

fail :: String -> Result a #

Applicative Result Source # 
Instance details

Defined in Data.Unjson

Methods

pure :: a -> Result a #

(<*>) :: Result (a -> b) -> Result a -> Result b #

liftA2 :: (a -> b -> c) -> Result a -> Result b -> Result c #

(*>) :: Result a -> Result b -> Result b #

(<*) :: Result a -> Result b -> Result a #

Eq a => Eq (Result a) Source # 
Instance details

Defined in Data.Unjson

Methods

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

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

Ord a => Ord (Result a) Source # 
Instance details

Defined in Data.Unjson

Methods

compare :: Result a -> Result a -> Ordering #

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

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

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

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

max :: Result a -> Result a -> Result a #

min :: Result a -> Result a -> Result a #

Show a => Show (Result a) Source # 
Instance details

Defined in Data.Unjson

Methods

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

show :: Result a -> String #

showList :: [Result a] -> ShowS #

data Anchored a Source #

A value at a specific position in JSON object.

Constructors

Anchored Path a 
Instances
Functor Anchored Source # 
Instance details

Defined in Data.Unjson

Methods

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

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

Eq a => Eq (Anchored a) Source # 
Instance details

Defined in Data.Unjson

Methods

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

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

Ord a => Ord (Anchored a) Source # 
Instance details

Defined in Data.Unjson

Methods

compare :: Anchored a -> Anchored a -> Ordering #

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

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

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

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

max :: Anchored a -> Anchored a -> Anchored a #

min :: Anchored a -> Anchored a -> Anchored a #

Show a => Show (Anchored a) Source # 
Instance details

Defined in Data.Unjson

Methods

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

show :: Anchored a -> String #

showList :: [Anchored a] -> ShowS #

(Typeable a, Show a) => Exception (Anchored a) Source # 
Instance details

Defined in Data.Unjson

type Problem = Anchored Text Source #

Problem information is represented as a Text attached to a specific point in the JSON represenation tree.

type Problems = [Problem] Source #

In general JSON deserialization may result in many problems. Unjson reports all the problems at once.

newtype Path Source #

Paths are rendered in a nice way. For example: key.key2[34] indexes into "key", then into "key2" then into index 34 of an array.

Constructors

Path [PathElem] 
Instances
Eq Path Source # 
Instance details

Defined in Data.Unjson

Methods

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

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

Ord Path Source # 
Instance details

Defined in Data.Unjson

Methods

compare :: Path -> Path -> Ordering #

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

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

(>) :: Path -> Path -> Bool #

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

max :: Path -> Path -> Path #

min :: Path -> Path -> Path #

Show Path Source # 
Instance details

Defined in Data.Unjson

Methods

showsPrec :: Int -> Path -> ShowS #

show :: Path -> String #

showList :: [Path] -> ShowS #

Semigroup Path Source # 
Instance details

Defined in Data.Unjson

Methods

(<>) :: Path -> Path -> Path #

sconcat :: NonEmpty Path -> Path #

stimes :: Integral b => b -> Path -> Path #

Monoid Path Source # 
Instance details

Defined in Data.Unjson

Methods

mempty :: Path #

mappend :: Path -> Path -> Path #

mconcat :: [Path] -> Path #

data PathElem Source #

Describe a path from root JSON element to a specific position. JSON has only two types of containers: objects and arrays, so there are only two types of keys needed to index into those containers: Int and Text. See Path.

Instances
Eq PathElem Source # 
Instance details

Defined in Data.Unjson

Ord PathElem Source # 
Instance details

Defined in Data.Unjson

Show PathElem Source # 
Instance details

Defined in Data.Unjson

unjsonInvmapR :: (a -> Result b) -> (b -> a) -> UnjsonDef a -> UnjsonDef b Source #

unjsonIsConstrByName :: Data a => String -> a -> Bool Source #

Useful in DisjointUnjsonDef as second element in tuples list to check out if constructor is matching.

Example:

data X = A | B | C
unjsonIsConstrByName "B" B => True

unjsonIPv4AsWord32 :: UnjsonDef Word32 Source #

Parse and serialize dotted decimal notation for IPv4 addresses and uses Word32 as representation type. Note that network byte order applies, so 127.0.0.1 is 0x7F000001.