{-# 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.Config.GetCustomRulePolicy
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns the policy definition containing the logic for your Config
-- Custom Policy rule.
module Amazonka.Config.GetCustomRulePolicy
  ( -- * Creating a Request
    GetCustomRulePolicy (..),
    newGetCustomRulePolicy,

    -- * Request Lenses
    getCustomRulePolicy_configRuleName,

    -- * Destructuring the Response
    GetCustomRulePolicyResponse (..),
    newGetCustomRulePolicyResponse,

    -- * Response Lenses
    getCustomRulePolicyResponse_policyText,
    getCustomRulePolicyResponse_httpStatus,
  )
where

import Amazonka.Config.Types
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 qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newGetCustomRulePolicy' smart constructor.
data GetCustomRulePolicy = GetCustomRulePolicy'
  { -- | The name of your Config Custom Policy rule.
    GetCustomRulePolicy -> Maybe Text
configRuleName :: Prelude.Maybe Prelude.Text
  }
  deriving (GetCustomRulePolicy -> GetCustomRulePolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetCustomRulePolicy -> GetCustomRulePolicy -> Bool
$c/= :: GetCustomRulePolicy -> GetCustomRulePolicy -> Bool
== :: GetCustomRulePolicy -> GetCustomRulePolicy -> Bool
$c== :: GetCustomRulePolicy -> GetCustomRulePolicy -> Bool
Prelude.Eq, ReadPrec [GetCustomRulePolicy]
ReadPrec GetCustomRulePolicy
Int -> ReadS GetCustomRulePolicy
ReadS [GetCustomRulePolicy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetCustomRulePolicy]
$creadListPrec :: ReadPrec [GetCustomRulePolicy]
readPrec :: ReadPrec GetCustomRulePolicy
$creadPrec :: ReadPrec GetCustomRulePolicy
readList :: ReadS [GetCustomRulePolicy]
$creadList :: ReadS [GetCustomRulePolicy]
readsPrec :: Int -> ReadS GetCustomRulePolicy
$creadsPrec :: Int -> ReadS GetCustomRulePolicy
Prelude.Read, Int -> GetCustomRulePolicy -> ShowS
[GetCustomRulePolicy] -> ShowS
GetCustomRulePolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetCustomRulePolicy] -> ShowS
$cshowList :: [GetCustomRulePolicy] -> ShowS
show :: GetCustomRulePolicy -> String
$cshow :: GetCustomRulePolicy -> String
showsPrec :: Int -> GetCustomRulePolicy -> ShowS
$cshowsPrec :: Int -> GetCustomRulePolicy -> ShowS
Prelude.Show, forall x. Rep GetCustomRulePolicy x -> GetCustomRulePolicy
forall x. GetCustomRulePolicy -> Rep GetCustomRulePolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetCustomRulePolicy x -> GetCustomRulePolicy
$cfrom :: forall x. GetCustomRulePolicy -> Rep GetCustomRulePolicy x
Prelude.Generic)

-- |
-- Create a value of 'GetCustomRulePolicy' 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:
--
-- 'configRuleName', 'getCustomRulePolicy_configRuleName' - The name of your Config Custom Policy rule.
newGetCustomRulePolicy ::
  GetCustomRulePolicy
newGetCustomRulePolicy :: GetCustomRulePolicy
newGetCustomRulePolicy =
  GetCustomRulePolicy'
    { $sel:configRuleName:GetCustomRulePolicy' :: Maybe Text
configRuleName =
        forall a. Maybe a
Prelude.Nothing
    }

-- | The name of your Config Custom Policy rule.
getCustomRulePolicy_configRuleName :: Lens.Lens' GetCustomRulePolicy (Prelude.Maybe Prelude.Text)
getCustomRulePolicy_configRuleName :: Lens' GetCustomRulePolicy (Maybe Text)
getCustomRulePolicy_configRuleName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCustomRulePolicy' {Maybe Text
configRuleName :: Maybe Text
$sel:configRuleName:GetCustomRulePolicy' :: GetCustomRulePolicy -> Maybe Text
configRuleName} -> Maybe Text
configRuleName) (\s :: GetCustomRulePolicy
s@GetCustomRulePolicy' {} Maybe Text
a -> GetCustomRulePolicy
s {$sel:configRuleName:GetCustomRulePolicy' :: Maybe Text
configRuleName = Maybe Text
a} :: GetCustomRulePolicy)

instance Core.AWSRequest GetCustomRulePolicy where
  type
    AWSResponse GetCustomRulePolicy =
      GetCustomRulePolicyResponse
  request :: (Service -> Service)
-> GetCustomRulePolicy -> Request GetCustomRulePolicy
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 GetCustomRulePolicy
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetCustomRulePolicy)))
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 -> Int -> GetCustomRulePolicyResponse
GetCustomRulePolicyResponse'
            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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable GetCustomRulePolicy where
  hashWithSalt :: Int -> GetCustomRulePolicy -> Int
