{-# 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.SWF.UndeprecateDomain
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Undeprecates a previously deprecated domain. After a domain has been
-- undeprecated it can be used to create new workflow executions or
-- register new types.
--
-- This operation is eventually consistent. The results are best effort and
-- may not exactly reflect recent updates and changes.
--
-- __Access Control__
--
-- You can use IAM policies to control this action\'s access to Amazon SWF
-- resources as follows:
--
-- -   Use a @Resource@ element with the domain name to limit the action to
--     only specified domains.
--
-- -   Use an @Action@ element to allow or deny permission to call this
--     action.
--
-- -   You cannot use an IAM policy to constrain this action\'s parameters.
--
-- If the caller doesn\'t have sufficient permissions to invoke the action,
-- or the parameter values fall outside the specified constraints, the
-- action fails. The associated event attribute\'s @cause@ parameter is set
-- to @OPERATION_NOT_PERMITTED@. For details and example IAM policies, see
-- <https://docs.aws.amazon.com/amazonswf/latest/developerguide/swf-dev-iam.html Using IAM to Manage Access to Amazon SWF Workflows>
-- in the /Amazon SWF Developer Guide/.
module Amazonka.SWF.UndeprecateDomain
  ( -- * Creating a Request
    UndeprecateDomain (..),
    newUndeprecateDomain,

    -- * Request Lenses
    undeprecateDomain_name,

    -- * Destructuring the Response
    UndeprecateDomainResponse (..),
    newUndeprecateDomainResponse,
  )
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 qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.SWF.Types

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

-- |
-- Create a value of 'UndeprecateDomain' 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:
--
-- 'name', 'undeprecateDomain_name' - The name of the domain of the deprecated workflow type.
newUndeprecateDomain ::
  -- | 'name'
  Prelude.Text ->
  UndeprecateDomain
newUndeprecateDomain :: Text -> UndeprecateDomain
newUndeprecateDomain Text
pName_ =
  UndeprecateDomain' {$sel:name:UndeprecateDomain' :: Text
name = Text
pName_}

-- | The name of the domain of the deprecated workflow type.
undeprecateDomain_name :: Lens.Lens' UndeprecateDomain Prelude.Text
undeprecateDomain_name :: Lens' UndeprecateDomain Text
undeprecateDomain_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UndeprecateDomain' {Text
name :: Text
$sel:name:UndeprecateDomain' :: UndeprecateDomain -> Text
name} -> Text
name) (\s :: UndeprecateDomain
s@UndeprecateDomain' {} Text
a -> UndeprecateDomain
s {$sel:name:UndeprecateDomain' :: Text
name = Text
a} :: UndeprecateDomain)

instance Core.AWSRequest UndeprecateDomain where
  type
    AWSResponse UndeprecateDomain =
      UndeprecateDomainResponse
  request :: (Service -> Service)
-> UndeprecateDomain -> Request UndeprecateDomain
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 UndeprecateDomain
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UndeprecateDomain)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull UndeprecateDomainResponse
UndeprecateDomainResponse'

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

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

instance Data.ToHeaders UndeprecateDomain where
  toHeaders :: UndeprecateDomain -> [Header]
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 -> [Header]
Data.=# ( ByteString
"SimpleWorkflowService.UndeprecateDomain" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"application/x-amz-json-1.0" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON UndeprecateDomain where
  toJSON :: UndeprecateDomain -> Value
toJSON UndeprecateDomain' {Text
name :: Text
$sel:name:UndeprecateDomain' :: UndeprecateDomain -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name)]
      )

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

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

-- | /See:/ 'newUndeprecateDomainResponse' smart constructor.
data UndeprecateDomainResponse = UndeprecateDomainResponse'
  {
  }
  deriving (UndeprecateDomainResponse -> UndeprecateDomainResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UndeprecateDomainResponse -> UndeprecateDomainResponse -> Bool
$c/= :: UndeprecateDomainResponse -> UndeprecateDomainResponse -> Bool
== :: UndeprecateDomainResponse -> UndeprecateDomainResponse -> Bool
$c== :: UndeprecateDomainResponse -> UndeprecateDomainResponse -> Bool
Prelude.Eq, ReadPrec [UndeprecateDomainResponse]
ReadPrec UndeprecateDomainResponse
Int -> ReadS UndeprecateDomainResponse
ReadS [UndeprecateDomainResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UndeprecateDomainResponse]
$creadListPrec :: ReadPrec [UndeprecateDomainResponse]
readPrec :: ReadPrec UndeprecateDomainResponse
$creadPrec :: ReadPrec UndeprecateDomainResponse
readList :: ReadS [UndeprecateDomainResponse]
$creadList :: ReadS [UndeprecateDomainResponse]
readsPrec :: Int -> ReadS UndeprecateDomainResponse
$creadsPrec :: Int -> ReadS UndeprecateDomainResponse
Prelude.Read, Int -> UndeprecateDomainResponse -> ShowS
[UndeprecateDomainResponse] -> ShowS
UndeprecateDomainResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UndeprecateDomainResponse] -> ShowS
$cshowList :: [UndeprecateDomainResponse] -> ShowS
show :: UndeprecateDomainResponse -> String
$cshow :: UndeprecateDomainResponse -> String
showsPrec :: Int -> UndeprecateDomainResponse -> ShowS
$cshowsPrec :: Int -> UndeprecateDomainResponse -> ShowS
Prelude.Show, forall x.
Rep UndeprecateDomainResponse x -> UndeprecateDomainResponse
forall x.
UndeprecateDomainResponse -> Rep UndeprecateDomainResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UndeprecateDomainResponse x -> UndeprecateDomainResponse
$cfrom :: forall x.
UndeprecateDomainResponse -> Rep UndeprecateDomainResponse x
Prelude.Generic)

-- |
-- Create a value of 'UndeprecateDomainResponse' 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.
newUndeprecateDomainResponse ::
  UndeprecateDomainResponse
newUndeprecateDomainResponse :: UndeprecateDomainResponse
newUndeprecateDomainResponse =
  UndeprecateDomainResponse
UndeprecateDomainResponse'

instance Prelude.NFData UndeprecateDomainResponse where
  rnf :: UndeprecateDomainResponse -> ()
rnf UndeprecateDomainResponse
_ = ()