{-# 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.ImageBuilder.PutImageRecipePolicy
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Applies a policy to an image recipe. We recommend that you call the RAM
-- API
-- <https://docs.aws.amazon.com/ram/latest/APIReference/API_CreateResourceShare.html CreateResourceShare>
-- to share resources. If you call the Image Builder API
-- @PutImageRecipePolicy@, you must also call the RAM API
-- <https://docs.aws.amazon.com/ram/latest/APIReference/API_PromoteResourceShareCreatedFromPolicy.html PromoteResourceShareCreatedFromPolicy>
-- in order for the resource to be visible to all principals with whom the
-- resource is shared.
module Amazonka.ImageBuilder.PutImageRecipePolicy
  ( -- * Creating a Request
    PutImageRecipePolicy (..),
    newPutImageRecipePolicy,

    -- * Request Lenses
    putImageRecipePolicy_imageRecipeArn,
    putImageRecipePolicy_policy,

    -- * Destructuring the Response
    PutImageRecipePolicyResponse (..),
    newPutImageRecipePolicyResponse,

    -- * Response Lenses
    putImageRecipePolicyResponse_imageRecipeArn,
    putImageRecipePolicyResponse_requestId,
    putImageRecipePolicyResponse_httpStatus,
  )
where

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

-- | /See:/ 'newPutImageRecipePolicy' smart constructor.
data PutImageRecipePolicy = PutImageRecipePolicy'
  { -- | The Amazon Resource Name (ARN) of the image recipe that this policy
    -- should be applied to.
    PutImageRecipePolicy -> Text
imageRecipeArn :: Prelude.Text,
    -- | The policy to apply.
    PutImageRecipePolicy -> Text
policy :: Prelude.Text
  }
  deriving (PutImageRecipePolicy -> PutImageRecipePolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutImageRecipePolicy -> PutImageRecipePolicy -> Bool
$c/= :: PutImageRecipePolicy -> PutImageRecipePolicy -> Bool
== :: PutImageRecipePolicy -> PutImageRecipePolicy -> Bool
$c== :: PutImageRecipePolicy -> PutImageRecipePolicy -> Bool
Prelude.Eq, ReadPrec [PutImageRecipePolicy]
ReadPrec PutImageRecipePolicy
Int -> ReadS PutImageRecipePolicy
ReadS [PutImageRecipePolicy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutImageRecipePolicy]
$creadListPrec :: ReadPrec [PutImageRecipePolicy]
readPrec :: ReadPrec PutImageRecipePolicy
$creadPrec :: ReadPrec PutImageRecipePolicy
readList :: ReadS [PutImageRecipePolicy]
$creadList :: ReadS [PutImageRecipePolicy]
readsPrec :: Int -> ReadS PutImageRecipePolicy
$creadsPrec :: Int -> ReadS PutImageRecipePolicy
Prelude.Read, Int -> PutImageRecipePolicy -> ShowS
[PutImageRecipePolicy] -> ShowS
PutImageRecipePolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutImageRecipePolicy] -> ShowS
$cshowList :: [PutImageRecipePolicy] -> ShowS
show :: PutImageRecipePolicy -> String
$cshow :: PutImageRecipePolicy -> String
showsPrec :: Int -> PutImageRecipePolicy -> ShowS
$cshowsPrec :: Int -> PutImageRecipePolicy -> ShowS
Prelude.Show, forall x. Rep PutImageRecipePolicy x -> PutImageRecipePolicy
forall x. PutImageRecipePolicy -> Rep PutImageRecipePolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PutImageRecipePolicy x -> PutImageRecipePolicy
$cfrom :: forall x. PutImageRecipePolicy -> Rep PutImageRecipePolicy x
Prelude.Generic)

-- |
-- Create a value of 'PutImageRecipePolicy' 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:
--
-- 'imageRecipeArn', 'putImageRecipePolicy_imageRecipeArn' - The Amazon Resource Name (ARN) of the image recipe that this policy
-- should be applied to.
--
-- 'policy', 'putImageRecipePolicy_policy' - The policy to apply.
newPutImageRecipePolicy ::
  -- | 'imageRecipeArn'
  Prelude.Text ->
  -- | 'policy'
  Prelude.Text ->
  PutImageRecipePolicy
newPutImageRecipePolicy :: Text -> Text -> PutImageRecipePolicy
newPutImageRecipePolicy Text
pImageRecipeArn_ Text
pPolicy_ =
  PutImageRecipePolicy'
    { $sel:imageRecipeArn:PutImageRecipePolicy' :: Text
imageRecipeArn =
        Text
pImageRecipeArn_,
      $sel:policy:PutImageRecipePolicy' :: Text
policy = Text
pPolicy_
    }

