{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}

module Database.Bloodhound.Internal.Versions.OpenSearch2.Types.PointInTime where

import Database.Bloodhound.Internal.Utils.Imports
import Database.Bloodhound.Internal.Versions.Common.Types.Nodes (ShardResult)

data OpenPointInTimeResponse = OpenPointInTimeResponse
  { OpenPointInTimeResponse -> Text
oos2PitId :: Text,
    OpenPointInTimeResponse -> ShardResult
oos2Shards :: ShardResult,
    OpenPointInTimeResponse -> POSIXTime
oos2CreationTime :: POSIXTime
  }
  deriving stock (OpenPointInTimeResponse -> OpenPointInTimeResponse -> Bool
(OpenPointInTimeResponse -> OpenPointInTimeResponse -> Bool)
-> (OpenPointInTimeResponse -> OpenPointInTimeResponse -> Bool)
-> Eq OpenPointInTimeResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OpenPointInTimeResponse -> OpenPointInTimeResponse -> Bool
== :: OpenPointInTimeResponse -> OpenPointInTimeResponse -> Bool
$c/= :: OpenPointInTimeResponse -> OpenPointInTimeResponse -> Bool
/= :: OpenPointInTimeResponse -> OpenPointInTimeResponse -> Bool
Eq, Int -> OpenPointInTimeResponse -> ShowS
[OpenPointInTimeResponse] -> ShowS
OpenPointInTimeResponse -> String
(Int -> OpenPointInTimeResponse -> ShowS)
-> (OpenPointInTimeResponse -> String)
-> ([OpenPointInTimeResponse] -> ShowS)
-> Show OpenPointInTimeResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OpenPointInTimeResponse -> ShowS
showsPrec :: Int -> OpenPointInTimeResponse -> ShowS
$cshow :: OpenPointInTimeResponse -> String
show :: OpenPointInTimeResponse -> String
$cshowList :: [OpenPointInTimeResponse] -> ShowS
showList :: [OpenPointInTimeResponse] -> ShowS
Show)

instance ToJSON OpenPointInTimeResponse where
  toJSON :: OpenPointInTimeResponse -> Value
toJSON OpenPointInTimeResponse {Text
POSIXTime
ShardResult
oos2PitId :: OpenPointInTimeResponse -> Text
oos2Shards :: OpenPointInTimeResponse -> ShardResult
oos2CreationTime :: OpenPointInTimeResponse -> POSIXTime
oos2PitId :: Text
oos2Shards :: ShardResult
oos2CreationTime :: POSIXTime
..} =
    [Pair] -> Value
object [Key
"pit_id" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
oos2PitId, Key
"_shards" Key -> ShardResult -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= ShardResult
oos2Shards, Key
"creation_time" Key -> POSIXTime -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= POSIXTime
oos2CreationTime]

instance FromJSON OpenPointInTimeResponse where
  parseJSON :: Value -> Parser OpenPointInTimeResponse
parseJSON (Object Object
o) =
    Text -> ShardResult -> POSIXTime -> OpenPointInTimeResponse
OpenPointInTimeResponse
      (Text -> ShardResult -> POSIXTime -> OpenPointInTimeResponse)
-> Parser Text
-> Parser (ShardResult -> POSIXTime -> OpenPointInTimeResponse)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"pit_id"
      Parser (ShardResult -> POSIXTime -> OpenPointInTimeResponse)
-> Parser ShardResult
-> Parser (POSIXTime -> OpenPointInTimeResponse)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser ShardResult
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"_shards"
      Parser (POSIXTime -> OpenPointInTimeResponse)
-> Parser POSIXTime -> Parser OpenPointInTimeResponse
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser POSIXTime
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"creation_time"
  parseJSON Value
x = String -> Value -> Parser OpenPointInTimeResponse
forall a. String -> Value -> Parser a
typeMismatch String
"OpenPointInTimeResponse" Value
x

