{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
module Waargonaut.Decode.Traversal
(
Err (..)
, CursorHistory (..)
, DecodeResult (..)
, JCursorMove
, JCursor
, Decoder
, withCursor
, runDecoder
, runDecoderResult
, runPureDecode
, simpleDecode
, generaliseDecoder
, into
, up
, down
, moveLeftN
, moveLeft1
, moveRightN
, moveRight1
, moveToKey
, try
, fromKey
, atKey
, atCursor
, focus
, scientific
, integral
, int
, bool
, text
, string
, boundedChar
, unboundedChar
, null
, json
, foldCursor
, leftwardCons
, rightwardSnoc
, nonEmptyAt
, nonempty
, listAt
, list
, maybeOrNull
, withDefault
, either
) where
import Prelude hiding (either, maybe, null)
import Numeric.Natural (Natural)
import Control.Lens (Bazaar', Cons, LensLike', Snoc,
(^.), (^?))
import qualified Control.Lens as L
import Control.Lens.Internal.Indexed (Indexed, Indexing)
import Control.Monad ((>=>))
import Control.Monad.Except (MonadError)
import Control.Monad.Morph (MFunctor (..), MMonad (..),
generalize)
import Control.Monad.State (MonadState)
import Control.Monad.Trans.Class (MonadTrans (..))
import Control.Error.Util (note)
import Control.Monad.Error.Hoist ((<%?>), (<?>))
import Control.Zipper ((:>>))
import qualified Control.Zipper as Z
import Data.Functor.Identity (Identity, runIdentity)
import qualified Data.Maybe as Maybe
import Data.List.NonEmpty (NonEmpty ((:|)))
import qualified Data.Bool as Bool
import Data.Text (Text)
import Data.Scientific (Scientific)
import Waargonaut.Types (AsJType, Elems, JAssoc, Json)
import qualified Waargonaut.Types as WT
import Waargonaut.Decode.Error (Err (..))
import Waargonaut.Decode.Internal (CursorHistory' (..),
DecodeError (..), DecodeResultT,
Decoder' (..), ZipperMove (..),
runDecoderResultT, try)
import qualified Waargonaut.Decode.Internal as DR
newtype CursorHistory = CursorHist
{ unCursorHist :: CursorHistory' Int
}
deriving (Show, Eq)
newtype DecodeResult f a = DecodeResult
{ unDecodeResult :: DecodeResultT Int DecodeError f a
}
deriving ( Functor
, Applicative
, Monad
, MonadState (CursorHistory' Int)
, MonadError DecodeError
)
instance MonadTrans DecodeResult where
lift = DecodeResult . lift
instance MFunctor DecodeResult where
hoist nat (DecodeResult dr) = DecodeResult (hoist nat dr)
instance MMonad DecodeResult where
embed f (DecodeResult dr) = DecodeResult (embed (unDecodeResult . f) dr)
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
generaliseDecoder :: Monad f => Decoder Identity a -> Decoder f a
generaliseDecoder dr = Decoder' (embed generalize . runDecoder' dr)
{-# INLINE generaliseDecoder #-}
withCursor
:: (forall h. JCursor h Json -> DecodeResult f a)
-> Decoder f a
withCursor f =
Decoder' (unDecodeResult . f)
runDecoder
:: Decoder f a
-> JCursor h Json
-> DecodeResult f a
runDecoder f =
DecodeResult . DR.runDecoder' f
runDecoderResult
:: Monad f
=> DecodeResult f a
-> f (Either (DecodeError, CursorHistory) a)
runDecoderResult =
L.over (L.mapped . L._Left . L._2) CursorHist
. runDecoderResultT
. unDecodeResult
runPureDecode
:: Decoder Identity a
-> JCursor h Json
-> Either (DecodeError, CursorHistory) a
runPureDecode dec = runIdentity
. runDecoderResult
. runDecoder dec
simpleDecode
:: (s -> Either e Json)
-> Decoder Identity a
-> s
-> Either (Err CursorHistory e) a
simpleDecode p dec =
L.bimap Parse Z.zipper . p >=>
L.over L._Left Decode . runPureDecode dec
moveAndKeepHistory
:: Monad f
=> ZipperMove
-> Maybe (JCursor h s)
-> DecodeResult f (JCursor h s)
moveAndKeepHistory dir mCurs = do
a <- mCurs <?> FailedToMove dir
a <$ DR.recordZipperMove dir (Z.tooth a)
into
:: Monad f
=> Text
-> JCursorMove s a
-> JCursor h s
-> DecodeResult f (JCursor (JCursor h s) a)
into tgt l =
moveAndKeepHistory (DAt tgt) . Z.within l
down
:: Monad f
=> Text
-> JCursor h Json
-> DecodeResult f (JCursor (JCursor h Json) Json)
down tgt =
into tgt WT.jsonTraversal
up
:: Monad f
=> JCursor (JCursor h s) a
-> DecodeResult f (JCursor h s)
up =
moveAndKeepHistory U . pure . Z.upward
moveLeftN
:: Monad f
=> Natural
-> JCursor h a
-> DecodeResult f (JCursor h a)
moveLeftN n cur =
moveAndKeepHistory (L n) (Z.jerks Z.leftward (fromIntegral n) cur)
moveRightN
:: Monad f
=> Natural
-> JCursor h a
-> DecodeResult f (JCursor h a)
moveRightN n cur =
moveAndKeepHistory (R n) (Z.jerks Z.rightward (fromIntegral n) cur)
moveLeft1
:: Monad f
=> JCursor h a
-> DecodeResult f (JCursor h a)
moveLeft1 =
moveLeftN 1
moveRight1
:: Monad f
=> JCursor h a
-> DecodeResult f (JCursor h a)
moveRight1 =
moveRightN 1
atCursor
:: Monad f
=> Text
-> (Json -> Maybe b)
-> Decoder f b
atCursor t f = withCursor $ \c -> do
b <- c ^. Z.focus . L.to (note t . f) <%?> ConversionFailure
b <$ DR.recordZipperMove (Item t) (Z.tooth c)
moveToKey
:: ( AsJType s ws s
, Monad f
)
=> Text
-> JCursor h s
-> DecodeResult f (h :>> s :>> Elems ws (JAssoc ws s) :>> JAssoc ws s :>> s)
moveToKey k =
moveAndKeepHistory (DAt k)
. ( Z.within intoElems
>=> Z.within traverse
>=> shuffleToKey
>=> Z.within WT.jsonAssocVal
)
where
shuffleToKey cu = Z.within WT.jsonAssocKey cu ^? L._Just . Z.focus . L.re WT._JString
>>= Bool.bool (Just cu) (Z.rightward cu >>= shuffleToKey) . (/=k)
intoElems = WT._JObj . L._1 . L._Wrapped . WT._CommaSeparated . L._2 . L._Just
fromKey
:: ( Monad f
)
=> Text
-> Decoder f b
-> JCursor h Json
-> DecodeResult f b
fromKey k d =
moveToKey k >=> runDecoder d
atKey
:: Monad f
=> Text
-> Decoder f a
-> Decoder f a
atKey k d =
withCursor (fromKey k d)
scientific :: Monad f => Decoder f Scientific
scientific = atCursor "Scientific" DR.scientific'
integral :: (Bounded i, Integral i, Monad f) => Decoder f i
integral = atCursor "Integral" DR.integral'
int :: Monad f => Decoder f Int
int = atCursor "Int" DR.int'
bool :: Monad f => Decoder f Bool
bool = atCursor "Bool" DR.bool'
text :: Monad f => Decoder f Text
text = atCursor "Text" DR.text'
string :: Monad f => Decoder f String
string = atCursor "String" DR.string'
null :: Monad f => Decoder f ()
null = atCursor "null" DR.null'
boundedChar :: Monad f => Decoder f Char
boundedChar = atCursor "Bounded Char" DR.boundedChar'
unboundedChar :: Monad f => Decoder f Char
unboundedChar = atCursor "Unbounded Char" DR.unboundedChar'
json :: Monad f => Decoder f Json
json = atCursor "JSON" pure
focus
:: Decoder f a
-> JCursor h Json
-> DecodeResult f a
focus =
runDecoder
foldCursor
:: Monad f
=> s
-> (s -> a -> s)
-> (JCursor h Json -> DecodeResult f (JCursor h Json))
-> Decoder f a
-> JCursor h Json
-> DecodeResult f s
foldCursor s sas mvCurs elemD = DecodeResult
. DR.foldCursor'
s
sas
(unDecodeResult . mvCurs)
elemD
leftwardCons
:: ( Monad f
, Cons s s a a
)
=> s
-> Decoder f a
-> JCursor h Json
-> DecodeResult f s
leftwardCons s elemD = DecodeResult
. DR.foldCursor' s
(flip L.cons)
(unDecodeResult . moveLeft1)
elemD
rightwardSnoc
:: ( Monad f
, Snoc s s a a
)
=> s
-> Decoder f a
-> JCursor h Json
-> DecodeResult f s
rightwardSnoc s elemD = DecodeResult
. DR.foldCursor' s
L.snoc
(unDecodeResult . moveRight1)
elemD
nonEmptyAt
:: Monad f
=> Decoder f a
-> JCursor h Json
-> DecodeResult f (NonEmpty a)
nonEmptyAt elemD c =
moveAndKeepHistory D (Z.within WT.jsonTraversal c)
>>= \curs -> do
h <- focus elemD curs
moveRight1 curs >>= fmap (h:|) . rightwardSnoc [] elemD
nonempty :: Monad f => Decoder f b -> Decoder f (NonEmpty b)
nonempty d = withCursor (nonEmptyAt d)
listAt
:: Monad f
=> Decoder f a
-> JCursor h Json
-> DecodeResult f [a]
listAt elemD c =
try (moveAndKeepHistory D (Z.within WT.jsonTraversal c))
>>= Maybe.maybe (pure mempty) (rightwardSnoc mempty elemD)
list
:: Monad f
=> Decoder f b
-> Decoder f [b]
list d =
withCursor (listAt d)
withDefault
:: Monad f
=> a
-> Decoder f (Maybe a)
-> Decoder f a
withDefault def hasD =
withCursor (fmap (Maybe.fromMaybe def) . focus hasD)
maybeOrNull
:: Monad f
=> Decoder f a
-> Decoder f (Maybe a)
maybeOrNull hasD =
withCursor (try . focus hasD)
either
:: Monad f
=> Decoder f a
-> Decoder f b
-> Decoder f (Either a b)
either leftD rightD =
withCursor $ \c ->
try (focus (Right <$> rightD) c) >>=
Maybe.maybe (focus (Left <$> leftD) c) pure