{-# 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.ControlTower.EnableControl
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- This API call activates a control. It starts an asynchronous operation
-- that creates AWS resources on the specified organizational unit and the
-- accounts it contains. The resources created will vary according to the
-- control that you specify.
module Amazonka.ControlTower.EnableControl
  ( -- * Creating a Request
    EnableControl (..),
    newEnableControl,

    -- * Request Lenses
    enableControl_controlIdentifier,
    enableControl_targetIdentifier,

    -- * Destructuring the Response
    EnableControlResponse (..),
    newEnableControlResponse,

    -- * Response Lenses
    enableControlResponse_httpStatus,
    enableControlResponse_operationIdentifier,
  )
where

import Amazonka.ControlTower.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:/ 'newEnableControl' smart constructor.
data EnableControl = EnableControl'
  { -- | The ARN of the control. Only __Strongly recommended__ and __Elective__
    -- controls are permitted, with the exception of the __Region deny__
    -- guardrail.
    EnableControl -> Text
controlIdentifier :: Prelude.Text,
    -- | The ARN of the organizational unit.
    EnableControl -> Text
targetIdentifier :: Prelude.Text
  }
  deriving (EnableControl -> EnableControl -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnableControl -> EnableControl -> Bool
$c/= :: EnableControl -> EnableControl -> Bool
== :: EnableControl -> EnableControl -> Bool
$c== :: EnableControl -> EnableControl -> Bool
Prelude.Eq, ReadPrec [EnableControl]
ReadPrec EnableControl
Int -> ReadS EnableControl
ReadS [EnableControl]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EnableControl]
$creadListPrec :: ReadPrec [EnableControl]
readPrec :: ReadPrec EnableControl
$creadPrec :: ReadPrec EnableControl
readList :: ReadS [EnableControl]
$creadList :: ReadS [EnableControl]
readsPrec :: Int -> ReadS EnableControl
$creadsPrec :: Int -> ReadS EnableControl
Prelude.Read, Int -> EnableControl -> ShowS
[EnableControl] -> ShowS
EnableControl -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EnableControl] -> ShowS
$cshowList :: [EnableControl] -> ShowS
show :: EnableControl -> String
$cshow :: EnableControl -> String
showsPrec :: Int -> EnableControl -> ShowS
$cshowsPrec :: Int -> EnableControl -> ShowS
Prelude.Show, forall x. Rep EnableControl x -> EnableControl
forall x. EnableControl -> Rep EnableControl x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EnableControl x -> EnableControl
$cfrom :: forall x. EnableControl -> Rep EnableControl x
Prelude.Generic)

-- |
-- Create a value of 'EnableControl' 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:
--
-- 'controlIdentifier', 'enableControl_controlIdentifier' - The ARN of the control. Only __Strongly recommended__ and __Elective__
-- controls are permitted, with the exception of the __Region deny__
-- guardrail.
--
-- 'targetIdentifier', 'enableControl_targetIdentifier' - The ARN of the organizational unit.
newEnableControl ::
  -- | 'controlIdentifier'
  Prelude.Text ->
  -- | 'targetIdentifier'
  Prelude.Text ->
  EnableControl
newEnableControl :: Text -> Text -> EnableControl
newEnableControl
  Text
pControlIdentifier_
  Text
pTargetIdentifier_ =
    EnableControl'
      { $sel:controlIdentifier:EnableControl' :: Text
controlIdentifier =
          Text
pControlIdentifier_,
        $sel:targetIdentifier:EnableControl' :: Text
targetIdentifier = Text
pTargetIdentifier_
      }

-- | The ARN of the control. Only __Strongly recommended__ and __Elective__
-- controls are permitted, with the exception of the __Region deny__
-- guardrail.
enableControl_controlIdentifier :: Lens.Lens' EnableControl Prelude.Text
enableControl_controlIdentifier :: Lens' EnableControl Text
enableControl_controlIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnableControl' {Text
controlIdentifier :: Text
$sel:controlIdentifier:EnableControl' :: EnableControl -> Text
controlIdentifier} -> Text
controlIdentifier) (\s :: EnableControl
s@EnableControl' {} Text
a -> EnableControl
s {$sel:controlIdentifier:EnableControl' :: Text
controlIdentifier = Text
a} :: EnableControl)

-- | The ARN of the organizational unit.
enableControl_targetIdentifier :: Lens.Lens' EnableControl Prelude.Text
enableControl_targetIdentifier :: Lens' EnableControl Text
enableControl_targetIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnableControl' {Text
targetIdentifier :: Text
$sel:targetIdentifier:EnableControl' :: EnableControl -> Text
targetIdentifier} -> Text
targetIdentifier) (\s :: EnableControl
s@EnableControl' {} Text
a -> EnableControl
s {$sel:targetIdentifier:EnableControl' :: Text
targetIdentifier = Text
a} :: EnableControl)

instance Core.AWSRequest EnableControl where
  type
    AWSResponse EnableControl =
      EnableControlResponse
  request :: (Service -> Service) -> EnableControl -> Request EnableControl
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 EnableControl
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse EnableControl)))
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 ->
          Int -> Text -> EnableControlResponse
EnableControlResponse'
            forall (f :: * -> *) a b. Functor 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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"operationIdentifier")
      )

instance Prelude.Hashable EnableControl where
  hashWithSalt :: Int -> EnableControl -> Int
hashWithSalt Int
_salt EnableControl' {Text
targetIdentifier :: Text
controlIdentifier :: Text
$sel:targetIdentifier:EnableControl' :: EnableControl -> Text
$sel:controlIdentifier:EnableControl' :: EnableControl -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
controlIdentifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
targetIdentifier

instance Prelude.NFData EnableControl where
  rnf :: EnableControl -> ()
rnf EnableControl' {Text
targetIdentifier :: Text
controlIdentifier :: Text
$sel:targetIdentifier:EnableControl' :: EnableControl -> Text
$sel:controlIdentifier:EnableControl' :: EnableControl -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
controlIdentifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
targetIdentifier

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

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

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

-- | /See:/ 'newEnableControlResponse' smart constructor.
data EnableControlResponse = EnableControlResponse'
  { -- | The response's http status code.
    EnableControlResponse -> Int
httpStatus :: Prelude.Int,
    -- | The ID of the asynchronous operation, which is used to track status. The
    -- operation is available for 90 days.
    EnableControlResponse -> Text
operationIdentifier :: Prelude.Text
  }
  deriving (EnableControlResponse -> EnableControlResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnableControlResponse -> EnableControlResponse -> Bool
$c/= :: EnableControlResponse -> EnableControlResponse -> Bool
== :: EnableControlResponse -> EnableControlResponse -> Bool
$c== :: EnableControlResponse -> EnableControlResponse -> Bool
Prelude.Eq, ReadPrec [EnableControlResponse]
ReadPrec EnableControlResponse
Int -> ReadS EnableControlResponse
ReadS [EnableControlResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EnableControlResponse]
$creadListPrec :: ReadPrec [EnableControlResponse]
readPrec :: ReadPrec EnableControlResponse
$creadPrec :: ReadPrec EnableControlResponse
readList :: ReadS [EnableControlResponse]
$creadList :: ReadS [EnableControlResponse]
readsPrec :: Int -> ReadS EnableControlResponse
$creadsPrec :: Int -> ReadS EnableControlResponse
Prelude.Read, Int -> EnableControlResponse -> ShowS
[EnableControlResponse] -> ShowS
EnableControlResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EnableControlResponse] -> ShowS
$cshowList :: [EnableControlResponse] -> ShowS
show :: EnableControlResponse -> String
$cshow :: EnableControlResponse -> String
showsPrec :: Int -> EnableControlResponse -> ShowS
$cshowsPrec :: Int -> EnableControlResponse -> ShowS
Prelude.Show, forall x. Rep EnableControlResponse x -> EnableControlResponse
forall x. EnableControlResponse -> Rep EnableControlResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EnableControlResponse x -> EnableControlResponse
$cfrom :: forall x. EnableControlResponse -> Rep EnableControlResponse x
Prelude.Generic)

-- |
-- Create a value of 'EnableControlResponse' 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:
--
-- 'httpStatus', 'enableControlResponse_httpStatus' - The response's http status code.
--
-- 'operationIdentifier', 'enableControlResponse_operationIdentifier' - The ID of the asynchronous operation, which is used to track status. The
-- operation is available for 90 days.
newEnableControlResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'operationIdentifier'
  Prelude.Text ->
  EnableControlResponse
newEnableControlResponse :: Int -> Text -> EnableControlResponse
newEnableControlResponse
  Int
pHttpStatus_
  Text
pOperationIdentifier_ =
    EnableControlResponse'
      { $sel:httpStatus:EnableControlResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:operationIdentifier:EnableControlResponse' :: Text
operationIdentifier = Text
pOperationIdentifier_
      }

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

-- | The ID of the asynchronous operation, which is used to track status. The
-- operation is available for 90 days.
enableControlResponse_operationIdentifier :: Lens.Lens' EnableControlResponse Prelude.Text
enableControlResponse_operationIdentifier :: Lens' EnableControlResponse Text
enableControlResponse_operationIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnableControlResponse' {Text
operationIdentifier :: Text
$sel:operationIdentifier:EnableControlResponse' :: EnableControlResponse -> Text
operationIdentifier} -> Text
operationIdentifier) (\s :: EnableControlResponse
s@EnableControlResponse' {} Text
a -> EnableControlResponse
s {$sel:operationIdentifier:EnableControlResponse' :: Text
operationIdentifier = Text
a} :: EnableControlResponse)

instance Prelude.NFData EnableControlResponse where
  rnf :: EnableControlResponse -> ()
rnf EnableControlResponse' {Int
Text
operationIdentifier :: Text
httpStatus :: Int
$sel:operationIdentifier:EnableControlResponse' :: EnableControlResponse -> Text
$sel:httpStatus:EnableControlResponse' :: EnableControlResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
operationIdentifier