Safe Haskell | None |
---|---|
Language | Haskell2010 |
Deprecated: Use Decode
. This module will be removed in a future release.
Types and functions to convert Json values into your data types.
This module uses the Traversal
based Zipper
as the basis for the Decoder
. It is provided for compatibility and
comparison. It is not as fast as the succinct data structure based
Decoder
.
Synopsis
- data Err c e
- = Parse e
- | Decode (DecodeError, c)
- newtype CursorHistory = CursorHist {}
- newtype DecodeResult f a = DecodeResult {}
- type JCursorMove s a = LensLike' (Indexing (Bazaar' (Indexed Int) a)) s a
- type JCursor h a = h :>> a
- type Decoder f a = forall h. Decoder' (JCursor h Json) Int DecodeError f a
- withCursor :: (forall h. JCursor h Json -> DecodeResult f a) -> Decoder f a
- runDecoder :: Decoder f a -> JCursor h Json -> DecodeResult f a
- runDecoderResult :: Monad f => DecodeResult f a -> f (Either (DecodeError, CursorHistory) a)
- runPureDecode :: Decoder Identity a -> JCursor h Json -> Either (DecodeError, CursorHistory) a
- simpleDecode :: (s -> Either e Json) -> Decoder Identity a -> s -> Either (Err CursorHistory e) a
- generaliseDecoder :: Monad f => Decoder Identity a -> Decoder f a
- into :: Monad f => Text -> JCursorMove s a -> JCursor h s -> DecodeResult f (JCursor (JCursor h s) a)
- up :: Monad f => JCursor (JCursor h s) a -> DecodeResult f (JCursor h s)
- down :: Monad f => Text -> JCursor h Json -> DecodeResult f (JCursor (JCursor h Json) Json)
- moveLeftN :: Monad f => Natural -> JCursor h a -> DecodeResult f (JCursor h a)
- moveLeft1 :: Monad f => JCursor h a -> DecodeResult f (JCursor h a)
- moveRightN :: Monad f => Natural -> JCursor h a -> DecodeResult f (JCursor h a)
- moveRight1 :: Monad f => JCursor h a -> DecodeResult f (JCursor h a)
- moveToKey :: (AsJType s ws s, Monad f) => Text -> JCursor h s -> DecodeResult f ((((h :>> s) :>> Elems ws (JAssoc ws s)) :>> JAssoc ws s) :>> s)
- try :: MonadError e m => m a -> m (Maybe a)
- fromKey :: Monad f => Text -> Decoder f b -> JCursor h Json -> DecodeResult f b
- atKey :: Monad f => Text -> Decoder f a -> Decoder f a
- atCursor :: Monad f => Text -> (Json -> Maybe b) -> Decoder f b
- focus :: Decoder f a -> JCursor h Json -> DecodeResult f a
- scientific :: Monad f => Decoder f Scientific
- integral :: (Bounded i, Integral i, Monad f) => Decoder f i
- int :: Monad f => Decoder f Int
- bool :: Monad f => Decoder f Bool
- text :: Monad f => Decoder f Text
- string :: Monad f => Decoder f String
- boundedChar :: Monad f => Decoder f Char
- unboundedChar :: Monad f => Decoder f Char
- null :: Monad f => Decoder f ()
- json :: Monad f => Decoder f Json
- foldCursor :: Monad f => s -> (s -> a -> s) -> (JCursor h Json -> DecodeResult f (JCursor h Json)) -> Decoder f a -> JCursor h Json -> DecodeResult f s
- leftwardCons :: (Monad f, Cons s s a a) => s -> Decoder f a -> JCursor h Json -> DecodeResult f s
- rightwardSnoc :: (Monad f, Snoc s s a a) => s -> Decoder f a -> JCursor h Json -> DecodeResult f s
- nonEmptyAt :: Monad f => Decoder f a -> JCursor h Json -> DecodeResult f (NonEmpty a)
- nonempty :: Monad f => Decoder f b -> Decoder f (NonEmpty b)
- listAt :: Monad f => Decoder f a -> JCursor h Json -> DecodeResult f [a]
- list :: Monad f => Decoder f b -> Decoder f [b]
- maybeOrNull :: Monad f => Decoder f a -> Decoder f (Maybe a)
- withDefault :: Monad f => a -> Decoder f (Maybe a) -> Decoder f a
- either :: Monad f => Decoder f a -> Decoder f b -> Decoder f (Either a b)
Documentation
Convenience Error structure for the separate parsing/decoding phases. For when things really aren't that complicated.
Parse e | |
Decode (DecodeError, c) |
newtype CursorHistory Source #
Convenience Error structure for the separate parsing/decoding phases. For when things really aren't that complicated.
Wrapper for our CursorHistory'
to define our index as being an Int
.
Instances
Eq CursorHistory Source # | |
Defined in Waargonaut.Decode.Traversal (==) :: CursorHistory -> CursorHistory -> Bool # (/=) :: CursorHistory -> CursorHistory -> Bool # | |
Show CursorHistory Source # | |
Defined in Waargonaut.Decode.Traversal showsPrec :: Int -> CursorHistory -> ShowS # show :: CursorHistory -> String # showList :: [CursorHistory] -> ShowS # |
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.
Instances
Type aliases
type JCursorMove s a = LensLike' (Indexing (Bazaar' (Indexed Int) a)) s a Source #
Type alias to describe the lens that may be given to a zipper movement
function to more directly target something within the Json
data structure.
type JCursor h a = h :>> a Source #
This is an alias to help explain a type from the zipper that is used to move
around the Json
data structure. 'JCursor h a' represents a "cursor" that is
currently located on a thing of type a
, having previously been on a thing
of type h
.
This type will grow as a form of "breadcrumb" trail as the cursor moves
through the data structure. It may be used interchangably with 'h :>> a' from
the Zipper
module.
Decoder creation
withCursor :: (forall h. JCursor h Json -> 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 -> 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.
Decoder execution
runDecoder :: Decoder f a -> JCursor h Json -> DecodeResult f a Source #
runDecoderResult :: Monad f => DecodeResult f a -> f (Either (DecodeError, CursorHistory) a) Source #
Execute a DecodeResult
to determine if the process has been successful,
providing a descriptive error and the path history of the cursor movements to
assist in debugging any failures.
runPureDecode :: Decoder Identity a -> JCursor h Json -> Either (DecodeError, CursorHistory) a Source #
Run a pure decoder with Identity
.
simpleDecode :: (s -> Either e Json) -> Decoder Identity a -> s -> Either (Err CursorHistory e) a Source #
Cursor movement
into :: Monad f => Text -> JCursorMove s a -> JCursor h s -> DecodeResult f (JCursor (JCursor h s) a) Source #
Using a given LensLike
, try to step down into the Json
data structure
to the location targeted by the lens.
This can be used to move large steps over the data structure, or more
precisely to specific keys at deeper levels. On a successful step, the
history will be recorded as a single step into the thing described by the
Text
input.
up :: Monad f => JCursor (JCursor h s) a -> DecodeResult f (JCursor h s) Source #
Attempt to step one level "up" from the current cursor location.
down :: Monad f => Text -> JCursor h Json -> DecodeResult f (JCursor (JCursor h Json) Json) Source #
moveLeftN :: Monad f => Natural -> JCursor h a -> DecodeResult f (JCursor h a) Source #
From the current cursor location, try to move n
steps to the left.
moveLeft1 :: Monad f => JCursor h a -> DecodeResult f (JCursor h a) Source #
From the current cursor location, try to move 1 step to the left.
moveRightN :: Monad f => Natural -> JCursor h a -> DecodeResult f (JCursor h a) Source #
From the current cursor location, try to move n
steps to the right.
moveRight1 :: Monad f => JCursor h a -> DecodeResult f (JCursor h a) Source #
From the current cursor location, try to move 1 step to the right.
moveToKey :: (AsJType s ws s, Monad f) => Text -> JCursor h s -> DecodeResult f ((((h :>> s) :>> Elems ws (JAssoc ws s)) :>> JAssoc ws s) :>> s) Source #
From the current cursor position, try to move to the value for the first occurence of that key. This move expects that you've positioned the cursor on an object.
try :: MonadError e m => m a -> m (Maybe a) Source #
Decode at Cursor
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:
data MyRec = MyRec { fieldA :: Text, fieldB :: Int } myRecDecoder :: Decoder f MyRec myRecDecoder = MyRec $ atKey "field_a" text * atKey "field_b" int
atCursor :: Monad f => Text -> (Json -> Maybe b) -> Decoder f b Source #
Provide a conversion
function and create a Decoder
that uses the
current cursor and runs the given function. Fails with ConversionFailure
and
the given Text
description.
focus :: Decoder f a -> JCursor h Json -> DecodeResult f a Source #
Try to decode the value at the current focus using the given Decoder
.
Provided decoders
scientific :: Monad f => Decoder f Scientific Source #
Decoder for Scientific
integral :: (Bounded i, Integral i, Monad f) => Decoder f i Source #
Decoder for a bounded integral value.
unboundedChar :: Monad f => Decoder f Char Source #
Decoder for a Haskell Char
value whose values represent Unicode
(or equivalently ISO/IEC 10646) characters.
json :: Monad f => Decoder f Json Source #
Decoder for pulling out the Json
Haskell data structure at the current cursor.
foldCursor :: Monad f => s -> (s -> a -> s) -> (JCursor h Json -> DecodeResult f (JCursor h Json)) -> Decoder f a -> JCursor h Json -> DecodeResult f s Source #
Allows for folding over the results of repeated cursor movements.
intList :: Decoder f [String] intList = withCursor $ curs -> foldCursor [] (acc a -> acc <> [a]) moveRight1 string curs
leftwardCons :: (Monad f, Cons s s a a) => s -> Decoder f a -> JCursor h Json -> DecodeResult f s Source #
Use the Cons
typeclass and move leftwards from the current cursor
position, "consing" the values to the s
as it moves.
rightwardSnoc :: (Monad f, Snoc s s a a) => s -> Decoder f a -> JCursor h Json -> DecodeResult f s Source #
Use the Snoc
typeclass and move rightwards from the current cursor
position, "snocing" the values to the s
as it moves.
nonEmptyAt :: Monad f => Decoder f a -> JCursor h Json -> DecodeResult f (NonEmpty a) Source #
Decode a NonEmpty
list of a
at the given cursor position.
listAt :: Monad f => Decoder f a -> JCursor h Json -> DecodeResult f [a] Source #
Decode a '[a]' at the current cursor position.
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.