{-# 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.SageMaker.CreateAction
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates an /action/. An action is a lineage tracking entity that
-- represents an action or activity. For example, a model deployment or an
-- HPO job. Generally, an action involves at least one input or output
-- artifact. For more information, see
-- <https://docs.aws.amazon.com/sagemaker/latest/dg/lineage-tracking.html Amazon SageMaker ML Lineage Tracking>.
module Amazonka.SageMaker.CreateAction
  ( -- * Creating a Request
    CreateAction (..),
    newCreateAction,

    -- * Request Lenses
    createAction_description,
    createAction_metadataProperties,
    createAction_properties,
    createAction_status,
    createAction_tags,
    createAction_actionName,
    createAction_source,
    createAction_actionType,

    -- * Destructuring the Response
    CreateActionResponse (..),
    newCreateActionResponse,

    -- * Response Lenses
    createActionResponse_actionArn,
    createActionResponse_httpStatus,
  )
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.SageMaker.Types

-- | /See:/ 'newCreateAction' smart constructor.
data CreateAction = CreateAction'
  { -- | The description of the action.
    CreateAction -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    CreateAction -> Maybe MetadataProperties
metadataProperties :: Prelude.Maybe MetadataProperties,
    -- | A list of properties to add to the action.
    CreateAction -> Maybe (HashMap Text Text)
properties :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The status of the action.
    CreateAction -> Maybe ActionStatus
status :: Prelude.Maybe ActionStatus,
    -- | A list of tags to apply to the action.
    CreateAction -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The name of the action. Must be unique to your account in an Amazon Web
    -- Services Region.
    CreateAction -> Text
actionName :: Prelude.Text,
    -- | The source type, ID, and URI.
    CreateAction -> ActionSource
source :: ActionSource,
    -- | The action type.
    CreateAction -> Text
actionType :: Prelude.Text
  }
  deriving (CreateAction -> CreateAction -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateAction -> CreateAction -> Bool
$c/= :: CreateAction -> CreateAction -> Bool
== :: CreateAction -> CreateAction -> Bool
$c== :: CreateAction -> CreateAction -> Bool
Prelude.Eq, ReadPrec [CreateAction]
ReadPrec CreateAction
Int -> ReadS CreateAction
ReadS [CreateAction]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateAction]
$creadListPrec :: ReadPrec [CreateAction]
readPrec :: ReadPrec CreateAction
$creadPrec :: ReadPrec CreateAction
readList :: ReadS [CreateAction]
$creadList :: ReadS [CreateAction]
readsPrec :: Int -> ReadS CreateAction
$creadsPrec :: Int -> ReadS CreateAction
Prelude.Read, Int -> CreateAction -> ShowS
[CreateAction] -> ShowS
CreateAction -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateAction] -> ShowS
$cshowList :: [CreateAction] -> ShowS
show :: CreateAction -> String
$cshow :: CreateAction -> String
showsPrec :: Int -> CreateAction -> ShowS
$cshowsPrec :: Int -> CreateAction -> ShowS
Prelude.Show, forall x. Rep CreateAction x -> CreateAction
forall x. CreateAction -> Rep CreateAction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateAction x -> CreateAction
$cfrom :: forall x. CreateAction -> Rep CreateAction x
Prelude.Generic)

-- |
-- Create a value of 'CreateAction' 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', 'createAction_description' - The description of the action.
--
-- 'metadataProperties', 'createAction_metadataProperties' - Undocumented member.
--
-- 'properties', 'createAction_properties' - A list of properties to add to the action.
--
-- 'status', 'createAction_status' - The status of the action.
--
-- 'tags', 'createAction_tags' - A list of tags to apply to the action.
--
-- 'actionName', 'createAction_actionName' - The name of the action. Must be unique to your account in an Amazon Web
-- Services Region.
--
-- 'source', 'createAction_source' - The source type, ID, and URI.
--
-- 'actionType', 'createAction_actionType' - The action type.
newCreateAction ::
  -- | 'actionName'
  Prelude.Text ->
  -- | 'source'
  ActionSource ->
  -- | 'actionType'
  Prelude.Text ->
  CreateAction
