{-# 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.CreateContainerServiceRegistryLogin
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a temporary set of log in credentials that you can use to log in
-- to the Docker process on your local machine. After you\'re logged in,
-- you can use the native Docker commands to push your local container
-- images to the container image registry of your Amazon Lightsail account
-- so that you can use them with your Lightsail container service. The log
-- in credentials expire 12 hours after they are created, at which point
-- you will need to create a new set of log in credentials.
--
-- You can only push container images to the container service registry of
-- your Lightsail account. You cannot pull container images or perform any
-- other container image management actions on the container service
-- registry.
--
-- After you push your container images to the container image registry of
-- your Lightsail account, use the @RegisterContainerImage@ action to
-- register the pushed images to a specific Lightsail container service.
--
-- This action is not required if you install and use the Lightsail Control
-- (lightsailctl) plugin to push container images to your Lightsail
-- container service. For more information, see
-- <https://lightsail.aws.amazon.com/ls/docs/en_us/articles/amazon-lightsail-pushing-container-images Pushing and managing container images on your Amazon Lightsail container services>
-- in the /Amazon Lightsail Developer Guide/.
module Amazonka.Lightsail.CreateContainerServiceRegistryLogin
  ( -- * Creating a Request
    CreateContainerServiceRegistryLogin (..),
    newCreateContainerServiceRegistryLogin,

    -- * Destructuring the Response
    CreateContainerServiceRegistryLoginResponse (..),
    newCreateContainerServiceRegistryLoginResponse,

    -- * Response Lenses
    createContainerServiceRegistryLoginResponse_registryLogin,
    createContainerServiceRegistryLoginResponse_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:/ 'newCreateContainerServiceRegistryLogin' smart constructor.
data CreateContainerServiceRegistryLogin = CreateContainerServiceRegistryLogin'
  {
  }
  deriving (CreateContainerServiceRegistryLogin
-> CreateContainerServiceRegistryLogin -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateContainerServiceRegistryLogin
-> CreateContainerServiceRegistryLogin -> Bool
$c/= :: CreateContainerServiceRegistryLogin
-> CreateContainerServiceRegistryLogin -> Bool
== :: CreateContainerServiceRegistryLogin
-> CreateContainerServiceRegistryLogin -> Bool
$c== :: CreateContainerServiceRegistryLogin
-> CreateContainerServiceRegistryLogin -> Bool
Prelude.Eq, ReadPrec [CreateContainerServiceRegistryLogin]
ReadPrec CreateContainerServiceRegistryLogin
Int -> ReadS CreateContainerServiceRegistryLogin
ReadS [CreateContainerServiceRegistryLogin]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateContainerServiceRegistryLogin]
$creadListPrec :: ReadPrec [CreateContainerServiceRegistryLogin]
readPrec :: ReadPrec CreateContainerServiceRegistryLogin
$creadPrec :: ReadPrec CreateContainerServiceRegistryLogin
readList :: ReadS [CreateContainerServiceRegistryLogin]
$creadList :: ReadS [CreateContainerServiceRegistryLogin]
readsPrec :: Int -> ReadS CreateContainerServiceRegistryLogin
$creadsPrec :: Int -> ReadS CreateContainerServiceRegistryLogin
Prelude.Read, Int -> CreateContainerServiceRegistryLogin -> ShowS
[CreateContainerServiceRegistryLogin] -> ShowS
CreateContainerServiceRegistryLogin -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateContainerServiceRegistryLogin] -> ShowS
$cshowList :: [CreateContainerServiceRegistryLogin] -> ShowS
show :: CreateContainerServiceRegistryLogin -> String
$cshow :: CreateContainerServiceRegistryLogin -> String
showsPrec :: Int -> CreateContainerServiceRegistryLogin -> ShowS
$cshowsPrec :: Int -> CreateContainerServiceRegistryLogin -> ShowS
Prelude.Show, forall x.
Rep CreateContainerServiceRegistryLogin x
-> CreateContainerServiceRegistryLogin
forall x.
CreateContainerServiceRegistryLogin
-> Rep CreateContainerServiceRegistryLogin x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateContainerServiceRegistryLogin x
-> CreateContainerServiceRegistryLogin
$cfrom :: forall x.
CreateContainerServiceRegistryLogin
-> Rep CreateContainerServiceRegistryLogin x
Prelude.Generic)