openPointInTimeIdLens :: Lens' OpenPointInTimeResponse Text
openPointInTimeIdLens :: Lens' OpenPointInTimeResponse Text
openPointInTimeIdLens = (OpenPointInTimeResponse -> Text)
-> (OpenPointInTimeResponse -> Text -> OpenPointInTimeResponse)
-> Lens' OpenPointInTimeResponse Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens OpenPointInTimeResponse -> Text
oos2PitId (\OpenPointInTimeResponse
x Text
y -> OpenPointInTimeResponse
x {oos2PitId = y})

openPointInTimeShardsLens :: Lens' OpenPointInTimeResponse ShardResult
openPointInTimeShardsLens :: Lens' OpenPointInTimeResponse ShardResult
openPointInTimeShardsLens = (OpenPointInTimeResponse -> ShardResult)
-> (OpenPointInTimeResponse
    -> ShardResult -> OpenPointInTimeResponse)
-> Lens' OpenPointInTimeResponse ShardResult
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens OpenPointInTimeResponse -> ShardResult
oos2Shards (\OpenPointInTimeResponse
x ShardResult
y -> OpenPointInTimeResponse
x {oos2Shards = y})

openPointInTimeCreationTimeLens :: Lens' OpenPointInTimeResponse POSIXTime
openPointInTimeCreationTimeLens :: Lens' OpenPointInTimeResponse POSIXTime
openPointInTimeCreationTimeLens = (OpenPointInTimeResponse -> POSIXTime)
-> (OpenPointInTimeResponse
    -> POSIXTime -> OpenPointInTimeResponse)
-> Lens' OpenPointInTimeResponse POSIXTime
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens OpenPointInTimeResponse -> POSIXTime
oos2CreationTime (\OpenPointInTimeResponse
x POSIXTime
y -> OpenPointInTimeResponse
x {oos2CreationTime = y})

data ClosePointInTime = ClosePointInTime
  { ClosePointInTime -> Text
cPitId :: Text
  }
  deriving stock (ClosePointInTime -> ClosePointInTime -> Bool
(ClosePointInTime -> ClosePointInTime -> Bool)
-> (ClosePointInTime -> ClosePointInTime -> Bool)
-> Eq ClosePointInTime
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ClosePointInTime -> ClosePointInTime -> Bool
== :: ClosePointInTime -> ClosePointInTime -> Bool
$c/= :: ClosePointInTime -> ClosePointInTime -> Bool
/= :: ClosePointInTime -> ClosePointInTime -> Bool
Eq, Int -> ClosePointInTime -> ShowS
[ClosePointInTime] -> ShowS
ClosePointInTime -> String
(Int -> ClosePointInTime -> ShowS)
-> (ClosePointInTime -> String)
-> ([ClosePointInTime] -> ShowS)
-> Show ClosePointInTime
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ClosePointInTime -> ShowS
showsPrec :: Int -> ClosePointInTime -> ShowS
$cshow :: ClosePointInTime -> String
show :: ClosePointInTime -> String
$cshowList :: [ClosePointInTime] -> ShowS
showList :: [ClosePointInTime] -> ShowS
Show)

instance ToJSON ClosePointInTime where
  toJSON :: ClosePointInTime -> Value
toJSON ClosePointInTime {Text
cPitId :: ClosePointInTime -> Text
cPitId :: Text
..} =
    [Pair] -> Value
object [Key
"id" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
cPitId]

instance FromJSON ClosePointInTime where
  parseJSON :: Value -> Parser ClosePointInTime
parseJSON (Object Object
o) = Text -> ClosePointInTime
ClosePointInTime (Text -> ClosePointInTime)
-> Parser Text -> Parser ClosePointInTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"
  parseJSON Value
x = String -> Value -> Parser ClosePointInTime
forall a. String -> Value -> Parser a
typeMismatch String
"ClosePointInTime" Value
x

closePointInTimeIdLens :: Lens' ClosePointInTime Text
closePointInTimeIdLens :: Lens' ClosePointInTime Text
closePointInTimeIdLens = (ClosePointInTime -> Text)
-> (ClosePointInTime -> Text -> ClosePointInTime)
-> Lens' ClosePointInTime Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ClosePointInTime -> Text
cPitId (\ClosePointInTime
x Text
y -> ClosePointInTime
x {cPitId = y})

