{-# 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.IoT.GetPolicy
-- 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 information about the specified policy with the policy document of
-- the default version.
--
-- Requires permission to access the
-- <https://docs.aws.amazon.com/service-authorization/latest/reference/list_awsiot.html#awsiot-actions-as-permissions GetPolicy>
-- action.
module Amazonka.IoT.GetPolicy
  ( -- * Creating a Request
    GetPolicy (..),
    newGetPolicy,

    -- * Request Lenses
    getPolicy_policyName,

    -- * Destructuring the Response
    GetPolicyResponse (..),
    newGetPolicyResponse,

    -- * Response Lenses
    getPolicyResponse_creationDate,
    getPolicyResponse_defaultVersionId,
    getPolicyResponse_generationId,
    getPolicyResponse_lastModifiedDate,
    getPolicyResponse_policyArn,
    getPolicyResponse_policyDocument,
    getPolicyResponse_policyName,
    getPolicyResponse_httpStatus,
  )
where

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

-- | The input for the GetPolicy operation.
--
-- /See:/ 'newGetPolicy' smart constructor.
data GetPolicy = GetPolicy'
  { -- | The name of the policy.
    GetPolicy -> Text
policyName :: Prelude.Text
  }
  deriving (GetPolicy -> GetPolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetPolicy -> GetPolicy -> Bool
$c/= :: GetPolicy -> GetPolicy -> Bool
== :: GetPolicy -> GetPolicy -> Bool
$c== :: GetPolicy -> GetPolicy -> Bool
Prelude.Eq, ReadPrec [GetPolicy]
ReadPrec GetPolicy
Int -> ReadS GetPolicy
ReadS [GetPolicy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetPolicy]
$creadListPrec :: ReadPrec [GetPolicy]
readPrec :: ReadPrec GetPolicy
$creadPrec :: ReadPrec GetPolicy
readList :: ReadS [GetPolicy]
$creadList :: ReadS [GetPolicy]
readsPrec :: Int -> ReadS GetPolicy
$creadsPrec :: Int -> ReadS GetPolicy
Prelude.Read, Int -> GetPolicy -> ShowS
[GetPolicy] -> ShowS
GetPolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetPolicy] -> ShowS
$cshowList :: [GetPolicy] -> ShowS
show :: GetPolicy -> String
$cshow :: GetPolicy -> String
showsPrec :: Int -> GetPolicy -> ShowS
$cshowsPrec :: Int -> GetPolicy -> ShowS
Prelude.Show, forall x. Rep GetPolicy x -> GetPolicy
forall x. GetPolicy -> Rep GetPolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetPolicy x -> GetPolicy
$cfrom :: forall x. GetPolicy -> Rep GetPolicy x
Prelude.Generic)

-- |
-- Create a value of 'GetPolicy' 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:
--
-- 'policyName', 'getPolicy_policyName' - The name of the policy.
newGetPolicy ::
  -- | 'policyName'
  Prelude.Text ->
  GetPolicy
newGetPolicy :: Text -> GetPolicy
newGetPolicy Text
pPolicyName_ =
  GetPolicy' {$sel:policyName:GetPolicy' :: Text
policyName = Text
pPolicyName_}

-- | The name of the policy.
getPolicy_policyName :: Lens.Lens' GetPolicy Prelude.Text
getPolicy_policyName :: Lens' GetPolicy Text
getPolicy_policyName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetPolicy' {Text
policyName :: Text
$sel:policyName:GetPolicy' :: GetPolicy -> Text
policyName} -> Text
policyName) (\s :: GetPolicy
s@GetPolicy' {} Text
a -> GetPolicy
s {$sel:policyName:GetPolicy' :: Text
policyName = Text
a} :: GetPolicy)

instance Core.AWSRequest GetPolicy where
  type AWSResponse GetPolicy = GetPolicyResponse
  request :: (Service -> Service) -> GetPolicy -> Request GetPolicy
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 GetPolicy
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetPolicy)))
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 POSIX
-> Maybe Text
-> Maybe Text
-> Maybe POSIX
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Int
-> GetPolicyResponse
GetPolicyResponse'
            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
"creationDate")
            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
"defaultVersionId")
            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
"generationId")
            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
"lastModifiedDate")
            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
"policyArn")
            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
"policyDocument")
            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
"policyName")
            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 GetPolicy where
  hashWithSalt :: Int -> GetPolicy -> Int
hashWithSalt Int
_salt GetPolicy' {Text
policyName :: Text
$sel:policyName:GetPolicy' :: GetPolicy -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
policyName

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

instance Data.ToHeaders GetPolicy where
  toHeaders :: GetPolicy -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToPath GetPolicy where
  toPath :: GetPolicy -> ByteString
toPath GetPolicy' {Text
policyName :: Text
$sel:policyName:GetPolicy' :: GetPolicy -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/policies/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
policyName]

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

-- | The output from the GetPolicy operation.
--
-- /See:/ 'newGetPolicyResponse' smart constructor.
data GetPolicyResponse = GetPolicyResponse'
  { -- | The date the policy was created.
    GetPolicyResponse -> Maybe POSIX
creationDate :: Prelude.Maybe Data.POSIX,
    -- | The default policy version ID.
    GetPolicyResponse -> Maybe Text
defaultVersionId :: Prelude.Maybe Prelude.Text,
    -- | The generation ID of the policy.
    GetPolicyResponse -> Maybe Text
generationId :: Prelude.Maybe Prelude.Text,
    -- | The date the policy was last modified.
    GetPolicyResponse -> Maybe POSIX
lastModifiedDate :: Prelude.Maybe Data.POSIX,
    -- | The policy ARN.
    GetPolicyResponse -> Maybe Text
policyArn :: Prelude.Maybe Prelude.Text,
    -- | The JSON document that describes the policy.
    GetPolicyResponse -> Maybe Text
policyDocument :: Prelude.Maybe Prelude.Text,
    -- | The policy name.
    GetPolicyResponse -> Maybe Text
policyName :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetPolicyResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetPolicyResponse -> GetPolicyResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetPolicyResponse -> GetPolicyResponse -> Bool
$c/= :: GetPolicyResponse -> GetPolicyResponse -> Bool
== :: GetPolicyResponse -> GetPolicyResponse -> Bool
$c== :: GetPolicyResponse -> GetPolicyResponse -> Bool
Prelude.Eq, ReadPrec [GetPolicyResponse]
ReadPrec GetPolicyResponse
Int -> ReadS GetPolicyResponse
ReadS [GetPolicyResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetPolicyResponse]
$creadListPrec :: ReadPrec [GetPolicyResponse]
readPrec :: ReadPrec GetPolicyResponse
$creadPrec :: ReadPrec GetPolicyResponse
readList :: ReadS [GetPolicyResponse]
$creadList :: ReadS [GetPolicyResponse]
readsPrec :: Int -> ReadS GetPolicyResponse
$creadsPrec :: Int -> ReadS GetPolicyResponse
Prelude.Read, Int -> GetPolicyResponse -> ShowS
[GetPolicyResponse] -> ShowS
GetPolicyResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetPolicyResponse] -> ShowS
$cshowList :: [GetPolicyResponse] -> ShowS
show :: GetPolicyResponse -> String
$cshow :: GetPolicyResponse -> String
showsPrec :: Int -> GetPolicyResponse -> ShowS
$cshowsPrec :: Int -> GetPolicyResponse -> ShowS
Prelude.Show, forall x. Rep GetPolicyResponse x -> GetPolicyResponse
forall x. GetPolicyResponse -> Rep GetPolicyResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetPolicyResponse x -> GetPolicyResponse
$cfrom :: forall x. GetPolicyResponse -> Rep GetPolicyResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetPolicyResponse' 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:
--
-- 'creationDate', 'getPolicyResponse_creationDate' - The date the policy was created.
--
-- 'defaultVersionId', 'getPolicyResponse_defaultVersionId' - The default policy version ID.
--
-- 'generationId', 'getPolicyResponse_generationId' - The generation ID of the policy.
--
-- 'lastModifiedDate', 'getPolicyResponse_lastModifiedDate' - The date the policy was last modified.
--
-- 'policyArn', 'getPolicyResponse_policyArn' - The policy ARN.
--
-- 'policyDocument', 'getPolicyResponse_policyDocument' - The JSON document that describes the policy.
--
-- 'policyName', 'getPolicyResponse_policyName' - The policy name.
--
-- 'httpStatus', 'getPolicyResponse_httpStatus' - The response's http status code.
newGetPolicyResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetPolicyResponse
newGetPolicyResponse :: Int -> GetPolicyResponse
newGetPolicyResponse Int
pHttpStatus_ =
  GetPolicyResponse'
    { $sel:creationDate:GetPolicyResponse' :: Maybe POSIX
creationDate = forall a. Maybe a
Prelude.Nothing,
      $sel:defaultVersionId:GetPolicyResponse' :: Maybe Text
defaultVersionId = forall a. Maybe a
Prelude.Nothing,
      $sel:generationId:GetPolicyResponse' :: Maybe Text
generationId = forall a. Maybe a
Prelude.Nothing,
      $sel:lastModifiedDate:GetPolicyResponse' :: Maybe POSIX
lastModifiedDate = forall a. Maybe a
Prelude.Nothing,
      $sel:policyArn:GetPolicyResponse' :: Maybe Text
policyArn = forall a. Maybe a
Prelude.Nothing,
      $sel:policyDocument:GetPolicyResponse' :: Maybe Text
policyDocument = forall a. Maybe a
Prelude.Nothing,
      $sel:policyName:GetPolicyResponse' :: Maybe Text
policyName = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetPolicyResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The date the policy was created.
getPolicyResponse_creationDate :: Lens.Lens' GetPolicyResponse (Prelude.Maybe Prelude.UTCTime)
getPolicyResponse_creationDate :: Lens' GetPolicyResponse (Maybe UTCTime)
getPolicyResponse_creationDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetPolicyResponse' {Maybe POSIX
creationDate :: Maybe POSIX
$sel:creationDate:GetPolicyResponse' :: GetPolicyResponse -> Maybe POSIX
creationDate} -> Maybe POSIX
creationDate) (\s :: GetPolicyResponse
s@GetPolicyResponse' {} Maybe POSIX
a -> GetPolicyResponse
s {$sel:creationDate:GetPolicyResponse' :: Maybe POSIX
creationDate = Maybe POSIX
a} :: GetPolicyResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The default policy version ID.
getPolicyResponse_defaultVersionId :: Lens.Lens' GetPolicyResponse (Prelude.Maybe Prelude.Text)
getPolicyResponse_defaultVersionId :: Lens' GetPolicyResponse (Maybe Text)
getPolicyResponse_defaultVersionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetPolicyResponse' {Maybe Text
defaultVersionId :: Maybe Text
$sel:defaultVersionId:GetPolicyResponse' :: GetPolicyResponse -> Maybe Text
defaultVersionId} -> Maybe Text
defaultVersionId) (\s :: GetPolicyResponse
s@GetPolicyResponse' {} Maybe Text
a -> GetPolicyResponse
s {$sel:defaultVersionId:GetPolicyResponse' :: Maybe Text
defaultVersionId = Maybe Text
a} :: GetPolicyResponse)