-- |
-- Create a value of 'CreateContainerServiceRegistryLogin' 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.
newCreateContainerServiceRegistryLogin ::
  CreateContainerServiceRegistryLogin
newCreateContainerServiceRegistryLogin :: CreateContainerServiceRegistryLogin
newCreateContainerServiceRegistryLogin =
  CreateContainerServiceRegistryLogin
CreateContainerServiceRegistryLogin'

instance
  Core.AWSRequest
    CreateContainerServiceRegistryLogin
  where
  type
    AWSResponse CreateContainerServiceRegistryLogin =
      CreateContainerServiceRegistryLoginResponse
  request :: (Service -> Service)
-> CreateContainerServiceRegistryLogin
-> Request CreateContainerServiceRegistryLogin
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 CreateContainerServiceRegistryLogin
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse CreateContainerServiceRegistryLogin)))
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 ContainerServiceRegistryLogin
-> Int -> CreateContainerServiceRegistryLoginResponse
CreateContainerServiceRegistryLoginResponse'
            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
"registryLogin")
            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
    CreateContainerServiceRegistryLogin
  where
  hashWithSalt :: Int -> CreateContainerServiceRegistryLogin -> Int
hashWithSalt Int
_salt CreateContainerServiceRegistryLogin
_ =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ()

instance
  Prelude.NFData
    CreateContainerServiceRegistryLogin
  where
  rnf :: CreateContainerServiceRegistryLogin -> ()
rnf CreateContainerServiceRegistryLogin
_ = ()

instance
  Data.ToHeaders
    CreateContainerServiceRegistryLogin
  where
  toHeaders :: CreateContainerServiceRegistryLogin -> 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.CreateContainerServiceRegistryLogin" ::
                          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
    CreateContainerServiceRegistryLogin
  where
  toJSON :: CreateContainerServiceRegistryLogin -> Value
toJSON = forall a b. a -> b -> a
Prelude.const (Object -> Value
Data.Object forall a. Monoid a => a
Prelude.mempty)

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

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

-- | /See:/ 'newCreateContainerServiceRegistryLoginResponse' smart constructor.
data CreateContainerServiceRegistryLoginResponse = CreateContainerServiceRegistryLoginResponse'
  { -- | An object that describes the log in information for the container
    -- service registry of your Lightsail account.
    CreateContainerServiceRegistryLoginResponse
-> Maybe ContainerServiceRegistryLogin
registryLogin :: Prelude.Maybe ContainerServiceRegistryLogin,
    -- | The response's http status code.
    CreateContainerServiceRegistryLoginResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateContainerServiceRegistryLoginResponse
-> CreateContainerServiceRegistryLoginResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateContainerServiceRegistryLoginResponse
-> CreateContainerServiceRegistryLoginResponse -> Bool
$c/= :: CreateContainerServiceRegistryLoginResponse
-> CreateContainerServiceRegistryLoginResponse -> Bool
== :: CreateContainerServiceRegistryLoginResponse
-> CreateContainerServiceRegistryLoginResponse -> Bool
$c== :: CreateContainerServiceRegistryLoginResponse
-> CreateContainerServiceRegistryLoginResponse -> Bool
Prelude.Eq, ReadPrec [CreateContainerServiceRegistryLoginResponse]
ReadPrec CreateContainerServiceRegistryLoginResponse
Int -> ReadS CreateContainerServiceRegistryLoginResponse
ReadS [CreateContainerServiceRegistryLoginResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateContainerServiceRegistryLoginResponse]
$creadListPrec :: ReadPrec [CreateContainerServiceRegistryLoginResponse]
readPrec :: ReadPrec CreateContainerServiceRegistryLoginResponse
$creadPrec :: ReadPrec CreateContainerServiceRegistryLoginResponse
readList :: ReadS [CreateContainerServiceRegistryLoginResponse]
$creadList :: ReadS [CreateContainerServiceRegistryLoginResponse]
readsPrec :: Int -> ReadS CreateContainerServiceRegistryLoginResponse
$creadsPrec :: Int -> ReadS CreateContainerServiceRegistryLoginResponse
Prelude.Read, Int -> CreateContainerServiceRegistryLoginResponse -> ShowS
[CreateContainerServiceRegistryLoginResponse] -> ShowS
CreateContainerServiceRegistryLoginResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateContainerServiceRegistryLoginResponse] -> ShowS
$cshowList :: [CreateContainerServiceRegistryLoginResponse] -> ShowS
show :: CreateContainerServiceRegistryLoginResponse -> String
$cshow :: CreateContainerServiceRegistryLoginResponse -> String
showsPrec :: Int -> CreateContainerServiceRegistryLoginResponse -> ShowS
$cshowsPrec :: Int -> CreateContainerServiceRegistryLoginResponse -> ShowS
Prelude.Show, forall x.
Rep CreateContainerServiceRegistryLoginResponse x
-> CreateContainerServiceRegistryLoginResponse
forall x.
CreateContainerServiceRegistryLoginResponse
-> Rep CreateContainerServiceRegistryLoginResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateContainerServiceRegistryLoginResponse x
-> CreateContainerServiceRegistryLoginResponse
$cfrom :: forall x.
CreateContainerServiceRegistryLoginResponse
-> Rep CreateContainerServiceRegistryLoginResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateContainerServiceRegistryLoginResponse' 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:
--
-- 'registryLogin', 'createContainerServiceRegistryLoginResponse_registryLogin' - An object that describes the log in information for the container
-- service registry of your Lightsail account.
--
-- 'httpStatus', 'createContainerServiceRegistryLoginResponse_httpStatus' - The response's http status code.
newCreateContainerServiceRegistryLoginResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateContainerServiceRegistryLoginResponse
newCreateContainerServiceRegistryLoginResponse :: Int -> CreateContainerServiceRegistryLoginResponse
newCreateContainerServiceRegistryLoginResponse
  Int