-- | The Amazon Resource Name (ARN) of the image recipe that this policy
-- should be applied to.
putImageRecipePolicy_imageRecipeArn :: Lens.Lens' PutImageRecipePolicy Prelude.Text
putImageRecipePolicy_imageRecipeArn :: Lens' PutImageRecipePolicy Text
putImageRecipePolicy_imageRecipeArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutImageRecipePolicy' {Text
imageRecipeArn :: Text
$sel:imageRecipeArn:PutImageRecipePolicy' :: PutImageRecipePolicy -> Text
imageRecipeArn} -> Text
imageRecipeArn) (\s :: PutImageRecipePolicy
s@PutImageRecipePolicy' {} Text
a -> PutImageRecipePolicy
s {$sel:imageRecipeArn:PutImageRecipePolicy' :: Text
imageRecipeArn = Text
a} :: PutImageRecipePolicy)

-- | The policy to apply.
putImageRecipePolicy_policy :: Lens.Lens' PutImageRecipePolicy Prelude.Text
putImageRecipePolicy_policy :: Lens' PutImageRecipePolicy Text
putImageRecipePolicy_policy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutImageRecipePolicy' {Text
policy :: Text
$sel:policy:PutImageRecipePolicy' :: PutImageRecipePolicy -> Text
policy} -> Text
policy) (\s :: PutImageRecipePolicy
s@PutImageRecipePolicy' {} Text
a -> PutImageRecipePolicy
s {$sel:policy:PutImageRecipePolicy' :: Text
policy = Text
a} :: PutImageRecipePolicy)

instance Core.AWSRequest PutImageRecipePolicy where
  type
    AWSResponse PutImageRecipePolicy =
      PutImageRecipePolicyResponse
  request :: (Service -> Service)
-> PutImageRecipePolicy -> Request PutImageRecipePolicy
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy PutImageRecipePolicy
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse PutImageRecipePolicy)))
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 -> PutImageRecipePolicyResponse
PutImageRecipePolicyResponse'
            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
"imageRecipeArn")
            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
"requestId")
            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 PutImageRecipePolicy where
  hashWithSalt :: Int -> PutImageRecipePolicy -> Int
hashWithSalt Int
_salt PutImageRecipePolicy' {Text
policy :: Text
imageRecipeArn :: Text
$sel:policy:PutImageRecipePolicy' :: PutImageRecipePolicy -> Text
$sel:imageRecipeArn:PutImageRecipePolicy' :: PutImageRecipePolicy -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
imageRecipeArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
policy

instance Prelude.NFData PutImageRecipePolicy where
  rnf :: PutImageRecipePolicy -> ()
rnf PutImageRecipePolicy' {Text
policy :: Text
imageRecipeArn :: Text
$sel:policy:PutImageRecipePolicy' :: PutImageRecipePolicy -> Text
$sel:imageRecipeArn:PutImageRecipePolicy' :: PutImageRecipePolicy -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
imageRecipeArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
policy

instance Data.ToHeaders PutImageRecipePolicy where
  toHeaders :: PutImageRecipePolicy -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON PutImageRecipePolicy where
  toJSON :: PutImageRecipePolicy -> Value
toJSON PutImageRecipePolicy' {Text
policy :: Text
imageRecipeArn :: Text
$sel:policy:PutImageRecipePolicy' :: PutImageRecipePolicy -> Text
$sel:imageRecipeArn:PutImageRecipePolicy' :: PutImageRecipePolicy -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"imageRecipeArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
imageRecipeArn),
            forall a. a -> Maybe a
Prelude.Just (Key
"policy" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
policy)
          ]
      )

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

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

-- | /See:/ 'newPutImageRecipePolicyResponse' smart constructor.
data PutImageRecipePolicyResponse = PutImageRecipePolicyResponse'
  { -- | The Amazon Resource Name (ARN) of the image recipe that this policy was
    -- applied to.
    PutImageRecipePolicyResponse -> Maybe Text
imageRecipeArn :: Prelude.Maybe Prelude.Text,
    -- | The request ID that uniquely identifies this request.
    PutImageRecipePolicyResponse -> Maybe Text
requestId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    PutImageRecipePolicyResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (PutImageRecipePolicyResponse
-> PutImageRecipePolicyResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutImageRecipePolicyResponse
-> PutImageRecipePolicyResponse -> Bool
$c/= :: PutImageRecipePolicyResponse
-> PutImageRecipePolicyResponse -> Bool
== :: PutImageRecipePolicyResponse
-> PutImageRecipePolicyResponse -> Bool
$c== :: PutImageRecipePolicyResponse
-> PutImageRecipePolicyResponse -> Bool
Prelude.Eq, ReadPrec [PutImageRecipePolicyResponse]
ReadPrec PutImageRecipePolicyResponse
Int -> ReadS PutImageRecipePolicyResponse
ReadS [PutImageRecipePolicyResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutImageRecipePolicyResponse]
$creadListPrec :: ReadPrec [PutImageRecipePolicyResponse]
readPrec :: ReadPrec PutImageRecipePolicyResponse
$creadPrec :: ReadPrec PutImageRecipePolicyResponse
readList :: ReadS [PutImageRecipePolicyResponse]
$creadList :: ReadS [PutImageRecipePolicyResponse]
readsPrec :: Int -> ReadS PutImageRecipePolicyResponse
$creadsPrec :: Int -> ReadS PutImageRecipePolicyResponse
Prelude.Read, Int -> PutImageRecipePolicyResponse -> ShowS
[PutImageRecipePolicyResponse] -> ShowS
PutImageRecipePolicyResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutImageRecipePolicyResponse] -> ShowS
$cshowList :: [PutImageRecipePolicyResponse] -> ShowS
show :: PutImageRecipePolicyResponse -> String
$cshow :: PutImageRecipePolicyResponse -> String
showsPrec :: Int -> PutImageRecipePolicyResponse -> ShowS
$cshowsPrec :: Int -> PutImageRecipePolicyResponse -> ShowS
Prelude.Show, forall x.
Rep PutImageRecipePolicyResponse x -> PutImageRecipePolicyResponse
forall x.
PutImageRecipePolicyResponse -> Rep PutImageRecipePolicyResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep PutImageRecipePolicyResponse x -> PutImageRecipePolicyResponse
$cfrom :: forall x.
PutImageRecipePolicyResponse -> Rep PutImageRecipePolicyResponse x
Prelude.Generic)