-- | The generation ID of the policy.
getPolicyResponse_generationId :: Lens.Lens' GetPolicyResponse (Prelude.Maybe Prelude.Text)
getPolicyResponse_generationId :: Lens' GetPolicyResponse (Maybe Text)
getPolicyResponse_generationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetPolicyResponse' {Maybe Text
generationId :: Maybe Text
$sel:generationId:GetPolicyResponse' :: GetPolicyResponse -> Maybe Text
generationId} -> Maybe Text
generationId) (\s :: GetPolicyResponse
s@GetPolicyResponse' {} Maybe Text
a -> GetPolicyResponse
s {$sel:generationId:GetPolicyResponse' :: Maybe Text
generationId = Maybe Text
a} :: GetPolicyResponse)

-- | The date the policy was last modified.
getPolicyResponse_lastModifiedDate :: Lens.Lens' GetPolicyResponse (Prelude.Maybe Prelude.UTCTime)
getPolicyResponse_lastModifiedDate :: Lens' GetPolicyResponse (Maybe UTCTime)
getPolicyResponse_lastModifiedDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetPolicyResponse' {Maybe POSIX
lastModifiedDate :: Maybe POSIX
$sel:lastModifiedDate:GetPolicyResponse' :: GetPolicyResponse -> Maybe POSIX
lastModifiedDate} -> Maybe POSIX
lastModifiedDate) (\s :: GetPolicyResponse
s@GetPolicyResponse' {} Maybe POSIX
a -> GetPolicyResponse
s {$sel:lastModifiedDate:GetPolicyResponse' :: Maybe POSIX
lastModifiedDate = Maybe POSIX
a} :: GetPolicyResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The policy ARN.
getPolicyResponse_policyArn :: Lens.Lens' GetPolicyResponse (Prelude.Maybe Prelude.Text)
getPolicyResponse_policyArn :: Lens' GetPolicyResponse (Maybe Text)
getPolicyResponse_policyArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetPolicyResponse' {Maybe Text
policyArn :: Maybe Text
$sel:policyArn:GetPolicyResponse' :: GetPolicyResponse -> Maybe Text
policyArn} -> Maybe Text
policyArn) (\s :: GetPolicyResponse
s@GetPolicyResponse' {} Maybe Text
a -> GetPolicyResponse
s {$sel:policyArn:GetPolicyResponse' :: Maybe Text
policyArn = Maybe Text
a} :: GetPolicyResponse)