pHttpStatus_ =
    CreateContainerServiceRegistryLoginResponse'
      { $sel:registryLogin:CreateContainerServiceRegistryLoginResponse' :: Maybe ContainerServiceRegistryLogin
registryLogin =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:CreateContainerServiceRegistryLoginResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | An object that describes the log in information for the container
-- service registry of your Lightsail account.
createContainerServiceRegistryLoginResponse_registryLogin :: Lens.Lens' CreateContainerServiceRegistryLoginResponse (Prelude.Maybe ContainerServiceRegistryLogin)
createContainerServiceRegistryLoginResponse_registryLogin :: Lens'
  CreateContainerServiceRegistryLoginResponse
  (Maybe ContainerServiceRegistryLogin)
createContainerServiceRegistryLoginResponse_registryLogin = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateContainerServiceRegistryLoginResponse' {Maybe ContainerServiceRegistryLogin
registryLogin :: Maybe ContainerServiceRegistryLogin
$sel:registryLogin:CreateContainerServiceRegistryLoginResponse' :: CreateContainerServiceRegistryLoginResponse
-> Maybe ContainerServiceRegistryLogin
registryLogin} -> Maybe ContainerServiceRegistryLogin
registryLogin) (\s :: CreateContainerServiceRegistryLoginResponse
s@CreateContainerServiceRegistryLoginResponse' {} Maybe ContainerServiceRegistryLogin
a -> CreateContainerServiceRegistryLoginResponse
s {$sel:registryLogin:CreateContainerServiceRegistryLoginResponse' :: Maybe ContainerServiceRegistryLogin
registryLogin = Maybe ContainerServiceRegistryLogin
a} :: CreateContainerServiceRegistryLoginResponse)

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

instance
  Prelude.NFData
    CreateContainerServiceRegistryLoginResponse
  where
  rnf :: CreateContainerServiceRegistryLoginResponse -> ()
rnf CreateContainerServiceRegistryLoginResponse' {Int
Maybe ContainerServiceRegistryLogin
httpStatus :: Int
registryLogin :: Maybe ContainerServiceRegistryLogin
$sel:httpStatus:CreateContainerServiceRegistryLoginResponse' :: CreateContainerServiceRegistryLoginResponse -> Int
$sel:registryLogin:CreateContainerServiceRegistryLoginResponse' :: CreateContainerServiceRegistryLoginResponse
-> Maybe ContainerServiceRegistryLogin
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ContainerServiceRegistryLogin
registryLogin
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus