{-# 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.GetImagePolicy
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets an image policy.
module Amazonka.ImageBuilder.GetImagePolicy
  ( -- * Creating a Request
    GetImagePolicy (..),
    newGetImagePolicy,

    -- * Request Lenses
    getImagePolicy_imageArn,

    -- * Destructuring the Response
    GetImagePolicyResponse (..),
    newGetImagePolicyResponse,

    -- * Response Lenses
    getImagePolicyResponse_policy,
    getImagePolicyResponse_requestId,
    getImagePolicyResponse_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:/ 'newGetImagePolicy' smart constructor.
data GetImagePolicy = GetImagePolicy'
  { -- | The Amazon Resource Name (ARN) of the image whose policy you want to
    -- retrieve.
    GetImagePolicy -> Text
imageArn :: Prelude.Text
  }
  deriving (GetImagePolicy -> GetImagePolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetImagePolicy -> GetImagePolicy -> Bool
$c/= :: GetImagePolicy -> GetImagePolicy -> Bool
== :: GetImagePolicy -> GetImagePolicy -> Bool
$c== :: GetImagePolicy -> GetImagePolicy -> Bool
Prelude.Eq, ReadPrec [GetImagePolicy]
ReadPrec GetImagePolicy
Int -> ReadS GetImagePolicy
ReadS [GetImagePolicy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetImagePolicy]
$creadListPrec :: ReadPrec [GetImagePolicy]
readPrec :: ReadPrec GetImagePolicy
$creadPrec :: ReadPrec GetImagePolicy
readList :: ReadS [GetImagePolicy]
$creadList :: ReadS [GetImagePolicy]
readsPrec :: Int -> ReadS GetImagePolicy
$creadsPrec :: Int -> ReadS GetImagePolicy
Prelude.Read, Int -> GetImagePolicy -> ShowS
[GetImagePolicy] -> ShowS
GetImagePolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetImagePolicy] -> ShowS
$cshowList :: [GetImagePolicy] -> ShowS
show :: GetImagePolicy -> String
$cshow :: GetImagePolicy -> String
showsPrec :: Int -> GetImagePolicy -> ShowS
$cshowsPrec :: Int -> GetImagePolicy -> ShowS
Prelude.Show, forall x. Rep GetImagePolicy x -> GetImagePolicy
forall x. GetImagePolicy -> Rep GetImagePolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetImagePolicy x -> GetImagePolicy
$cfrom :: forall x. GetImagePolicy -> Rep GetImagePolicy x
Prelude.Generic)

-- |
-- Create a value of 'GetImagePolicy' 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:
--
-- 'imageArn', 'getImagePolicy_imageArn' - The Amazon Resource Name (ARN) of the image whose policy you want to
-- retrieve.
newGetImagePolicy ::
  -- | 'imageArn'
  Prelude.Text ->
  GetImagePolicy
newGetImagePolicy :: Text -> GetImagePolicy
newGetImagePolicy Text
pImageArn_ =
  GetImagePolicy' {$sel:imageArn:GetImagePolicy' :: Text
imageArn = Text
pImageArn_}

-- | The Amazon Resource Name (ARN) of the image whose policy you want to
-- retrieve.
getImagePolicy_imageArn :: Lens.Lens' GetImagePolicy Prelude.Text
getImagePolicy_imageArn :: Lens' GetImagePolicy Text
getImagePolicy_imageArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetImagePolicy' {Text
imageArn :: Text
$sel:imageArn:GetImagePolicy' :: GetImagePolicy -> Text
imageArn} -> Text
imageArn) (\s :: GetImagePolicy
s@GetImagePolicy' {} Text
a -> GetImagePolicy
s {$sel:imageArn:GetImagePolicy' :: Text
imageArn = Text
a} :: GetImagePolicy)

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

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

instance Data.ToHeaders GetImagePolicy where
  toHeaders :: GetImagePolicy -> 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.ToPath GetImagePolicy where
  toPath :: GetImagePolicy -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/GetImagePolicy"

instance Data.ToQuery GetImagePolicy where
  toQuery :: GetImagePolicy -> QueryString
toQuery GetImagePolicy' {Text
imageArn :: Text
$sel:imageArn:GetImagePolicy' :: GetImagePolicy -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"imageArn" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
imageArn]

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

-- |
-- Create a value of 'GetImagePolicyResponse' 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:
--
-- 'policy', 'getImagePolicyResponse_policy' - The image policy object.
--
-- 'requestId', 'getImagePolicyResponse_requestId' - The request ID that uniquely identifies this request.
--
-- 'httpStatus', 'getImagePolicyResponse_httpStatus' - The response's http status code.
newGetImagePolicyResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetImagePolicyResponse
newGetImagePolicyResponse :: Int -> GetImagePolicyResponse
newGetImagePolicyResponse Int
pHttpStatus_ =
  GetImagePolicyResponse'
    { $sel:policy:GetImagePolicyResponse' :: Maybe Text
policy = forall a. Maybe a
Prelude.Nothing,
      $sel:requestId:GetImagePolicyResponse' :: Maybe Text
requestId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetImagePolicyResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The image policy object.
getImagePolicyResponse_policy :: Lens.Lens' GetImagePolicyResponse (Prelude.Maybe Prelude.Text)
getImagePolicyResponse_policy :: Lens' GetImagePolicyResponse (Maybe Text)
getImagePolicyResponse_policy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetImagePolicyResponse' {Maybe Text
policy :: Maybe Text
$sel:policy:GetImagePolicyResponse' :: GetImagePolicyResponse -> Maybe Text
policy} -> Maybe Text
policy) (\s :: GetImagePolicyResponse
s@GetImagePolicyResponse' {} Maybe Text
a -> GetImagePolicyResponse
s {$sel:policy:GetImagePolicyResponse' :: Maybe Text
policy = Maybe Text
a} :: GetImagePolicyResponse)

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

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

instance Prelude.NFData GetImagePolicyResponse where
  rnf :: GetImagePolicyResponse -> ()
rnf GetImagePolicyResponse' {Int
Maybe Text
httpStatus :: Int
requestId :: Maybe Text
policy :: Maybe Text
$sel:httpStatus:GetImagePolicyResponse' :: GetImagePolicyResponse -> Int
$sel:requestId:GetImagePolicyResponse' :: GetImagePolicyResponse -> Maybe Text
$sel:policy:GetImagePolicyResponse' :: GetImagePolicyResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
policy
      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