{-# 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.ECR.DescribeRegistry
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Describes the settings for a registry. The replication configuration for
-- a repository can be created or updated with the
-- PutReplicationConfiguration API action.
module Amazonka.ECR.DescribeRegistry
  ( -- * Creating a Request
    DescribeRegistry (..),
    newDescribeRegistry,

    -- * Destructuring the Response
    DescribeRegistryResponse (..),
    newDescribeRegistryResponse,

    -- * Response Lenses
    describeRegistryResponse_registryId,
    describeRegistryResponse_replicationConfiguration,
    describeRegistryResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDescribeRegistry' smart constructor.
data DescribeRegistry = DescribeRegistry'
  {
  }
  deriving (DescribeRegistry -> DescribeRegistry -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeRegistry -> DescribeRegistry -> Bool
$c/= :: DescribeRegistry -> DescribeRegistry -> Bool
== :: DescribeRegistry -> DescribeRegistry -> Bool
$c== :: DescribeRegistry -> DescribeRegistry -> Bool
Prelude.Eq, ReadPrec [DescribeRegistry]
ReadPrec DescribeRegistry
Int -> ReadS DescribeRegistry
ReadS [DescribeRegistry]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeRegistry]
$creadListPrec :: ReadPrec [DescribeRegistry]
readPrec :: ReadPrec DescribeRegistry
$creadPrec :: ReadPrec DescribeRegistry
readList :: ReadS [DescribeRegistry]
$creadList :: ReadS [DescribeRegistry]
readsPrec :: Int -> ReadS DescribeRegistry
$creadsPrec :: Int -> ReadS DescribeRegistry
Prelude.Read, Int -> DescribeRegistry -> ShowS
[DescribeRegistry] -> ShowS
DescribeRegistry -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeRegistry] -> ShowS
$cshowList :: [DescribeRegistry] -> ShowS
show :: DescribeRegistry -> String
$cshow :: DescribeRegistry -> String
showsPrec :: Int -> DescribeRegistry -> ShowS
$cshowsPrec :: Int -> DescribeRegistry -> ShowS
Prelude.Show, forall x. Rep DescribeRegistry x -> DescribeRegistry
forall x. DescribeRegistry -> Rep DescribeRegistry x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeRegistry x -> DescribeRegistry
$cfrom :: forall x. DescribeRegistry -> Rep DescribeRegistry x
Prelude.Generic)

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

instance Core.AWSRequest DescribeRegistry where
  type
    AWSResponse DescribeRegistry =
      DescribeRegistryResponse
  request :: (Service -> Service)
-> DescribeRegistry -> Request DescribeRegistry
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 DescribeRegistry
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DescribeRegistry)))
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 Text
-> Maybe ReplicationConfiguration
-> Int
-> DescribeRegistryResponse
DescribeRegistryResponse'
            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
"registryId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"replicationConfiguration")
            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 DescribeRegistry where
  hashWithSalt :: Int -> DescribeRegistry -> Int
hashWithSalt Int
_salt DescribeRegistry
_ =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ()

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

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

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

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