newCreateAction :: Text -> ActionSource -> Text -> CreateAction
newCreateAction Text
pActionName_ ActionSource
pSource_ Text
pActionType_ =
  CreateAction'
    { $sel:description:CreateAction' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:metadataProperties:CreateAction' :: Maybe MetadataProperties
metadataProperties = forall a. Maybe a
Prelude.Nothing,
      $sel:properties:CreateAction' :: Maybe (HashMap Text Text)
properties = forall a. Maybe a
Prelude.Nothing,
      $sel:status:CreateAction' :: Maybe ActionStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateAction' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:actionName:CreateAction' :: Text
actionName = Text
pActionName_,
      $sel:source:CreateAction' :: ActionSource
source = ActionSource
pSource_,
      $sel:actionType:CreateAction' :: Text
actionType = Text
pActionType_
    }

-- | The description of the action.
createAction_description :: Lens.Lens' CreateAction (Prelude.Maybe Prelude.Text)
createAction_description :: Lens' CreateAction (Maybe Text)
createAction_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAction' {Maybe Text
description :: Maybe Text
$sel:description:CreateAction' :: CreateAction -> Maybe Text
description} -> Maybe Text
description) (\s :: CreateAction
s@CreateAction' {} Maybe Text
a -> CreateAction
s {$sel:description:CreateAction' :: Maybe Text
description = Maybe Text
a} :: CreateAction)

-- | Undocumented member.
createAction_metadataProperties :: Lens.Lens' CreateAction (Prelude.Maybe MetadataProperties)
createAction_metadataProperties :: Lens' CreateAction (Maybe MetadataProperties)
createAction_metadataProperties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAction' {Maybe MetadataProperties
metadataProperties :: Maybe MetadataProperties
$sel:metadataProperties:CreateAction' :: CreateAction -> Maybe MetadataProperties
metadataProperties} -> Maybe MetadataProperties
metadataProperties) (\s :: CreateAction
s@CreateAction' {} Maybe MetadataProperties
a -> CreateAction
s {$sel:metadataProperties:CreateAction' :: Maybe MetadataProperties
metadataProperties = Maybe MetadataProperties
a} :: CreateAction)

-- | A list of properties to add to the action.
createAction_properties :: Lens.Lens' CreateAction (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createAction_properties :: Lens' CreateAction (Maybe (HashMap Text Text))
createAction_properties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAction' {Maybe (HashMap Text Text)
properties :: Maybe (HashMap Text Text)
$sel:properties:CreateAction' :: CreateAction -> Maybe (HashMap Text Text)
properties} -> Maybe (HashMap Text Text)
properties) (\s :: CreateAction
s@CreateAction' {} Maybe (HashMap Text Text)
a -> CreateAction
s {$sel:properties:CreateAction' :: Maybe (HashMap Text Text)
properties = Maybe (HashMap Text Text)
a} :: CreateAction) 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

-- | The status of the action.
createAction_status :: Lens.Lens' CreateAction (Prelude.Maybe ActionStatus)
createAction_status :: Lens' CreateAction (Maybe ActionStatus)
createAction_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAction' {Maybe ActionStatus
status :: Maybe ActionStatus
$sel:status:CreateAction' :: CreateAction -> Maybe ActionStatus
status} -> Maybe ActionStatus
status) (\s :: CreateAction
s@CreateAction' {} Maybe ActionStatus
a -> CreateAction
s {$sel:status:CreateAction' :: Maybe ActionStatus
status = Maybe ActionStatus
a} :: CreateAction)

-- | A list of tags to apply to the action.
createAction_tags :: Lens.Lens' CreateAction (Prelude.Maybe [Tag])
createAction_tags :: Lens' CreateAction (Maybe [Tag])
createAction_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAction' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreateAction' :: CreateAction -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreateAction
s@CreateAction' {} Maybe [Tag]
a -> CreateAction
s {$sel:tags:CreateAction' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: CreateAction) 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

-- | The name of the action. Must be unique to your account in an Amazon Web
-- Services Region.
createAction_actionName :: Lens.Lens' CreateAction Prelude.Text
createAction_actionName :: Lens' CreateAction Text
createAction_actionName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAction' {Text
actionName :: Text
$sel:actionName:CreateAction' :: CreateAction -> Text
actionName} -> Text
actionName) (\s :: CreateAction
s@CreateAction' {} Text
a -> CreateAction
s {$sel:actionName:CreateAction' :: Text
actionName = Text
a} :: CreateAction)

-- | The source type, ID, and URI.
createAction_source :: Lens.Lens' CreateAction ActionSource
createAction_source :: Lens' CreateAction ActionSource
createAction_source = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAction' {ActionSource
source :: ActionSource
$sel:source:CreateAction' :: CreateAction -> ActionSource
source} -> ActionSource
source) (\s :: CreateAction
s@CreateAction' {} ActionSource
a -> CreateAction
s {$sel:source:CreateAction' :: ActionSource
source = ActionSource
a} :: CreateAction)

-- | The action type.
createAction_actionType :: Lens.Lens' CreateAction Prelude.Text
createAction_actionType :: Lens' CreateAction Text
createAction_actionType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAction' {Text
actionType :: Text
$sel:actionType:CreateAction' :: CreateAction -> Text
actionType} -> Text
actionType) (\s :: CreateAction
s@CreateAction' {} Text
a -> CreateAction
s {$sel:actionType:CreateAction' :: Text
actionType = Text
a} :: CreateAction)

instance Core.AWSRequest CreateAction where
  type AWSResponse CreateAction = CreateActionResponse
  request :: (Service -> Service) -> CreateAction -> Request CreateAction
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 CreateAction
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateAction)))
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 -> CreateActionResponse
CreateActionResponse'
            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
"ActionArn")
            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 CreateAction where
  hashWithSalt :: Int -> CreateAction -> Int
hashWithSalt Int
_salt CreateAction' {Maybe [Tag]
Maybe Text
Maybe (HashMap Text Text)
Maybe ActionStatus
Maybe MetadataProperties
Text
ActionSource
actionType :: Text
source :: ActionSource
actionName :: Text
tags :: Maybe [Tag]
status :: Maybe ActionStatus
properties :: Maybe (HashMap Text Text)
metadataProperties :: Maybe MetadataProperties
description :: Maybe Text
$sel:actionType:CreateAction' :: CreateAction -> Text
$sel:source:CreateAction' :: CreateAction -> ActionSource
$sel:actionName:CreateAction' :: CreateAction -> Text
$sel:tags:CreateAction' :: CreateAction -> Maybe [Tag]
$sel:status:CreateAction' :: CreateAction -> Maybe ActionStatus
$sel:properties:CreateAction' :: CreateAction -> Maybe (HashMap Text Text)
$sel:metadataProperties:CreateAction' :: CreateAction -> Maybe MetadataProperties
$sel:description:CreateAction' :: CreateAction -> 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 MetadataProperties
metadataProperties
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
properties
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ActionStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
actionName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ActionSource
source
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
actionType

instance Prelude.NFData CreateAction where
  rnf :: CreateAction -> ()
rnf CreateAction' {Maybe [Tag]
Maybe Text
Maybe (HashMap Text Text)
Maybe ActionStatus
Maybe MetadataProperties
Text
ActionSource
actionType :: Text
source :: ActionSource
actionName :: Text
tags :: Maybe [Tag]
status :: Maybe ActionStatus
properties :: Maybe (HashMap Text Text)
metadataProperties :: Maybe MetadataProperties
description :: Maybe Text
$sel:actionType:CreateAction' :: CreateAction -> Text
$sel:source:CreateAction' :: CreateAction -> ActionSource
$sel:actionName:CreateAction' :: CreateAction -> Text
$sel:tags:CreateAction' :: CreateAction -> Maybe [Tag]
$sel:status:CreateAction' :: CreateAction -> Maybe ActionStatus
$sel:properties:CreateAction' :: CreateAction -> Maybe (HashMap Text Text)
$sel:metadataProperties:CreateAction' :: CreateAction -> Maybe MetadataProperties
$sel:description:CreateAction' :: CreateAction -> 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 MetadataProperties
metadataProperties
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
properties
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ActionStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
actionName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ActionSource
source
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
actionType

instance Data.ToHeaders CreateAction where
  toHeaders :: CreateAction -> 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
"SageMaker.CreateAction" :: 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 CreateAction where
  toJSON :: CreateAction -> Value
