{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.CodePipeline.Types.ActionDeclaration
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.CodePipeline.Types.ActionDeclaration where

import Amazonka.CodePipeline.Types.ActionTypeId
import Amazonka.CodePipeline.Types.InputArtifact
import Amazonka.CodePipeline.Types.OutputArtifact
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

-- | Represents information about an action declaration.
--
-- /See:/ 'newActionDeclaration' smart constructor.
data ActionDeclaration = ActionDeclaration'
  { -- | The action\'s configuration. These are key-value pairs that specify
    -- input values for an action. For more information, see
    -- <https://docs.aws.amazon.com/codepipeline/latest/userguide/reference-pipeline-structure.html#action-requirements Action Structure Requirements in CodePipeline>.
    -- For the list of configuration properties for the AWS CloudFormation
    -- action type in CodePipeline, see
    -- <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/continuous-delivery-codepipeline-action-reference.html Configuration Properties Reference>
    -- in the /AWS CloudFormation User Guide/. For template snippets with
    -- examples, see
    -- <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/continuous-delivery-codepipeline-parameter-override-functions.html Using Parameter Override Functions with CodePipeline Pipelines>
    -- in the /AWS CloudFormation User Guide/.
    --
    -- The values can be represented in either JSON or YAML format. For
    -- example, the JSON configuration item format is as follows:
    --
    -- /JSON:/
    --
    -- @\"Configuration\" : { Key : Value },@
    ActionDeclaration -> Maybe (HashMap Text Text)
configuration :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The name or ID of the artifact consumed by the action, such as a test or
    -- build artifact.
    ActionDeclaration -> Maybe [InputArtifact]
inputArtifacts :: Prelude.Maybe [InputArtifact],
    -- | The variable namespace associated with the action. All variables
    -- produced as output by this action fall under this namespace.
    ActionDeclaration -> Maybe Text
namespace :: Prelude.Maybe Prelude.Text,
    -- | The name or ID of the result of the action declaration, such as a test
    -- or build artifact.
    ActionDeclaration -> Maybe [OutputArtifact]
outputArtifacts :: Prelude.Maybe [OutputArtifact],
    -- | The action declaration\'s AWS Region, such as us-east-1.
    ActionDeclaration -> Maybe Text
region :: Prelude.Maybe Prelude.Text,
    -- | The ARN of the IAM service role that performs the declared action. This
    -- is assumed through the roleArn for the pipeline.
    ActionDeclaration -> Maybe Text
roleArn :: Prelude.Maybe Prelude.Text,
    -- | The order in which actions are run.
    ActionDeclaration -> Maybe Natural
runOrder :: Prelude.Maybe Prelude.Natural,
    -- | The action declaration\'s name.
    ActionDeclaration -> Text
name :: Prelude.Text,
    -- | Specifies the action type and the provider of the action.
    ActionDeclaration -> ActionTypeId
actionTypeId :: ActionTypeId
  }
  deriving (ActionDeclaration -> ActionDeclaration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ActionDeclaration -> ActionDeclaration -> Bool
$c/= :: ActionDeclaration -> ActionDeclaration -> Bool
== :: ActionDeclaration -> ActionDeclaration -> Bool
$c== :: ActionDeclaration -> ActionDeclaration -> Bool
Prelude.Eq, ReadPrec [ActionDeclaration]
ReadPrec ActionDeclaration
Int -> ReadS ActionDeclaration
ReadS [ActionDeclaration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ActionDeclaration]
$creadListPrec :: ReadPrec [ActionDeclaration]
readPrec :: ReadPrec ActionDeclaration
$creadPrec :: ReadPrec ActionDeclaration
readList :: ReadS [ActionDeclaration]
$creadList :: ReadS [ActionDeclaration]
readsPrec :: Int -> ReadS ActionDeclaration
$creadsPrec :: Int -> ReadS ActionDeclaration
Prelude.Read, Int -> ActionDeclaration -> ShowS
[ActionDeclaration] -> ShowS
ActionDeclaration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ActionDeclaration] -> ShowS
$cshowList :: [ActionDeclaration] -> ShowS
show :: ActionDeclaration -> String
$cshow :: ActionDeclaration -> String
showsPrec :: Int -> ActionDeclaration -> ShowS
$cshowsPrec :: Int -> ActionDeclaration -> ShowS
Prelude.Show, forall x. Rep ActionDeclaration x -> ActionDeclaration
forall x. ActionDeclaration -> Rep ActionDeclaration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ActionDeclaration x -> ActionDeclaration
$cfrom :: forall x. ActionDeclaration -> Rep ActionDeclaration x
Prelude.Generic)

-- |
-- Create a value of 'ActionDeclaration' 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:
--
-- 'configuration', 'actionDeclaration_configuration' - The action\'s configuration. These are key-value pairs that specify
-- input values for an action. For more information, see
-- <https://docs.aws.amazon.com/codepipeline/latest/userguide/reference-pipeline-structure.html#action-requirements Action Structure Requirements in CodePipeline>.
-- For the list of configuration properties for the AWS CloudFormation
-- action type in CodePipeline, see
-- <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/continuous-delivery-codepipeline-action-reference.html Configuration Properties Reference>
-- in the /AWS CloudFormation User Guide/. For template snippets with
-- examples, see
-- <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/continuous-delivery-codepipeline-parameter-override-functions.html Using Parameter Override Functions with CodePipeline Pipelines>
-- in the /AWS CloudFormation User Guide/.
--
-- The values can be represented in either JSON or YAML format. For
-- example, the JSON configuration item format is as follows:
--
-- /JSON:/
--
-- @\"Configuration\" : { Key : Value },@
--
-- 'inputArtifacts', 'actionDeclaration_inputArtifacts' - The name or ID of the artifact consumed by the action, such as a test or
-- build artifact.
--
-- 'namespace', 'actionDeclaration_namespace' - The variable namespace associated with the action. All variables
-- produced as output by this action fall under this namespace.
--
-- 'outputArtifacts', 'actionDeclaration_outputArtifacts' - The name or ID of the result of the action declaration, such as a test
-- or build artifact.
--
-- 'region', 'actionDeclaration_region' - The action declaration\'s AWS Region, such as us-east-1.
--
-- 'roleArn', 'actionDeclaration_roleArn' - The ARN of the IAM service role that performs the declared action. This
-- is assumed through the roleArn for the pipeline.
--
-- 'runOrder', 'actionDeclaration_runOrder' - The order in which actions are run.
--
-- 'name', 'actionDeclaration_name' - The action declaration\'s name.
--
-- 'actionTypeId', 'actionDeclaration_actionTypeId' - Specifies the action type and the provider of the action.
newActionDeclaration ::
  -- | 'name'
  Prelude.Text ->
  -- | 'actionTypeId'
  ActionTypeId ->
  ActionDeclaration
newActionDeclaration :: Text -> ActionTypeId -> ActionDeclaration
newActionDeclaration Text
pName_ ActionTypeId
pActionTypeId_ =
  ActionDeclaration'
    { $sel:configuration:ActionDeclaration' :: Maybe (HashMap Text Text)
configuration = forall a. Maybe a
Prelude.Nothing,
      $sel:inputArtifacts:ActionDeclaration' :: Maybe [InputArtifact]
inputArtifacts = forall a. Maybe a
Prelude.Nothing,
      $sel:namespace:ActionDeclaration' :: Maybe Text
namespace = forall a. Maybe a
Prelude.Nothing,
      $sel:outputArtifacts:ActionDeclaration' :: Maybe [OutputArtifact]
outputArtifacts = forall a. Maybe a
Prelude.Nothing,
      $sel:region:ActionDeclaration' :: Maybe Text
region = forall a. Maybe a
Prelude.Nothing,
      $sel:roleArn:ActionDeclaration' :: Maybe Text
roleArn = forall a. Maybe a
Prelude.Nothing,
      $sel:runOrder:ActionDeclaration' :: Maybe Natural
runOrder = forall a. Maybe a
Prelude.Nothing,
      $sel:name:ActionDeclaration' :: Text
name = Text
pName_,
      $sel:actionTypeId:ActionDeclaration' :: ActionTypeId
actionTypeId = ActionTypeId
pActionTypeId_
    }

