{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.CodeDeploy.BatchGetDeployments
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets information about one or more deployments. The maximum number of
-- deployments that can be returned is 25.
module Amazonka.CodeDeploy.BatchGetDeployments
  ( -- * Creating a Request
    BatchGetDeployments (..),
    newBatchGetDeployments,

    -- * Request Lenses
    batchGetDeployments_deploymentIds,

    -- * Destructuring the Response
    BatchGetDeploymentsResponse (..),
    newBatchGetDeploymentsResponse,

    -- * Response Lenses
    batchGetDeploymentsResponse_deploymentsInfo,
    batchGetDeploymentsResponse_httpStatus,
  )
where

import Amazonka.CodeDeploy.Types
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | Represents the input of a @BatchGetDeployments@ operation.
--
-- /See:/ 'newBatchGetDeployments' smart constructor.
data BatchGetDeployments = BatchGetDeployments'
  { -- | A list of deployment IDs, separated by spaces. The maximum number of
    -- deployment IDs you can specify is 25.
    BatchGetDeployments -> [Text]
deploymentIds :: [Prelude.Text]
  }
  deriving (BatchGetDeployments -> BatchGetDeployments -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchGetDeployments -> BatchGetDeployments -> Bool
$c/= :: BatchGetDeployments -> BatchGetDeployments -> Bool
== :: BatchGetDeployments -> BatchGetDeployments -> Bool
$c== :: BatchGetDeployments -> BatchGetDeployments -> Bool
Prelude.Eq, ReadPrec [BatchGetDeployments]
ReadPrec BatchGetDeployments
Int -> ReadS BatchGetDeployments
ReadS [BatchGetDeployments]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BatchGetDeployments]
$creadListPrec :: ReadPrec [BatchGetDeployments]
readPrec :: ReadPrec BatchGetDeployments
$creadPrec :: ReadPrec BatchGetDeployments
readList :: ReadS [BatchGetDeployments]
$creadList :: ReadS [BatchGetDeployments]
readsPrec :: Int -> ReadS BatchGetDeployments
$creadsPrec :: Int -> ReadS BatchGetDeployments
Prelude.Read, Int -> BatchGetDeployments -> ShowS
[BatchGetDeployments] -> ShowS
BatchGetDeployments -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchGetDeployments] -> ShowS
$cshowList :: [BatchGetDeployments] -> ShowS
show :: BatchGetDeployments -> String
$cshow :: BatchGetDeployments -> String
showsPrec :: Int -> BatchGetDeployments -> ShowS
$cshowsPrec :: Int -> BatchGetDeployments -> ShowS
Prelude.Show, forall x. Rep BatchGetDeployments x -> BatchGetDeployments
forall x. BatchGetDeployments -> Rep BatchGetDeployments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BatchGetDeployments x -> BatchGetDeployments
$cfrom :: forall x. BatchGetDeployments -> Rep BatchGetDeployments x
Prelude.Generic)

-- |
-- Create a value of 'BatchGetDeployments' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'deploymentIds', 'batchGetDeployments_deploymentIds' - A list of deployment IDs, separated by spaces. The maximum number of
-- deployment IDs you can specify is 25.
newBatchGetDeployments ::
  BatchGetDeployments
newBatchGetDeployments :: BatchGetDeployments
newBatchGetDeployments =
  BatchGetDeployments'
    { $sel:deploymentIds:BatchGetDeployments' :: [Text]
deploymentIds =
        forall a. Monoid a => a
Prelude.mempty
    }

-- | A list of deployment IDs, separated by spaces. The maximum number of
-- deployment IDs you can specify is 25.
batchGetDeployments_deploymentIds :: Lens.Lens' BatchGetDeployments [Prelude.Text]
batchGetDeployments_deploymentIds :: Lens' BatchGetDeployments [Text]
batchGetDeployments_deploymentIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchGetDeployments' {[Text]
deploymentIds :: [Text]
$sel:deploymentIds:BatchGetDeployments' :: BatchGetDeployments -> [Text]
deploymentIds} -> [Text]
deploymentIds) (\s :: BatchGetDeployments
s@BatchGetDeployments' {} [Text]
a -> BatchGetDeployments
s {$sel:deploymentIds:BatchGetDeployments' :: [Text]
deploymentIds = [Text]
a} :: BatchGetDeployments) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Core.AWSRequest BatchGetDeployments where
  type
    AWSResponse BatchGetDeployments =
      BatchGetDeploymentsResponse
  request :: (Service -> Service)