toJSON CreateAction' {Maybe [Tag]
Maybe Text
Maybe (HashMap Text Text)
Maybe ActionStatus
Maybe MetadataProperties
Text
ActionSource
actionType :: Text
source :: ActionSource
actionName :: Text
tags :: Maybe [Tag]
status :: Maybe ActionStatus
properties :: Maybe (HashMap Text Text)
metadataProperties :: Maybe MetadataProperties
description :: Maybe Text
$sel:actionType:CreateAction' :: CreateAction -> Text
$sel:source:CreateAction' :: CreateAction -> ActionSource
$sel:actionName:CreateAction' :: CreateAction -> Text
$sel:tags:CreateAction' :: CreateAction -> Maybe [Tag]
$sel:status:CreateAction' :: CreateAction -> Maybe ActionStatus
$sel:properties:CreateAction' :: CreateAction -> Maybe (HashMap Text Text)
$sel:metadataProperties:CreateAction' :: CreateAction -> Maybe MetadataProperties
$sel:description:CreateAction' :: CreateAction -> 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
"MetadataProperties" 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 MetadataProperties
metadataProperties,
            (Key
"Properties" 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 (HashMap Text Text)
properties,
            (Key
"Status" 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 ActionStatus
status,
            (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 [Tag]
tags,
            forall a. a -> Maybe a
Prelude.Just (Key
"ActionName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
actionName),
            forall a. a -> Maybe a
Prelude.Just (Key
"Source" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ActionSource
source),
            forall a. a -> Maybe a
Prelude.Just (Key
"ActionType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
actionType)
          ]
      )

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

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

-- | /See:/ 'newCreateActionResponse' smart constructor.
data CreateActionResponse = CreateActionResponse'
  { -- | The Amazon Resource Name (ARN) of the action.
    CreateActionResponse -> Maybe Text
actionArn :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CreateActionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateActionResponse -> CreateActionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateActionResponse -> CreateActionResponse -> Bool
$c/= :: CreateActionResponse -> CreateActionResponse -> Bool
== :: CreateActionResponse -> CreateActionResponse -> Bool
$c== :: CreateActionResponse -> CreateActionResponse -> Bool
Prelude.Eq, ReadPrec [CreateActionResponse]
ReadPrec CreateActionResponse
Int -> ReadS CreateActionResponse
ReadS [CreateActionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateActionResponse]
$creadListPrec :: ReadPrec [CreateActionResponse]
readPrec :: ReadPrec CreateActionResponse
$creadPrec :: ReadPrec CreateActionResponse
readList :: ReadS [CreateActionResponse]
$creadList :: ReadS [CreateActionResponse]
readsPrec :: Int -> ReadS CreateActionResponse
$creadsPrec :: Int -> ReadS CreateActionResponse
Prelude.Read, Int -> CreateActionResponse -> ShowS
[CreateActionResponse] -> ShowS
CreateActionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateActionResponse] -> ShowS
$cshowList :: [CreateActionResponse] -> ShowS
show :: CreateActionResponse -> String
$cshow :: CreateActionResponse -> String
showsPrec :: Int -> CreateActionResponse -> ShowS
$cshowsPrec :: Int -> CreateActionResponse -> ShowS
Prelude.Show, forall x. Rep CreateActionResponse x -> CreateActionResponse
forall x. CreateActionResponse -> Rep CreateActionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateActionResponse x -> CreateActionResponse
$cfrom :: forall x. CreateActionResponse -> Rep CreateActionResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateActionResponse' 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:
--
-- 'actionArn', 'createActionResponse_actionArn' - The Amazon Resource Name (ARN) of the action.
--
-- 'httpStatus', 'createActionResponse_httpStatus' - The response's http status code.
newCreateActionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateActionResponse
newCreateActionResponse :: Int -> CreateActionResponse
newCreateActionResponse Int
pHttpStatus_ =
  CreateActionResponse'
    { $sel:actionArn:CreateActionResponse' :: Maybe Text
actionArn = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateActionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Resource Name (ARN) of the action.
createActionResponse_actionArn :: Lens.Lens' CreateActionResponse (Prelude.Maybe Prelude.Text)
createActionResponse_actionArn :: Lens' CreateActionResponse (Maybe Text)
createActionResponse_actionArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateActionResponse' {Maybe Text
actionArn :: Maybe Text
$sel:actionArn:CreateActionResponse' :: CreateActionResponse -> Maybe Text
actionArn} -> Maybe Text
actionArn) (\s :: CreateActionResponse
s@CreateActionResponse' {} Maybe Text
a -> CreateActionResponse
s {$sel:actionArn:CreateActionResponse' :: Maybe Text
actionArn = Maybe Text
a} :: CreateActionResponse)

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

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