-- | The action\'s configuration. These are key-value pairs that specify
-- input values for an action. For more information, see
-- <https://docs.aws.amazon.com/codepipeline/latest/userguide/reference-pipeline-structure.html#action-requirements Action Structure Requirements in CodePipeline>.
-- For the list of configuration properties for the AWS CloudFormation
-- action type in CodePipeline, see
-- <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/continuous-delivery-codepipeline-action-reference.html Configuration Properties Reference>
-- in the /AWS CloudFormation User Guide/. For template snippets with
-- examples, see
-- <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/continuous-delivery-codepipeline-parameter-override-functions.html Using Parameter Override Functions with CodePipeline Pipelines>
-- in the /AWS CloudFormation User Guide/.
--
-- The values can be represented in either JSON or YAML format. For
-- example, the JSON configuration item format is as follows:
--
-- /JSON:/
--
-- @\"Configuration\" : { Key : Value },@
actionDeclaration_configuration :: Lens.Lens' ActionDeclaration (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
actionDeclaration_configuration :: Lens' ActionDeclaration (Maybe (HashMap Text Text))
actionDeclaration_configuration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ActionDeclaration' {Maybe (HashMap Text Text)
configuration :: Maybe (HashMap Text Text)
$sel:configuration:ActionDeclaration' :: ActionDeclaration -> Maybe (HashMap Text Text)
configuration} -> Maybe (HashMap Text Text)
configuration) (\s :: ActionDeclaration
s@ActionDeclaration' {} Maybe (HashMap Text Text)
a -> ActionDeclaration
s {$sel:configuration:ActionDeclaration' :: Maybe (HashMap Text Text)
configuration = Maybe (HashMap Text Text)
a} :: ActionDeclaration) 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 or ID of the artifact consumed by the action, such as a test or
-- build artifact.
actionDeclaration_inputArtifacts :: Lens.Lens' ActionDeclaration (Prelude.Maybe [InputArtifact])
actionDeclaration_inputArtifacts :: Lens' ActionDeclaration (Maybe [InputArtifact])
actionDeclaration_inputArtifacts = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ActionDeclaration' {Maybe [InputArtifact]
inputArtifacts :: Maybe [InputArtifact]
$sel:inputArtifacts:ActionDeclaration' :: ActionDeclaration -> Maybe [InputArtifact]
inputArtifacts} -> Maybe [InputArtifact]
inputArtifacts) (\s :: ActionDeclaration
s@ActionDeclaration' {} Maybe [InputArtifact]
a -> ActionDeclaration
s {$sel:inputArtifacts:ActionDeclaration' :: Maybe [InputArtifact]
inputArtifacts = Maybe [InputArtifact]
a} :: ActionDeclaration) 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 variable namespace associated with the action. All variables
-- produced as output by this action fall under this namespace.
actionDeclaration_namespace :: Lens.Lens' ActionDeclaration (Prelude.Maybe Prelude.Text)
actionDeclaration_namespace :: Lens' ActionDeclaration (Maybe Text)
actionDeclaration_namespace = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ActionDeclaration' {Maybe Text
namespace :: Maybe Text
$sel:namespace:ActionDeclaration' :: ActionDeclaration -> Maybe Text
namespace} -> Maybe Text
namespace) (\s :: ActionDeclaration
s@ActionDeclaration' {} Maybe Text
a -> ActionDeclaration
s {$sel:namespace:ActionDeclaration' :: Maybe Text
namespace = Maybe Text
a} :: ActionDeclaration)

-- | The name or ID of the result of the action declaration, such as a test
-- or build artifact.
actionDeclaration_outputArtifacts :: Lens.Lens' ActionDeclaration (Prelude.Maybe [OutputArtifact])
actionDeclaration_outputArtifacts :: Lens' ActionDeclaration (Maybe [OutputArtifact])
actionDeclaration_outputArtifacts = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ActionDeclaration' {Maybe [OutputArtifact]
outputArtifacts :: Maybe [OutputArtifact]
$sel:outputArtifacts:ActionDeclaration' :: ActionDeclaration -> Maybe [OutputArtifact]
outputArtifacts} -> Maybe [OutputArtifact]
outputArtifacts) (\s :: ActionDeclaration
s@ActionDeclaration' {} Maybe [OutputArtifact]
a -> ActionDeclaration
s {$sel:outputArtifacts:ActionDeclaration' :: Maybe [OutputArtifact]
outputArtifacts = Maybe [OutputArtifact]
a} :: ActionDeclaration) 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 action declaration\'s AWS Region, such as us-east-1.
actionDeclaration_region :: Lens.Lens' ActionDeclaration (Prelude.Maybe Prelude.Text)
actionDeclaration_region :: Lens' ActionDeclaration (Maybe Text)
actionDeclaration_region = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ActionDeclaration' {Maybe Text
region :: Maybe Text
$sel:region:ActionDeclaration' :: ActionDeclaration -> Maybe Text
region} -> Maybe Text
region) (\s :: ActionDeclaration
s@ActionDeclaration' {} Maybe Text
a -> ActionDeclaration
s {$sel:region:ActionDeclaration' :: Maybe Text
region = Maybe Text
a} :: ActionDeclaration)