-- | /See:/ 'newDescribeRegistryResponse' smart constructor.
data DescribeRegistryResponse = DescribeRegistryResponse'
  { -- | The ID of the registry.
    DescribeRegistryResponse -> Maybe Text
registryId :: Prelude.Maybe Prelude.Text,
    -- | The replication configuration for the registry.
    DescribeRegistryResponse -> Maybe ReplicationConfiguration
replicationConfiguration :: Prelude.Maybe ReplicationConfiguration,
    -- | The response's http status code.
    DescribeRegistryResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeRegistryResponse -> DescribeRegistryResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeRegistryResponse -> DescribeRegistryResponse -> Bool
$c/= :: DescribeRegistryResponse -> DescribeRegistryResponse -> Bool
== :: DescribeRegistryResponse -> DescribeRegistryResponse -> Bool
$c== :: DescribeRegistryResponse -> DescribeRegistryResponse -> Bool
Prelude.Eq, ReadPrec [DescribeRegistryResponse]
ReadPrec DescribeRegistryResponse
Int -> ReadS DescribeRegistryResponse
ReadS [DescribeRegistryResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeRegistryResponse]
$creadListPrec :: ReadPrec [DescribeRegistryResponse]
readPrec :: ReadPrec DescribeRegistryResponse
$creadPrec :: ReadPrec DescribeRegistryResponse
readList :: ReadS [DescribeRegistryResponse]
$creadList :: ReadS [DescribeRegistryResponse]
readsPrec :: Int -> ReadS DescribeRegistryResponse
$creadsPrec :: Int -> ReadS DescribeRegistryResponse
Prelude.Read, Int -> DescribeRegistryResponse -> ShowS
[DescribeRegistryResponse] -> ShowS
DescribeRegistryResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeRegistryResponse] -> ShowS
$cshowList :: [DescribeRegistryResponse] -> ShowS
show :: DescribeRegistryResponse -> String
$cshow :: DescribeRegistryResponse -> String
showsPrec :: Int -> DescribeRegistryResponse -> ShowS
$cshowsPrec :: Int -> DescribeRegistryResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeRegistryResponse x -> DescribeRegistryResponse
forall x.
DescribeRegistryResponse -> Rep DescribeRegistryResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeRegistryResponse x -> DescribeRegistryResponse
$cfrom :: forall x.
DescribeRegistryResponse -> Rep DescribeRegistryResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeRegistryResponse' 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:
--
-- 'registryId', 'describeRegistryResponse_registryId' - The ID of the registry.
--
-- 'replicationConfiguration', 'describeRegistryResponse_replicationConfiguration' - The replication configuration for the registry.
--
-- 'httpStatus', 'describeRegistryResponse_httpStatus' - The response's http status code.
newDescribeRegistryResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeRegistryResponse
newDescribeRegistryResponse :: Int -> DescribeRegistryResponse
newDescribeRegistryResponse Int
pHttpStatus_ =
  DescribeRegistryResponse'
    { $sel:registryId:DescribeRegistryResponse' :: Maybe Text
registryId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:replicationConfiguration:DescribeRegistryResponse' :: Maybe ReplicationConfiguration
replicationConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeRegistryResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The ID of the registry.
describeRegistryResponse_registryId :: Lens.Lens' DescribeRegistryResponse (Prelude.Maybe Prelude.Text)
describeRegistryResponse_registryId :: Lens' DescribeRegistryResponse (Maybe Text)
describeRegistryResponse_registryId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeRegistryResponse' {Maybe Text
registryId :: Maybe Text
$sel:registryId:DescribeRegistryResponse' :: DescribeRegistryResponse -> Maybe Text
registryId} -> Maybe Text
registryId) (\s :: DescribeRegistryResponse
s@DescribeRegistryResponse' {} Maybe Text
a -> DescribeRegistryResponse
s {$sel:registryId:DescribeRegistryResponse' :: Maybe Text
registryId = Maybe Text
a} :: DescribeRegistryResponse)

-- | The replication configuration for the registry.
describeRegistryResponse_replicationConfiguration :: Lens.Lens' DescribeRegistryResponse (Prelude.Maybe ReplicationConfiguration)
describeRegistryResponse_replicationConfiguration :: Lens' DescribeRegistryResponse (Maybe ReplicationConfiguration)
describeRegistryResponse_replicationConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeRegistryResponse' {Maybe ReplicationConfiguration
replicationConfiguration :: Maybe ReplicationConfiguration
$sel:replicationConfiguration:DescribeRegistryResponse' :: DescribeRegistryResponse -> Maybe ReplicationConfiguration
replicationConfiguration} -> Maybe ReplicationConfiguration
replicationConfiguration) (\s :: DescribeRegistryResponse
s@DescribeRegistryResponse' {} Maybe ReplicationConfiguration
a -> DescribeRegistryResponse
s {$sel:replicationConfiguration:DescribeRegistryResponse' :: Maybe ReplicationConfiguration
replicationConfiguration = Maybe ReplicationConfiguration
a} :: DescribeRegistryResponse)

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

instance Prelude.NFData DescribeRegistryResponse where
  rnf :: DescribeRegistryResponse -> ()
rnf DescribeRegistryResponse' {Int
Maybe Text
Maybe ReplicationConfiguration
httpStatus :: Int
replicationConfiguration :: Maybe ReplicationConfiguration
registryId :: Maybe Text
$sel:httpStatus:DescribeRegistryResponse' :: DescribeRegistryResponse -> Int
$sel:replicationConfiguration:DescribeRegistryResponse' :: DescribeRegistryResponse -> Maybe ReplicationConfiguration
$sel:registryId:DescribeRegistryResponse' :: DescribeRegistryResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
registryId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ReplicationConfiguration
replicationConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus