{-# 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.GetRegistryPolicy
-- 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 the permissions policy for a registry.
module Amazonka.ECR.GetRegistryPolicy
  ( -- * Creating a Request
    GetRegistryPolicy (..),
    newGetRegistryPolicy,

    -- * Destructuring the Response
    GetRegistryPolicyResponse (..),
    newGetRegistryPolicyResponse,

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

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

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

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

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

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

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

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

-- |
-- Create a value of 'GetRegistryPolicyResponse' 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:
--
-- 'policyText', 'getRegistryPolicyResponse_policyText' - The JSON text of the permissions policy for a registry.
--
-- 'registryId', 'getRegistryPolicyResponse_registryId' - The ID of the registry.
--
-- 'httpStatus', 'getRegistryPolicyResponse_httpStatus' - The response's http status code.
newGetRegistryPolicyResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetRegistryPolicyResponse
newGetRegistryPolicyResponse :: Int -> GetRegistryPolicyResponse
newGetRegistryPolicyResponse Int
pHttpStatus_ =
  GetRegistryPolicyResponse'
    { $sel:policyText:GetRegistryPolicyResponse' :: Maybe Text
policyText =
        forall a. Maybe a
Prelude.Nothing,
      $sel:registryId:GetRegistryPolicyResponse' :: Maybe Text
registryId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetRegistryPolicyResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The JSON text of the permissions policy for a registry.
getRegistryPolicyResponse_policyText :: Lens.Lens' GetRegistryPolicyResponse (Prelude.Maybe Prelude.Text)
getRegistryPolicyResponse_policyText :: Lens' GetRegistryPolicyResponse (Maybe Text)
getRegistryPolicyResponse_policyText = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRegistryPolicyResponse' {Maybe Text
policyText :: Maybe Text
$sel:policyText:GetRegistryPolicyResponse' :: GetRegistryPolicyResponse -> Maybe Text
policyText} -> Maybe Text
policyText) (\s :: GetRegistryPolicyResponse
s@GetRegistryPolicyResponse' {} Maybe Text
a -> GetRegistryPolicyResponse
s {$sel:policyText:GetRegistryPolicyResponse' :: Maybe Text
policyText = Maybe Text
a} :: GetRegistryPolicyResponse)

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

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

instance Prelude.NFData GetRegistryPolicyResponse where
  rnf :: GetRegistryPolicyResponse -> ()
rnf GetRegistryPolicyResponse' {Int
Maybe Text
httpStatus :: Int
registryId :: Maybe Text
policyText :: Maybe Text
$sel:httpStatus:GetRegistryPolicyResponse' :: GetRegistryPolicyResponse -> Int
$sel:registryId:GetRegistryPolicyResponse' :: GetRegistryPolicyResponse -> Maybe Text
$sel:policyText:GetRegistryPolicyResponse' :: GetRegistryPolicyResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
policyText
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 Int
httpStatus