-- |
-- Create a value of 'PutImageRecipePolicyResponse' 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:
--
-- 'imageRecipeArn', 'putImageRecipePolicyResponse_imageRecipeArn' - The Amazon Resource Name (ARN) of the image recipe that this policy was
-- applied to.
--
-- 'requestId', 'putImageRecipePolicyResponse_requestId' - The request ID that uniquely identifies this request.
--
-- 'httpStatus', 'putImageRecipePolicyResponse_httpStatus' - The response's http status code.
newPutImageRecipePolicyResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  PutImageRecipePolicyResponse
newPutImageRecipePolicyResponse :: Int -> PutImageRecipePolicyResponse
newPutImageRecipePolicyResponse Int
pHttpStatus_ =
  PutImageRecipePolicyResponse'
    { $sel:imageRecipeArn:PutImageRecipePolicyResponse' :: Maybe Text
imageRecipeArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:requestId:PutImageRecipePolicyResponse' :: Maybe Text
requestId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:PutImageRecipePolicyResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Resource Name (ARN) of the image recipe that this policy was
-- applied to.
putImageRecipePolicyResponse_imageRecipeArn :: Lens.Lens' PutImageRecipePolicyResponse (Prelude.Maybe Prelude.Text)
putImageRecipePolicyResponse_imageRecipeArn :: Lens' PutImageRecipePolicyResponse (Maybe Text)
putImageRecipePolicyResponse_imageRecipeArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutImageRecipePolicyResponse' {Maybe Text
imageRecipeArn :: Maybe Text
$sel:imageRecipeArn:PutImageRecipePolicyResponse' :: PutImageRecipePolicyResponse -> Maybe Text
imageRecipeArn} -> Maybe Text
imageRecipeArn) (\s :: PutImageRecipePolicyResponse
s@PutImageRecipePolicyResponse' {} Maybe Text
a -> PutImageRecipePolicyResponse
s {$sel:imageRecipeArn:PutImageRecipePolicyResponse' :: Maybe Text
imageRecipeArn = Maybe Text
a} :: PutImageRecipePolicyResponse)

-- | The request ID that uniquely identifies this request.
putImageRecipePolicyResponse_requestId :: Lens.Lens' PutImageRecipePolicyResponse (Prelude.Maybe Prelude.Text)
putImageRecipePolicyResponse_requestId :: Lens' PutImageRecipePolicyResponse (Maybe Text)
putImageRecipePolicyResponse_requestId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutImageRecipePolicyResponse' {Maybe Text
requestId :: Maybe Text
$sel:requestId:PutImageRecipePolicyResponse' :: PutImageRecipePolicyResponse -> Maybe Text
requestId} -> Maybe Text
requestId) (\s :: PutImageRecipePolicyResponse
s@PutImageRecipePolicyResponse' {} Maybe Text
a -> PutImageRecipePolicyResponse
s {$sel:requestId:PutImageRecipePolicyResponse' :: Maybe Text
requestId = Maybe Text
a} :: PutImageRecipePolicyResponse)

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

instance Prelude.NFData PutImageRecipePolicyResponse where
  rnf :: PutImageRecipePolicyResponse -> ()
rnf PutImageRecipePolicyResponse' {Int
Maybe Text
httpStatus :: Int
requestId :: Maybe Text
imageRecipeArn :: Maybe Text
$sel:httpStatus:PutImageRecipePolicyResponse' :: PutImageRecipePolicyResponse -> Int
$sel:requestId:PutImageRecipePolicyResponse' :: PutImageRecipePolicyResponse -> Maybe Text
$sel:imageRecipeArn:PutImageRecipePolicyResponse' :: PutImageRecipePolicyResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
imageRecipeArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
requestId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus