Safe Haskell | None |
---|---|
Language | Haskell2010 |
Types and Functions for turning JSON into Haskell.
Synopsis
- type CursorHistory = CursorHistory' Count
- type SuccinctCursor = JsonCursor ByteString Poppy512 (SimpleBalancedParens (Vector Word64))
- newtype DecodeResult f a = DecodeResult {}
- newtype Decoder f a = Decoder {
- runDecoder :: ParseFn -> JCurs -> DecodeResultT Count DecodeError f a
- newtype JCurs = JCurs {}
- type ParseFn = ByteString -> Either DecodeError Json
- data Err c e
- = Parse e
- | Decode (DecodeError, c)
- runDecode :: Monad f => Decoder f a -> ParseFn -> JCurs -> f (Either (DecodeError, CursorHistory) a)
- runDecodeResult :: Monad f => ParseFn -> DecodeResult f a -> f (Either (DecodeError, CursorHistory) a)
- runPureDecode :: Decoder Identity a -> ParseFn -> JCurs -> Either (DecodeError, CursorHistory) a
- simpleDecode :: Decoder Identity a -> ParseFn -> ByteString -> Either (DecodeError, CursorHistory) a
- overrideParser :: Monad f => ParseFn -> DecodeResult f a -> DecodeResult f a
- 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' (JsonCursor s i p) 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
- 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 :: MonadError DecodeError f => 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
- 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]
- 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)
Types
type CursorHistory = CursorHistory' Count Source #
We define the index of our CursorHistory'
to be the Count
.
type SuccinctCursor = JsonCursor ByteString Poppy512 (SimpleBalancedParens (Vector Word64)) Source #
Convenience alias defined for the concrete JsonCursor
type.
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 | |
|
Wrapper type for the SuccinctCursor
type ParseFn = ByteString -> Either DecodeError Json Source #
Another convenience alias for the type of the function we will use to parse the input string
into the Json
structure.
Convenience Error structure for the separate parsing/decoding phases. For when things really aren't that complicated.
Parse e | |
Decode (DecodeError, c) |
Runners
runDecode :: Monad f => Decoder f a -> ParseFn -> JCurs -> f (Either (DecodeError, CursorHistory) a) Source #
Run a Decoder
for the final result to see if you have your a
or an error.
runDecodeResult :: Monad f => ParseFn -> DecodeResult f a -> f (Either (DecodeError, CursorHistory) a) Source #
Using the ParseFn
, complete a DecodeResult
to find out if we have the type we're after. This
is mostly used internally to help build Decoder
structures. Exported as it may prove useful
when abstracting over the Decoder
types or other such shenanigans.
runPureDecode :: Decoder Identity a -> ParseFn -> JCurs -> Either (DecodeError, CursorHistory) a Source #
Similar to the simpleDecode
function, however this function expects
you've already converted your input to a JCurs
.
simpleDecode :: Decoder Identity a -> ParseFn -> ByteString -> Either (DecodeError, CursorHistory) a Source #
Basic usage of a Decoder
is to specialise the f
to be Identity
, then
provide the ParseFn
and the ByteString
input. This will run the Decoder
to
try to parse and decode the JSON to the a
you require.
This function takes care of converting the ByteString
to a JCurs
.
simpleDecode (list int) myParseFn "[1,2,3]" = Right [1,2,3]
overrideParser :: Monad f => ParseFn -> DecodeResult f a -> DecodeResult f a Source #
This function lets you override the parsing function that is being used in
a decoder for a different one. This means that when building your Decoder
you
are not bound to only using a single parsing function. If you have specific
needs for alternate parsers then you can use this function in your Decoder
to
make that change.
myTricksyObj = withCursor $ curs -> do curs' <- down curs fA <- fromKey "normalFieldA" int curs' fB <- fromKey "normalFieldB" text curs' wB <- overrideParser handTunedParser $ fromKey "weirdFieldC" fieldCDecoder curs' pure $ Foo fA fB wB
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
cursorRankL :: Lens' (JsonCursor s i p) Count Source #
Lens for accessing the rank
of the JsonCursor
. The rank
forms part of
the calculation that is the cursors current position in the index.
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.
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 #
Attempt a Decoder
action that might fail and return a Maybe
value
instead.
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
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 impelemented 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 :: MonadError DecodeError f => DecodeError -> Prism' a b -> Decoder f a -> Decoder f b Source #
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.
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.
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.