{-# 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.GetOrganizationCustomRulePolicy
-- 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 organization
-- Config Custom Policy rule.
module Amazonka.Config.GetOrganizationCustomRulePolicy
  ( -- * Creating a Request
    GetOrganizationCustomRulePolicy (..),
    newGetOrganizationCustomRulePolicy,

    -- * Request Lenses
    getOrganizationCustomRulePolicy_organizationConfigRuleName,

    -- * Destructuring the Response
    GetOrganizationCustomRulePolicyResponse (..),
    newGetOrganizationCustomRulePolicyResponse,

    -- * Response Lenses
    getOrganizationCustomRulePolicyResponse_policyText,
    getOrganizationCustomRulePolicyResponse_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:/ 'newGetOrganizationCustomRulePolicy' smart constructor.
data GetOrganizationCustomRulePolicy = GetOrganizationCustomRulePolicy'
  { -- | The name of your organization Config Custom Policy rule.
    GetOrganizationCustomRulePolicy -> Text
organizationConfigRuleName :: Prelude.Text
  }
  deriving (GetOrganizationCustomRulePolicy
-> GetOrganizationCustomRulePolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetOrganizationCustomRulePolicy
-> GetOrganizationCustomRulePolicy -> Bool
$c/= :: GetOrganizationCustomRulePolicy
-> GetOrganizationCustomRulePolicy -> Bool
== :: GetOrganizationCustomRulePolicy
-> GetOrganizationCustomRulePolicy -> Bool
$c== :: GetOrganizationCustomRulePolicy
-> GetOrganizationCustomRulePolicy -> Bool
Prelude.Eq, ReadPrec [GetOrganizationCustomRulePolicy]
ReadPrec GetOrganizationCustomRulePolicy
Int -> ReadS GetOrganizationCustomRulePolicy
ReadS [GetOrganizationCustomRulePolicy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetOrganizationCustomRulePolicy]
$creadListPrec :: ReadPrec [GetOrganizationCustomRulePolicy]
readPrec :: ReadPrec GetOrganizationCustomRulePolicy
$creadPrec :: ReadPrec GetOrganizationCustomRulePolicy
readList :: ReadS [GetOrganizationCustomRulePolicy]
$creadList :: ReadS [GetOrganizationCustomRulePolicy]
readsPrec :: Int -> ReadS GetOrganizationCustomRulePolicy
$creadsPrec :: Int -> ReadS GetOrganizationCustomRulePolicy
Prelude.Read, Int -> GetOrganizationCustomRulePolicy -> ShowS
[GetOrganizationCustomRulePolicy] -> ShowS
GetOrganizationCustomRulePolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetOrganizationCustomRulePolicy] -> ShowS
$cshowList :: [GetOrganizationCustomRulePolicy] -> ShowS
show :: GetOrganizationCustomRulePolicy -> String
$cshow :: GetOrganizationCustomRulePolicy -> String
showsPrec :: Int -> GetOrganizationCustomRulePolicy -> ShowS
$cshowsPrec :: Int -> GetOrganizationCustomRulePolicy -> ShowS
Prelude.Show, forall x.
Rep GetOrganizationCustomRulePolicy x
-> GetOrganizationCustomRulePolicy
forall x.
GetOrganizationCustomRulePolicy
-> Rep GetOrganizationCustomRulePolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetOrganizationCustomRulePolicy x
-> GetOrganizationCustomRulePolicy
$cfrom :: forall x.
GetOrganizationCustomRulePolicy
-> Rep GetOrganizationCustomRulePolicy x
Prelude.Generic)

-- |
-- Create a value of 'GetOrganizationCustomRulePolicy' 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:
--
-- 'organizationConfigRuleName', 'getOrganizationCustomRulePolicy_organizationConfigRuleName' - The name of your organization Config Custom Policy rule.
newGetOrganizationCustomRulePolicy ::
  -- | 'organizationConfigRuleName'
  Prelude.Text ->
  GetOrganizationCustomRulePolicy
newGetOrganizationCustomRulePolicy :: Text -> GetOrganizationCustomRulePolicy
newGetOrganizationCustomRulePolicy
  Text
pOrganizationConfigRuleName_ =
    GetOrganizationCustomRulePolicy'
      { $sel:organizationConfigRuleName:GetOrganizationCustomRulePolicy' :: Text
organizationConfigRuleName =
          Text
pOrganizationConfigRuleName_
      }

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

instance
  Core.AWSRequest
    GetOrganizationCustomRulePolicy
  where
  type
    AWSResponse GetOrganizationCustomRulePolicy =
      GetOrganizationCustomRulePolicyResponse
  request :: (Service -> Service)
-> GetOrganizationCustomRulePolicy
-> Request GetOrganizationCustomRulePolicy
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 GetOrganizationCustomRulePolicy
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse GetOrganizationCustomRulePolicy)))
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 -> GetOrganizationCustomRulePolicyResponse
GetOrganizationCustomRulePolicyResponse'
            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
    GetOrganizationCustomRulePolicy
  where
  hashWithSalt :: Int -> GetOrganizationCustomRulePolicy -> Int
hashWithSalt
    Int
_salt
    GetOrganizationCustomRulePolicy' {Text
organizationConfigRuleName :: Text
$sel:organizationConfigRuleName:GetOrganizationCustomRulePolicy' :: GetOrganizationCustomRulePolicy -> Text
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
organizationConfigRuleName

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

instance
  Data.ToHeaders
    GetOrganizationCustomRulePolicy
  where
  toHeaders :: GetOrganizationCustomRulePolicy -> 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.GetOrganizationCustomRulePolicy" ::
                          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 GetOrganizationCustomRulePolicy where
  toJSON :: GetOrganizationCustomRulePolicy -> Value
toJSON GetOrganizationCustomRulePolicy' {Text
organizationConfigRuleName :: Text
$sel:organizationConfigRuleName:GetOrganizationCustomRulePolicy' :: GetOrganizationCustomRulePolicy -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              ( Key
"OrganizationConfigRuleName"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
organizationConfigRuleName
              )
          ]
      )

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

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

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

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

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

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

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