{-# 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.Lightsail.GetContainerServiceDeployments
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns the deployments for your Amazon Lightsail container service
--
-- A deployment specifies the settings, such as the ports and launch
-- command, of containers that are deployed to your container service.
--
-- The deployments are ordered by version in ascending order. The newest
-- version is listed at the top of the response.
--
-- A set number of deployments are kept before the oldest one is replaced
-- with the newest one. For more information, see
-- <https://docs.aws.amazon.com/general/latest/gr/lightsail.html Amazon Lightsail endpoints and quotas>
-- in the /Amazon Web Services General Reference/.
module Amazonka.Lightsail.GetContainerServiceDeployments
  ( -- * Creating a Request
    GetContainerServiceDeployments (..),
    newGetContainerServiceDeployments,

    -- * Request Lenses
    getContainerServiceDeployments_serviceName,

    -- * Destructuring the Response
    GetContainerServiceDeploymentsResponse (..),
    newGetContainerServiceDeploymentsResponse,

    -- * Response Lenses
    getContainerServiceDeploymentsResponse_deployments,
    getContainerServiceDeploymentsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newGetContainerServiceDeployments' smart constructor.
data GetContainerServiceDeployments = GetContainerServiceDeployments'
  { -- | The name of the container service for which to return deployments.
    GetContainerServiceDeployments -> Text
serviceName :: Prelude.Text
  }
  deriving (GetContainerServiceDeployments
-> GetContainerServiceDeployments -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetContainerServiceDeployments
-> GetContainerServiceDeployments -> Bool
$c/= :: GetContainerServiceDeployments
-> GetContainerServiceDeployments -> Bool
== :: GetContainerServiceDeployments
-> GetContainerServiceDeployments -> Bool
$c== :: GetContainerServiceDeployments
-> GetContainerServiceDeployments -> Bool
Prelude.Eq, ReadPrec [GetContainerServiceDeployments]
ReadPrec GetContainerServiceDeployments
Int -> ReadS GetContainerServiceDeployments
ReadS [GetContainerServiceDeployments]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetContainerServiceDeployments]
$creadListPrec :: ReadPrec [GetContainerServiceDeployments]
readPrec :: ReadPrec GetContainerServiceDeployments
$creadPrec :: ReadPrec GetContainerServiceDeployments
readList :: ReadS [GetContainerServiceDeployments]
$creadList :: ReadS [GetContainerServiceDeployments]
readsPrec :: Int -> ReadS GetContainerServiceDeployments
$creadsPrec :: Int -> ReadS GetContainerServiceDeployments
Prelude.Read, Int -> GetContainerServiceDeployments -> ShowS
[GetContainerServiceDeployments] -> ShowS
GetContainerServiceDeployments -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetContainerServiceDeployments] -> ShowS
$cshowList :: [GetContainerServiceDeployments] -> ShowS
show :: GetContainerServiceDeployments -> String
$cshow :: GetContainerServiceDeployments -> String
showsPrec :: Int -> GetContainerServiceDeployments -> ShowS
$cshowsPrec :: Int -> GetContainerServiceDeployments -> ShowS
Prelude.Show, forall x.
Rep GetContainerServiceDeployments x
-> GetContainerServiceDeployments
forall x.
GetContainerServiceDeployments
-> Rep GetContainerServiceDeployments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetContainerServiceDeployments x
-> GetContainerServiceDeployments
$cfrom :: forall x.
GetContainerServiceDeployments
-> Rep GetContainerServiceDeployments x
Prelude.Generic)

-- |
-- Create a value of 'GetContainerServiceDeployments' 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:
--
-- 'serviceName', 'getContainerServiceDeployments_serviceName' - The name of the container service for which to return deployments.
newGetContainerServiceDeployments ::
  -- | 'serviceName'
  Prelude.Text ->
  GetContainerServiceDeployments
newGetContainerServiceDeployments :: Text -> GetContainerServiceDeployments
newGetContainerServiceDeployments Text
pServiceName_ =
  GetContainerServiceDeployments'
    { $sel:serviceName:GetContainerServiceDeployments' :: Text
serviceName =
        Text
pServiceName_
    }