-- | The ARN of the IAM service role that performs the declared action. This
-- is assumed through the roleArn for the pipeline.
actionDeclaration_roleArn :: Lens.Lens' ActionDeclaration (Prelude.Maybe Prelude.Text)
actionDeclaration_roleArn :: Lens' ActionDeclaration (Maybe Text)
actionDeclaration_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ActionDeclaration' {Maybe Text
roleArn :: Maybe Text
$sel:roleArn:ActionDeclaration' :: ActionDeclaration -> Maybe Text
roleArn} -> Maybe Text
roleArn) (\s :: ActionDeclaration
s@ActionDeclaration' {} Maybe Text
a -> ActionDeclaration
s {$sel:roleArn:ActionDeclaration' :: Maybe Text
roleArn = Maybe Text
a} :: ActionDeclaration)

-- | The order in which actions are run.
actionDeclaration_runOrder :: Lens.Lens' ActionDeclaration (Prelude.Maybe Prelude.Natural)
actionDeclaration_runOrder :: Lens' ActionDeclaration (Maybe Natural)
actionDeclaration_runOrder = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ActionDeclaration' {Maybe Natural
runOrder :: Maybe Natural
$sel:runOrder:ActionDeclaration' :: ActionDeclaration -> Maybe Natural
runOrder} -> Maybe Natural
runOrder) (\s :: ActionDeclaration
s@ActionDeclaration' {} Maybe Natural
a -> ActionDeclaration
s {$sel:runOrder:ActionDeclaration' :: Maybe Natural
runOrder = Maybe Natural
a} :: ActionDeclaration)

-- | The action declaration\'s name.
actionDeclaration_name :: Lens.Lens' ActionDeclaration Prelude.Text
actionDeclaration_name :: Lens' ActionDeclaration Text
actionDeclaration_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ActionDeclaration' {Text
name :: Text
$sel:name:ActionDeclaration' :: ActionDeclaration -> Text
name} -> Text
name) (\s :: ActionDeclaration
s@ActionDeclaration' {} Text
a -> ActionDeclaration
s {$sel:name:ActionDeclaration' :: Text
name = Text
a} :: ActionDeclaration)

-- | Specifies the action type and the provider of the action.
actionDeclaration_actionTypeId :: Lens.Lens' ActionDeclaration ActionTypeId
actionDeclaration_actionTypeId :: Lens' ActionDeclaration ActionTypeId
actionDeclaration_actionTypeId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ActionDeclaration' {ActionTypeId
actionTypeId :: ActionTypeId
$sel:actionTypeId:ActionDeclaration' :: ActionDeclaration -> ActionTypeId
actionTypeId} -> ActionTypeId
actionTypeId) (\s :: ActionDeclaration
s@ActionDeclaration' {} ActionTypeId
a -> ActionDeclaration
s {$sel:actionTypeId:ActionDeclaration' :: ActionTypeId
actionTypeId = ActionTypeId
a} :: ActionDeclaration)

instance Data.FromJSON ActionDeclaration where
  parseJSON :: Value -> Parser ActionDeclaration
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"ActionDeclaration"
      ( \Object
x ->
          Maybe (HashMap Text Text)
-> Maybe [InputArtifact]
-> Maybe Text
-> Maybe [OutputArtifact]
-> Maybe Text
-> Maybe Text
-> Maybe Natural
-> Text
-> ActionTypeId
-> ActionDeclaration
ActionDeclaration'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"configuration" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"inputArtifacts" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"namespace")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"outputArtifacts"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"region")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"roleArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"runOrder")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"name")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"actionTypeId")
      )

instance Prelude.Hashable ActionDeclaration where
  hashWithSalt :: Int -> ActionDeclaration -> Int
hashWithSalt Int
_salt ActionDeclaration' {Maybe Natural
Maybe [InputArtifact]
Maybe [OutputArtifact]
Maybe Text
Maybe (HashMap Text Text)
Text
ActionTypeId
actionTypeId :: ActionTypeId
name :: Text
runOrder :: Maybe Natural
roleArn :: Maybe Text
region :: Maybe Text
outputArtifacts :: Maybe [OutputArtifact]
namespace :: Maybe Text
inputArtifacts :: Maybe [InputArtifact]
configuration :: Maybe (HashMap Text Text)
$sel:actionTypeId:ActionDeclaration' :: ActionDeclaration -> ActionTypeId
$sel:name:ActionDeclaration' :: ActionDeclaration -> Text
$sel:runOrder:ActionDeclaration' :: ActionDeclaration -> Maybe Natural
$sel:roleArn:ActionDeclaration' :: ActionDeclaration -> Maybe Text
$sel:region:ActionDeclaration' :: ActionDeclaration -> Maybe Text
$sel:outputArtifacts:ActionDeclaration' :: ActionDeclaration -> Maybe [OutputArtifact]
$sel:namespace:ActionDeclaration' :: ActionDeclaration -> Maybe Text
$sel:inputArtifacts:ActionDeclaration' :: ActionDeclaration -> Maybe [InputArtifact]
$sel:configuration:ActionDeclaration' :: ActionDeclaration -> Maybe (HashMap Text Text)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
configuration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [InputArtifact]
inputArtifacts
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
namespace
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [OutputArtifact]
outputArtifacts
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
region
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
roleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
runOrder
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ActionTypeId
actionTypeId