hashWithSalt Int
_salt GetCustomRulePolicy' {Maybe Text
configRuleName :: Maybe Text
$sel:configRuleName:GetCustomRulePolicy' :: GetCustomRulePolicy -> Maybe Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
configRuleName

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

instance Data.ToHeaders GetCustomRulePolicy where
  toHeaders :: GetCustomRulePolicy -> 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
"StarlingDoveService.GetCustomRulePolicy" ::
                          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 GetCustomRulePolicy where
  toJSON :: GetCustomRulePolicy -> Value
toJSON GetCustomRulePolicy' {Maybe Text
configRuleName :: Maybe Text
$sel:configRuleName:GetCustomRulePolicy' :: GetCustomRulePolicy -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ConfigRuleName" 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 Text
configRuleName
          ]
      )

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

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

-- | /See:/ 'newGetCustomRulePolicyResponse' smart constructor.
data GetCustomRulePolicyResponse = GetCustomRulePolicyResponse'
  { -- | The policy definition containing the logic for your Config Custom Policy
    -- rule.
    GetCustomRulePolicyResponse -> Maybe Text
policyText :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetCustomRulePolicyResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetCustomRulePolicyResponse -> GetCustomRulePolicyResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetCustomRulePolicyResponse -> GetCustomRulePolicyResponse -> Bool
$c/= :: GetCustomRulePolicyResponse -> GetCustomRulePolicyResponse -> Bool
== :: GetCustomRulePolicyResponse -> GetCustomRulePolicyResponse -> Bool
$c== :: GetCustomRulePolicyResponse -> GetCustomRulePolicyResponse -> Bool
Prelude.Eq, ReadPrec [GetCustomRulePolicyResponse]
ReadPrec GetCustomRulePolicyResponse
Int -> ReadS GetCustomRulePolicyResponse
ReadS [GetCustomRulePolicyResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetCustomRulePolicyResponse]
$creadListPrec :: ReadPrec [GetCustomRulePolicyResponse]
readPrec :: ReadPrec GetCustomRulePolicyResponse
$creadPrec :: ReadPrec GetCustomRulePolicyResponse
readList :: ReadS [GetCustomRulePolicyResponse]
$creadList :: ReadS [GetCustomRulePolicyResponse]
readsPrec :: Int -> ReadS GetCustomRulePolicyResponse
$creadsPrec :: Int -> ReadS GetCustomRulePolicyResponse
Prelude.Read, Int -> GetCustomRulePolicyResponse -> ShowS
[GetCustomRulePolicyResponse] -> ShowS
GetCustomRulePolicyResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetCustomRulePolicyResponse] -> ShowS
$cshowList :: [GetCustomRulePolicyResponse] -> ShowS
show :: GetCustomRulePolicyResponse -> String
$cshow :: GetCustomRulePolicyResponse -> String
showsPrec :: Int -> GetCustomRulePolicyResponse -> ShowS
$cshowsPrec :: Int -> GetCustomRulePolicyResponse -> ShowS
Prelude.Show, forall x.
Rep GetCustomRulePolicyResponse x -> GetCustomRulePolicyResponse
forall x.
GetCustomRulePolicyResponse -> Rep GetCustomRulePolicyResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetCustomRulePolicyResponse x -> GetCustomRulePolicyResponse
$cfrom :: forall x.
GetCustomRulePolicyResponse -> Rep GetCustomRulePolicyResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetCustomRulePolicyResponse' 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', 'getCustomRulePolicyResponse_policyText' - The policy definition containing the logic for your Config Custom Policy
-- rule.
--
-- 'httpStatus', 'getCustomRulePolicyResponse_httpStatus' - The response's http status code.
newGetCustomRulePolicyResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetCustomRulePolicyResponse
newGetCustomRulePolicyResponse :: Int -> GetCustomRulePolicyResponse
newGetCustomRulePolicyResponse Int
pHttpStatus_ =
  GetCustomRulePolicyResponse'
    { $sel:policyText:GetCustomRulePolicyResponse' :: Maybe Text
policyText =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetCustomRulePolicyResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The policy definition containing the logic for your Config Custom Policy
-- rule.
getCustomRulePolicyResponse_policyText :: Lens.Lens' GetCustomRulePolicyResponse (Prelude.Maybe Prelude.Text)
getCustomRulePolicyResponse_policyText :: Lens' GetCustomRulePolicyResponse (Maybe Text)
getCustomRulePolicyResponse_policyText = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCustomRulePolicyResponse' {Maybe Text
policyText :: Maybe Text
$sel:policyText:GetCustomRulePolicyResponse' :: GetCustomRulePolicyResponse -> Maybe Text
policyText} -> Maybe Text
policyText) (\s :: GetCustomRulePolicyResponse
s@GetCustomRulePolicyResponse' {} Maybe Text
a -> GetCustomRulePolicyResponse
s {$sel:policyText:GetCustomRulePolicyResponse' :: Maybe Text
policyText = Maybe Text
a} :: GetCustomRulePolicyResponse)

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

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