-> BatchGetDeployments -> Request BatchGetDeployments
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy BatchGetDeployments
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse BatchGetDeployments)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe [DeploymentInfo] -> Int -> BatchGetDeploymentsResponse
BatchGetDeploymentsResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"deploymentsInfo"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable BatchGetDeployments where
  hashWithSalt :: Int -> BatchGetDeployments -> Int
hashWithSalt Int
_salt BatchGetDeployments' {[Text]
deploymentIds :: [Text]
$sel:deploymentIds:BatchGetDeployments' :: BatchGetDeployments -> [Text]
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
deploymentIds

instance Prelude.NFData BatchGetDeployments where
  rnf :: BatchGetDeployments -> ()
rnf BatchGetDeployments' {[Text]
deploymentIds :: [Text]
$sel:deploymentIds:BatchGetDeployments' :: BatchGetDeployments -> [Text]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf [Text]
deploymentIds

instance Data.ToHeaders BatchGetDeployments where
  toHeaders :: BatchGetDeployments -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"CodeDeploy_20141006.BatchGetDeployments" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON BatchGetDeployments where
  toJSON :: BatchGetDeployments -> Value
toJSON BatchGetDeployments' {[Text]
deploymentIds :: [Text]
$sel:deploymentIds:BatchGetDeployments' :: BatchGetDeployments -> [Text]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"deploymentIds" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [Text]
deploymentIds)
          ]
      )

instance Data.ToPath BatchGetDeployments where
  toPath :: BatchGetDeployments -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

instance Data.ToQuery BatchGetDeployments where
  toQuery :: BatchGetDeployments -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | Represents the output of a @BatchGetDeployments@ operation.
--
-- /See:/ 'newBatchGetDeploymentsResponse' smart constructor.
data BatchGetDeploymentsResponse = BatchGetDeploymentsResponse'
  { -- | Information about the deployments.
    BatchGetDeploymentsResponse -> Maybe [DeploymentInfo]
deploymentsInfo :: Prelude.Maybe [DeploymentInfo],
    -- | The response's http status code.
    BatchGetDeploymentsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (BatchGetDeploymentsResponse -> BatchGetDeploymentsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchGetDeploymentsResponse -> BatchGetDeploymentsResponse -> Bool
$c/= :: BatchGetDeploymentsResponse -> BatchGetDeploymentsResponse -> Bool
== :: BatchGetDeploymentsResponse -> BatchGetDeploymentsResponse -> Bool
$c== :: BatchGetDeploymentsResponse -> BatchGetDeploymentsResponse -> Bool
Prelude.Eq, ReadPrec [BatchGetDeploymentsResponse]
ReadPrec BatchGetDeploymentsResponse
Int -> ReadS BatchGetDeploymentsResponse
ReadS [BatchGetDeploymentsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BatchGetDeploymentsResponse]
$creadListPrec :: ReadPrec [BatchGetDeploymentsResponse]
readPrec :: ReadPrec BatchGetDeploymentsResponse
$creadPrec :: ReadPrec BatchGetDeploymentsResponse
readList :: ReadS [BatchGetDeploymentsResponse]
$creadList :: ReadS [BatchGetDeploymentsResponse]
readsPrec :: Int -> ReadS BatchGetDeploymentsResponse
$creadsPrec :: Int -> ReadS BatchGetDeploymentsResponse
Prelude.Read, Int -> BatchGetDeploymentsResponse -> ShowS
[BatchGetDeploymentsResponse] -> ShowS
BatchGetDeploymentsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchGetDeploymentsResponse] -> ShowS
$cshowList :: [BatchGetDeploymentsResponse] -> ShowS
show :: BatchGetDeploymentsResponse -> String
$cshow :: BatchGetDeploymentsResponse -> String
showsPrec :: Int -> BatchGetDeploymentsResponse -> ShowS
$cshowsPrec :: Int -> BatchGetDeploymentsResponse -> ShowS
Prelude.Show, forall x.
Rep BatchGetDeploymentsResponse x -> BatchGetDeploymentsResponse
forall x.
BatchGetDeploymentsResponse -> Rep BatchGetDeploymentsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep BatchGetDeploymentsResponse x -> BatchGetDeploymentsResponse
$cfrom :: forall x.
BatchGetDeploymentsResponse -> Rep BatchGetDeploymentsResponse x
Prelude.Generic)

