{-# 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.RAM.GetPermission
-- 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 the contents of an RAM permission in JSON format.
module Amazonka.RAM.GetPermission
  ( -- * Creating a Request
    GetPermission (..),
    newGetPermission,

    -- * Request Lenses
    getPermission_permissionVersion,
    getPermission_permissionArn,

    -- * Destructuring the Response
    GetPermissionResponse (..),
    newGetPermissionResponse,

    -- * Response Lenses
    getPermissionResponse_permission,
    getPermissionResponse_httpStatus,
  )
where

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

-- | /See:/ 'newGetPermission' smart constructor.
data GetPermission = GetPermission'
  { -- | Specifies identifier for the version of the RAM permission to retrieve.
    -- If you don\'t specify this parameter, the operation retrieves the
    -- default version.
    GetPermission -> Maybe Int
permissionVersion :: Prelude.Maybe Prelude.Int,
    -- | Specifies the
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resoure Name (ARN)>
    -- of the permission whose contents you want to retrieve. To find the ARN
    -- for a permission, use either the ListPermissions operation or go to the
    -- <https://console.aws.amazon.com/ram/home#Permissions: Permissions library>
    -- page in the RAM console and then choose the name of the permission. The
    -- ARN is displayed on the detail page.
    GetPermission -> Text
permissionArn :: Prelude.Text
  }
  deriving (GetPermission -> GetPermission -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetPermission -> GetPermission -> Bool
$c/= :: GetPermission -> GetPermission -> Bool
== :: GetPermission -> GetPermission -> Bool
$c== :: GetPermission -> GetPermission -> Bool
Prelude.Eq, ReadPrec [GetPermission]
ReadPrec GetPermission
Int -> ReadS GetPermission
ReadS [GetPermission]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetPermission]
$creadListPrec :: ReadPrec [GetPermission]
readPrec :: ReadPrec GetPermission
$creadPrec :: ReadPrec GetPermission
readList :: ReadS [GetPermission]
$creadList :: ReadS [GetPermission]
readsPrec :: Int -> ReadS GetPermission
$creadsPrec :: Int -> ReadS GetPermission
Prelude.Read, Int -> GetPermission -> ShowS
[GetPermission] -> ShowS
GetPermission -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetPermission] -> ShowS
$cshowList :: [GetPermission] -> ShowS
show :: GetPermission -> String
$cshow :: GetPermission -> String
showsPrec :: Int -> GetPermission -> ShowS
$cshowsPrec :: Int -> GetPermission -> ShowS
Prelude.Show, forall x. Rep GetPermission x -> GetPermission
forall x. GetPermission -> Rep GetPermission x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetPermission x -> GetPermission
$cfrom :: forall x. GetPermission -> Rep GetPermission x
Prelude.Generic)

-- |
-- Create a value of 'GetPermission' 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:
--
-- 'permissionVersion', 'getPermission_permissionVersion' - Specifies identifier for the version of the RAM permission to retrieve.
-- If you don\'t specify this parameter, the operation retrieves the
-- default version.
--
-- 'permissionArn', 'getPermission_permissionArn' - Specifies the
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resoure Name (ARN)>
-- of the permission whose contents you want to retrieve. To find the ARN
-- for a permission, use either the ListPermissions operation or go to the
-- <https://console.aws.amazon.com/ram/home#Permissions: Permissions library>
-- page in the RAM console and then choose the name of the permission. The
-- ARN is displayed on the detail page.
newGetPermission ::
  -- | 'permissionArn'
  Prelude.Text ->
  GetPermission
newGetPermission :: Text -> GetPermission
newGetPermission Text
pPermissionArn_ =
  GetPermission'
    { $sel:permissionVersion:GetPermission' :: Maybe Int
permissionVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:permissionArn:GetPermission' :: Text
permissionArn = Text
pPermissionArn_
    }

-- | Specifies identifier for the version of the RAM permission to retrieve.
-- If you don\'t specify this parameter, the operation retrieves the
-- default version.
getPermission_permissionVersion :: Lens.Lens' GetPermission (Prelude.Maybe Prelude.Int)
getPermission_permissionVersion :: Lens' GetPermission (Maybe Int)
getPermission_permissionVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetPermission' {Maybe Int
permissionVersion :: Maybe Int
$sel:permissionVersion:GetPermission' :: GetPermission -> Maybe Int
permissionVersion} -> Maybe Int
permissionVersion) (\s :: GetPermission
s@GetPermission' {} Maybe Int
a -> GetPermission
s {$sel:permissionVersion:GetPermission' :: Maybe Int
permissionVersion = Maybe Int
a} :: GetPermission)

-- | Specifies the
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resoure Name (ARN)>
-- of the permission whose contents you want to retrieve. To find the ARN
-- for a permission, use either the ListPermissions operation or go to the
-- <https://console.aws.amazon.com/ram/home#Permissions: Permissions library>
-- page in the RAM console and then choose the name of the permission. The
-- ARN is displayed on the detail page.
getPermission_permissionArn :: Lens.Lens' GetPermission Prelude.Text
getPermission_permissionArn :: Lens' GetPermission Text
getPermission_permissionArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetPermission' {Text
permissionArn :: Text
$sel:permissionArn:GetPermission' :: GetPermission -> Text
permissionArn} -> Text
permissionArn) (\s :: GetPermission
s@GetPermission' {} Text
a -> GetPermission
s {$sel:permissionArn:GetPermission' :: Text
permissionArn = Text
a} :: GetPermission)

