{-# 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.DeprecateWorkflowType
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Deprecates the specified /workflow type/. After a workflow type has been
-- deprecated, you cannot create new executions of that type. Executions
-- that were started before the type was deprecated continues to run. A
-- deprecated workflow type may still be used when calling visibility
-- actions.
--
-- 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.
--
-- -   Constrain the following parameters by using a @Condition@ element
--     with the appropriate keys.
--
--     -   @workflowType.name@: String constraint. The key is
--         @swf:workflowType.name@.
--
--     -   @workflowType.version@: String constraint. The key is
--         @swf:workflowType.version@.
--
-- 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.DeprecateWorkflowType
  ( -- * Creating a Request
    DeprecateWorkflowType (..),
    newDeprecateWorkflowType,

    -- * Request Lenses
    deprecateWorkflowType_domain,
    deprecateWorkflowType_workflowType,

    -- * Destructuring the Response
    DeprecateWorkflowTypeResponse (..),
    newDeprecateWorkflowTypeResponse,
  )
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:/ 'newDeprecateWorkflowType' smart constructor.
data DeprecateWorkflowType = DeprecateWorkflowType'
  { -- | The name of the domain in which the workflow type is registered.
    DeprecateWorkflowType -> Text
domain :: Prelude.Text,
    -- | The workflow type to deprecate.
    DeprecateWorkflowType -> WorkflowType
workflowType :: WorkflowType
  }
  deriving (DeprecateWorkflowType -> DeprecateWorkflowType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeprecateWorkflowType -> DeprecateWorkflowType -> Bool
$c/= :: DeprecateWorkflowType -> DeprecateWorkflowType -> Bool
== :: DeprecateWorkflowType -> DeprecateWorkflowType -> Bool
$c== :: DeprecateWorkflowType -> DeprecateWorkflowType -> Bool
Prelude.Eq, ReadPrec [DeprecateWorkflowType]
ReadPrec DeprecateWorkflowType
Int -> ReadS DeprecateWorkflowType
ReadS [DeprecateWorkflowType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeprecateWorkflowType]
$creadListPrec :: ReadPrec [DeprecateWorkflowType]
readPrec :: ReadPrec DeprecateWorkflowType
$creadPrec :: ReadPrec DeprecateWorkflowType
readList :: ReadS [DeprecateWorkflowType]
$creadList :: ReadS [DeprecateWorkflowType]
readsPrec :: Int -> ReadS DeprecateWorkflowType
$creadsPrec :: Int -> ReadS DeprecateWorkflowType
Prelude.Read, Int -> DeprecateWorkflowType -> ShowS
[DeprecateWorkflowType] -> ShowS
DeprecateWorkflowType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeprecateWorkflowType] -> ShowS
$cshowList :: [DeprecateWorkflowType] -> ShowS
show :: DeprecateWorkflowType -> String
$cshow :: DeprecateWorkflowType -> String
showsPrec :: Int -> DeprecateWorkflowType -> ShowS
$cshowsPrec :: Int -> DeprecateWorkflowType -> ShowS
Prelude.Show, forall x. Rep DeprecateWorkflowType x -> DeprecateWorkflowType
forall x. DeprecateWorkflowType -> Rep DeprecateWorkflowType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeprecateWorkflowType x -> DeprecateWorkflowType
$cfrom :: forall x. DeprecateWorkflowType -> Rep DeprecateWorkflowType x
Prelude.Generic)

-- |
-- Create a value of 'DeprecateWorkflowType' 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:
--
-- 'domain', 'deprecateWorkflowType_domain' - The name of the domain in which the workflow type is registered.
--
-- 'workflowType', 'deprecateWorkflowType_workflowType' - The workflow type to deprecate.
newDeprecateWorkflowType ::
  -- | 'domain'
  Prelude.Text ->
  -- | 'workflowType'
  WorkflowType ->
  DeprecateWorkflowType
newDeprecateWorkflowType :: Text -> WorkflowType -> DeprecateWorkflowType
newDeprecateWorkflowType Text
pDomain_ WorkflowType
pWorkflowType_ =
  DeprecateWorkflowType'
    { $sel:domain:DeprecateWorkflowType' :: Text
domain = Text
pDomain_,
      $sel:workflowType:DeprecateWorkflowType' :: WorkflowType
workflowType = WorkflowType
pWorkflowType_
    }

-- | The name of the domain in which the workflow type is registered.
deprecateWorkflowType_domain :: Lens.Lens' DeprecateWorkflowType Prelude.Text
deprecateWorkflowType_domain :: Lens' DeprecateWorkflowType Text
deprecateWorkflowType_domain = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeprecateWorkflowType' {Text
domain :: Text
$sel:domain:DeprecateWorkflowType' :: DeprecateWorkflowType -> Text
domain} -> Text
domain) (\s :: DeprecateWorkflowType
s@DeprecateWorkflowType' {} Text
a -> DeprecateWorkflowType
s {$sel:domain:DeprecateWorkflowType' :: Text
domain = Text
a} :: DeprecateWorkflowType)

-- | The workflow type to deprecate.
deprecateWorkflowType_workflowType :: Lens.Lens' DeprecateWorkflowType WorkflowType
deprecateWorkflowType_workflowType :: Lens' DeprecateWorkflowType WorkflowType
deprecateWorkflowType_workflowType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeprecateWorkflowType' {WorkflowType
workflowType :: WorkflowType
$sel:workflowType:DeprecateWorkflowType' :: DeprecateWorkflowType -> WorkflowType
workflowType} -> WorkflowType
workflowType) (\s :: DeprecateWorkflowType
s@DeprecateWorkflowType' {} WorkflowType
a -> DeprecateWorkflowType
s {$sel:workflowType:DeprecateWorkflowType' :: WorkflowType
workflowType = WorkflowType
a} :: DeprecateWorkflowType)

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

instance Prelude.Hashable DeprecateWorkflowType where
  hashWithSalt :: Int -> DeprecateWorkflowType -> Int
hashWithSalt Int
_salt DeprecateWorkflowType' {Text
WorkflowType
workflowType :: WorkflowType
domain :: Text
$sel:workflowType:DeprecateWorkflowType' :: DeprecateWorkflowType -> WorkflowType
$sel:domain:DeprecateWorkflowType' :: DeprecateWorkflowType -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
domain
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` WorkflowType
workflowType

instance Prelude.NFData DeprecateWorkflowType where
  rnf :: DeprecateWorkflowType -> ()
rnf DeprecateWorkflowType' {Text
WorkflowType
workflowType :: WorkflowType
domain :: Text
$sel:workflowType:DeprecateWorkflowType' :: DeprecateWorkflowType -> WorkflowType
$sel:domain:DeprecateWorkflowType' :: DeprecateWorkflowType -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
domain
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf WorkflowType
workflowType

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

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

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

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

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

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