-- |
-- Create a value of 'BatchGetDeploymentsResponse' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'deploymentsInfo', 'batchGetDeploymentsResponse_deploymentsInfo' - Information about the deployments.
--
-- 'httpStatus', 'batchGetDeploymentsResponse_httpStatus' - The response's http status code.
newBatchGetDeploymentsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  BatchGetDeploymentsResponse
newBatchGetDeploymentsResponse :: Int -> BatchGetDeploymentsResponse
newBatchGetDeploymentsResponse Int
pHttpStatus_ =
  BatchGetDeploymentsResponse'
    { $sel:deploymentsInfo:BatchGetDeploymentsResponse' :: Maybe [DeploymentInfo]
deploymentsInfo =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:BatchGetDeploymentsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Information about the deployments.
batchGetDeploymentsResponse_deploymentsInfo :: Lens.Lens' BatchGetDeploymentsResponse (Prelude.Maybe [DeploymentInfo])
batchGetDeploymentsResponse_deploymentsInfo :: Lens' BatchGetDeploymentsResponse (Maybe [DeploymentInfo])
batchGetDeploymentsResponse_deploymentsInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchGetDeploymentsResponse' {Maybe [DeploymentInfo]
deploymentsInfo :: Maybe [DeploymentInfo]
$sel:deploymentsInfo:BatchGetDeploymentsResponse' :: BatchGetDeploymentsResponse -> Maybe [DeploymentInfo]
deploymentsInfo} -> Maybe [DeploymentInfo]
deploymentsInfo) (\s :: BatchGetDeploymentsResponse
s@BatchGetDeploymentsResponse' {} Maybe [DeploymentInfo]
a -> BatchGetDeploymentsResponse
s {$sel:deploymentsInfo:BatchGetDeploymentsResponse' :: Maybe [DeploymentInfo]
deploymentsInfo = Maybe [DeploymentInfo]
a} :: BatchGetDeploymentsResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The response's http status code.
batchGetDeploymentsResponse_httpStatus :: Lens.Lens' BatchGetDeploymentsResponse Prelude.Int
batchGetDeploymentsResponse_httpStatus :: Lens' BatchGetDeploymentsResponse Int
batchGetDeploymentsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchGetDeploymentsResponse' {Int
httpStatus :: Int
$sel:httpStatus:BatchGetDeploymentsResponse' :: BatchGetDeploymentsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: BatchGetDeploymentsResponse
s@BatchGetDeploymentsResponse' {} Int
a -> BatchGetDeploymentsResponse
s {$sel:httpStatus:BatchGetDeploymentsResponse' :: Int
httpStatus = Int
a} :: BatchGetDeploymentsResponse)

instance Prelude.NFData BatchGetDeploymentsResponse where
  rnf :: BatchGetDeploymentsResponse -> ()
rnf BatchGetDeploymentsResponse' {Int
Maybe [DeploymentInfo]
httpStatus :: Int
deploymentsInfo :: Maybe [DeploymentInfo]
$sel:httpStatus:BatchGetDeploymentsResponse' :: BatchGetDeploymentsResponse -> Int
$sel:deploymentsInfo:BatchGetDeploymentsResponse' :: BatchGetDeploymentsResponse -> Maybe [DeploymentInfo]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [DeploymentInfo]
deploymentsInfo
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus