Safe Haskell | None |
---|---|
Language | Haskell2010 |
Types and Functions for turning JSON into Haskell.
We will work through a basic example, using the following type:
data Person = Person { _personName :: Text , _personAge :: Int , _personAddress :: Text , _personFavouriteLotteryNumbers :: [Int] } deriving (Eq, Show)
Expect the following JSON as input:
{ "name": "Krag" , "age": 88 , "address": "Red House 4, Three Neck Lane, Greentown." , "numbers": [86,3,32,42,73] }
We'll need to import the Decode
module. You may of course use whatever import scheme you like,
I prefer this method:
import Waargonaut.Decode (Decoder) import qualified Waargonaut.Decode as D
The Decoder
is based upon a data structure called a zipper
. This allows us
to move around the JSON structure using arbitrary movements. Such as
moveRight1
to move from a key on an object to the value at that key. Or
down
to move into the first element of an array or object. Waargonaut
provides a suite of these functions to move around and dissect the JSON input.
This zipper is combined with a StateT
transformer that maintains a history of your movements.
So if the JSON input is not as your Decoder
expects you are given a complete
path to where things went awry.
Decoding a JSON value is done by moving the cursor to specific points of interest, then focusing
on that point with a Decoder
of the desired value.
NB: The Monad constraint is provided as a flexibility for more interesting and nefarious uses
of Decoder
.
Here is the Decoder
for our Person
data type. It will help to turn on the
OverloadedStrings
language pragma as these functions expect Text
input.
personDecoder :: Monad f => Decoder f Person personDecoder = D.withCursor $ \c -> do o <- D.down c name <- D.fromKey "name" D.text o age <- D.fromKey "age" D.int o addr <- D.fromKey "address" D.text o lotto <- D.fromKey "numbers" (D.list D.int) o pure $ Person name age addr lotto
The withCursor
function provides our cursor: c
. We then move
down
into the JSON object. The reasons for this are:
- The initial cursor position is always at the very beginning of the input. On freshly indexed JSON input, using our example, the cursor will be at:
<cursor>{ "name": "Krag" , "age": 88 ...
- Because of the above reason, our decoder makes an assumption about the placement of the cursor on the JSON input. This sort of assumption is reasonable for reasons we will go over later.
The cursor output from down
will located here:
{ <cursor>"name": "Krag" , "age": 88 ...
Then we use one of the helper functions, fromKey
to find the "key - value"
pair that we're interested in and decode it for us:
fromKey :: Monad f => Text -> Decoder f b -> JCurs -> DecodeResult f b
We could also write this Decoder
as:
personDecoder2 :: Monad f => Decoder f Person personDecoder2 = Person <$> D.atKey "name" D.text <*> D.atKey "age" D.int <*> D.atKey "address" D.text <*> D.atKey "numbers" (D.list D.int)
Using the atKey
function which tries to handle those basic movements for us
and has those assumptions included. Very useful for when the JSON input closely mirrors your data
structure.
atKey :: Monad f => Text -> Decoder f a -> Decoder f a
The next part is being able to apply our Decoder
to some input. Assuming we
have some input. We want to pass it through our personDecoder
for a result. Waargonaut uses
the parsers package to define its parser. This
allows you to choose your own favourite parsing library to do the heavy lifting. Provided it
implements the right typeclasses from the parsers
package.
To apply a Decoder
to some input you will need one of the
decoder running functions from Decode
. There are a few different
functions provided for some of the common input text-like types.:
decodeFromByteString :: ( CharParsing f , Monad f , Monad g , Show e ) => (forall a. f a -> ByteString -> Either e a) -> Decoder g x -> ByteString -> g (Either (DecodeError, CursorHistory) x)
As well as a parsing function from your parsing library of choice, that also
has an implementation of the CharParsing
typeclass from parsers
. We will
use attoparsec
in the examples below.
import qualified Data.Attoparsec.ByteString as AB
decodeFromByteString AB.parseOnly personDecode inp
Which will run the personDecode
Decoder
using the parsing function
(AB.parseOnly
), starting at the cursor from the top of the inp
input.
Again the Monad
constraint is there so that you have more options available for utilising the
Decoder
in ways we haven't thought of.
Or if you don't need the Monad
constraint then you may use pureDecodeFromByteString
.
This function specialises the Monad
constraint to Identity
.:
pureDecodeFromByteString :: ( Monad f , CharParsing f , Show e ) => (forall a. f a -> ByteString -> Either e a) -> Decoder Identity x -> ByteString -> Either (DecodeError, CursorHistory) x
pureDecodeFromByteString AB.parseOnly personDecode inp
Waargonaut provides some default implementations using the attoparsec package in the Waargonaut.Attoparsec
module. These functions have exactly the same behaviour as the functions above, without the need to provide the parsing function.
Synopsis
- type CursorHistory = CursorHistory' Count
- type Cursor = GenericCursor ByteString CsPoppy1 (RangeMin CsPoppy1)
- newtype DecodeResult f a = DecodeResult {}
- newtype Decoder f a = Decoder {
- runDecoder :: ParseFn -> JCurs -> DecodeResultT Count DecodeError f a
- newtype JCurs = JCurs {}
- data Err c e
- = Parse e
- | Decode (DecodeError, c)
- data JsonType
- module Waargonaut.Decode.Runners
- generaliseDecoder :: Monad f => Decoder Identity a -> Decoder f a
- ppCursorHistory :: CursorHistory' i -> Doc a
- withCursor :: (JCurs -> DecodeResult f a) -> Decoder f a
- mkCursor :: ByteString -> JCurs
- cursorRankL :: Lens' Cursor Count
- manyMoves :: Monad m => Natural -> (b -> m b) -> b -> m b
- down :: Monad f => JCurs -> DecodeResult f JCurs
- up :: Monad f => JCurs -> DecodeResult f JCurs
- try :: MonadError e m => m a -> m (Maybe a)
- moveRightN :: Monad f => Natural -> JCurs -> DecodeResult f JCurs
- moveRight1 :: Monad f => JCurs -> DecodeResult f JCurs
- moveLeftN :: Monad f => Natural -> JCurs -> DecodeResult f JCurs
- moveLeft1 :: Monad f => JCurs -> DecodeResult f JCurs
- moveToKey :: Monad f => Text -> JCurs -> DecodeResult f JCurs
- moveToRankN :: Monad f => Word64 -> JCurs -> DecodeResult f JCurs
- jsonAtCursor :: Monad f => (ByteString -> Either DecodeError a) -> JCurs -> DecodeResult f a
- fromKey :: Monad f => Text -> Decoder f b -> JCurs -> DecodeResult f b
- atKey :: Monad f => Text -> Decoder f a -> Decoder f a
- focus :: Monad f => Decoder f a -> JCurs -> DecodeResult f a
- fromKeyOptional :: Monad f => Text -> Decoder f b -> JCurs -> DecodeResult f (Maybe b)
- atKeyOptional :: Monad f => Text -> Decoder f b -> Decoder f (Maybe b)
- withType :: Monad f => JsonType -> (JCurs -> DecodeResult f a) -> JCurs -> DecodeResult f a
- jsonTypeAt :: JsonTypeAt a => a -> Maybe JsonType
- leftwardCons :: (Monad f, Cons s s a a) => s -> Decoder f a -> JCurs -> DecodeResult f s
- rightwardSnoc :: (Monad f, Snoc s s a a) => s -> Decoder f a -> JCurs -> DecodeResult f s
- foldCursor :: Monad f => (b -> a -> b) -> (JCurs -> DecodeResult f JCurs) -> b -> Decoder f a -> JCurs -> DecodeResult f b
- rank :: Monad f => Decoder f Count
- prismD :: Monad f => Prism' a b -> Decoder f a -> Decoder f (Maybe b)
- prismDOrFail :: Monad f => DecodeError -> Prism' a b -> Decoder f a -> Decoder f b
- prismDOrFail' :: Monad f => (a -> DecodeError) -> Prism' a b -> Decoder f a -> Decoder f b
- json :: Monad f => Decoder f Json
- int :: Monad f => Decoder f Int
- scientific :: Monad f => Decoder f Scientific
- integral :: (Monad f, Integral n, Bounded n) => Decoder f n
- string :: Monad f => Decoder f String
- strictByteString :: Monad f => Decoder f ByteString
- lazyByteString :: Monad f => Decoder f ByteString
- unboundedChar :: Monad f => Decoder f Char
- boundedChar :: Monad f => Decoder f Char
- text :: Monad f => Decoder f Text
- bool :: Monad f => Decoder f Bool
- null :: Monad f => Decoder f ()
- nonemptyAt :: Monad f => Decoder f a -> JCurs -> DecodeResult f (NonEmpty a)
- nonempty :: Monad f => Decoder f a -> Decoder f (NonEmpty a)
- listAt :: Monad f => Decoder f a -> JCurs -> DecodeResult f [a]
- list :: Monad f => Decoder f a -> Decoder f [a]
- objectAsKeyValuesAt :: Monad f => Decoder f k -> Decoder f v -> JCurs -> DecodeResult f [(k, v)]
- objectAsKeyValues :: Monad f => Decoder f k -> Decoder f v -> Decoder f [(k, v)]
- withDefault :: Monad f => a -> Decoder f (Maybe a) -> Decoder f a
- maybeOrNull :: Monad f => Decoder f a -> Decoder f (Maybe a)
- either :: Monad f => Decoder f a -> Decoder f b -> Decoder f (Either a b)
- oneOf :: (Foldable g, Monad f, Eq a) => Decoder f a -> Text -> g (a, b) -> Decoder f b
- passKeysToValues :: (Snoc c c v v, Monad f) => c -> Decoder f k -> (k -> Decoder f v) -> Decoder f c
Types
type CursorHistory = CursorHistory' Count Source #
We define the index of our CursorHistory'
to be the Count
.
type Cursor = GenericCursor ByteString CsPoppy1 (RangeMin CsPoppy1) #
newtype DecodeResult f a Source #
Provide some of the type parameters that the underlying DecodeResultT
requires. This contains the state and error management as we walk around our
zipper and decode our JSON input.
Addtionally we keep our parsing function in a ReaderT
such that it's
accessible for all of the decoding steps.
Instances
Decoder | |
|
Instances
Monad f => MonadError DecodeError (Decoder f) Source # | |
Defined in Waargonaut.Decode.Types throwError :: DecodeError -> Decoder f a # catchError :: Decoder f a -> (DecodeError -> Decoder f a) -> Decoder f a # | |
Monad f => Monad (Decoder f) Source # | |
Functor f => Functor (Decoder f) Source # | |
Monad f => Applicative (Decoder f) Source # | |
Monad f => Alt (Decoder f) Source # | |
MFunctor Decoder Source # | |
Wrapper type for the SuccinctCursor
Instances
JsonTypeAt JCurs Source # | |
Defined in Waargonaut.Decode.Types | |
Wrapped JCurs Source # | |
JCurs ~ t => Rewrapped JCurs t Source # | |
Defined in Waargonaut.Decode.Types | |
type Unwrapped JCurs Source # | |
Defined in Waargonaut.Decode.Types |
Convenience Error structure for the separate parsing/decoding phases. For when things really aren't that complicated.
Parse e | |
Decode (DecodeError, c) |
Runners
module Waargonaut.Decode.Runners
Helpers
ppCursorHistory :: CursorHistory' i -> Doc a Source #
Pretty print the given CursorHistory'
to a more useful format compared to a Seq
of i
.
Cursors
withCursor :: (JCurs -> DecodeResult f a) -> Decoder f a Source #
Function to define a Decoder
for a specific data type.
For example, given the following data type:
data Image = Image { _imageW :: Int , _imageH :: Int , _imageTitle :: Text , _imageAnimated :: Bool , _imageIDs :: [Int] }
We can use withCursor
to write a decoder that
will be given a cursor that we can use to build the data types that
we need.
imageDecoder :: Monad f => Decoder f Image imageDecoder = withCursor $ \curs -> D.down curs >>= Image <$> D.fromKey "Width" D.int curs <*> D.fromKey "Height" D.int curs <*> D.fromKey "Title" D.text curs <*> D.fromKey "Animated" D.bool curs <*> D.fromKey "IDs" intArray curs
It's up to you to provide a cursor that is at the correct position for a
Decoder
to operate, but building decoders in this way simplifies creating
decoders for larger structures, as the smaller pieces contain fewer
assumptions. This encourages greater reuse of decoders and simplifies the
debugging process.
mkCursor :: ByteString -> JCurs Source #
Take a ByteString
input and build an index of the JSON structure inside
manyMoves :: Monad m => Natural -> (b -> m b) -> b -> m b Source #
Execute the given function n
times.
down :: Monad f => JCurs -> DecodeResult f JCurs Source #
Move the cursor down or into the child of the current cursor position.
The following examples use "*" to represent the cursor position.
Starting position:
*{"fred": 33, "sally": 44 }
After moving down
:
{ *"fred": 33, "sally": 44 }
This function will also move into the elements in an array:
Starting position:
*[1,2,3]
After moving down
:
[*1,2,3]
This function is essential when dealing with the inner elements of objects or
arrays. As you must first move down
into the focus. However, you cannot
move down into an empty list or empty object. The reason for this is that
there will be nothing in the index for the element at the first position.
Thus the movement will be considered invalid.
These will fail if you attempt to move down
:
*[]
*{}
up :: Monad f => JCurs -> DecodeResult f JCurs Source #
Move the cursor up into the parent of the current cursor position.
The following examples use "*" to represent the cursor position.
Starting position:
{ "fred": 33, *"sally": 44 }
After moving up
:
*{"fred": 33, "sally": 44 }
try :: MonadError e m => m a -> m (Maybe a) Source #
moveRightN :: Monad f => Natural -> JCurs -> DecodeResult f JCurs Source #
Move the cursor rightwards n
times.
Starting position:
[*1, 2, 3]
After moveRightN 2
:
[1, 2, *3]
moveRight1 :: Monad f => JCurs -> DecodeResult f JCurs Source #
Helper function to move right once.
moveLeftN :: Monad f => Natural -> JCurs -> DecodeResult f JCurs Source #
Move the cursor leftwards n
times.
moveToKey :: Monad f => Text -> JCurs -> DecodeResult f JCurs Source #
Attempt to move to the value at a given key on the current JSON object.
This will only work if you have already moved down
into the JSON object,
because the cursor allows you to step over an entire object in a single. It has
to be told to move into the object first, otherwise it will not look in the
correct location for keys.
Cursor position indicated by "*".
Assuming cursor positioned here:
*{ "foo": 33, "fieldB": "pew pew" }
This won't work, because we're AT the object, not IN the object:
moveToKey "foo" cursor
This will work, because we've moved down
INTO the object:
down cursor >>= moveToKey "foo"
moveToRankN :: Monad f => Word64 -> JCurs -> DecodeResult f JCurs Source #
Given a rank
value, attempt to move the cursor directly to that position.
Returns a InputOutOfBounds
error if that position is invalid.
Decoding at cursor
jsonAtCursor :: Monad f => (ByteString -> Either DecodeError a) -> JCurs -> DecodeResult f a Source #
Using the given parsing function, attempt to decode the value of the
ByteString
at the current cursor position.
atKey :: Monad f => Text -> Decoder f a -> Decoder f a Source #
A simplified version of fromKey
that takes a Text
value indicating a
key to be moved to and decoded using the given 'Decoder f a'. If you don't
need any special cursor movements to reach the list of keys you require, you
could use this function to build a trivial Decoder
for a record type:
This decoder assumes it is positioned at the top of an object and will move
down
each time, before attempting to find the given key.
data MyRec = MyRec { fieldA :: Text, fieldB :: Int } myRecDecoder :: Decoder f MyRec myRecDecoder = MyRec <$> atKey "field_a" text <*> atKey "field_b" int
focus :: Monad f => Decoder f a -> JCurs -> DecodeResult f a Source #
Using the given Decoder
, try to decode the current focus.
myIntList <- focus (list int) cursor
Attempting decoding
fromKeyOptional :: Monad f => Text -> Decoder f b -> JCurs -> DecodeResult f (Maybe b) Source #
atKeyOptional :: Monad f => Text -> Decoder f b -> Decoder f (Maybe b) Source #
A version of atKey
that returns its result in Maybe
. If the key is
not present in the object, Nothing
is returned. If the key is present,
decoding will be performed as with atKey
.
For example, if a key could be absent and could be null if present, it could be decoded as follows:
join <$> atKeyOptional "key" (maybeOrNull text)
Inspection
withType :: Monad f => JsonType -> (JCurs -> DecodeResult f a) -> JCurs -> DecodeResult f a Source #
jsonTypeAt :: JsonTypeAt a => a -> Maybe JsonType #
Provided Decoders
leftwardCons :: (Monad f, Cons s s a a) => s -> Decoder f a -> JCurs -> DecodeResult f s Source #
From the current cursor position, move leftwards one position at a time and
push each a
onto the front of some Cons
structure.
rightwardSnoc :: (Monad f, Snoc s s a a) => s -> Decoder f a -> JCurs -> DecodeResult f s Source #
From the current cursor position, move rightwards one position at a time,
and append the a
to some Snoc
structure.
foldCursor :: Monad f => (b -> a -> b) -> (JCurs -> DecodeResult f JCurs) -> b -> Decoder f a -> JCurs -> DecodeResult f b Source #
Higher order function for combining a folding function with repeated cursor movements. This lets you combine arbitrary cursor movements with an accumulating function.
The functions leftwardCons
and rightwardSnoc
are both implemented using
this function.
leftwardCons = foldCursor (flip cons) moveLeft1
rightwardSnoc = foldCursor snoc moveRight1
rank :: Monad f => Decoder f Count Source #
At the given cursor position, return the Count
or rank
of that
position. Useful if you want to build a map of a complicated structure such that
you're able to optimise your Decoder
by using moveToRankN
instead of
individual cursor movements.
prismDOrFail :: Monad f => DecodeError -> Prism' a b -> Decoder f a -> Decoder f b Source #
prismDOrFail' :: Monad f => (a -> DecodeError) -> Prism' a b -> Decoder f a -> Decoder f b Source #
Like prismDOrFail
, but lets you use the a
to construct the error.
json :: Monad f => Decoder f Json Source #
Decode the Json
structure at the cursor. Useful if you don't have a need
to convert the Json and only want to make changes before sending it on its way.
scientific :: Monad f => Decoder f Scientific Source #
Decode a Scientific
number value.
integral :: (Monad f, Integral n, Bounded n) => Decoder f n Source #
Decoder for some Integral
type. This conversion is walked through Mayan,
I mean, Scientific
to try to avoid numeric explosion issues.
strictByteString :: Monad f => Decoder f ByteString Source #
Decode a strict ByteString
value.
lazyByteString :: Monad f => Decoder f ByteString Source #
Decode a lazy ByteString
value.
null :: Monad f => Decoder f () Source #
Decode an explicit null
value at the current cursor position.
nonemptyAt :: Monad f => Decoder f a -> JCurs -> DecodeResult f (NonEmpty a) Source #
nonempty :: Monad f => Decoder f a -> Decoder f (NonEmpty a) Source #
Helper to create a 'NonEmpty a' Decoder
.
listAt :: Monad f => Decoder f a -> JCurs -> DecodeResult f [a] Source #
Like nonemptyAt
, this takes a Decoder
of a
and at the given cursor
will try to decode a '[a]'.
list :: Monad f => Decoder f a -> Decoder f [a] Source #
Helper function to simplify writing a '[]' decoder.
objectAsKeyValuesAt :: Monad f => Decoder f k -> Decoder f v -> JCurs -> DecodeResult f [(k, v)] Source #
Try to decode an object using the given key and value Decoder
s at the
given cursor.
objectAsKeyValues :: Monad f => Decoder f k -> Decoder f v -> Decoder f [(k, v)] Source #
Helper function to simplify writing a '{}' decoder.
withDefault :: Monad f => a -> Decoder f (Maybe a) -> Decoder f a Source #
Try to decode an optional value, returning the given default value if
Nothing
is returned.
maybeOrNull :: Monad f => Decoder f a -> Decoder f (Maybe a) Source #
Named to match it's Encoder
counterpart, this function will decode an
optional value.
oneOf :: (Foldable g, Monad f, Eq a) => Decoder f a -> Text -> g (a, b) -> Decoder f b Source #
Helper function for "pattern matching" on a decoded value to some Haskell
value. The Text
argument is used in the error message should this decoder
fail. Normally it would simply be the name of the type you are writing the
decoder for.
This is useful for decoding sum types, such as:
data MyEnum = A | B | C decodeMyEnum :: Monad f => Decoder f MyEnum decodeMyEnum = D.oneOf D.text "MyEnum" [ ("a", A) , ("b", B) , ("c", C) ] decodeMyEnumFromInt :: Monad f => Decoder f MyEnum decodeMyEnumFromInt = D.oneOf D.int "MyEnum" [ (1, A) , (2, B) , (3, C) ]
passKeysToValues :: (Snoc c c v v, Monad f) => c -> Decoder f k -> (k -> Decoder f v) -> Decoder f c Source #
A specialised decoder for moving over a JSON object where the keys are values that you would like to have as part of the value at the different keys.
An example of such an input is:
{ "Collection" : { "BobsInput_ce43dff22": { "someValue": "Some data" }, "FredsInput_a4b32def": { "someValue": "Some different data" } }
Where those key values like "XInput_YYYY" are to be included in the object.
Given a type like this:
data ContainsItsKey = ContainsItsKey { _containsItsKey_KeyValue :: Text , _containsItsKey_SomeValue :: Text }
To decode the above you would use this function like so:
takesKeyDecoder :: Monad f => Text -> Decoder f ContainsItsKey takesKeyDecoder k = ContainsItsKey k <$> D.atKey "someValue" D.text collectionDecoder :: Monad f => Decoder f [ContainsItsKey] collectionDecoder = D.atKey "Collection" $ D.passKeysToValues [] D.text takesKeyDecoder