-- | The name of the container service for which to return deployments.
getContainerServiceDeployments_serviceName :: Lens.Lens' GetContainerServiceDeployments Prelude.Text
getContainerServiceDeployments_serviceName :: Lens' GetContainerServiceDeployments Text
getContainerServiceDeployments_serviceName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetContainerServiceDeployments' {Text
serviceName :: Text
$sel:serviceName:GetContainerServiceDeployments' :: GetContainerServiceDeployments -> Text
serviceName} -> Text
serviceName) (\s :: GetContainerServiceDeployments
s@GetContainerServiceDeployments' {} Text
a -> GetContainerServiceDeployments
s {$sel:serviceName:GetContainerServiceDeployments' :: Text
serviceName = Text
a} :: GetContainerServiceDeployments)

instance
  Core.AWSRequest
    GetContainerServiceDeployments
  where
  type
    AWSResponse GetContainerServiceDeployments =
      GetContainerServiceDeploymentsResponse
  request :: (Service -> Service)
-> GetContainerServiceDeployments
-> Request GetContainerServiceDeployments
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 GetContainerServiceDeployments
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse GetContainerServiceDeployments)))
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 [ContainerServiceDeployment]
-> Int -> GetContainerServiceDeploymentsResponse
GetContainerServiceDeploymentsResponse'
            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
"deployments" 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
    GetContainerServiceDeployments
  where
  hashWithSalt :: Int -> GetContainerServiceDeployments -> Int
hashWithSalt
    Int
_salt
    GetContainerServiceDeployments' {Text
serviceName :: Text
$sel:serviceName:GetContainerServiceDeployments' :: GetContainerServiceDeployments -> Text
..} =
      Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
serviceName

instance
  Prelude.NFData
    GetContainerServiceDeployments
  where
  rnf :: GetContainerServiceDeployments -> ()
rnf GetContainerServiceDeployments' {Text
serviceName :: Text
$sel:serviceName:GetContainerServiceDeployments' :: GetContainerServiceDeployments -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
serviceName

instance
  Data.ToHeaders
    GetContainerServiceDeployments
  where
  toHeaders :: GetContainerServiceDeployments -> 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
"Lightsail_20161128.GetContainerServiceDeployments" ::
                          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 GetContainerServiceDeployments where
  toJSON :: GetContainerServiceDeployments -> Value
toJSON GetContainerServiceDeployments' {Text
serviceName :: Text
$sel:serviceName:GetContainerServiceDeployments' :: GetContainerServiceDeployments -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"serviceName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
serviceName)]
      )

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

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