-- | The JSON document that describes the policy.
getPolicyResponse_policyDocument :: Lens.Lens' GetPolicyResponse (Prelude.Maybe Prelude.Text)
getPolicyResponse_policyDocument :: Lens' GetPolicyResponse (Maybe Text)
getPolicyResponse_policyDocument = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetPolicyResponse' {Maybe Text
policyDocument :: Maybe Text
$sel:policyDocument:GetPolicyResponse' :: GetPolicyResponse -> Maybe Text
policyDocument} -> Maybe Text
policyDocument) (\s :: GetPolicyResponse
s@GetPolicyResponse' {} Maybe Text
a -> GetPolicyResponse
s {$sel:policyDocument:GetPolicyResponse' :: Maybe Text
policyDocument = Maybe Text
a} :: GetPolicyResponse)

-- | The policy name.
getPolicyResponse_policyName :: Lens.Lens' GetPolicyResponse (Prelude.Maybe Prelude.Text)
getPolicyResponse_policyName :: Lens' GetPolicyResponse (Maybe Text)
getPolicyResponse_policyName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetPolicyResponse' {Maybe Text
policyName :: Maybe Text
$sel:policyName:GetPolicyResponse' :: GetPolicyResponse -> Maybe Text
policyName} -> Maybe Text
policyName) (\s :: GetPolicyResponse
s@GetPolicyResponse' {} Maybe Text
a -> GetPolicyResponse
s {$sel:policyName:GetPolicyResponse' :: Maybe Text
policyName = Maybe Text
a} :: GetPolicyResponse)

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

instance Prelude.NFData GetPolicyResponse where
  rnf :: GetPolicyResponse -> ()
rnf GetPolicyResponse' {Int
Maybe Text
Maybe POSIX
httpStatus :: Int
policyName :: Maybe Text
policyDocument :: Maybe Text
policyArn :: Maybe Text
lastModifiedDate :: Maybe POSIX
generationId :: Maybe Text
defaultVersionId :: Maybe Text
creationDate :: Maybe POSIX
$sel:httpStatus:GetPolicyResponse' :: GetPolicyResponse -> Int
$sel:policyName:GetPolicyResponse' :: GetPolicyResponse -> Maybe Text
$sel:policyDocument:GetPolicyResponse' :: GetPolicyResponse -> Maybe Text
$sel:policyArn:GetPolicyResponse' :: GetPolicyResponse -> Maybe Text
$sel:lastModifiedDate:GetPolicyResponse' :: GetPolicyResponse -> Maybe POSIX
$sel:generationId:GetPolicyResponse' :: GetPolicyResponse -> Maybe Text
$sel:defaultVersionId:GetPolicyResponse' :: GetPolicyResponse -> Maybe Text
$sel:creationDate:GetPolicyResponse' :: GetPolicyResponse -> Maybe POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
creationDate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
defaultVersionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
generationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastModifiedDate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
policyArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
policyDocument
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
policyName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus