{-# 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.PutRegistryPolicy
-- 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 or updates the permissions policy for your registry.
--
-- A registry policy is used to specify permissions for another Amazon Web
-- Services account and is used when configuring cross-account replication.
-- For more information, see
-- <https://docs.aws.amazon.com/AmazonECR/latest/userguide/registry-permissions.html Registry permissions>
-- in the /Amazon Elastic Container Registry User Guide/.
module Amazonka.ECR.PutRegistryPolicy
  ( -- * Creating a Request
    PutRegistryPolicy (..),
    newPutRegistryPolicy,

    -- * Request Lenses
    putRegistryPolicy_policyText,

    -- * Destructuring the Response
    PutRegistryPolicyResponse (..),
    newPutRegistryPolicyResponse,

    -- * Response Lenses
    putRegistryPolicyResponse_policyText,
    putRegistryPolicyResponse_registryId,
    putRegistryPolicyResponse_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:/ 'newPutRegistryPolicy' smart constructor.
data PutRegistryPolicy = PutRegistryPolicy'
  { -- | The JSON policy text to apply to your registry. The policy text follows
    -- the same format as IAM policy text. For more information, see
    -- <https://docs.aws.amazon.com/AmazonECR/latest/userguide/registry-permissions.html Registry permissions>
    -- in the /Amazon Elastic Container Registry User Guide/.
    PutRegistryPolicy -> Text
policyText :: Prelude.Text
  }
  deriving (PutRegistryPolicy -> PutRegistryPolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutRegistryPolicy -> PutRegistryPolicy -> Bool
$c/= :: PutRegistryPolicy -> PutRegistryPolicy -> Bool
== :: PutRegistryPolicy -> PutRegistryPolicy -> Bool
$c== :: PutRegistryPolicy -> PutRegistryPolicy -> Bool
Prelude.Eq, ReadPrec [PutRegistryPolicy]
ReadPrec PutRegistryPolicy
Int -> ReadS PutRegistryPolicy
ReadS [PutRegistryPolicy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutRegistryPolicy]
$creadListPrec :: ReadPrec [PutRegistryPolicy]
readPrec :: ReadPrec PutRegistryPolicy
$creadPrec :: ReadPrec PutRegistryPolicy
readList :: ReadS [PutRegistryPolicy]
$creadList :: ReadS [PutRegistryPolicy]
readsPrec :: Int -> ReadS PutRegistryPolicy
$creadsPrec :: Int -> ReadS PutRegistryPolicy
Prelude.Read, Int -> PutRegistryPolicy -> ShowS
[PutRegistryPolicy] -> ShowS
PutRegistryPolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutRegistryPolicy] -> ShowS
$cshowList :: [PutRegistryPolicy] -> ShowS
show :: PutRegistryPolicy -> String
$cshow :: PutRegistryPolicy -> String
showsPrec :: Int -> PutRegistryPolicy -> ShowS
$cshowsPrec :: Int -> PutRegistryPolicy -> ShowS
Prelude.Show, forall x. Rep PutRegistryPolicy x -> PutRegistryPolicy
forall x. PutRegistryPolicy -> Rep PutRegistryPolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PutRegistryPolicy x -> PutRegistryPolicy
$cfrom :: forall x. PutRegistryPolicy -> Rep PutRegistryPolicy x
Prelude.Generic)

-- |
-- Create a value of 'PutRegistryPolicy' 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', 'putRegistryPolicy_policyText' - The JSON policy text to apply to your registry. The policy text follows
-- the same format as IAM policy text. For more information, see
-- <https://docs.aws.amazon.com/AmazonECR/latest/userguide/registry-permissions.html Registry permissions>
-- in the /Amazon Elastic Container Registry User Guide/.
newPutRegistryPolicy ::
  -- | 'policyText'
  Prelude.Text ->
  PutRegistryPolicy
newPutRegistryPolicy :: Text -> PutRegistryPolicy
newPutRegistryPolicy Text
pPolicyText_ =
  PutRegistryPolicy' {$sel:policyText:PutRegistryPolicy' :: Text
policyText = Text
pPolicyText_}

-- | The JSON policy text to apply to your registry. The policy text follows
-- the same format as IAM policy text. For more information, see
-- <https://docs.aws.amazon.com/AmazonECR/latest/userguide/registry-permissions.html Registry permissions>
-- in the /Amazon Elastic Container Registry User Guide/.
putRegistryPolicy_policyText :: Lens.Lens' PutRegistryPolicy Prelude.Text
putRegistryPolicy_policyText :: Lens' PutRegistryPolicy Text
putRegistryPolicy_policyText = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutRegistryPolicy' {Text
policyText :: Text
$sel:policyText:PutRegistryPolicy' :: PutRegistryPolicy -> Text
policyText} -> Text
policyText) (\s :: PutRegistryPolicy
s@PutRegistryPolicy' {} Text
a -> PutRegistryPolicy
s {$sel:policyText:PutRegistryPolicy' :: Text
policyText = Text
a} :: PutRegistryPolicy)

instance Core.AWSRequest PutRegistryPolicy where
  type
    AWSResponse PutRegistryPolicy =
      PutRegistryPolicyResponse
  request :: (Service -> Service)
-> PutRegistryPolicy -> Request PutRegistryPolicy
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 PutRegistryPolicy
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse PutRegistryPolicy)))
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 -> PutRegistryPolicyResponse
PutRegistryPolicyResponse'
            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 PutRegistryPolicy where
  hashWithSalt :: Int -> PutRegistryPolicy -> Int
hashWithSalt Int
_salt PutRegistryPolicy' {Text
policyText :: Text
$sel:policyText:PutRegistryPolicy' :: PutRegistryPolicy -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
policyText

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

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

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

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

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

-- |
-- Create a value of 'PutRegistryPolicyResponse' 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', 'putRegistryPolicyResponse_policyText' - The JSON policy text for your registry.
--
-- 'registryId', 'putRegistryPolicyResponse_registryId' - The registry ID.
--
-- 'httpStatus', 'putRegistryPolicyResponse_httpStatus' - The response's http status code.
newPutRegistryPolicyResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  PutRegistryPolicyResponse
newPutRegistryPolicyResponse :: Int -> PutRegistryPolicyResponse
newPutRegistryPolicyResponse Int
pHttpStatus_ =
  PutRegistryPolicyResponse'
    { $sel:policyText:PutRegistryPolicyResponse' :: Maybe Text
policyText =
        forall a. Maybe a
Prelude.Nothing,
      $sel:registryId:PutRegistryPolicyResponse' :: Maybe Text
registryId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:PutRegistryPolicyResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

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

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

instance Prelude.NFData PutRegistryPolicyResponse where
  rnf :: PutRegistryPolicyResponse -> ()
rnf PutRegistryPolicyResponse' {Int
Maybe Text
httpStatus :: Int
registryId :: Maybe Text
policyText :: Maybe Text
$sel:httpStatus:PutRegistryPolicyResponse' :: PutRegistryPolicyResponse -> Int
$sel:registryId:PutRegistryPolicyResponse' :: PutRegistryPolicyResponse -> Maybe Text
$sel:policyText:PutRegistryPolicyResponse' :: PutRegistryPolicyResponse -> 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