data ClosePointInTimeResponse = ClosePointInTimeResponse
  { ClosePointInTimeResponse -> Bool
succeeded :: Bool,
    ClosePointInTimeResponse -> Int
numFreed :: Int
  }
  deriving stock (ClosePointInTimeResponse -> ClosePointInTimeResponse -> Bool
(ClosePointInTimeResponse -> ClosePointInTimeResponse -> Bool)
-> (ClosePointInTimeResponse -> ClosePointInTimeResponse -> Bool)
-> Eq ClosePointInTimeResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ClosePointInTimeResponse -> ClosePointInTimeResponse -> Bool
== :: ClosePointInTimeResponse -> ClosePointInTimeResponse -> Bool
$c/= :: ClosePointInTimeResponse -> ClosePointInTimeResponse -> Bool
/= :: ClosePointInTimeResponse -> ClosePointInTimeResponse -> Bool
Eq, Int -> ClosePointInTimeResponse -> ShowS
[ClosePointInTimeResponse] -> ShowS
ClosePointInTimeResponse -> String
(Int -> ClosePointInTimeResponse -> ShowS)
-> (ClosePointInTimeResponse -> String)
-> ([ClosePointInTimeResponse] -> ShowS)
-> Show ClosePointInTimeResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ClosePointInTimeResponse -> ShowS
showsPrec :: Int -> ClosePointInTimeResponse -> ShowS
$cshow :: ClosePointInTimeResponse -> String
show :: ClosePointInTimeResponse -> String
$cshowList :: [ClosePointInTimeResponse] -> ShowS
showList :: [ClosePointInTimeResponse] -> ShowS
Show)

instance ToJSON ClosePointInTimeResponse where
  toJSON :: ClosePointInTimeResponse -> Value
toJSON ClosePointInTimeResponse {Bool
Int
succeeded :: ClosePointInTimeResponse -> Bool
numFreed :: ClosePointInTimeResponse -> Int
succeeded :: Bool
numFreed :: Int
..} =
    [Pair] -> Value
object
      [ Key
"succeeded" Key -> Bool -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Bool
succeeded,
        Key
"num_freed" Key -> Int -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Int
numFreed
      ]

instance FromJSON ClosePointInTimeResponse where
  parseJSON :: Value -> Parser ClosePointInTimeResponse
parseJSON (Object Object
o) = do
    Bool
succeeded' <- Object
o Object -> Key -> Parser Bool
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"succeeded"
    Int
numFreed' <- Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"num_freed"
    ClosePointInTimeResponse -> Parser ClosePointInTimeResponse
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (ClosePointInTimeResponse -> Parser ClosePointInTimeResponse)
-> ClosePointInTimeResponse -> Parser ClosePointInTimeResponse
forall a b. (a -> b) -> a -> b
$ Bool -> Int -> ClosePointInTimeResponse
ClosePointInTimeResponse Bool
succeeded' Int
numFreed'
  parseJSON Value
x = String -> Value -> Parser ClosePointInTimeResponse
forall a. String -> Value -> Parser a
typeMismatch String
"ClosePointInTimeResponse" Value
x

closePointInTimeSucceededLens :: Lens' ClosePointInTimeResponse Bool
closePointInTimeSucceededLens :: Lens' ClosePointInTimeResponse Bool
closePointInTimeSucceededLens = (ClosePointInTimeResponse -> Bool)
-> (ClosePointInTimeResponse -> Bool -> ClosePointInTimeResponse)
-> Lens' ClosePointInTimeResponse Bool
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ClosePointInTimeResponse -> Bool
succeeded (\ClosePointInTimeResponse
x Bool
y -> ClosePointInTimeResponse
x {succeeded = y})

closePointInTimeNumFreedLens :: Lens' ClosePointInTimeResponse Int
closePointInTimeNumFreedLens :: Lens' ClosePointInTimeResponse Int
closePointInTimeNumFreedLens = (ClosePointInTimeResponse -> Int)
-> (ClosePointInTimeResponse -> Int -> ClosePointInTimeResponse)
-> Lens' ClosePointInTimeResponse Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ClosePointInTimeResponse -> Int
numFreed (\ClosePointInTimeResponse
x Int
y -> ClosePointInTimeResponse
x {numFreed = y})