-- | /See:/ 'newGetContainerServiceDeploymentsResponse' smart constructor.
data GetContainerServiceDeploymentsResponse = GetContainerServiceDeploymentsResponse'
  { -- | An array of objects that describe deployments for a container service.
    GetContainerServiceDeploymentsResponse
-> Maybe [ContainerServiceDeployment]
deployments :: Prelude.Maybe [ContainerServiceDeployment],
    -- | The response's http status code.
    GetContainerServiceDeploymentsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetContainerServiceDeploymentsResponse
-> GetContainerServiceDeploymentsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetContainerServiceDeploymentsResponse
-> GetContainerServiceDeploymentsResponse -> Bool
$c/= :: GetContainerServiceDeploymentsResponse
-> GetContainerServiceDeploymentsResponse -> Bool
== :: GetContainerServiceDeploymentsResponse
-> GetContainerServiceDeploymentsResponse -> Bool
$c== :: GetContainerServiceDeploymentsResponse
-> GetContainerServiceDeploymentsResponse -> Bool
Prelude.Eq, ReadPrec [GetContainerServiceDeploymentsResponse]
ReadPrec GetContainerServiceDeploymentsResponse
Int -> ReadS GetContainerServiceDeploymentsResponse
ReadS [GetContainerServiceDeploymentsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetContainerServiceDeploymentsResponse]
$creadListPrec :: ReadPrec [GetContainerServiceDeploymentsResponse]
readPrec :: ReadPrec GetContainerServiceDeploymentsResponse
$creadPrec :: ReadPrec GetContainerServiceDeploymentsResponse
readList :: ReadS [GetContainerServiceDeploymentsResponse]
$creadList :: ReadS [GetContainerServiceDeploymentsResponse]
readsPrec :: Int -> ReadS GetContainerServiceDeploymentsResponse
$creadsPrec :: Int -> ReadS GetContainerServiceDeploymentsResponse
Prelude.Read, Int -> GetContainerServiceDeploymentsResponse -> ShowS
[GetContainerServiceDeploymentsResponse] -> ShowS
GetContainerServiceDeploymentsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetContainerServiceDeploymentsResponse] -> ShowS
$cshowList :: [GetContainerServiceDeploymentsResponse] -> ShowS
show :: GetContainerServiceDeploymentsResponse -> String
$cshow :: GetContainerServiceDeploymentsResponse -> String
showsPrec :: Int -> GetContainerServiceDeploymentsResponse -> ShowS
$cshowsPrec :: Int -> GetContainerServiceDeploymentsResponse -> ShowS
Prelude.Show, forall x.
Rep GetContainerServiceDeploymentsResponse x
-> GetContainerServiceDeploymentsResponse
forall x.
GetContainerServiceDeploymentsResponse
-> Rep GetContainerServiceDeploymentsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetContainerServiceDeploymentsResponse x
-> GetContainerServiceDeploymentsResponse
$cfrom :: forall x.
GetContainerServiceDeploymentsResponse
-> Rep GetContainerServiceDeploymentsResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetContainerServiceDeploymentsResponse' 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:
--
-- 'deployments', 'getContainerServiceDeploymentsResponse_deployments' - An array of objects that describe deployments for a container service.
--
-- 'httpStatus', 'getContainerServiceDeploymentsResponse_httpStatus' - The response's http status code.
newGetContainerServiceDeploymentsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetContainerServiceDeploymentsResponse
newGetContainerServiceDeploymentsResponse :: Int -> GetContainerServiceDeploymentsResponse
newGetContainerServiceDeploymentsResponse
  Int
pHttpStatus_ =
    GetContainerServiceDeploymentsResponse'
      { $sel:deployments:GetContainerServiceDeploymentsResponse' :: Maybe [ContainerServiceDeployment]
deployments =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:GetContainerServiceDeploymentsResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | An array of objects that describe deployments for a container service.
getContainerServiceDeploymentsResponse_deployments :: Lens.Lens' GetContainerServiceDeploymentsResponse (Prelude.Maybe [ContainerServiceDeployment])
getContainerServiceDeploymentsResponse_deployments :: Lens'
  GetContainerServiceDeploymentsResponse
  (Maybe [ContainerServiceDeployment])
getContainerServiceDeploymentsResponse_deployments = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetContainerServiceDeploymentsResponse' {Maybe [ContainerServiceDeployment]
deployments :: Maybe [ContainerServiceDeployment]
$sel:deployments:GetContainerServiceDeploymentsResponse' :: GetContainerServiceDeploymentsResponse
-> Maybe [ContainerServiceDeployment]
deployments} -> Maybe [ContainerServiceDeployment]
deployments) (\s :: GetContainerServiceDeploymentsResponse
s@GetContainerServiceDeploymentsResponse' {} Maybe [ContainerServiceDeployment]
a -> GetContainerServiceDeploymentsResponse
s {$sel:deployments:GetContainerServiceDeploymentsResponse' :: Maybe [ContainerServiceDeployment]
deployments = Maybe [ContainerServiceDeployment]
a} :: GetContainerServiceDeploymentsResponse) 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.
getContainerServiceDeploymentsResponse_httpStatus :: Lens.Lens' GetContainerServiceDeploymentsResponse Prelude.Int
getContainerServiceDeploymentsResponse_httpStatus :: Lens' GetContainerServiceDeploymentsResponse Int
getContainerServiceDeploymentsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetContainerServiceDeploymentsResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetContainerServiceDeploymentsResponse' :: GetContainerServiceDeploymentsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetContainerServiceDeploymentsResponse
s@GetContainerServiceDeploymentsResponse' {} Int
a -> GetContainerServiceDeploymentsResponse
s {$sel:httpStatus:GetContainerServiceDeploymentsResponse' :: Int
httpStatus = Int
a} :: GetContainerServiceDeploymentsResponse)

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