{-# LANGUAGE CPP                   #-}
{-# LANGUAGE DefaultSignatures     #-}
{-# LANGUAGE DeriveDataTypeable    #-}
{-# LANGUAGE FlexibleContexts      #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PatternSynonyms       #-}
{-# LANGUAGE RankNTypes            #-}
{-# LANGUAGE Trustworthy           #-}
{-# LANGUAGE TypeFamilies          #-}
{-# LANGUAGE ViewPatterns          #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
--------------------------------------------------------------------
-- |
-- Copyright :  (c) Oleg Grenrus 2019, (c) Edward Kmett 2013-2019, (c) Paul Wilson 2012
-- License   :  MIT
-- Maintainer:  Edward Kmett <ekmett@gmail.com>
-- Stability :  experimental
-- Portability: non-portable
--
-- This module also exports orphan @'Ixed' 'Value'@ and
-- @'Plated' 'Value'@ instances.
--------------------------------------------------------------------
module Data.Aeson.Optics
  (
  -- * Numbers
    AsNumber(..)
  , _Integral
  , nonNull
  -- * Objects and Arrays
  , AsValue(..)
  , key, members
  , nth, values
  , IsKey (..)
  -- * Decoding
  , AsJSON(..)
  , _JSON'
  -- * Pattern Synonyms
  , pattern JSON
  , pattern Value_
  , pattern Number_
  , pattern Double
  , pattern Integer
  , pattern Integral
  , pattern Bool_
  , pattern String_
  , pattern Null_
  , pattern Key_
  ) where

import Prelude hiding (null)

import Data.Aeson
       (FromJSON, Result (..), ToJSON, Value (..), encode, fromJSON, toJSON, decode)
import Data.Scientific                 (Scientific)
import Data.Text                       (Text)
import Data.Text.Optics                (packed)
import Data.Text.Short                 (ShortText)
import Data.Vector                     (Vector)

import Optics.At ()
import Optics.Core
import Optics.Indexed ()

import qualified Data.Aeson.Key             as Key
import qualified Data.Aeson.KeyMap          as KM
import qualified Data.ByteString            as Strict
import qualified Data.ByteString.Lazy       as LBS
import qualified Data.Scientific            as Scientific
import qualified Data.Text                  as StrictText
import qualified Data.Text.Encoding         as StrictText
import qualified Data.Text.Lazy             as LazyText
import qualified Data.Text.Lazy.Encoding    as LazyText

-- $setup
-- >>> import Optics.Core
-- >>> import Data.Aeson (Value (..))
-- >>> import Data.Text (Text)
-- >>> import qualified Data.ByteString             as Strict
-- >>> import qualified Data.ByteString.Char8       as Strict.Char8
-- >>> import qualified Data.ByteString.Lazy        as Lazy
-- >>> import qualified Data.ByteString.Lazy.Char8  as Lazy.Char8
-- >>> import qualified Data.Aeson.KeyMap           as KeyMap
-- >>> import qualified Data.Vector                 as Vector
-- >>> :set -XOverloadedStrings
-- >>> import Optics.Operators

------------------------------------------------------------------------------
-- Scientific prisms
------------------------------------------------------------------------------

class AsNumber t where
  -- |
  -- >>> "[1, \"x\"]" ^? nth 0 % _Number
  -- Just 1.0
  --
  -- >>> "[1, \"x\"]" ^? nth 1 % _Number
  -- Nothing
  _Number :: Prism' t Scientific
  default _Number :: AsValue t => Prism' t Scientific
  _Number = forall (t :: OpticKind). AsValue t => Prism' t Value
_Valueforall (k :: OpticKind) (l :: OpticKind) (m :: OpticKind)
       (is :: IxList) (js :: IxList) (ks :: IxList) (s :: OpticKind)
       (t :: OpticKind) (u :: OpticKind) (v :: OpticKind) (a :: OpticKind)
       (b :: OpticKind).
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
%forall (t :: OpticKind). AsNumber t => Prism' t Scientific
_Number
  {-# INLINE _Number #-}

  -- |
  -- Prism into an 'Double' over a 'Value', 'Primitive' or 'Scientific'
  --
  -- >>> "[10.2]" ^? nth 0 % _Double
  -- Just 10.2
  _Double :: Prism' t Double
  _Double = forall (t :: OpticKind). AsNumber t => Prism' t Scientific
_Numberforall (k :: OpticKind) (l :: OpticKind) (m :: OpticKind)
       (is :: IxList) (js :: IxList) (ks :: IxList) (s :: OpticKind)
       (t :: OpticKind) (u :: OpticKind) (v :: OpticKind) (a :: OpticKind)
       (b :: OpticKind).
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
%forall (s :: OpticKind) (a :: OpticKind) (b :: OpticKind)
       (t :: OpticKind).
(s -> a) -> (b -> t) -> Iso s t a b
iso forall (a :: OpticKind). RealFloat a => Scientific -> a
Scientific.toRealFloat forall (a :: OpticKind) (b :: OpticKind).
(Real a, Fractional b) =>
a -> b
realToFrac
  {-# INLINE _Double #-}

  -- |
  -- Prism into an 'Integer' over a 'Value', 'Primitive' or 'Scientific'
  --
  -- >>> "[10]" ^? nth 0 % _Integer
  -- Just 10
  --
  -- >>> "[10.5]" ^? nth 0 % _Integer
  -- Just 10
  --
  -- >>> "42" ^? _Integer
  -- Just 42
  _Integer :: Prism' t Integer
  _Integer = forall (t :: OpticKind). AsNumber t => Prism' t Scientific
_Numberforall (k :: OpticKind) (l :: OpticKind) (m :: OpticKind)
       (is :: IxList) (js :: IxList) (ks :: IxList) (s :: OpticKind)
       (t :: OpticKind) (u :: OpticKind) (v :: OpticKind) (a :: OpticKind)
       (b :: OpticKind).
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
%forall (s :: OpticKind) (a :: OpticKind) (b :: OpticKind)
       (t :: OpticKind).
(s -> a) -> (b -> t) -> Iso s t a b
iso forall (a :: OpticKind) (b :: OpticKind).
(RealFrac a, Integral b) =>
a -> b
floor forall (a :: OpticKind) (b :: OpticKind).
(Integral a, Num b) =>
a -> b
fromIntegral
  {-# INLINE _Integer #-}

instance AsNumber Value where
  _Number :: Prism' Value Scientific
_Number = forall (b :: OpticKind) (t :: OpticKind) (s :: OpticKind)
       (a :: OpticKind).
(b -> t) -> (s -> Either t a) -> Prism s t a b
prism Scientific -> Value
Number forall (a :: OpticKind) b. (a -> b) -> a -> b
$ \Value
v -> case Value
v of Number Scientific
n -> forall (a :: OpticKind) (b :: OpticKind). b -> Either a b
Right Scientific
n; Value
_ -> forall (a :: OpticKind) (b :: OpticKind). a -> Either a b
Left Value
v
  {-# INLINE _Number #-}

instance AsNumber Scientific where
  _Number :: Prism' Scientific Scientific
_Number = forall (destKind :: OpticKind) (srcKind :: OpticKind)
       (is :: IxList) (s :: OpticKind) (t :: OpticKind) (a :: OpticKind)
       (b :: OpticKind).
Is srcKind destKind =>
Optic srcKind is s t a b -> Optic destKind is s t a b
castOptic forall (a :: OpticKind). Iso' a a
simple
  {-# INLINE _Number #-}

instance AsNumber Strict.ByteString
instance AsNumber LBS.ByteString
instance AsNumber Text
instance AsNumber LazyText.Text
instance AsNumber String

------------------------------------------------------------------------------
-- Conversion Prisms
------------------------------------------------------------------------------

-- | Access Integer 'Value's as Integrals.
--
-- >>> "[10]" ^? nth 0 % _Integral
-- Just 10
--
-- >>> "[10.5]" ^? nth 0 % _Integral
-- Just 10
_Integral :: (AsNumber t, Integral a) => Prism' t a
_Integral :: forall (t :: OpticKind) (a :: OpticKind).
(AsNumber t, Integral a) =>
Prism' t a
_Integral = forall (t :: OpticKind). AsNumber t => Prism' t Scientific
_Number forall (k :: OpticKind) (l :: OpticKind) (m :: OpticKind)
       (is :: IxList) (js :: IxList) (ks :: IxList) (s :: OpticKind)
       (t :: OpticKind) (u :: OpticKind) (v :: OpticKind) (a :: OpticKind)
       (b :: OpticKind).
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall (s :: OpticKind) (a :: OpticKind) (b :: OpticKind)
       (t :: OpticKind).
(s -> a) -> (b -> t) -> Iso s t a b
iso forall (a :: OpticKind) (b :: OpticKind).
(RealFrac a, Integral b) =>
a -> b
floor forall (a :: OpticKind) (b :: OpticKind).
(Integral a, Num b) =>
a -> b
fromIntegral
{-# INLINE _Integral #-}

-- | Prism into non-'Null' values
--
-- >>> "{\"a\": \"xyz\", \"b\": null}" ^? key "a" % nonNull
-- Just (String "xyz")
--
-- >>> "{\"a\": {}, \"b\": null}" ^? key "a" % nonNull
-- Just (Object (fromList []))
--
-- >>> "{\"a\": \"xyz\", \"b\": null}" ^? key "b" % nonNull
-- Nothing
nonNull :: Prism' Value Value
nonNull :: Prism' Value Value
nonNull = forall (b :: OpticKind) (t :: OpticKind) (s :: OpticKind)
       (a :: OpticKind).
(b -> t) -> (s -> Either t a) -> Prism s t a b
prism forall (a :: OpticKind). a -> a
id (\Value
v -> if forall (k :: OpticKind) (is :: IxList) (s :: OpticKind)
       (a :: OpticKind).
Is k An_AffineFold =>
Optic' k is s a -> s -> Bool
isn't forall (t :: OpticKind). AsValue t => Prism' t ()
_Null Value
v then forall (a :: OpticKind) (b :: OpticKind). b -> Either a b
Right Value
v else forall (a :: OpticKind) (b :: OpticKind). a -> Either a b
Left Value
v)
{-# INLINE nonNull #-}

------------------------------------------------------------------------------
-- Non-primitive traversals
------------------------------------------------------------------------------

class AsNumber t => AsValue t where
  -- |
  -- >>> preview _Value "[1,2,3]" == Just (Array (Vector.fromList [Number 1.0,Number 2.0,Number 3.0]))
  -- True
  _Value :: Prism' t Value

  -- |
  -- >>> "{\"a\": {}, \"b\": null}" ^? key "a" % _Object
  -- Just (fromList [])
  --
  -- >>> "{\"a\": {}, \"b\": null}" ^? key "b" % _Object
  -- Nothing
  --
  -- >>> _Object # KeyMap.fromList [("key", _String # "value")] :: String
  -- "{\"key\":\"value\"}"
  _Object :: Prism' t (KM.KeyMap Value)
  _Object = forall (t :: OpticKind). AsValue t => Prism' t Value
_Valueforall (k :: OpticKind) (l :: OpticKind) (m :: OpticKind)
       (is :: IxList) (js :: IxList) (ks :: IxList) (s :: OpticKind)
       (t :: OpticKind) (u :: OpticKind) (v :: OpticKind) (a :: OpticKind)
       (b :: OpticKind).
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
%forall (b :: OpticKind) (t :: OpticKind) (s :: OpticKind)
       (a :: OpticKind).
(b -> t) -> (s -> Either t a) -> Prism s t a b
prism KeyMap Value -> Value
Object  (\Value
v -> case Value
v of Object KeyMap Value
o -> forall (a :: OpticKind) (b :: OpticKind). b -> Either a b
Right KeyMap Value
o; Value
_ -> forall (a :: OpticKind) (b :: OpticKind). a -> Either a b
Left Value
v)

  -- |
  -- >>> preview _Array "[1,2,3]" == Just (Vector.fromList [Number 1.0,Number 2.0,Number 3.0])
  -- True
  _Array :: Prism' t (Vector Value)
  _Array = forall (t :: OpticKind). AsValue t => Prism' t Value
_Valueforall (k :: OpticKind) (l :: OpticKind) (m :: OpticKind)
       (is :: IxList) (js :: IxList) (ks :: IxList) (s :: OpticKind)
       (t :: OpticKind) (u :: OpticKind) (v :: OpticKind) (a :: OpticKind)
       (b :: OpticKind).
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
%forall (b :: OpticKind) (t :: OpticKind) (s :: OpticKind)
       (a :: OpticKind).
(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 -> forall (a :: OpticKind) (b :: OpticKind). b -> Either a b
Right Vector Value
a; Value
_ -> forall (a :: OpticKind) (b :: OpticKind). a -> Either a b
Left Value
v)
  {-# INLINE _Array #-}

  -- |
  -- >>> "{\"a\": \"xyz\", \"b\": true}" ^? key "a" % _String
  -- Just "xyz"
  --
  -- >>> "{\"a\": \"xyz\", \"b\": true}" ^? key "b" % _String
  -- Nothing
  --
  -- >>> _Object # KeyMap.fromList [("key", _String # "value")] :: String
  -- "{\"key\":\"value\"}"
  _String :: Prism' t Text
  _String = forall (t :: OpticKind). AsValue t => Prism' t Value
_Valueforall (k :: OpticKind) (l :: OpticKind) (m :: OpticKind)
       (is :: IxList) (js :: IxList) (ks :: IxList) (s :: OpticKind)
       (t :: OpticKind) (u :: OpticKind) (v :: OpticKind) (a :: OpticKind)
       (b :: OpticKind).
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
%forall (b :: OpticKind) (t :: OpticKind) (s :: OpticKind)
       (a :: OpticKind).
(b -> t) -> (s -> Either t a) -> Prism s t a b
prism Text -> Value
String (\Value
v -> case Value
v of String Text
s -> forall (a :: OpticKind) (b :: OpticKind). b -> Either a b
Right Text
s; Value
_ -> forall (a :: OpticKind) (b :: OpticKind). a -> Either a b
Left Value
v)
  {-# INLINE _String #-}

  -- |
  -- >>> "{\"a\": \"xyz\", \"b\": true}" ^? key "b" % _Bool
  -- Just True
  --
  -- >>> "{\"a\": \"xyz\", \"b\": true}" ^? key "a" % _Bool
  -- Nothing
  --
  -- >>> _Bool # True :: String
  -- "true"
  --
  -- >>> _Bool # False :: String
  -- "false"
  _Bool :: Prism' t Bool
  _Bool = forall (t :: OpticKind). AsValue t => Prism' t Value
_Valueforall (k :: OpticKind) (l :: OpticKind) (m :: OpticKind)
       (is :: IxList) (js :: IxList) (ks :: IxList) (s :: OpticKind)
       (t :: OpticKind) (u :: OpticKind) (v :: OpticKind) (a :: OpticKind)
       (b :: OpticKind).
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
%forall (b :: OpticKind) (t :: OpticKind) (s :: OpticKind)
       (a :: OpticKind).
(b -> t) -> (s -> Either t a) -> Prism s t a b
prism Bool -> Value
Bool (\Value
v -> case Value
v of Bool Bool
b -> forall (a :: OpticKind) (b :: OpticKind). b -> Either a b
Right Bool
b; Value
_ -> forall (a :: OpticKind) (b :: OpticKind). a -> Either a b
Left Value
v)
  {-# INLINE _Bool #-}

  -- |
  -- >>> "{\"a\": \"xyz\", \"b\": null}" ^? key "b" % _Null
  -- Just ()
  --
  -- >>> "{\"a\": \"xyz\", \"b\": null}" ^? key "a" % _Null
  -- Nothing
  --
  -- >>> _Null # () :: String
  -- "null"
  _Null :: Prism' t ()
  _Null = forall (t :: OpticKind). AsValue t => Prism' t Value
_Value forall (k :: OpticKind) (l :: OpticKind) (m :: OpticKind)
       (is :: IxList) (js :: IxList) (ks :: IxList) (s :: OpticKind)
       (t :: OpticKind) (u :: OpticKind) (v :: OpticKind) (a :: OpticKind)
       (b :: OpticKind).
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall (b :: OpticKind) (t :: OpticKind) (s :: OpticKind)
       (a :: OpticKind).
(b -> t) -> (s -> Either t a) -> Prism s t a b
prism (forall (a :: OpticKind) (b :: OpticKind). a -> b -> a
const Value
Null) (\Value
v -> case Value
v of Value
Null -> forall (a :: OpticKind) (b :: OpticKind). b -> Either a b
Right (); Value
_ -> forall (a :: OpticKind) (b :: OpticKind). a -> Either a b
Left Value
v)
  {-# INLINE _Null #-}


instance AsValue Value where
  _Value :: Prism' Value Value
_Value = forall (destKind :: OpticKind) (srcKind :: OpticKind)
       (is :: IxList) (s :: OpticKind) (t :: OpticKind) (a :: OpticKind)
       (b :: OpticKind).
Is srcKind destKind =>
Optic srcKind is s t a b -> Optic destKind is s t a b
castOptic forall (a :: OpticKind). Iso' a a
simple
  {-# INLINE _Value #-}

instance AsValue Strict.ByteString where
  _Value :: Prism' ByteString Value
_Value = forall (t :: OpticKind) (a :: OpticKind) (b :: OpticKind).
(AsJSON t, FromJSON a, ToJSON b) =>
Prism t t a b
_JSON
  {-# INLINE _Value #-}

instance AsValue LBS.ByteString where
  _Value :: Prism' ByteString Value
_Value = forall (t :: OpticKind) (a :: OpticKind) (b :: OpticKind).
(AsJSON t, FromJSON a, ToJSON b) =>
Prism t t a b
_JSON
  {-# INLINE _Value #-}

instance AsValue String where
  _Value :: Prism' String Value
_Value = Iso' String ByteString
strictUtf8forall (k :: OpticKind) (l :: OpticKind) (m :: OpticKind)
       (is :: IxList) (js :: IxList) (ks :: IxList) (s :: OpticKind)
       (t :: OpticKind) (u :: OpticKind) (v :: OpticKind) (a :: OpticKind)
       (b :: OpticKind).
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
%forall (t :: OpticKind) (a :: OpticKind) (b :: OpticKind).
(AsJSON t, FromJSON a, ToJSON b) =>
Prism t t a b
_JSON
  {-# INLINE _Value #-}

instance AsValue Text where
  _Value :: Prism' Text Value
_Value = Iso' Text ByteString
strictTextUtf8forall (k :: OpticKind) (l :: OpticKind) (m :: OpticKind)
       (is :: IxList) (js :: IxList) (ks :: IxList) (s :: OpticKind)
       (t :: OpticKind) (u :: OpticKind) (v :: OpticKind) (a :: OpticKind)
       (b :: OpticKind).
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
%forall (t :: OpticKind) (a :: OpticKind) (b :: OpticKind).
(AsJSON t, FromJSON a, ToJSON b) =>
Prism t t a b
_JSON
  {-# INLINE _Value #-}

instance AsValue LazyText.Text where
  _Value :: Prism' Text Value
_Value = Iso' Text ByteString
lazyTextUtf8forall (k :: OpticKind) (l :: OpticKind) (m :: OpticKind)
       (is :: IxList) (js :: IxList) (ks :: IxList) (s :: OpticKind)
       (t :: OpticKind) (u :: OpticKind) (v :: OpticKind) (a :: OpticKind)
       (b :: OpticKind).
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
%forall (t :: OpticKind) (a :: OpticKind) (b :: OpticKind).
(AsJSON t, FromJSON a, ToJSON b) =>
Prism t t a b
_JSON
  {-# INLINE _Value #-}

-- |
-- Like 'ix', but for 'Object' with Text indices. This often has better
-- inference than 'ix' when used with OverloadedStrings.
--
-- >>> "{\"a\": 100, \"b\": 200}" ^? key "a"
-- Just (Number 100.0)
--
-- >>> "[1,2,3]" ^? key "a"
-- Nothing
key :: AsValue t => Key.Key -> AffineTraversal' t Value
key :: forall (t :: OpticKind).
AsValue t =>
Key -> AffineTraversal' t Value
key Key
i = forall (t :: OpticKind). AsValue t => Prism' t (KeyMap Value)
_Object forall (k :: OpticKind) (l :: OpticKind) (m :: OpticKind)
       (is :: IxList) (js :: IxList) (ks :: IxList) (s :: OpticKind)
       (t :: OpticKind) (u :: OpticKind) (v :: OpticKind) (a :: OpticKind)
       (b :: OpticKind).
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall (m :: OpticKind).
Ixed m =>
Index m -> Optic' (IxKind m) NoIx m (IxValue m)
ix Key
i
{-# INLINE key #-}

-- | An indexed Traversal into Object properties
--
-- >>> Data.List.sort (itoListOf (members % _Number) "{\"a\": 4, \"b\": 7}")
-- [("a",4.0),("b",7.0)]
--
-- >>> "{\"a\": 4}" & members % _Number %~ (*10)
-- "{\"a\":40}"
members :: AsValue t => IxTraversal' Key.Key t Value
members :: forall (t :: OpticKind). AsValue t => IxTraversal' Key t Value
members = forall (t :: OpticKind). AsValue t => Prism' t (KeyMap Value)
_Object forall (k :: OpticKind) (l :: OpticKind) (m :: OpticKind)
       (is :: IxList) (js :: IxList) (ks :: IxList) (s :: OpticKind)
       (t :: OpticKind) (u :: OpticKind) (v :: OpticKind) (a :: OpticKind)
       (b :: OpticKind).
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall (i :: OpticKind) (f :: OpticKind -> OpticKind)
       (a :: OpticKind) (b :: OpticKind).
TraversableWithIndex i f =>
IxTraversal i (f a) (f b) a b
itraversed
{-# INLINE members #-}

-- | Like 'ix', but for Arrays with Int indexes
--
-- >>> "[1,2,3]" ^? nth 1
-- Just (Number 2.0)
--
-- >>> "{\"a\": 100, \"b\": 200}" ^? nth 1
-- Nothing
--
-- >>> "[1,2,3]" & nth 1 .~ Number 20
-- "[1,20,3]"
nth :: AsValue t => Int -> AffineTraversal' t Value
nth :: forall (t :: OpticKind).
AsValue t =>
Int -> AffineTraversal' t Value
nth Int
i = forall (t :: OpticKind). AsValue t => Prism' t (Vector Value)
_Array forall (k :: OpticKind) (l :: OpticKind) (m :: OpticKind)
       (is :: IxList) (js :: IxList) (ks :: IxList) (s :: OpticKind)
       (t :: OpticKind) (u :: OpticKind) (v :: OpticKind) (a :: OpticKind)
       (b :: OpticKind).
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall (m :: OpticKind).
Ixed m =>
Index m -> Optic' (IxKind m) NoIx m (IxValue m)
ix Int
i
{-# INLINE nth #-}

-- | An indexed Traversal into Array elements
--
-- >>> "[1,2,3]" ^.. values
-- [Number 1.0,Number 2.0,Number 3.0]
--
-- >>> "[1,2,3]" & values % _Number %~ (*10)
-- "[10,20,30]"
values :: AsValue t => IxTraversal' Int t Value
values :: forall (t :: OpticKind). AsValue t => IxTraversal' Int t Value
values = forall (t :: OpticKind). AsValue t => Prism' t (Vector Value)
_Array forall (k :: OpticKind) (l :: OpticKind) (m :: OpticKind)
       (is :: IxList) (js :: IxList) (ks :: IxList) (s :: OpticKind)
       (t :: OpticKind) (u :: OpticKind) (v :: OpticKind) (a :: OpticKind)
       (b :: OpticKind).
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall (i :: OpticKind) (f :: OpticKind -> OpticKind)
       (a :: OpticKind) (b :: OpticKind).
TraversableWithIndex i f =>
IxTraversal i (f a) (f b) a b
itraversed
{-# INLINE values #-}

strictUtf8 :: Iso' String Strict.ByteString
strictUtf8 :: Iso' String ByteString
strictUtf8 = forall (t :: OpticKind). IsText t => Iso' String t
packed forall (k :: OpticKind) (l :: OpticKind) (m :: OpticKind)
       (is :: IxList) (js :: IxList) (ks :: IxList) (s :: OpticKind)
       (t :: OpticKind) (u :: OpticKind) (v :: OpticKind) (a :: OpticKind)
       (b :: OpticKind).
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% Iso' Text ByteString
strictTextUtf8

strictTextUtf8 :: Iso' StrictText.Text Strict.ByteString
strictTextUtf8 :: Iso' Text ByteString
strictTextUtf8 = forall (s :: OpticKind) (a :: OpticKind) (b :: OpticKind)
       (t :: OpticKind).
(s -> a) -> (b -> t) -> Iso s t a b
iso Text -> ByteString
StrictText.encodeUtf8 ByteString -> Text
StrictText.decodeUtf8

lazyTextUtf8 :: Iso' LazyText.Text LBS.ByteString
lazyTextUtf8 :: Iso' Text ByteString
lazyTextUtf8 = forall (s :: OpticKind) (a :: OpticKind) (b :: OpticKind)
       (t :: OpticKind).
(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' :: forall (t :: OpticKind) (a :: OpticKind).
(AsJSON t, FromJSON a, ToJSON a) =>
Prism' t a
_JSON' = forall (t :: OpticKind) (a :: OpticKind) (b :: OpticKind).
(AsJSON t, FromJSON a, ToJSON b) =>
Prism t t a b
_JSON

class IsKey t where
  -- | '_Key' is an 'Iso' from something to a 'Key'. This is primarily intended
  -- for situations where one wishes to use object keys that are not string
  -- literals and therefore must be converted:
  --
  -- >>> let k = "a" :: Text
  -- >>> "{\"a\": 100, \"b\": 200}" ^? key (k ^. _Key)
  -- Just (Number 100.0)
  --
  -- Note that applying '_Key' directly to a string literal
  -- (e.g., @\"a\" ^. '_Key'@) will likely not typecheck when
  -- @OverloadedStrings@ is enabled.
  _Key :: Iso' t Key.Key

instance IsKey Key.Key where
  _Key :: Iso' Key Key
_Key = forall (a :: OpticKind). Iso' a a
simple
  {-# INLINE _Key #-}

instance IsKey String where
  _Key :: Iso' String Key
_Key = forall (s :: OpticKind) (a :: OpticKind) (b :: OpticKind)
       (t :: OpticKind).
(s -> a) -> (b -> t) -> Iso s t a b
iso String -> Key
Key.fromString Key -> String
Key.toString
  {-# INLINE _Key #-}

instance IsKey Text where
  _Key :: Iso' Text Key
_Key = forall (s :: OpticKind) (a :: OpticKind) (b :: OpticKind)
       (t :: OpticKind).
(s -> a) -> (b -> t) -> Iso s t a b
iso Text -> Key
Key.fromText Key -> Text
Key.toText
  {-# INLINE _Key #-}

instance IsKey LazyText.Text where
  _Key :: Iso' Text Key
_Key = forall (s :: OpticKind) (a :: OpticKind) (b :: OpticKind)
       (t :: OpticKind).
(s -> a) -> (b -> t) -> Iso s t a b
iso Text -> Text
LazyText.toStrict Text -> Text
LazyText.fromStrict forall (k :: OpticKind) (l :: OpticKind) (m :: OpticKind)
       (is :: IxList) (js :: IxList) (ks :: IxList) (s :: OpticKind)
       (t :: OpticKind) (u :: OpticKind) (v :: OpticKind) (a :: OpticKind)
       (b :: OpticKind).
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall (t :: OpticKind). IsKey t => Iso' t Key
_Key
  {-# INLINE _Key #-}

instance IsKey ShortText where
  _Key :: Iso' ShortText Key
_Key = forall (s :: OpticKind) (a :: OpticKind) (b :: OpticKind)
       (t :: OpticKind).
(s -> a) -> (b -> t) -> Iso s t a b
iso ShortText -> Key
Key.fromShortText Key -> ShortText
Key.toShortText
  {-# INLINE _Key #-}

{-
https://github.com/lens/lens-aeson/issues/48
instance IsKey Strict.ByteString where
  _Key = from strictTextUtf8._Key
  {-# INLINE _Key #-}

instance IsKey LBS.ByteString where
  _Key = from lazyTextUtf8._Key
  {-# INLINE _Key #-}
-}

class AsJSON t where
  -- | '_JSON' is a 'Prism' from something containing JSON to something encoded in that structure
  _JSON :: (FromJSON a, ToJSON b) => Prism t t a b

instance AsJSON Strict.ByteString where
  _JSON :: forall (a :: OpticKind) (b :: OpticKind).
(FromJSON a, ToJSON b) =>
Prism ByteString ByteString a b
_JSON = forall (s :: OpticKind) (a :: OpticKind) (b :: OpticKind)
       (t :: OpticKind).
(s -> a) -> (b -> t) -> Iso s t a b
iso ByteString -> ByteString
LBS.fromStrict ByteString -> ByteString
LBS.toStrict forall (k :: OpticKind) (l :: OpticKind) (m :: OpticKind)
       (is :: IxList) (js :: IxList) (ks :: IxList) (s :: OpticKind)
       (t :: OpticKind) (u :: OpticKind) (v :: OpticKind) (a :: OpticKind)
       (b :: OpticKind).
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall (t :: OpticKind) (a :: OpticKind) (b :: OpticKind).
(AsJSON t, FromJSON a, ToJSON b) =>
Prism t t a b
_JSON
  {-# INLINE _JSON #-}

instance AsJSON LBS.ByteString where
  _JSON :: forall (a :: OpticKind) (b :: OpticKind).
(FromJSON a, ToJSON b) =>
Prism ByteString ByteString a b
_JSON = forall (b :: OpticKind) (s :: OpticKind) (a :: OpticKind).
(b -> s) -> (s -> Maybe a) -> Prism s s a b
prism' forall (a :: OpticKind). ToJSON a => a -> ByteString
encode forall (a :: OpticKind). FromJSON a => ByteString -> Maybe a
decode
  {-# INLINE _JSON #-}

instance AsJSON String where
  _JSON :: forall (a :: OpticKind) (b :: OpticKind).
(FromJSON a, ToJSON b) =>
Prism String String a b
_JSON = Iso' String ByteString
strictUtf8 forall (k :: OpticKind) (l :: OpticKind) (m :: OpticKind)
       (is :: IxList) (js :: IxList) (ks :: IxList) (s :: OpticKind)
       (t :: OpticKind) (u :: OpticKind) (v :: OpticKind) (a :: OpticKind)
       (b :: OpticKind).
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall (t :: OpticKind) (a :: OpticKind) (b :: OpticKind).
(AsJSON t, FromJSON a, ToJSON b) =>
Prism t t a b
_JSON
  {-# INLINE _JSON #-}

instance AsJSON Text where
  _JSON :: forall (a :: OpticKind) (b :: OpticKind).
(FromJSON a, ToJSON b) =>
Prism Text Text a b
_JSON = Iso' Text ByteString
strictTextUtf8 forall (k :: OpticKind) (l :: OpticKind) (m :: OpticKind)
       (is :: IxList) (js :: IxList) (ks :: IxList) (s :: OpticKind)
       (t :: OpticKind) (u :: OpticKind) (v :: OpticKind) (a :: OpticKind)
       (b :: OpticKind).
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall (t :: OpticKind) (a :: OpticKind) (b :: OpticKind).
(AsJSON t, FromJSON a, ToJSON b) =>
Prism t t a b
_JSON
  {-# INLINE _JSON #-}

instance AsJSON LazyText.Text where
  _JSON :: forall (a :: OpticKind) (b :: OpticKind).
(FromJSON a, ToJSON b) =>
Prism Text Text a b
_JSON = Iso' Text ByteString
lazyTextUtf8 forall (k :: OpticKind) (l :: OpticKind) (m :: OpticKind)
       (is :: IxList) (js :: IxList) (ks :: IxList) (s :: OpticKind)
       (t :: OpticKind) (u :: OpticKind) (v :: OpticKind) (a :: OpticKind)
       (b :: OpticKind).
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall (t :: OpticKind) (a :: OpticKind) (b :: OpticKind).
(AsJSON t, FromJSON a, ToJSON b) =>
Prism t t a b
_JSON
  {-# INLINE _JSON #-}

instance AsJSON Value where
  _JSON :: forall (a :: OpticKind) (b :: OpticKind).
(FromJSON a, ToJSON b) =>
Prism Value Value a b
_JSON = forall (b :: OpticKind) (t :: OpticKind) (s :: OpticKind)
       (a :: OpticKind).
(b -> t) -> (s -> Either t a) -> Prism s t a b
prism forall (a :: OpticKind). ToJSON a => a -> Value
toJSON forall (a :: OpticKind) b. (a -> b) -> a -> b
$ \Value
x -> case forall (a :: OpticKind). FromJSON a => Value -> Result a
fromJSON Value
x of
    Success a
y -> forall (a :: OpticKind) (b :: OpticKind). b -> Either a b
Right a
y;
    Result a
_         -> forall (a :: OpticKind) (b :: OpticKind). a -> Either a b
Left Value
x
  {-# INLINE _JSON #-}

------------------------------------------------------------------------------
-- Some additional tests for prismhood; see https://github.com/ekmett/lens/issues/439.
------------------------------------------------------------------------------

-- $LazyByteStringTests
-- >>> "42" ^? (_JSON :: Prism' Lazy.ByteString Value)
-- Just (Number 42.0)
--
-- >>> preview (_Integer :: Prism' Lazy.ByteString Integer) "42"
-- Just 42
--
-- >>> Lazy.Char8.unpack (review (_Integer :: Prism' Lazy.ByteString Integer) 42)
-- "42"

-- $StrictByteStringTests
-- >>> "42" ^? (_JSON :: Prism' Strict.ByteString Value)
-- Just (Number 42.0)
--
-- >>> preview (_Integer :: Prism' Strict.ByteString Integer) "42"
-- Just 42
--
-- >>> Strict.Char8.unpack (review (_Integer :: Prism' Strict.ByteString Integer) 42)
-- "42"

-- $StringTests
-- >>> "42" ^? (_JSON :: Prism' String Value)
-- Just (Number 42.0)
--
-- >>> preview (_Integer :: Prism' String Integer) "42"
-- Just 42
--
-- >>> review (_Integer :: Prism' String Integer) 42
-- "42"

------------------------------------------------------------------------------
-- Orphan instances for lens library interop
------------------------------------------------------------------------------

type instance Index Value = Key.Key

type instance IxValue Value = Value
instance Ixed Value where
  ix :: Index Value -> Optic' (IxKind Value) NoIx Value (IxValue Value)
ix Index Value
i = forall (t :: OpticKind). AsValue t => Prism' t (KeyMap Value)
_Object forall (k :: OpticKind) (l :: OpticKind) (m :: OpticKind)
       (is :: IxList) (js :: IxList) (ks :: IxList) (s :: OpticKind)
       (t :: OpticKind) (u :: OpticKind) (v :: OpticKind) (a :: OpticKind)
       (b :: OpticKind).
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall (m :: OpticKind).
Ixed m =>
Index m -> Optic' (IxKind m) NoIx m (IxValue m)
ix Index Value
i
  {-# INLINE ix #-}

{-
instance Plated Value where
  plate f (Object o) = Object <$> traverse f o
  plate f (Array a) = Array <$> traverse f a
  plate _ xs = pure xs
  {-# INLINE plate #-}
-}

type instance Index (KM.KeyMap v) = Key.Key
type instance IxValue (KM.KeyMap v) = v

instance Ixed (KM.KeyMap v)

instance At (KM.KeyMap v) where
  at :: Index (KeyMap v) -> Lens' (KeyMap v) (Maybe (IxValue (KeyMap v)))
at Index (KeyMap v)
i = forall (s :: OpticKind) (t :: OpticKind) (a :: OpticKind)
       (b :: OpticKind).
LensVL s t a b -> Lens s t a b
lensVL (\Maybe v -> f (Maybe v)
f -> forall (f :: OpticKind -> OpticKind) (v :: OpticKind).
Functor f =>
(Maybe v -> f (Maybe v)) -> Key -> KeyMap v -> f (KeyMap v)
KM.alterF Maybe v -> f (Maybe v)
f Index (KeyMap v)
i)
  {-# INLINE at #-}

instance Each Key.Key (KM.KeyMap a) (KM.KeyMap b) a b where
  each :: IxTraversal Key (KeyMap a) (KeyMap b) a b
each = forall (i :: OpticKind) (s :: OpticKind) (t :: OpticKind)
       (a :: OpticKind) (b :: OpticKind).
IxTraversalVL i s t a b -> IxTraversal i s t a b
itraversalVL forall (f :: OpticKind -> OpticKind) (v1 :: OpticKind)
       (v2 :: OpticKind).
Applicative f =>
(Key -> v1 -> f v2) -> KeyMap v1 -> f (KeyMap v2)
KM.traverseWithKey
  {-# INLINE[1] each #-}

------------------------------------------------------------------------------
-- Pattern Synonyms
------------------------------------------------------------------------------

pattern JSON :: (FromJSON a, ToJSON a, AsJSON t) => () => a -> t
pattern $bJSON :: forall (a :: OpticKind) (t :: OpticKind).
(FromJSON a, ToJSON a, AsJSON t) =>
a -> t
$mJSON :: forall {r} {a :: OpticKind} {t :: OpticKind}.
(FromJSON a, ToJSON a, AsJSON t) =>
t -> (a -> r) -> ((# #) -> r) -> r
JSON a <- (preview _JSON -> Just a) where
  JSON a
a = forall (t :: OpticKind) (a :: OpticKind) (b :: OpticKind).
(AsJSON t, FromJSON a, ToJSON b) =>
Prism t t a b
_JSON forall (k :: OpticKind) (is :: IxList) (t :: OpticKind)
       (b :: OpticKind).
Is k A_Review =>
Optic' k is t b -> b -> t
# a
a

pattern Value_ :: (FromJSON a, ToJSON a) => () => a -> Value
pattern $bValue_ :: forall (a :: OpticKind). (FromJSON a, ToJSON a) => a -> Value
$mValue_ :: forall {r} {a :: OpticKind}.
(FromJSON a, ToJSON a) =>
Value -> (a -> r) -> ((# #) -> r) -> r
Value_ a <- (fromJSON -> Success a) where
  Value_ a
a = forall (a :: OpticKind). ToJSON a => a -> Value
toJSON a
a

pattern Number_ :: AsNumber t => Scientific -> t
pattern $bNumber_ :: forall (t :: OpticKind). AsNumber t => Scientific -> t
$mNumber_ :: forall {r} {t :: OpticKind}.
AsNumber t =>
t -> (Scientific -> r) -> ((# #) -> r) -> r
Number_ n <- (preview _Number -> Just n) where
  Number_ Scientific
n = forall (t :: OpticKind). AsNumber t => Prism' t Scientific
_Number forall (k :: OpticKind) (is :: IxList) (t :: OpticKind)
       (b :: OpticKind).
Is k A_Review =>
Optic' k is t b -> b -> t
# Scientific
n

pattern Double :: AsNumber t => Double -> t
pattern $bDouble :: forall (t :: OpticKind). AsNumber t => Double -> t
$mDouble :: forall {r} {t :: OpticKind}.
AsNumber t =>
t -> (Double -> r) -> ((# #) -> r) -> r
Double d <- (preview _Double -> Just d) where
  Double Double
d = forall (t :: OpticKind). AsNumber t => Prism' t Double
_Double forall (k :: OpticKind) (is :: IxList) (t :: OpticKind)
       (b :: OpticKind).
Is k A_Review =>
Optic' k is t b -> b -> t
# Double
d

pattern Integer :: AsNumber t => Integer -> t
pattern $bInteger :: forall (t :: OpticKind). AsNumber t => Integer -> t
$mInteger :: forall {r} {t :: OpticKind}.
AsNumber t =>
t -> (Integer -> r) -> ((# #) -> r) -> r
Integer i <- (preview _Integer -> Just i) where
  Integer Integer
i = forall (t :: OpticKind). AsNumber t => Prism' t Integer
_Integer forall (k :: OpticKind) (is :: IxList) (t :: OpticKind)
       (b :: OpticKind).
Is k A_Review =>
Optic' k is t b -> b -> t
# Integer
i

pattern Integral :: (AsNumber t, Integral a) => a -> t
pattern $bIntegral :: forall (t :: OpticKind) (a :: OpticKind).
(AsNumber t, Integral a) =>
a -> t
$mIntegral :: forall {r} {t :: OpticKind} {a :: OpticKind}.
(AsNumber t, Integral a) =>
t -> (a -> r) -> ((# #) -> r) -> r
Integral d <- (preview _Integral -> Just d) where
  Integral a
d = forall (t :: OpticKind) (a :: OpticKind).
(AsNumber t, Integral a) =>
Prism' t a
_Integral forall (k :: OpticKind) (is :: IxList) (t :: OpticKind)
       (b :: OpticKind).
Is k A_Review =>
Optic' k is t b -> b -> t
# a
d

pattern Bool_ :: AsValue t => Bool -> t
pattern $bBool_ :: forall (t :: OpticKind). AsValue t => Bool -> t
$mBool_ :: forall {r} {t :: OpticKind}.
AsValue t =>
t -> (Bool -> r) -> ((# #) -> r) -> r
Bool_ b <- (preview _Bool -> Just b) where
  Bool_ Bool
b = forall (t :: OpticKind). AsValue t => Prism' t Bool
_Bool forall (k :: OpticKind) (is :: IxList) (t :: OpticKind)
       (b :: OpticKind).
Is k A_Review =>
Optic' k is t b -> b -> t
# Bool
b

pattern String_ :: AsValue t => Text -> t
pattern $bString_ :: forall (t :: OpticKind). AsValue t => Text -> t
$mString_ :: forall {r} {t :: OpticKind}.
AsValue t =>
t -> (Text -> r) -> ((# #) -> r) -> r
String_ p <- (preview _String -> Just p) where
  String_ Text
p = forall (t :: OpticKind). AsValue t => Prism' t Text
_String forall (k :: OpticKind) (is :: IxList) (t :: OpticKind)
       (b :: OpticKind).
Is k A_Review =>
Optic' k is t b -> b -> t
# Text
p

pattern Null_ :: AsValue t => t
pattern $bNull_ :: forall (t :: OpticKind). AsValue t => t
$mNull_ :: forall {r} {t :: OpticKind}.
AsValue t =>
t -> ((# #) -> r) -> ((# #) -> r) -> r
Null_ <- (preview _Null -> Just ()) where
  Null_ = forall (t :: OpticKind). AsValue t => Prism' t ()
_Null forall (k :: OpticKind) (is :: IxList) (t :: OpticKind)
       (b :: OpticKind).
Is k A_Review =>
Optic' k is t b -> b -> t
# ()

pattern Key_ :: IsKey t => Key.Key -> t
pattern $bKey_ :: forall (t :: OpticKind). IsKey t => Key -> t
$mKey_ :: forall {r} {t :: OpticKind}.
IsKey t =>
t -> (Key -> r) -> ((# #) -> r) -> r
Key_ k <- (preview _Key -> Just k) where
  Key_ Key
k = forall (t :: OpticKind). IsKey t => Iso' t Key
_Key forall (k :: OpticKind) (is :: IxList) (t :: OpticKind)
       (b :: OpticKind).
Is k A_Review =>
Optic' k is t b -> b -> t
# Key
k