module Data.JSON.Patch.Apply.AsValue
( PatchError (..)
, patchAsValue
) where
import Data.JSON.Patch.Prelude
import Data.Aeson (FromJSON, Result (..), ToJSON (..), Value (..), fromJSON)
import Data.Aeson.Optics (AsValue (..))
import Data.JSON.Patch.Apply
import Optics.Core
patchAsValue
:: (AsValue patch, FromJSON v, ToJSON v) => patch -> v -> Either PatchError v
patchAsValue :: forall patch v.
(AsValue patch, FromJSON v, ToJSON v) =>
patch -> v -> Either PatchError v
patchAsValue patch
p v
target = do
Value
pVal <- PatchError -> Maybe Value -> Either PatchError Value
forall e a. e -> Maybe a -> Either e a
note (Value -> String -> PatchError
ParseError Value
Null String
"not JSON") (Maybe Value -> Either PatchError Value)
-> Maybe Value -> Either PatchError Value
forall a b. (a -> b) -> a -> b
$ patch
p patch -> Optic' A_Prism NoIx patch Value -> Maybe Value
forall k s (is :: IxList) a.
Is k An_AffineFold =>
s -> Optic' k is s a -> Maybe a
^? Optic' A_Prism NoIx patch Value
forall t. AsValue t => Prism' t Value
_Value
[Patch]
patches <- Value -> Either PatchError [Patch]
forall a. FromJSON a => Value -> Either PatchError a
fromJSONEither Value
pVal
Value
result <- [Patch] -> Value -> Either PatchError Value
patchValue [Patch]
patches (Value -> Either PatchError Value)
-> Value -> Either PatchError Value
forall a b. (a -> b) -> a -> b
$ v -> Value
forall a. ToJSON a => a -> Value
toJSON v
target
Value -> Either PatchError v
forall a. FromJSON a => Value -> Either PatchError a
fromJSONEither Value
result
fromJSONEither :: FromJSON a => Value -> Either PatchError a
fromJSONEither :: forall a. FromJSON a => Value -> Either PatchError a
fromJSONEither Value
v = case Value -> Result a
forall a. FromJSON a => Value -> Result a
fromJSON Value
v of
Error String
e -> PatchError -> Either PatchError a
forall a b. a -> Either a b
Left (PatchError -> Either PatchError a)
-> PatchError -> Either PatchError a
forall a b. (a -> b) -> a -> b
$ Value -> String -> PatchError
ParseError Value
v String
e
Success a
a -> a -> Either PatchError a
forall a b. b -> Either a b
Right a
a