{-# 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.ECRPublic.GetRegistryCatalogData
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves catalog metadata for a public registry.
module Amazonka.ECRPublic.GetRegistryCatalogData
  ( -- * Creating a Request
    GetRegistryCatalogData (..),
    newGetRegistryCatalogData,

    -- * Destructuring the Response
    GetRegistryCatalogDataResponse (..),
    newGetRegistryCatalogDataResponse,

    -- * Response Lenses
    getRegistryCatalogDataResponse_httpStatus,
    getRegistryCatalogDataResponse_registryCatalogData,
  )
where

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

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

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

instance Core.AWSRequest GetRegistryCatalogData where
  type
    AWSResponse GetRegistryCatalogData =
      GetRegistryCatalogDataResponse
  request :: (Service -> Service)
-> GetRegistryCatalogData -> Request GetRegistryCatalogData
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 GetRegistryCatalogData
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetRegistryCatalogData)))
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 ->
          Int -> RegistryCatalogData -> GetRegistryCatalogDataResponse
GetRegistryCatalogDataResponse'
            forall (f :: * -> *) a b. Functor 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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"registryCatalogData")
      )

instance Prelude.Hashable GetRegistryCatalogData where
  hashWithSalt :: Int -> GetRegistryCatalogData -> Int
hashWithSalt Int
_salt GetRegistryCatalogData
_ =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ()

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

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

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

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

-- | /See:/ 'newGetRegistryCatalogDataResponse' smart constructor.
data GetRegistryCatalogDataResponse = GetRegistryCatalogDataResponse'
  { -- | The response's http status code.
    GetRegistryCatalogDataResponse -> Int
httpStatus :: Prelude.Int,
    -- | The catalog metadata for the public registry.
    GetRegistryCatalogDataResponse -> RegistryCatalogData
registryCatalogData :: RegistryCatalogData
  }
  deriving (GetRegistryCatalogDataResponse
-> GetRegistryCatalogDataResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetRegistryCatalogDataResponse
-> GetRegistryCatalogDataResponse -> Bool
$c/= :: GetRegistryCatalogDataResponse
-> GetRegistryCatalogDataResponse -> Bool
== :: GetRegistryCatalogDataResponse
-> GetRegistryCatalogDataResponse -> Bool
$c== :: GetRegistryCatalogDataResponse
-> GetRegistryCatalogDataResponse -> Bool
Prelude.Eq, ReadPrec [GetRegistryCatalogDataResponse]
ReadPrec GetRegistryCatalogDataResponse
Int -> ReadS GetRegistryCatalogDataResponse
ReadS [GetRegistryCatalogDataResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetRegistryCatalogDataResponse]
$creadListPrec :: ReadPrec [GetRegistryCatalogDataResponse]
readPrec :: ReadPrec GetRegistryCatalogDataResponse
$creadPrec :: ReadPrec GetRegistryCatalogDataResponse
readList :: ReadS [GetRegistryCatalogDataResponse]
$creadList :: ReadS [GetRegistryCatalogDataResponse]
readsPrec :: Int -> ReadS GetRegistryCatalogDataResponse
$creadsPrec :: Int -> ReadS GetRegistryCatalogDataResponse
Prelude.Read, Int -> GetRegistryCatalogDataResponse -> ShowS
[GetRegistryCatalogDataResponse] -> ShowS
GetRegistryCatalogDataResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetRegistryCatalogDataResponse] -> ShowS
$cshowList :: [GetRegistryCatalogDataResponse] -> ShowS
show :: GetRegistryCatalogDataResponse -> String
$cshow :: GetRegistryCatalogDataResponse -> String
showsPrec :: Int -> GetRegistryCatalogDataResponse -> ShowS
$cshowsPrec :: Int -> GetRegistryCatalogDataResponse -> ShowS
Prelude.Show, forall x.
Rep GetRegistryCatalogDataResponse x
-> GetRegistryCatalogDataResponse
forall x.
GetRegistryCatalogDataResponse
-> Rep GetRegistryCatalogDataResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetRegistryCatalogDataResponse x
-> GetRegistryCatalogDataResponse
$cfrom :: forall x.
GetRegistryCatalogDataResponse
-> Rep GetRegistryCatalogDataResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetRegistryCatalogDataResponse' 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:
--
-- 'httpStatus', 'getRegistryCatalogDataResponse_httpStatus' - The response's http status code.
--
-- 'registryCatalogData', 'getRegistryCatalogDataResponse_registryCatalogData' - The catalog metadata for the public registry.
newGetRegistryCatalogDataResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'registryCatalogData'
  RegistryCatalogData ->
  GetRegistryCatalogDataResponse
newGetRegistryCatalogDataResponse :: Int -> RegistryCatalogData -> GetRegistryCatalogDataResponse
newGetRegistryCatalogDataResponse
  Int
pHttpStatus_
  RegistryCatalogData
pRegistryCatalogData_ =
    GetRegistryCatalogDataResponse'
      { $sel:httpStatus:GetRegistryCatalogDataResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:registryCatalogData:GetRegistryCatalogDataResponse' :: RegistryCatalogData
registryCatalogData = RegistryCatalogData
pRegistryCatalogData_
      }

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

-- | The catalog metadata for the public registry.
getRegistryCatalogDataResponse_registryCatalogData :: Lens.Lens' GetRegistryCatalogDataResponse RegistryCatalogData
getRegistryCatalogDataResponse_registryCatalogData :: Lens' GetRegistryCatalogDataResponse RegistryCatalogData
getRegistryCatalogDataResponse_registryCatalogData = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRegistryCatalogDataResponse' {RegistryCatalogData
registryCatalogData :: RegistryCatalogData
$sel:registryCatalogData:GetRegistryCatalogDataResponse' :: GetRegistryCatalogDataResponse -> RegistryCatalogData
registryCatalogData} -> RegistryCatalogData
registryCatalogData) (\s :: GetRegistryCatalogDataResponse
s@GetRegistryCatalogDataResponse' {} RegistryCatalogData
a -> GetRegistryCatalogDataResponse
s {$sel:registryCatalogData:GetRegistryCatalogDataResponse' :: RegistryCatalogData
registryCatalogData = RegistryCatalogData
a} :: GetRegistryCatalogDataResponse)

instance
  Prelude.NFData
    GetRegistryCatalogDataResponse
  where
  rnf :: GetRegistryCatalogDataResponse -> ()
rnf GetRegistryCatalogDataResponse' {Int
RegistryCatalogData
registryCatalogData :: RegistryCatalogData
httpStatus :: Int
$sel:registryCatalogData:GetRegistryCatalogDataResponse' :: GetRegistryCatalogDataResponse -> RegistryCatalogData
$sel:httpStatus:GetRegistryCatalogDataResponse' :: GetRegistryCatalogDataResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf RegistryCatalogData
registryCatalogData