{-# 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.RegisterDomain
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Registers a new domain.
--
-- __Access Control__
--
-- You can use IAM policies to control this action\'s access to Amazon SWF
-- resources as follows:
--
-- -   You cannot use an IAM policy to control domain access for this
--     action. The name of the domain being registered is available as the
--     resource of this action.
--
-- -   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.RegisterDomain
  ( -- * Creating a Request
    RegisterDomain (..),
    newRegisterDomain,

    -- * Request Lenses
    registerDomain_description,
    registerDomain_tags,
    registerDomain_name,
    registerDomain_workflowExecutionRetentionPeriodInDays,

    -- * Destructuring the Response
    RegisterDomainResponse (..),
    newRegisterDomainResponse,
  )
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:/ 'newRegisterDomain' smart constructor.
data RegisterDomain = RegisterDomain'
  { -- | A text description of the domain.
    RegisterDomain -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | Tags to be added when registering a domain.
    --
    -- Tags may only contain unicode letters, digits, whitespace, or these
    -- symbols: @_ . : \/ = + - \@@.
    RegisterDomain -> Maybe [ResourceTag]
tags :: Prelude.Maybe [ResourceTag],
    -- | Name of the domain to register. The name must be unique in the region
    -- that the domain is registered in.
    --
    -- The specified string must not start or end with whitespace. It must not
    -- contain a @:@ (colon), @\/@ (slash), @|@ (vertical bar), or any control
    -- characters (@\\u0000-\\u001f@ | @\\u007f-\\u009f@). Also, it must not
    -- /be/ the literal string @arn@.
    RegisterDomain -> Text
name :: Prelude.Text,
    -- | The duration (in days) that records and histories of workflow executions
    -- on the domain should be kept by the service. After the retention period,
    -- the workflow execution isn\'t available in the results of visibility
    -- calls.
    --
    -- If you pass the value @NONE@ or @0@ (zero), then the workflow execution
    -- history isn\'t retained. As soon as the workflow execution completes,
    -- the execution record and its history are deleted.
    --
    -- The maximum workflow execution retention period is 90 days. For more
    -- information about Amazon SWF service limits, see:
    -- <https://docs.aws.amazon.com/amazonswf/latest/developerguide/swf-dg-limits.html Amazon SWF Service Limits>
    -- in the /Amazon SWF Developer Guide/.
    RegisterDomain -> Text
workflowExecutionRetentionPeriodInDays :: Prelude.Text
  }
  deriving (RegisterDomain -> RegisterDomain -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RegisterDomain -> RegisterDomain -> Bool
$c/= :: RegisterDomain -> RegisterDomain -> Bool
== :: RegisterDomain -> RegisterDomain -> Bool
$c== :: RegisterDomain -> RegisterDomain -> Bool
Prelude.Eq, ReadPrec [RegisterDomain]
ReadPrec RegisterDomain
Int -> ReadS RegisterDomain
ReadS [RegisterDomain]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RegisterDomain]
$creadListPrec :: ReadPrec [RegisterDomain]
readPrec :: ReadPrec RegisterDomain
$creadPrec :: ReadPrec RegisterDomain
readList :: ReadS [RegisterDomain]
$creadList :: ReadS [RegisterDomain]
readsPrec :: Int -> ReadS RegisterDomain
$creadsPrec :: Int -> ReadS RegisterDomain
Prelude.Read, Int -> RegisterDomain -> ShowS
[RegisterDomain] -> ShowS
RegisterDomain -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RegisterDomain] -> ShowS
$cshowList :: [RegisterDomain] -> ShowS
show :: RegisterDomain -> String
$cshow :: RegisterDomain -> String
showsPrec :: Int -> RegisterDomain -> ShowS
$cshowsPrec :: Int -> RegisterDomain -> ShowS
Prelude.Show, forall x. Rep RegisterDomain x -> RegisterDomain
forall x. RegisterDomain -> Rep RegisterDomain x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RegisterDomain x -> RegisterDomain
$cfrom :: forall x. RegisterDomain -> Rep RegisterDomain x
Prelude.Generic)

-- |
-- Create a value of 'RegisterDomain' 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:
--
-- 'description', 'registerDomain_description' - A text description of the domain.
--
-- 'tags', 'registerDomain_tags' - Tags to be added when registering a domain.
--
-- Tags may only contain unicode letters, digits, whitespace, or these
-- symbols: @_ . : \/ = + - \@@.
--
-- 'name', 'registerDomain_name' - Name of the domain to register. The name must be unique in the region
-- that the domain is registered in.
--
-- The specified string must not start or end with whitespace. It must not
-- contain a @:@ (colon), @\/@ (slash), @|@ (vertical bar), or any control
-- characters (@\\u0000-\\u001f@ | @\\u007f-\\u009f@). Also, it must not
-- /be/ the literal string @arn@.
--
-- 'workflowExecutionRetentionPeriodInDays', 'registerDomain_workflowExecutionRetentionPeriodInDays' - The duration (in days) that records and histories of workflow executions
-- on the domain should be kept by the service. After the retention period,
-- the workflow execution isn\'t available in the results of visibility
-- calls.
--
-- If you pass the value @NONE@ or @0@ (zero), then the workflow execution
-- history isn\'t retained. As soon as the workflow execution completes,
-- the execution record and its history are deleted.
--
-- The maximum workflow execution retention period is 90 days. For more
-- information about Amazon SWF service limits, see:
-- <https://docs.aws.amazon.com/amazonswf/latest/developerguide/swf-dg-limits.html Amazon SWF Service Limits>
-- in the /Amazon SWF Developer Guide/.
newRegisterDomain ::
  -- | 'name'
  Prelude.Text ->
  -- | 'workflowExecutionRetentionPeriodInDays'
  Prelude.Text ->
  RegisterDomain
newRegisterDomain :: Text -> Text -> RegisterDomain
newRegisterDomain
  Text
pName_
  Text
pWorkflowExecutionRetentionPeriodInDays_ =
    RegisterDomain'
      { $sel:description:RegisterDomain' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
        $sel:tags:RegisterDomain' :: Maybe [ResourceTag]
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:name:RegisterDomain' :: Text
name = Text
pName_,
        $sel:workflowExecutionRetentionPeriodInDays:RegisterDomain' :: Text
workflowExecutionRetentionPeriodInDays =
          Text
pWorkflowExecutionRetentionPeriodInDays_
      }

-- | A text description of the domain.
registerDomain_description :: Lens.Lens' RegisterDomain (Prelude.Maybe Prelude.Text)
registerDomain_description :: Lens' RegisterDomain (Maybe Text)
registerDomain_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterDomain' {Maybe Text
description :: Maybe Text
$sel:description:RegisterDomain' :: RegisterDomain -> Maybe Text
description} -> Maybe Text
description) (\s :: RegisterDomain
s@RegisterDomain' {} Maybe Text
a -> RegisterDomain
s {$sel:description:RegisterDomain' :: Maybe Text
description = Maybe Text
a} :: RegisterDomain)

-- | Tags to be added when registering a domain.
--
-- Tags may only contain unicode letters, digits, whitespace, or these
-- symbols: @_ . : \/ = + - \@@.
registerDomain_tags :: Lens.Lens' RegisterDomain (Prelude.Maybe [ResourceTag])
registerDomain_tags :: Lens' RegisterDomain (Maybe [ResourceTag])
registerDomain_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterDomain' {Maybe [ResourceTag]
tags :: Maybe [ResourceTag]
$sel:tags:RegisterDomain' :: RegisterDomain -> Maybe [ResourceTag]
tags} -> Maybe [ResourceTag]
tags) (\s :: RegisterDomain
s@RegisterDomain' {} Maybe [ResourceTag]
a -> RegisterDomain
s {$sel:tags:RegisterDomain' :: Maybe [ResourceTag]
tags = Maybe [ResourceTag]
a} :: RegisterDomain) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | Name of the domain to register. The name must be unique in the region
-- that the domain is registered in.
--
-- The specified string must not start or end with whitespace. It must not
-- contain a @:@ (colon), @\/@ (slash), @|@ (vertical bar), or any control
-- characters (@\\u0000-\\u001f@ | @\\u007f-\\u009f@). Also, it must not
-- /be/ the literal string @arn@.
registerDomain_name :: Lens.Lens' RegisterDomain Prelude.Text
registerDomain_name :: Lens' RegisterDomain Text
registerDomain_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterDomain' {Text
name :: Text
$sel:name:RegisterDomain' :: RegisterDomain -> Text
name} -> Text
name) (\s :: RegisterDomain
s@RegisterDomain' {} Text
a -> RegisterDomain
s {$sel:name:RegisterDomain' :: Text
name = Text
a} :: RegisterDomain)

-- | The duration (in days) that records and histories of workflow executions
-- on the domain should be kept by the service. After the retention period,
-- the workflow execution isn\'t available in the results of visibility
-- calls.
--
-- If you pass the value @NONE@ or @0@ (zero), then the workflow execution
-- history isn\'t retained. As soon as the workflow execution completes,
-- the execution record and its history are deleted.
--
-- The maximum workflow execution retention period is 90 days. For more
-- information about Amazon SWF service limits, see:
-- <https://docs.aws.amazon.com/amazonswf/latest/developerguide/swf-dg-limits.html Amazon SWF Service Limits>
-- in the /Amazon SWF Developer Guide/.
registerDomain_workflowExecutionRetentionPeriodInDays :: Lens.Lens' RegisterDomain Prelude.Text
registerDomain_workflowExecutionRetentionPeriodInDays :: Lens' RegisterDomain Text
registerDomain_workflowExecutionRetentionPeriodInDays = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterDomain' {Text
workflowExecutionRetentionPeriodInDays :: Text
$sel:workflowExecutionRetentionPeriodInDays:RegisterDomain' :: RegisterDomain -> Text
workflowExecutionRetentionPeriodInDays} -> Text
workflowExecutionRetentionPeriodInDays) (\s :: RegisterDomain
s@RegisterDomain' {} Text
a -> RegisterDomain
s {$sel:workflowExecutionRetentionPeriodInDays:RegisterDomain' :: Text
workflowExecutionRetentionPeriodInDays = Text
a} :: RegisterDomain)

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

instance Prelude.Hashable RegisterDomain where
  hashWithSalt :: Int -> RegisterDomain -> Int
hashWithSalt Int
_salt RegisterDomain' {Maybe [ResourceTag]
Maybe Text
Text
workflowExecutionRetentionPeriodInDays :: Text
name :: Text
tags :: Maybe [ResourceTag]
description :: Maybe Text
$sel:workflowExecutionRetentionPeriodInDays:RegisterDomain' :: RegisterDomain -> Text
$sel:name:RegisterDomain' :: RegisterDomain -> Text
$sel:tags:RegisterDomain' :: RegisterDomain -> Maybe [ResourceTag]
$sel:description:RegisterDomain' :: RegisterDomain -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [ResourceTag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
workflowExecutionRetentionPeriodInDays

instance Prelude.NFData RegisterDomain where
  rnf :: RegisterDomain -> ()
rnf RegisterDomain' {Maybe [ResourceTag]
Maybe Text
Text
workflowExecutionRetentionPeriodInDays :: Text
name :: Text
tags :: Maybe [ResourceTag]
description :: Maybe Text
$sel:workflowExecutionRetentionPeriodInDays:RegisterDomain' :: RegisterDomain -> Text
$sel:name:RegisterDomain' :: RegisterDomain -> Text
$sel:tags:RegisterDomain' :: RegisterDomain -> Maybe [ResourceTag]
$sel:description:RegisterDomain' :: RegisterDomain -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ResourceTag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
workflowExecutionRetentionPeriodInDays

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

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

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

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

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

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