| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Waargonaut.Decode.Internal
Description
Internal types and functions for building Decoder infrastructure.
Synopsis
- newtype CursorHistory' i = CursorHistory' {
- unCursorHistory' :: Seq (ZipperMove, i)
 
 - ppCursorHistory :: CursorHistory' i -> Doc a
 - newtype DecodeResultT i e f a = DecodeResultT {
- runDecodeResult :: ExceptT e (StateT (CursorHistory' i) f) a
 
 - newtype Decoder' c i e f a = Decoder' {
- runDecoder' :: c -> DecodeResultT i e f a
 
 - withCursor' :: (c -> DecodeResultT i e f a) -> Decoder' c i e f a
 - runDecoderResultT :: Monad f => DecodeResultT i DecodeError f a -> f (Either (DecodeError, CursorHistory' i) a)
 - try :: MonadError e m => m a -> m (Maybe a)
 - recordZipperMove :: MonadState (CursorHistory' i) m => ZipperMove -> i -> m ()
 - null' :: AsJType a ws a => a -> Maybe ()
 - int' :: AsJType a ws a => a -> Maybe Int
 - text' :: AsJType a ws a => a -> Maybe Text
 - string' :: AsJType a ws a => a -> Maybe String
 - unboundedChar' :: AsJType a ws a => a -> Maybe Char
 - boundedChar' :: AsJType a ws a => a -> Maybe Char
 - bool' :: AsJType a ws a => a -> Maybe Bool
 - array' :: AsJType a ws a => (a -> Maybe b) -> a -> [b]
 - integral' :: (Bounded i, Integral i, AsJType a ws a) => a -> Maybe i
 - scientific' :: AsJType a ws a => a -> Maybe Scientific
 - objTuples' :: (Applicative f, AsJType a ws a) => (JString -> f k) -> (a -> f b) -> a -> f [(k, b)]
 - foldCursor' :: Monad f => b -> (b -> a -> b) -> (c -> DecodeResultT i e f c) -> Decoder' c i e f a -> c -> DecodeResultT i e f b
 - prismDOrFail' :: (AsDecodeError e, MonadError e f) => e -> Prism' a b -> Decoder' c i e f a -> c -> DecodeResultT i e f b
 - mapKeepingF :: (Ord k, Applicative f, AsJType a ws a) => (t -> Maybe v -> Maybe v) -> (JString -> f k) -> (a -> f t) -> a -> f (Map k v)
 - mapKeepingFirst :: (Ord k, Applicative f, AsJType a ws a) => (JString -> f k) -> (a -> f b) -> a -> f (Map k b)
 - mapKeepingLast :: (Ord k, Applicative f, AsJType a ws a) => (JString -> f k) -> (a -> f b) -> a -> f (Map k b)
 - class AsDecodeError r where
- _DecodeError :: Prism' r DecodeError
 - _ConversionFailure :: Prism' r Text
 - _KeyDecodeFailed :: Prism' r Text
 - _KeyNotFound :: Prism' r Text
 - _FailedToMove :: Prism' r ZipperMove
 - _NumberOutOfBounds :: Prism' r JNumber
 - _InputOutOfBounds :: Prism' r Word64
 - _ParseFailed :: Prism' r Text
 
 - data DecodeError
 - data ZipperMove
 - ppZipperMove :: ZipperMove -> Doc a
 
Documentation
newtype CursorHistory' i Source #
Track the history of the cursor as we move around the zipper.
It is indexed over the type of the index used to navigate the zipper.
Constructors
| CursorHistory' | |
Fields 
  | |
Instances
ppCursorHistory :: CursorHistory' i -> Doc a Source #
Pretty print the given CursorHistory' to a more useful format compared to a Seq of i.
newtype DecodeResultT i e f a Source #
The general structure used to maintain the history of the moves around the
 zipper, as well as handle the decoding or movement errors that may occur.
 This structure is generalised of the inner f to allow you to interleave the
 decoding with your own actions. As well as the error type e so that you may
 provide your own error type.
If you use the provided Decode module then you probably won't
 need to care about this type. It is provided so that you're not limited to
 how we decide you should be running your decoder.
Constructors
| DecodeResultT | |
Fields 
  | |
Instances
newtype Decoder' c i e f a Source #
Wrapper type to describe a Decoder from something that has a Jsonish
 value c, to some representation of a.
Constructors
| Decoder' | |
Fields 
  | |
Instances
| MFunctor (Decoder' c i e :: (Type -> Type) -> Type -> Type) Source # | |
| MonadTrans (Decoder' c i e) Source # | |
Defined in Waargonaut.Decode.Internal  | |
| Monad f => Monad (Decoder' c i e f) Source # | |
| Functor f => Functor (Decoder' c i e f) Source # | |
| Monad f => Applicative (Decoder' c i e f) Source # | |
Defined in Waargonaut.Decode.Internal Methods pure :: a -> Decoder' c i e f a # (<*>) :: Decoder' c i e f (a -> b) -> Decoder' c i e f a -> Decoder' c i e f b # liftA2 :: (a -> b -> c0) -> Decoder' c i e f a -> Decoder' c i e f b -> Decoder' c i e f c0 # (*>) :: Decoder' c i e f a -> Decoder' c i e f b -> Decoder' c i e f b # (<*) :: Decoder' c i e f a -> Decoder' c i e f b -> Decoder' c i e f a #  | |
withCursor' :: (c -> DecodeResultT i e f a) -> Decoder' c i e f a Source #
Helper function for constructing a Decoder'.
This function is used by the implemented decoders to simplify constructing a
 more specific Decoder type.
withCursor' $ curs -> ... ...
runDecoderResultT :: Monad f => DecodeResultT i DecodeError f a -> f (Either (DecodeError, CursorHistory' i) a) Source #
Execute a given DecoderResultT.
If you're building your own decoder structure, this function will take care
 of the CursorHistory' and error handling (via ExceptT).
try :: MonadError e m => m a -> m (Maybe a) Source #
Attempt a Decoder action that might fail and return a Maybe value
 instead.
recordZipperMove :: MonadState (CursorHistory' i) m => ZipperMove -> i -> m () Source #
Record a move on the zipper and the index of the position where the move occured.
Generalised Decoder Functions
text' :: AsJType a ws a => a -> Maybe Text Source #
Try to decode a Text value from some Json or value.
string' :: AsJType a ws a => a -> Maybe String Source #
Try to decode a String value from some Json or value.
unboundedChar' :: AsJType a ws a => a -> Maybe Char Source #
Decoder for a Haskell Char value whose values represent Unicode
 (or equivalently ISO/IEC 10646) characters
array' :: AsJType a ws a => (a -> Maybe b) -> a -> [b] Source #
Combined with another decoder function f, try to decode a list of a values.
array' int' :: Json -> [Int]
integral' :: (Bounded i, Integral i, AsJType a ws a) => a -> Maybe i Source #
Try to decode a bounded 'Integral n => n' value from some Json value.
scientific' :: AsJType a ws a => a -> Maybe Scientific Source #
Try to decode a Scientific value from some Json or value.
objTuples' :: (Applicative f, AsJType a ws a) => (JString -> f k) -> (a -> f b) -> a -> f [(k, b)] Source #
Try to decode a JSON Object into it's representative list of tuples '(key, value)'. The JSON RFC does not specify that an object must contain unique keys. We do not enforce unique keys during the decoding process and leave it to the user to decide if, and how, they would like to handle this situation.
foldCursor' :: Monad f => b -> (b -> a -> b) -> (c -> DecodeResultT i e f c) -> Decoder' c i e f a -> c -> DecodeResultT i e f b Source #
Generalised moving decoder function.
Starting from the given cursor position, try to move in the direction
 specified by the given cursor function. Attempting to decode each item at each
 position using the given Decoder, until the movement is unsuccessful.
The following could be used to leverage the Snoc instance of '[]' to build '[Int]'.
intList :: Monad f => JCurs -> DecodeResult f [Int] intList = directedConsumption' snoc moveRight1 int
prismDOrFail' :: (AsDecodeError e, MonadError e f) => e -> Prism' a b -> Decoder' c i e f a -> c -> DecodeResultT i e f b Source #
Build the basis for a Decoder based on a Prism'.
JSON Object to Map Functions
mapKeepingF :: (Ord k, Applicative f, AsJType a ws a) => (t -> Maybe v -> Maybe v) -> (JString -> f k) -> (a -> f t) -> a -> f (Map k v) Source #
Provide a generalised and low level way of turning a JSON object into a
 Map, without enforcing a choice of how we select keys.
mapKeepingFirst :: (Ord k, Applicative f, AsJType a ws a) => (JString -> f k) -> (a -> f b) -> a -> f (Map k b) Source #
Turn a JSON object into a Map by keeping the *first* occurence of any
 duplicate keys that are encountered.
mapKeepingLast :: (Ord k, Applicative f, AsJType a ws a) => (JString -> f k) -> (a -> f b) -> a -> f (Map k b) Source #
Turn a JSON object into a Map by keeping the *last* occurence of any
 duplicate keys that are encountered.
Re-exports
class AsDecodeError r where Source #
Describes the sorts of errors that may be treated as a DecodeError, for use with lens.
Minimal complete definition
Methods
_DecodeError :: Prism' r DecodeError Source #
_ConversionFailure :: Prism' r Text Source #
_KeyDecodeFailed :: Prism' r Text Source #
_KeyNotFound :: Prism' r Text Source #
_FailedToMove :: Prism' r ZipperMove Source #
_NumberOutOfBounds :: Prism' r JNumber Source #
_InputOutOfBounds :: Prism' r Word64 Source #
_ParseFailed :: Prism' r Text Source #
Instances
data DecodeError Source #
Set of errors that may occur during the decode phase.
Constructors
| ConversionFailure Text | |
| KeyDecodeFailed Text | |
| KeyNotFound Text | |
| FailedToMove ZipperMove | |
| NumberOutOfBounds JNumber | |
| InputOutOfBounds Word64 | |
| ParseFailed Text | 
Instances
data ZipperMove Source #
Set of moves that may be executed on a zipper.
Instances
| Eq ZipperMove Source # | |
Defined in Waargonaut.Decode.ZipperMove  | |
| Show ZipperMove Source # | |
Defined in Waargonaut.Decode.ZipperMove Methods showsPrec :: Int -> ZipperMove -> ShowS # show :: ZipperMove -> String # showList :: [ZipperMove] -> ShowS #  | |
| AsZipperMove ZipperMove Source # | |
Defined in Waargonaut.Decode.ZipperMove Methods _ZipperMove :: Prism' ZipperMove ZipperMove Source # _U :: Prism' ZipperMove () Source # _D :: Prism' ZipperMove () Source # _DAt :: Prism' ZipperMove Text Source # _Item :: Prism' ZipperMove Text Source #  | |
ppZipperMove :: ZipperMove -> Doc a Source #
Pretty print a given zipper movement, used when printing
 CursorHistory' to improve the readability of the errors.