instance Prelude.NFData ActionDeclaration where
  rnf :: ActionDeclaration -> ()
rnf ActionDeclaration' {Maybe Natural
Maybe [InputArtifact]
Maybe [OutputArtifact]
Maybe Text
Maybe (HashMap Text Text)
Text
ActionTypeId
actionTypeId :: ActionTypeId
name :: Text
runOrder :: Maybe Natural
roleArn :: Maybe Text
region :: Maybe Text
outputArtifacts :: Maybe [OutputArtifact]
namespace :: Maybe Text
inputArtifacts :: Maybe [InputArtifact]
configuration :: Maybe (HashMap Text Text)
$sel:actionTypeId:ActionDeclaration' :: ActionDeclaration -> ActionTypeId
$sel:name:ActionDeclaration' :: ActionDeclaration -> Text
$sel:runOrder:ActionDeclaration' :: ActionDeclaration -> Maybe Natural
$sel:roleArn:ActionDeclaration' :: ActionDeclaration -> Maybe Text
$sel:region:ActionDeclaration' :: ActionDeclaration -> Maybe Text
$sel:outputArtifacts:ActionDeclaration' :: ActionDeclaration -> Maybe [OutputArtifact]
$sel:namespace:ActionDeclaration' :: ActionDeclaration -> Maybe Text
$sel:inputArtifacts:ActionDeclaration' :: ActionDeclaration -> Maybe [InputArtifact]
$sel:configuration:ActionDeclaration' :: ActionDeclaration -> Maybe (HashMap Text Text)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
configuration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [InputArtifact]
inputArtifacts
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
namespace
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [OutputArtifact]
outputArtifacts
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
region
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
roleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
runOrder
      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 ActionTypeId
actionTypeId

instance Data.ToJSON ActionDeclaration where
  toJSON :: ActionDeclaration -> Value
toJSON ActionDeclaration' {Maybe Natural
Maybe [InputArtifact]
Maybe [OutputArtifact]
Maybe Text
Maybe (HashMap Text Text)
Text
ActionTypeId
actionTypeId :: ActionTypeId
name :: Text
runOrder :: Maybe Natural
roleArn :: Maybe Text
region :: Maybe Text
outputArtifacts :: Maybe [OutputArtifact]
namespace :: Maybe Text
inputArtifacts :: Maybe [InputArtifact]
configuration :: Maybe (HashMap Text Text)
$sel:actionTypeId:ActionDeclaration' :: ActionDeclaration -> ActionTypeId
$sel:name:ActionDeclaration' :: ActionDeclaration -> Text
$sel:runOrder:ActionDeclaration' :: ActionDeclaration -> Maybe Natural
$sel:roleArn:ActionDeclaration' :: ActionDeclaration -> Maybe Text
$sel:region:ActionDeclaration' :: ActionDeclaration -> Maybe Text
$sel:outputArtifacts:ActionDeclaration' :: ActionDeclaration -> Maybe [OutputArtifact]
$sel:namespace:ActionDeclaration' :: ActionDeclaration -> Maybe Text
$sel:inputArtifacts:ActionDeclaration' :: ActionDeclaration -> Maybe [InputArtifact]
$sel:configuration:ActionDeclaration' :: ActionDeclaration -> Maybe (HashMap Text Text)
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"configuration" 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)
configuration,
            (Key
"inputArtifacts" 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 [InputArtifact]
inputArtifacts,
            (Key
"namespace" 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
namespace,
            (Key
"outputArtifacts" 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 [OutputArtifact]
outputArtifacts,
            (Key
"region" 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
region,
            (Key
"roleArn" 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
roleArn,
            (Key
"runOrder" 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 Natural
runOrder,
            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
"actionTypeId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ActionTypeId
actionTypeId)
          ]
      )