instance Core.AWSRequest GetPermission where
  type
    AWSResponse GetPermission =
      GetPermissionResponse
  request :: (Service -> Service) -> GetPermission -> Request GetPermission
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 GetPermission
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetPermission)))
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 ResourceSharePermissionDetail -> Int -> GetPermissionResponse
GetPermissionResponse'
            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
"permission")
            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 GetPermission where
  hashWithSalt :: Int -> GetPermission -> Int
hashWithSalt Int
_salt GetPermission' {Maybe Int
Text
permissionArn :: Text
permissionVersion :: Maybe Int
$sel:permissionArn:GetPermission' :: GetPermission -> Text
$sel:permissionVersion:GetPermission' :: GetPermission -> Maybe Int
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
permissionVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
permissionArn

instance Prelude.NFData GetPermission where
  rnf :: GetPermission -> ()
rnf GetPermission' {Maybe Int
Text
permissionArn :: Text
permissionVersion :: Maybe Int
$sel:permissionArn:GetPermission' :: GetPermission -> Text
$sel:permissionVersion:GetPermission' :: GetPermission -> Maybe Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
permissionVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
permissionArn

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

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

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

-- | /See:/ 'newGetPermissionResponse' smart constructor.
data GetPermissionResponse = GetPermissionResponse'
  { -- | An object that contains information about the permission.
    GetPermissionResponse -> Maybe ResourceSharePermissionDetail
permission :: Prelude.Maybe ResourceSharePermissionDetail,
    -- | The response's http status code.
    GetPermissionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetPermissionResponse -> GetPermissionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetPermissionResponse -> GetPermissionResponse -> Bool
$c/= :: GetPermissionResponse -> GetPermissionResponse -> Bool
== :: GetPermissionResponse -> GetPermissionResponse -> Bool
$c== :: GetPermissionResponse -> GetPermissionResponse -> Bool
Prelude.Eq, ReadPrec [GetPermissionResponse]
ReadPrec GetPermissionResponse
Int -> ReadS GetPermissionResponse
ReadS [GetPermissionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetPermissionResponse]
$creadListPrec :: ReadPrec [GetPermissionResponse]
readPrec :: ReadPrec GetPermissionResponse
$creadPrec :: ReadPrec GetPermissionResponse
readList :: ReadS [GetPermissionResponse]
$creadList :: ReadS [GetPermissionResponse]
readsPrec :: Int -> ReadS GetPermissionResponse
$creadsPrec :: Int -> ReadS GetPermissionResponse
Prelude.Read, Int -> GetPermissionResponse -> ShowS
[GetPermissionResponse] -> ShowS
GetPermissionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetPermissionResponse] -> ShowS
$cshowList :: [GetPermissionResponse] -> ShowS
show :: GetPermissionResponse -> String
$cshow :: GetPermissionResponse -> String
showsPrec :: Int -> GetPermissionResponse -> ShowS
$cshowsPrec :: Int -> GetPermissionResponse -> ShowS
Prelude.Show, forall x. Rep GetPermissionResponse x -> GetPermissionResponse
forall x. GetPermissionResponse -> Rep GetPermissionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetPermissionResponse x -> GetPermissionResponse
$cfrom :: forall x. GetPermissionResponse -> Rep GetPermissionResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetPermissionResponse' 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:
--
-- 'permission', 'getPermissionResponse_permission' - An object that contains information about the permission.
--
-- 'httpStatus', 'getPermissionResponse_httpStatus' - The response's http status code.
newGetPermissionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetPermissionResponse
newGetPermissionResponse :: Int -> GetPermissionResponse
newGetPermissionResponse Int
pHttpStatus_ =
  GetPermissionResponse'
    { $sel:permission:GetPermissionResponse' :: Maybe ResourceSharePermissionDetail
permission =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetPermissionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An object that contains information about the permission.
getPermissionResponse_permission :: Lens.Lens' GetPermissionResponse (Prelude.Maybe ResourceSharePermissionDetail)
getPermissionResponse_permission :: Lens' GetPermissionResponse (Maybe ResourceSharePermissionDetail)
getPermissionResponse_permission = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetPermissionResponse' {Maybe ResourceSharePermissionDetail
permission :: Maybe ResourceSharePermissionDetail
$sel:permission:GetPermissionResponse' :: GetPermissionResponse -> Maybe ResourceSharePermissionDetail
permission} -> Maybe ResourceSharePermissionDetail
permission) (\s :: GetPermissionResponse
s@GetPermissionResponse' {} Maybe ResourceSharePermissionDetail
a -> GetPermissionResponse
s {$sel:permission:GetPermissionResponse' :: Maybe ResourceSharePermissionDetail
permission = Maybe ResourceSharePermissionDetail
a} :: GetPermissionResponse)

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

instance Prelude.NFData GetPermissionResponse where
  rnf :: GetPermissionResponse -> ()
rnf GetPermissionResponse' {Int
Maybe ResourceSharePermissionDetail
httpStatus :: Int
permission :: Maybe ResourceSharePermissionDetail
$sel:httpStatus:GetPermissionResponse' :: GetPermissionResponse -> Int
$sel:permission:GetPermissionResponse' :: GetPermissionResponse -> Maybe ResourceSharePermissionDetail
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ResourceSharePermissionDetail
permission
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus