{-# LANGUAGE CPP #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE DefaultSignatures #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
#if __GLASGOW_HASKELL__ >= 800
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ViewPatterns #-}
#endif
module Data.Aeson.Lens
(
AsNumber(..)
, _Integral
, nonNull
, Primitive(..)
, AsPrimitive(..)
, AsValue(..)
, key, members
, nth, values
, AsJSON(..)
, _JSON'
#if __GLASGOW_HASKELL__ >= 800
, pattern JSON
, pattern Value_
, pattern Number_
, pattern Double
, pattern Integer
, pattern Integral
, pattern Primitive
, pattern Bool_
, pattern String_
, pattern Null_
#endif
) where
import Control.Applicative
import Control.Lens
import Data.Aeson
import Data.Aeson.Parser (value)
import Data.Attoparsec.ByteString.Lazy (maybeResult, parse)
import Data.Scientific (Scientific)
import qualified Data.Scientific as Scientific
import qualified Data.ByteString as Strict
import Data.ByteString.Lazy.Char8 as Lazy hiding (putStrLn)
import Data.Data
import Data.HashMap.Strict (HashMap)
import Data.Text as Text
import qualified Data.Text.Lazy as LazyText
import Data.Text.Lens (packed)
import qualified Data.Text.Encoding as StrictText
import qualified Data.Text.Lazy.Encoding as LazyText
import Data.Vector (Vector)
import Prelude hiding (null)
class AsNumber t where
_Number :: Prism' t Scientific
default _Number :: AsPrimitive t => Prism' t Scientific
_Number = p Primitive (f Primitive) -> p t (f t)
forall t. AsPrimitive t => Prism' t Primitive
_Primitive(p Primitive (f Primitive) -> p t (f t))
-> (p Scientific (f Scientific) -> p Primitive (f Primitive))
-> p Scientific (f Scientific)
-> p t (f t)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.p Scientific (f Scientific) -> p Primitive (f Primitive)
forall t. AsNumber t => Prism' t Scientific
_Number
{-# INLINE _Number #-}
_Double :: Prism' t Double
_Double = p Scientific (f Scientific) -> p t (f t)
forall t. AsNumber t => Prism' t Scientific
_Number(p Scientific (f Scientific) -> p t (f t))
-> (p Double (f Double) -> p Scientific (f Scientific))
-> p Double (f Double)
-> p t (f t)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Scientific -> Double)
-> (Double -> Scientific)
-> Iso Scientific Scientific Double Double
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso Scientific -> Double
forall a. RealFloat a => Scientific -> a
Scientific.toRealFloat Double -> Scientific
forall a b. (Real a, Fractional b) => a -> b
realToFrac
{-# INLINE _Double #-}
_Integer :: Prism' t Integer
_Integer = p Scientific (f Scientific) -> p t (f t)
forall t. AsNumber t => Prism' t Scientific
_Number(p Scientific (f Scientific) -> p t (f t))
-> (p Integer (f Integer) -> p Scientific (f Scientific))
-> p Integer (f Integer)
-> p t (f t)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Scientific -> Integer)
-> (Integer -> Scientific)
-> Iso Scientific Scientific Integer Integer
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso Scientific -> Integer
forall a b. (RealFrac a, Integral b) => a -> b
floor Integer -> Scientific
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# INLINE _Integer #-}
instance AsNumber Value where
_Number :: p Scientific (f Scientific) -> p Value (f Value)
_Number = (Scientific -> Value)
-> (Value -> Either Value Scientific) -> Prism' Value Scientific
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism Scientific -> Value
Number ((Value -> Either Value Scientific) -> Prism' Value Scientific)
-> (Value -> Either Value Scientific) -> Prism' Value Scientific
forall a b. (a -> b) -> a -> b
$ \Value
v -> case Value
v of Number Scientific
n -> Scientific -> Either Value Scientific
forall a b. b -> Either a b
Right Scientific
n; Value
_ -> Value -> Either Value Scientific
forall a b. a -> Either a b
Left Value
v
{-# INLINE _Number #-}
instance AsNumber Scientific where
_Number :: p Scientific (f Scientific) -> p Scientific (f Scientific)
_Number = p Scientific (f Scientific) -> p Scientific (f Scientific)
forall a. a -> a
id
{-# INLINE _Number #-}
instance AsNumber Strict.ByteString
instance AsNumber Lazy.ByteString
instance AsNumber Text
instance AsNumber LazyText.Text
instance AsNumber String
_Integral :: (AsNumber t, Integral a) => Prism' t a
_Integral :: Prism' t a
_Integral = p Scientific (f Scientific) -> p t (f t)
forall t. AsNumber t => Prism' t Scientific
_Number (p Scientific (f Scientific) -> p t (f t))
-> (p a (f a) -> p Scientific (f Scientific))
-> p a (f a)
-> p t (f t)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Scientific -> a)
-> (a -> Scientific) -> Iso Scientific Scientific a a
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso Scientific -> a
forall a b. (RealFrac a, Integral b) => a -> b
floor a -> Scientific
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# INLINE _Integral #-}
data Primitive
= StringPrim !Text
| NumberPrim !Scientific
| BoolPrim !Bool
| NullPrim
deriving (Primitive -> Primitive -> Bool
(Primitive -> Primitive -> Bool)
-> (Primitive -> Primitive -> Bool) -> Eq Primitive
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Primitive -> Primitive -> Bool
$c/= :: Primitive -> Primitive -> Bool
== :: Primitive -> Primitive -> Bool
$c== :: Primitive -> Primitive -> Bool
Eq,Eq Primitive
Eq Primitive
-> (Primitive -> Primitive -> Ordering)
-> (Primitive -> Primitive -> Bool)
-> (Primitive -> Primitive -> Bool)
-> (Primitive -> Primitive -> Bool)
-> (Primitive -> Primitive -> Bool)
-> (Primitive -> Primitive -> Primitive)
-> (Primitive -> Primitive -> Primitive)
-> Ord Primitive
Primitive -> Primitive -> Bool
Primitive -> Primitive -> Ordering
Primitive -> Primitive -> Primitive
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Primitive -> Primitive -> Primitive
$cmin :: Primitive -> Primitive -> Primitive
max :: Primitive -> Primitive -> Primitive
$cmax :: Primitive -> Primitive -> Primitive
>= :: Primitive -> Primitive -> Bool
$c>= :: Primitive -> Primitive -> Bool
> :: Primitive -> Primitive -> Bool
$c> :: Primitive -> Primitive -> Bool
<= :: Primitive -> Primitive -> Bool
$c<= :: Primitive -> Primitive -> Bool
< :: Primitive -> Primitive -> Bool
$c< :: Primitive -> Primitive -> Bool
compare :: Primitive -> Primitive -> Ordering
$ccompare :: Primitive -> Primitive -> Ordering
$cp1Ord :: Eq Primitive
Ord,Int -> Primitive -> ShowS
[Primitive] -> ShowS
Primitive -> String
(Int -> Primitive -> ShowS)
-> (Primitive -> String)
-> ([Primitive] -> ShowS)
-> Show Primitive
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Primitive] -> ShowS
$cshowList :: [Primitive] -> ShowS
show :: Primitive -> String
$cshow :: Primitive -> String
showsPrec :: Int -> Primitive -> ShowS
$cshowsPrec :: Int -> Primitive -> ShowS
Show,Typeable Primitive
DataType
Constr
Typeable Primitive
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Primitive -> c Primitive)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Primitive)
-> (Primitive -> Constr)
-> (Primitive -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Primitive))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Primitive))
-> ((forall b. Data b => b -> b) -> Primitive -> Primitive)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Primitive -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Primitive -> r)
-> (forall u. (forall d. Data d => d -> u) -> Primitive -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> Primitive -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Primitive -> m Primitive)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Primitive -> m Primitive)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Primitive -> m Primitive)
-> Data Primitive
Primitive -> DataType
Primitive -> Constr
(forall b. Data b => b -> b) -> Primitive -> Primitive
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Primitive -> c Primitive
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Primitive
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Primitive -> u
forall u. (forall d. Data d => d -> u) -> Primitive -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Primitive -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Primitive -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Primitive -> m Primitive
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Primitive -> m Primitive
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Primitive
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Primitive -> c Primitive
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Primitive)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Primitive)
$cNullPrim :: Constr
$cBoolPrim :: Constr
$cNumberPrim :: Constr
$cStringPrim :: Constr
$tPrimitive :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Primitive -> m Primitive
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Primitive -> m Primitive
gmapMp :: (forall d. Data d => d -> m d) -> Primitive -> m Primitive
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Primitive -> m Primitive
gmapM :: (forall d. Data d => d -> m d) -> Primitive -> m Primitive
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Primitive -> m Primitive
gmapQi :: Int -> (forall d. Data d => d -> u) -> Primitive -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Primitive -> u
gmapQ :: (forall d. Data d => d -> u) -> Primitive -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Primitive -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Primitive -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Primitive -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Primitive -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Primitive -> r
gmapT :: (forall b. Data b => b -> b) -> Primitive -> Primitive
$cgmapT :: (forall b. Data b => b -> b) -> Primitive -> Primitive
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Primitive)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Primitive)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Primitive)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Primitive)
dataTypeOf :: Primitive -> DataType
$cdataTypeOf :: Primitive -> DataType
toConstr :: Primitive -> Constr
$ctoConstr :: Primitive -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Primitive
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Primitive
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Primitive -> c Primitive
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Primitive -> c Primitive
$cp1Data :: Typeable Primitive
Data,Typeable)
instance AsNumber Primitive where
_Number :: p Scientific (f Scientific) -> p Primitive (f Primitive)
_Number = (Scientific -> Primitive)
-> (Primitive -> Either Primitive Scientific)
-> Prism' Primitive Scientific
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism Scientific -> Primitive
NumberPrim ((Primitive -> Either Primitive Scientific)
-> Prism' Primitive Scientific)
-> (Primitive -> Either Primitive Scientific)
-> Prism' Primitive Scientific
forall a b. (a -> b) -> a -> b
$ \Primitive
v -> case Primitive
v of NumberPrim Scientific
s -> Scientific -> Either Primitive Scientific
forall a b. b -> Either a b
Right Scientific
s; Primitive
_ -> Primitive -> Either Primitive Scientific
forall a b. a -> Either a b
Left Primitive
v
{-# INLINE _Number #-}
class AsNumber t => AsPrimitive t where
_Primitive :: Prism' t Primitive
default _Primitive :: AsValue t => Prism' t Primitive
_Primitive = p Value (f Value) -> p t (f t)
forall t. AsValue t => Prism' t Value
_Value(p Value (f Value) -> p t (f t))
-> (p Primitive (f Primitive) -> p Value (f Value))
-> p Primitive (f Primitive)
-> p t (f t)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.p Primitive (f Primitive) -> p Value (f Value)
forall t. AsPrimitive t => Prism' t Primitive
_Primitive
{-# INLINE _Primitive #-}
_String :: Prism' t Text
_String = p Primitive (f Primitive) -> p t (f t)
forall t. AsPrimitive t => Prism' t Primitive
_Primitive(p Primitive (f Primitive) -> p t (f t))
-> (p Text (f Text) -> p Primitive (f Primitive))
-> p Text (f Text)
-> p t (f t)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Text -> Primitive)
-> (Primitive -> Either Primitive Text)
-> Prism Primitive Primitive Text Text
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism Text -> Primitive
StringPrim (\Primitive
v -> case Primitive
v of StringPrim Text
s -> Text -> Either Primitive Text
forall a b. b -> Either a b
Right Text
s; Primitive
_ -> Primitive -> Either Primitive Text
forall a b. a -> Either a b
Left Primitive
v)
{-# INLINE _String #-}
_Bool :: Prism' t Bool
_Bool = p Primitive (f Primitive) -> p t (f t)
forall t. AsPrimitive t => Prism' t Primitive
_Primitive(p Primitive (f Primitive) -> p t (f t))
-> (p Bool (f Bool) -> p Primitive (f Primitive))
-> p Bool (f Bool)
-> p t (f t)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Bool -> Primitive)
-> (Primitive -> Either Primitive Bool)
-> Prism Primitive Primitive Bool Bool
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism Bool -> Primitive
BoolPrim (\Primitive
v -> case Primitive
v of BoolPrim Bool
b -> Bool -> Either Primitive Bool
forall a b. b -> Either a b
Right Bool
b; Primitive
_ -> Primitive -> Either Primitive Bool
forall a b. a -> Either a b
Left Primitive
v)
{-# INLINE _Bool #-}
_Null :: Prism' t ()
_Null = p Primitive (f Primitive) -> p t (f t)
forall t. AsPrimitive t => Prism' t Primitive
_Primitive(p Primitive (f Primitive) -> p t (f t))
-> (p () (f ()) -> p Primitive (f Primitive))
-> p () (f ())
-> p t (f t)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(() -> Primitive)
-> (Primitive -> Either Primitive ())
-> Prism Primitive Primitive () ()
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism (Primitive -> () -> Primitive
forall a b. a -> b -> a
const Primitive
NullPrim) (\Primitive
v -> case Primitive
v of Primitive
NullPrim -> () -> Either Primitive ()
forall a b. b -> Either a b
Right (); Primitive
_ -> Primitive -> Either Primitive ()
forall a b. a -> Either a b
Left Primitive
v)
{-# INLINE _Null #-}
instance AsPrimitive Value where
_Primitive :: p Primitive (f Primitive) -> p Value (f Value)
_Primitive = (Primitive -> Value)
-> (Value -> Either Value Primitive) -> Prism' Value Primitive
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism Primitive -> Value
fromPrim Value -> Either Value Primitive
toPrim
where
toPrim :: Value -> Either Value Primitive
toPrim (String Text
s) = Primitive -> Either Value Primitive
forall a b. b -> Either a b
Right (Primitive -> Either Value Primitive)
-> Primitive -> Either Value Primitive
forall a b. (a -> b) -> a -> b
$ Text -> Primitive
StringPrim Text
s
toPrim (Number Scientific
n) = Primitive -> Either Value Primitive
forall a b. b -> Either a b
Right (Primitive -> Either Value Primitive)
-> Primitive -> Either Value Primitive
forall a b. (a -> b) -> a -> b
$ Scientific -> Primitive
NumberPrim Scientific
n
toPrim (Bool Bool
b) = Primitive -> Either Value Primitive
forall a b. b -> Either a b
Right (Primitive -> Either Value Primitive)
-> Primitive -> Either Value Primitive
forall a b. (a -> b) -> a -> b
$ Bool -> Primitive
BoolPrim Bool
b
toPrim Value
Null = Primitive -> Either Value Primitive
forall a b. b -> Either a b
Right Primitive
NullPrim
toPrim Value
v = Value -> Either Value Primitive
forall a b. a -> Either a b
Left Value
v
{-# INLINE toPrim #-}
fromPrim :: Primitive -> Value
fromPrim (StringPrim Text
s) = Text -> Value
String Text
s
fromPrim (NumberPrim Scientific
n) = Scientific -> Value
Number Scientific
n
fromPrim (BoolPrim Bool
b) = Bool -> Value
Bool Bool
b
fromPrim Primitive
NullPrim = Value
Null
{-# INLINE fromPrim #-}
{-# INLINE _Primitive #-}
_String :: p Text (f Text) -> p Value (f Value)
_String = (Text -> Value)
-> (Value -> Either Value Text) -> Prism' Value Text
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism Text -> Value
String ((Value -> Either Value Text) -> Prism' Value Text)
-> (Value -> Either Value Text) -> Prism' Value Text
forall a b. (a -> b) -> a -> b
$ \Value
v -> case Value
v of String Text
s -> Text -> Either Value Text
forall a b. b -> Either a b
Right Text
s; Value
_ -> Value -> Either Value Text
forall a b. a -> Either a b
Left Value
v
{-# INLINE _String #-}
_Bool :: p Bool (f Bool) -> p Value (f Value)
_Bool = (Bool -> Value)
-> (Value -> Either Value Bool) -> Prism' Value Bool
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism Bool -> Value
Bool (\Value
v -> case Value
v of Bool Bool
b -> Bool -> Either Value Bool
forall a b. b -> Either a b
Right Bool
b; Value
_ -> Value -> Either Value Bool
forall a b. a -> Either a b
Left Value
v)
{-# INLINE _Bool #-}
_Null :: p () (f ()) -> p Value (f Value)
_Null = (() -> Value) -> (Value -> Either Value ()) -> Prism' Value ()
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism (Value -> () -> Value
forall a b. a -> b -> a
const Value
Null) (\Value
v -> case Value
v of Value
Null -> () -> Either Value ()
forall a b. b -> Either a b
Right (); Value
_ -> Value -> Either Value ()
forall a b. a -> Either a b
Left Value
v)
{-# INLINE _Null #-}
instance AsPrimitive Strict.ByteString
instance AsPrimitive Lazy.ByteString
instance AsPrimitive Text.Text
instance AsPrimitive LazyText.Text
instance AsPrimitive String
instance AsPrimitive Primitive where
_Primitive :: p Primitive (f Primitive) -> p Primitive (f Primitive)
_Primitive = p Primitive (f Primitive) -> p Primitive (f Primitive)
forall a. a -> a
id
{-# INLINE _Primitive #-}
nonNull :: Prism' Value Value
nonNull :: p Value (f Value) -> p Value (f Value)
nonNull = (Value -> Value)
-> (Value -> Either Value Value) -> Prism Value Value Value Value
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism Value -> Value
forall a. a -> a
id (\Value
v -> if APrism Value Value () () -> Value -> Bool
forall s t a b. APrism s t a b -> s -> Bool
isn't APrism Value Value () ()
forall t. AsPrimitive t => Prism' t ()
_Null Value
v then Value -> Either Value Value
forall a b. b -> Either a b
Right Value
v else Value -> Either Value Value
forall a b. a -> Either a b
Left Value
v)
{-# INLINE nonNull #-}
class AsPrimitive t => AsValue t where
_Value :: Prism' t Value
_Object :: Prism' t (HashMap Text Value)
_Object = p Value (f Value) -> p t (f t)
forall t. AsValue t => Prism' t Value
_Value(p Value (f Value) -> p t (f t))
-> (p (HashMap Text Value) (f (HashMap Text Value))
-> p Value (f Value))
-> p (HashMap Text Value) (f (HashMap Text Value))
-> p t (f t)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(HashMap Text Value -> Value)
-> (Value -> Either Value (HashMap Text Value))
-> Prism Value Value (HashMap Text Value) (HashMap Text Value)
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism HashMap Text Value -> Value
Object (\Value
v -> case Value
v of Object HashMap Text Value
o -> HashMap Text Value -> Either Value (HashMap Text Value)
forall a b. b -> Either a b
Right HashMap Text Value
o; Value
_ -> Value -> Either Value (HashMap Text Value)
forall a b. a -> Either a b
Left Value
v)
{-# INLINE _Object #-}
_Array :: Prism' t (Vector Value)
_Array = p Value (f Value) -> p t (f t)
forall t. AsValue t => Prism' t Value
_Value(p Value (f Value) -> p t (f t))
-> (p (Vector Value) (f (Vector Value)) -> p Value (f Value))
-> p (Vector Value) (f (Vector Value))
-> p t (f t)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Vector Value -> Value)
-> (Value -> Either Value (Vector Value))
-> Prism Value Value (Vector Value) (Vector Value)
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism Vector Value -> Value
Array (\Value
v -> case Value
v of Array Vector Value
a -> Vector Value -> Either Value (Vector Value)
forall a b. b -> Either a b
Right Vector Value
a; Value
_ -> Value -> Either Value (Vector Value)
forall a b. a -> Either a b
Left Value
v)
{-# INLINE _Array #-}
instance AsValue Value where
_Value :: p Value (f Value) -> p Value (f Value)
_Value = p Value (f Value) -> p Value (f Value)
forall a. a -> a
id
{-# INLINE _Value #-}
instance AsValue Strict.ByteString where
_Value :: p Value (f Value) -> p ByteString (f ByteString)
_Value = p Value (f Value) -> p ByteString (f ByteString)
forall t a b. (AsJSON t, FromJSON a, ToJSON b) => Prism t t a b
_JSON
{-# INLINE _Value #-}
instance AsValue Lazy.ByteString where
_Value :: p Value (f Value) -> p ByteString (f ByteString)
_Value = p Value (f Value) -> p ByteString (f ByteString)
forall t a b. (AsJSON t, FromJSON a, ToJSON b) => Prism t t a b
_JSON
{-# INLINE _Value #-}
instance AsValue String where
_Value :: p Value (f Value) -> p String (f String)
_Value = p ByteString (f ByteString) -> p String (f String)
Iso' String ByteString
strictUtf8(p ByteString (f ByteString) -> p String (f String))
-> (p Value (f Value) -> p ByteString (f ByteString))
-> p Value (f Value)
-> p String (f String)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.p Value (f Value) -> p ByteString (f ByteString)
forall t a b. (AsJSON t, FromJSON a, ToJSON b) => Prism t t a b
_JSON
{-# INLINE _Value #-}
instance AsValue Text where
_Value :: p Value (f Value) -> p Text (f Text)
_Value = p ByteString (f ByteString) -> p Text (f Text)
Iso' Text ByteString
strictTextUtf8(p ByteString (f ByteString) -> p Text (f Text))
-> (p Value (f Value) -> p ByteString (f ByteString))
-> p Value (f Value)
-> p Text (f Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.p Value (f Value) -> p ByteString (f ByteString)
forall t a b. (AsJSON t, FromJSON a, ToJSON b) => Prism t t a b
_JSON
{-# INLINE _Value #-}
instance AsValue LazyText.Text where
_Value :: p Value (f Value) -> p Text (f Text)
_Value = p ByteString (f ByteString) -> p Text (f Text)
Iso' Text ByteString
lazyTextUtf8(p ByteString (f ByteString) -> p Text (f Text))
-> (p Value (f Value) -> p ByteString (f ByteString))
-> p Value (f Value)
-> p Text (f Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.p Value (f Value) -> p ByteString (f ByteString)
forall t a b. (AsJSON t, FromJSON a, ToJSON b) => Prism t t a b
_JSON
{-# INLINE _Value #-}
key :: AsValue t => Text -> Traversal' t Value
key :: Text -> Traversal' t Value
key Text
i = (HashMap Text Value -> f (HashMap Text Value)) -> t -> f t
forall t. AsValue t => Prism' t (HashMap Text Value)
_Object ((HashMap Text Value -> f (HashMap Text Value)) -> t -> f t)
-> ((Value -> f Value)
-> HashMap Text Value -> f (HashMap Text Value))
-> (Value -> f Value)
-> t
-> f t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index (HashMap Text Value)
-> Traversal' (HashMap Text Value) (IxValue (HashMap Text Value))
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Text
Index (HashMap Text Value)
i
{-# INLINE key #-}
members :: AsValue t => IndexedTraversal' Text t Value
members :: IndexedTraversal' Text t Value
members = (HashMap Text Value -> f (HashMap Text Value)) -> t -> f t
forall t. AsValue t => Prism' t (HashMap Text Value)
_Object ((HashMap Text Value -> f (HashMap Text Value)) -> t -> f t)
-> (p Value (f Value)
-> HashMap Text Value -> f (HashMap Text Value))
-> p Value (f Value)
-> t
-> f t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p Value (f Value) -> HashMap Text Value -> f (HashMap Text Value)
forall i (t :: * -> *) a b.
TraversableWithIndex i t =>
IndexedTraversal i (t a) (t b) a b
itraversed
{-# INLINE members #-}
nth :: AsValue t => Int -> Traversal' t Value
nth :: Int -> Traversal' t Value
nth Int
i = (Vector Value -> f (Vector Value)) -> t -> f t
forall t. AsValue t => Prism' t (Vector Value)
_Array ((Vector Value -> f (Vector Value)) -> t -> f t)
-> ((Value -> f Value) -> Vector Value -> f (Vector Value))
-> (Value -> f Value)
-> t
-> f t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index (Vector Value)
-> Traversal' (Vector Value) (IxValue (Vector Value))
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Int
Index (Vector Value)
i
{-# INLINE nth #-}
values :: AsValue t => IndexedTraversal' Int t Value
values :: IndexedTraversal' Int t Value
values = (Vector Value -> f (Vector Value)) -> t -> f t
forall t. AsValue t => Prism' t (Vector Value)
_Array ((Vector Value -> f (Vector Value)) -> t -> f t)
-> (p Value (f Value) -> Vector Value -> f (Vector Value))
-> p Value (f Value)
-> t
-> f t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p Value (f Value) -> Vector Value -> f (Vector Value)
forall (f :: * -> *) a b.
Traversable f =>
IndexedTraversal Int (f a) (f b) a b
traversed
{-# INLINE values #-}
strictUtf8 :: Iso' String Strict.ByteString
strictUtf8 :: p ByteString (f ByteString) -> p String (f String)
strictUtf8 = p Text (f Text) -> p String (f String)
forall t. IsText t => Iso' String t
packed (p Text (f Text) -> p String (f String))
-> (p ByteString (f ByteString) -> p Text (f Text))
-> p ByteString (f ByteString)
-> p String (f String)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p ByteString (f ByteString) -> p Text (f Text)
Iso' Text ByteString
strictTextUtf8
strictTextUtf8 :: Iso' Text.Text Strict.ByteString
strictTextUtf8 :: p ByteString (f ByteString) -> p Text (f Text)
strictTextUtf8 = (Text -> ByteString)
-> (ByteString -> Text) -> Iso' Text ByteString
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso Text -> ByteString
StrictText.encodeUtf8 ByteString -> Text
StrictText.decodeUtf8
lazyTextUtf8 :: Iso' LazyText.Text Lazy.ByteString
lazyTextUtf8 :: p ByteString (f ByteString) -> p Text (f Text)
lazyTextUtf8 = (Text -> ByteString)
-> (ByteString -> Text) -> Iso' Text ByteString
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso Text -> ByteString
LazyText.encodeUtf8 ByteString -> Text
LazyText.decodeUtf8
_JSON' :: (AsJSON t, FromJSON a, ToJSON a) => Prism' t a
_JSON' :: Prism' t a
_JSON' = p a (f a) -> p t (f t)
forall t a b. (AsJSON t, FromJSON a, ToJSON b) => Prism t t a b
_JSON
class AsJSON t where
_JSON :: (FromJSON a, ToJSON b) => Prism t t a b
instance AsJSON Strict.ByteString where
_JSON :: Prism ByteString ByteString a b
_JSON = p ByteString (f ByteString) -> p ByteString (f ByteString)
forall lazy strict. Strict lazy strict => Iso' strict lazy
lazy(p ByteString (f ByteString) -> p ByteString (f ByteString))
-> (p a (f b) -> p ByteString (f ByteString))
-> p a (f b)
-> p ByteString (f ByteString)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.p a (f b) -> p ByteString (f ByteString)
forall t a b. (AsJSON t, FromJSON a, ToJSON b) => Prism t t a b
_JSON
{-# INLINE _JSON #-}
instance AsJSON Lazy.ByteString where
_JSON :: Prism ByteString ByteString a b
_JSON = (b -> ByteString)
-> (ByteString -> Maybe a) -> Prism ByteString ByteString a b
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism' b -> ByteString
forall a. ToJSON a => a -> ByteString
encode ByteString -> Maybe a
forall a. FromJSON a => ByteString -> Maybe a
decodeValue
where
decodeValue :: (FromJSON a) => Lazy.ByteString -> Maybe a
decodeValue :: ByteString -> Maybe a
decodeValue ByteString
s = Result Value -> Maybe Value
forall r. Result r -> Maybe r
maybeResult (Parser Value -> ByteString -> Result Value
forall a. Parser a -> ByteString -> Result a
parse Parser Value
value ByteString
s) Maybe Value -> (Value -> Maybe a) -> Maybe a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Value
x -> case Value -> Result a
forall a. FromJSON a => Value -> Result a
fromJSON Value
x of
Success a
v -> a -> Maybe a
forall a. a -> Maybe a
Just a
v
Result a
_ -> Maybe a
forall a. Maybe a
Nothing
{-# INLINE _JSON #-}
instance AsJSON String where
_JSON :: Prism String String a b
_JSON = p ByteString (f ByteString) -> p String (f String)
Iso' String ByteString
strictUtf8(p ByteString (f ByteString) -> p String (f String))
-> (p a (f b) -> p ByteString (f ByteString))
-> p a (f b)
-> p String (f String)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.p a (f b) -> p ByteString (f ByteString)
forall t a b. (AsJSON t, FromJSON a, ToJSON b) => Prism t t a b
_JSON
{-# INLINE _JSON #-}
instance AsJSON Text where
_JSON :: Prism Text Text a b
_JSON = p ByteString (f ByteString) -> p Text (f Text)
Iso' Text ByteString
strictTextUtf8(p ByteString (f ByteString) -> p Text (f Text))
-> (p a (f b) -> p ByteString (f ByteString))
-> p a (f b)
-> p Text (f Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.p a (f b) -> p ByteString (f ByteString)
forall t a b. (AsJSON t, FromJSON a, ToJSON b) => Prism t t a b
_JSON
{-# INLINE _JSON #-}
instance AsJSON LazyText.Text where
_JSON :: Prism Text Text a b
_JSON = p ByteString (f ByteString) -> p Text (f Text)
Iso' Text ByteString
lazyTextUtf8(p ByteString (f ByteString) -> p Text (f Text))
-> (p a (f b) -> p ByteString (f ByteString))
-> p a (f b)
-> p Text (f Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.p a (f b) -> p ByteString (f ByteString)
forall t a b. (AsJSON t, FromJSON a, ToJSON b) => Prism t t a b
_JSON
{-# INLINE _JSON #-}
instance AsJSON Value where
_JSON :: Prism Value Value a b
_JSON = (b -> Value) -> (Value -> Either Value a) -> Prism Value Value a b
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism b -> Value
forall a. ToJSON a => a -> Value
toJSON ((Value -> Either Value a) -> Prism Value Value a b)
-> (Value -> Either Value a) -> Prism Value Value a b
forall a b. (a -> b) -> a -> b
$ \Value
x -> case Value -> Result a
forall a. FromJSON a => Value -> Result a
fromJSON Value
x of
Success a
y -> a -> Either Value a
forall a b. b -> Either a b
Right a
y;
Result a
_ -> Value -> Either Value a
forall a b. a -> Either a b
Left Value
x
{-# INLINE _JSON #-}
type instance Index Value = Text
type instance IxValue Value = Value
instance Ixed Value where
ix :: Index Value -> Traversal' Value (IxValue Value)
ix Index Value
i IxValue Value -> f (IxValue Value)
f (Object HashMap Text Value
o) = HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> f (HashMap Text Value) -> f Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Index (HashMap Text Value)
-> (IxValue (HashMap Text Value)
-> f (IxValue (HashMap Text Value)))
-> HashMap Text Value
-> f (HashMap Text Value)
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Index (HashMap Text Value)
Index Value
i IxValue (HashMap Text Value) -> f (IxValue (HashMap Text Value))
IxValue Value -> f (IxValue Value)
f HashMap Text Value
o
ix Index Value
_ IxValue Value -> f (IxValue Value)
_ Value
v = Value -> f Value
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
v
{-# INLINE ix #-}
instance Plated Value where
plate :: (Value -> f Value) -> Value -> f Value
plate Value -> f Value
f (Object HashMap Text Value
o) = HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> f (HashMap Text Value) -> f Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Value -> f Value) -> HashMap Text Value -> f (HashMap Text Value)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Value -> f Value
f HashMap Text Value
o
plate Value -> f Value
f (Array Vector Value
a) = Vector Value -> Value
Array (Vector Value -> Value) -> f (Vector Value) -> f Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Value -> f Value) -> Vector Value -> f (Vector Value)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Value -> f Value
f Vector Value
a
plate Value -> f Value
_ Value
xs = Value -> f Value
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
xs
{-# INLINE plate #-}
#if __GLASGOW_HASKELL__ >= 800
pattern JSON :: (FromJSON a, ToJSON a, AsJSON t) => () => a -> t
pattern $bJSON :: a -> t
$mJSON :: forall r a t.
(FromJSON a, ToJSON a, AsJSON t) =>
t -> (a -> r) -> (Void# -> r) -> r
JSON a <- (preview _JSON -> Just a) where
JSON a
a = Tagged a (Identity a) -> Tagged t (Identity t)
forall t a b. (AsJSON t, FromJSON a, ToJSON b) => Prism t t a b
_JSON (Tagged a (Identity a) -> Tagged t (Identity t)) -> a -> t
forall t b. AReview t b -> b -> t
# a
a
pattern Value_ :: (FromJSON a, ToJSON a) => () => a -> Value
pattern $bValue_ :: a -> Value
$mValue_ :: forall r a.
(FromJSON a, ToJSON a) =>
Value -> (a -> r) -> (Void# -> r) -> r
Value_ a <- (fromJSON -> Success a) where
Value_ a
a = a -> Value
forall a. ToJSON a => a -> Value
toJSON a
a
pattern Number_ :: AsNumber t => Scientific -> t
pattern $bNumber_ :: Scientific -> t
$mNumber_ :: forall r t.
AsNumber t =>
t -> (Scientific -> r) -> (Void# -> r) -> r
Number_ n <- (preview _Number -> Just n) where
Number_ Scientific
n = Tagged Scientific (Identity Scientific) -> Tagged t (Identity t)
forall t. AsNumber t => Prism' t Scientific
_Number (Tagged Scientific (Identity Scientific) -> Tagged t (Identity t))
-> Scientific -> t
forall t b. AReview t b -> b -> t
# Scientific
n
pattern Double :: AsNumber t => Double -> t
pattern $bDouble :: Double -> t
$mDouble :: forall r t. AsNumber t => t -> (Double -> r) -> (Void# -> r) -> r
Double d <- (preview _Double -> Just d) where
Double Double
d = Tagged Double (Identity Double) -> Tagged t (Identity t)
forall t. AsNumber t => Prism' t Double
_Double (Tagged Double (Identity Double) -> Tagged t (Identity t))
-> Double -> t
forall t b. AReview t b -> b -> t
# Double
d
pattern Integer :: AsNumber t => Integer -> t
pattern $bInteger :: Integer -> t
$mInteger :: forall r t. AsNumber t => t -> (Integer -> r) -> (Void# -> r) -> r
Integer i <- (preview _Integer -> Just i) where
Integer Integer
i = Tagged Integer (Identity Integer) -> Tagged t (Identity t)
forall t. AsNumber t => Prism' t Integer
_Integer (Tagged Integer (Identity Integer) -> Tagged t (Identity t))
-> Integer -> t
forall t b. AReview t b -> b -> t
# Integer
i
pattern Integral :: (AsNumber t, Integral a) => a -> t
pattern $bIntegral :: a -> t
$mIntegral :: forall r t a.
(AsNumber t, Integral a) =>
t -> (a -> r) -> (Void# -> r) -> r
Integral d <- (preview _Integral -> Just d) where
Integral a
d = Tagged a (Identity a) -> Tagged t (Identity t)
forall t a. (AsNumber t, Integral a) => Prism' t a
_Integral (Tagged a (Identity a) -> Tagged t (Identity t)) -> a -> t
forall t b. AReview t b -> b -> t
# a
d
pattern Primitive :: AsPrimitive t => Primitive -> t
pattern $bPrimitive :: Primitive -> t
$mPrimitive :: forall r t.
AsPrimitive t =>
t -> (Primitive -> r) -> (Void# -> r) -> r
Primitive p <- (preview _Primitive -> Just p) where
Primitive Primitive
p = Tagged Primitive (Identity Primitive) -> Tagged t (Identity t)
forall t. AsPrimitive t => Prism' t Primitive
_Primitive (Tagged Primitive (Identity Primitive) -> Tagged t (Identity t))
-> Primitive -> t
forall t b. AReview t b -> b -> t
# Primitive
p
pattern Bool_ :: AsPrimitive t => Bool -> t
pattern $bBool_ :: Bool -> t
$mBool_ :: forall r t. AsPrimitive t => t -> (Bool -> r) -> (Void# -> r) -> r
Bool_ b <- (preview _Bool -> Just b) where
Bool_ Bool
b = Tagged Bool (Identity Bool) -> Tagged t (Identity t)
forall t. AsPrimitive t => Prism' t Bool
_Bool (Tagged Bool (Identity Bool) -> Tagged t (Identity t)) -> Bool -> t
forall t b. AReview t b -> b -> t
# Bool
b
pattern String_ :: AsPrimitive t => Text -> t
pattern $bString_ :: Text -> t
$mString_ :: forall r t. AsPrimitive t => t -> (Text -> r) -> (Void# -> r) -> r
String_ p <- (preview _String -> Just p) where
String_ Text
p = Tagged Text (Identity Text) -> Tagged t (Identity t)
forall t. AsPrimitive t => Prism' t Text
_String (Tagged Text (Identity Text) -> Tagged t (Identity t)) -> Text -> t
forall t b. AReview t b -> b -> t
# Text
p
pattern Null_ :: AsPrimitive t => t
pattern $bNull_ :: t
$mNull_ :: forall r t. AsPrimitive t => t -> (Void# -> r) -> (Void# -> r) -> r
Null_ <- (preview _Null -> Just ()) where
Null_ = Tagged () (Identity ()) -> Tagged t (Identity t)
forall t. AsPrimitive t => Prism' t ()
_Null (Tagged () (Identity ()) -> Tagged t (Identity t)) -> () -> t
forall t b. AReview t b -> b -> t
# ()
#endif