{-# 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.ActionTypeDeclaration
-- 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.ActionTypeDeclaration where

import Amazonka.CodePipeline.Types.ActionTypeArtifactDetails
import Amazonka.CodePipeline.Types.ActionTypeExecutor
import Amazonka.CodePipeline.Types.ActionTypeIdentifier
import Amazonka.CodePipeline.Types.ActionTypePermissions
import Amazonka.CodePipeline.Types.ActionTypeProperty
import Amazonka.CodePipeline.Types.ActionTypeUrls
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

-- | The parameters for the action type definition that are provided when the
-- action type is created or updated.
--
-- /See:/ 'newActionTypeDeclaration' smart constructor.
data ActionTypeDeclaration = ActionTypeDeclaration'
  { -- | The description for the action type to be updated.
    ActionTypeDeclaration -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | Details identifying the accounts with permissions to use the action
    -- type.
    ActionTypeDeclaration -> Maybe ActionTypePermissions
permissions :: Prelude.Maybe ActionTypePermissions,
    -- | The properties of the action type to be updated.
    ActionTypeDeclaration -> Maybe [ActionTypeProperty]
properties :: Prelude.Maybe [ActionTypeProperty],
    -- | The links associated with the action type to be updated.
    ActionTypeDeclaration -> Maybe ActionTypeUrls
urls :: Prelude.Maybe ActionTypeUrls,
    -- | Information about the executor for an action type that was created with
    -- any supported integration model.
    ActionTypeDeclaration -> ActionTypeExecutor
executor :: ActionTypeExecutor,
    -- | The action category, owner, provider, and version of the action type to
    -- be updated.
    ActionTypeDeclaration -> ActionTypeIdentifier
id :: ActionTypeIdentifier,
    -- | Details for the artifacts, such as application files, to be worked on by
    -- the action. For example, the minimum and maximum number of input
    -- artifacts allowed.
    ActionTypeDeclaration -> ActionTypeArtifactDetails
inputArtifactDetails :: ActionTypeArtifactDetails,
    -- | Details for the output artifacts, such as a built application, that are
    -- the result of the action. For example, the minimum and maximum number of
    -- output artifacts allowed.
    ActionTypeDeclaration -> ActionTypeArtifactDetails
outputArtifactDetails :: ActionTypeArtifactDetails
  }
  deriving (ActionTypeDeclaration -> ActionTypeDeclaration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ActionTypeDeclaration -> ActionTypeDeclaration -> Bool
$c/= :: ActionTypeDeclaration -> ActionTypeDeclaration -> Bool
== :: ActionTypeDeclaration -> ActionTypeDeclaration -> Bool
$c== :: ActionTypeDeclaration -> ActionTypeDeclaration -> Bool
Prelude.Eq, ReadPrec [ActionTypeDeclaration]
ReadPrec ActionTypeDeclaration
Int -> ReadS ActionTypeDeclaration
ReadS [ActionTypeDeclaration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ActionTypeDeclaration]
$creadListPrec :: ReadPrec [ActionTypeDeclaration]
readPrec :: ReadPrec ActionTypeDeclaration
$creadPrec :: ReadPrec ActionTypeDeclaration
readList :: ReadS [ActionTypeDeclaration]
$creadList :: ReadS [ActionTypeDeclaration]
readsPrec :: Int -> ReadS ActionTypeDeclaration
$creadsPrec :: Int -> ReadS ActionTypeDeclaration
Prelude.Read, Int -> ActionTypeDeclaration -> ShowS
[ActionTypeDeclaration] -> ShowS
ActionTypeDeclaration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ActionTypeDeclaration] -> ShowS
$cshowList :: [ActionTypeDeclaration] -> ShowS
show :: ActionTypeDeclaration -> String
$cshow :: ActionTypeDeclaration -> String
showsPrec :: Int -> ActionTypeDeclaration -> ShowS
$cshowsPrec :: Int -> ActionTypeDeclaration -> ShowS
Prelude.Show, forall x. Rep ActionTypeDeclaration x -> ActionTypeDeclaration
forall x. ActionTypeDeclaration -> Rep ActionTypeDeclaration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ActionTypeDeclaration x -> ActionTypeDeclaration
$cfrom :: forall x. ActionTypeDeclaration -> Rep ActionTypeDeclaration x
Prelude.Generic)

-- |
-- Create a value of 'ActionTypeDeclaration' 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', 'actionTypeDeclaration_description' - The description for the action type to be updated.
--
-- 'permissions', 'actionTypeDeclaration_permissions' - Details identifying the accounts with permissions to use the action
-- type.
--
-- 'properties', 'actionTypeDeclaration_properties' - The properties of the action type to be updated.
--
-- 'urls', 'actionTypeDeclaration_urls' - The links associated with the action type to be updated.
--
-- 'executor', 'actionTypeDeclaration_executor' - Information about the executor for an action type that was created with
-- any supported integration model.
--
-- 'id', 'actionTypeDeclaration_id' - The action category, owner, provider, and version of the action type to
-- be updated.
--
-- 'inputArtifactDetails', 'actionTypeDeclaration_inputArtifactDetails' - Details for the artifacts, such as application files, to be worked on by
-- the action. For example, the minimum and maximum number of input
-- artifacts allowed.
--
-- 'outputArtifactDetails', 'actionTypeDeclaration_outputArtifactDetails' - Details for the output artifacts, such as a built application, that are
-- the result of the action. For example, the minimum and maximum number of
-- output artifacts allowed.
newActionTypeDeclaration ::
  -- | 'executor'
  ActionTypeExecutor ->
  -- | 'id'
  ActionTypeIdentifier ->
  -- | 'inputArtifactDetails'
  ActionTypeArtifactDetails ->
  -- | 'outputArtifactDetails'
  ActionTypeArtifactDetails ->
  ActionTypeDeclaration
newActionTypeDeclaration :: ActionTypeExecutor
-> ActionTypeIdentifier
-> ActionTypeArtifactDetails
-> ActionTypeArtifactDetails
-> ActionTypeDeclaration
newActionTypeDeclaration
  ActionTypeExecutor
pExecutor_
  ActionTypeIdentifier
pId_
  ActionTypeArtifactDetails
pInputArtifactDetails_
  ActionTypeArtifactDetails
pOutputArtifactDetails_ =
    ActionTypeDeclaration'
      { $sel:description:ActionTypeDeclaration' :: Maybe Text
description =
          forall a. Maybe a
Prelude.Nothing,
        $sel:permissions:ActionTypeDeclaration' :: Maybe ActionTypePermissions
permissions = forall a. Maybe a
Prelude.Nothing,
        $sel:properties:ActionTypeDeclaration' :: Maybe [ActionTypeProperty]
properties = forall a. Maybe a
Prelude.Nothing,
        $sel:urls:ActionTypeDeclaration' :: Maybe ActionTypeUrls
urls = forall a. Maybe a
Prelude.Nothing,
        $sel:executor:ActionTypeDeclaration' :: ActionTypeExecutor
executor = ActionTypeExecutor
pExecutor_,
        $sel:id:ActionTypeDeclaration' :: ActionTypeIdentifier
id = ActionTypeIdentifier
pId_,
        $sel:inputArtifactDetails:ActionTypeDeclaration' :: ActionTypeArtifactDetails
inputArtifactDetails = ActionTypeArtifactDetails
pInputArtifactDetails_,
        $sel:outputArtifactDetails:ActionTypeDeclaration' :: ActionTypeArtifactDetails
outputArtifactDetails = ActionTypeArtifactDetails
pOutputArtifactDetails_
      }

-- | The description for the action type to be updated.
actionTypeDeclaration_description :: Lens.Lens' ActionTypeDeclaration (Prelude.Maybe Prelude.Text)
actionTypeDeclaration_description :: Lens' ActionTypeDeclaration (Maybe Text)
actionTypeDeclaration_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ActionTypeDeclaration' {Maybe Text
description :: Maybe Text
$sel:description:ActionTypeDeclaration' :: ActionTypeDeclaration -> Maybe Text
description} -> Maybe Text
description) (\s :: ActionTypeDeclaration
s@ActionTypeDeclaration' {} Maybe Text
a -> ActionTypeDeclaration
s {$sel:description:ActionTypeDeclaration' :: Maybe Text
description = Maybe Text
a} :: ActionTypeDeclaration)

-- | Details identifying the accounts with permissions to use the action
-- type.
actionTypeDeclaration_permissions :: Lens.Lens' ActionTypeDeclaration (Prelude.Maybe ActionTypePermissions)
actionTypeDeclaration_permissions :: Lens' ActionTypeDeclaration (Maybe ActionTypePermissions)
actionTypeDeclaration_permissions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ActionTypeDeclaration' {Maybe ActionTypePermissions
permissions :: Maybe ActionTypePermissions
$sel:permissions:ActionTypeDeclaration' :: ActionTypeDeclaration -> Maybe ActionTypePermissions
permissions} -> Maybe ActionTypePermissions
permissions) (\s :: ActionTypeDeclaration
s@ActionTypeDeclaration' {} Maybe ActionTypePermissions
a -> ActionTypeDeclaration
s {$sel:permissions:ActionTypeDeclaration' :: Maybe ActionTypePermissions
permissions = Maybe ActionTypePermissions
a} :: ActionTypeDeclaration)

-- | The properties of the action type to be updated.
actionTypeDeclaration_properties :: Lens.Lens' ActionTypeDeclaration (Prelude.Maybe [ActionTypeProperty])
actionTypeDeclaration_properties :: Lens' ActionTypeDeclaration (Maybe [ActionTypeProperty])
actionTypeDeclaration_properties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ActionTypeDeclaration' {Maybe [ActionTypeProperty]
properties :: Maybe [ActionTypeProperty]
$sel:properties:ActionTypeDeclaration' :: ActionTypeDeclaration -> Maybe [ActionTypeProperty]
properties} -> Maybe [ActionTypeProperty]
properties) (\s :: ActionTypeDeclaration
s@ActionTypeDeclaration' {} Maybe [ActionTypeProperty]
a -> ActionTypeDeclaration
s {$sel:properties:ActionTypeDeclaration' :: Maybe [ActionTypeProperty]
properties = Maybe [ActionTypeProperty]
a} :: ActionTypeDeclaration) 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 links associated with the action type to be updated.
actionTypeDeclaration_urls :: Lens.Lens' ActionTypeDeclaration (Prelude.Maybe ActionTypeUrls)
actionTypeDeclaration_urls :: Lens' ActionTypeDeclaration (Maybe ActionTypeUrls)
actionTypeDeclaration_urls = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ActionTypeDeclaration' {Maybe ActionTypeUrls
urls :: Maybe ActionTypeUrls
$sel:urls:ActionTypeDeclaration' :: ActionTypeDeclaration -> Maybe ActionTypeUrls
urls} -> Maybe ActionTypeUrls
urls) (\s :: ActionTypeDeclaration
s@ActionTypeDeclaration' {} Maybe ActionTypeUrls
a -> ActionTypeDeclaration
s {$sel:urls:ActionTypeDeclaration' :: Maybe ActionTypeUrls
urls = Maybe ActionTypeUrls
a} :: ActionTypeDeclaration)

-- | Information about the executor for an action type that was created with
-- any supported integration model.
actionTypeDeclaration_executor :: Lens.Lens' ActionTypeDeclaration ActionTypeExecutor
actionTypeDeclaration_executor :: Lens' ActionTypeDeclaration ActionTypeExecutor
actionTypeDeclaration_executor = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ActionTypeDeclaration' {ActionTypeExecutor
executor :: ActionTypeExecutor
$sel:executor:ActionTypeDeclaration' :: ActionTypeDeclaration -> ActionTypeExecutor
executor} -> ActionTypeExecutor
executor) (\s :: ActionTypeDeclaration
s@ActionTypeDeclaration' {} ActionTypeExecutor
a -> ActionTypeDeclaration
s {$sel:executor:ActionTypeDeclaration' :: ActionTypeExecutor
executor = ActionTypeExecutor
a} :: ActionTypeDeclaration)

-- | The action category, owner, provider, and version of the action type to
-- be updated.
actionTypeDeclaration_id :: Lens.Lens' ActionTypeDeclaration ActionTypeIdentifier
actionTypeDeclaration_id :: Lens' ActionTypeDeclaration ActionTypeIdentifier
actionTypeDeclaration_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ActionTypeDeclaration' {ActionTypeIdentifier
id :: ActionTypeIdentifier
$sel:id:ActionTypeDeclaration' :: ActionTypeDeclaration -> ActionTypeIdentifier
id} -> ActionTypeIdentifier
id) (\s :: ActionTypeDeclaration
s@ActionTypeDeclaration' {} ActionTypeIdentifier
a -> ActionTypeDeclaration
s {$sel:id:ActionTypeDeclaration' :: ActionTypeIdentifier
id = ActionTypeIdentifier
a} :: ActionTypeDeclaration)

-- | Details for the artifacts, such as application files, to be worked on by
-- the action. For example, the minimum and maximum number of input
-- artifacts allowed.
actionTypeDeclaration_inputArtifactDetails :: Lens.Lens' ActionTypeDeclaration ActionTypeArtifactDetails
actionTypeDeclaration_inputArtifactDetails :: Lens' ActionTypeDeclaration ActionTypeArtifactDetails
actionTypeDeclaration_inputArtifactDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ActionTypeDeclaration' {ActionTypeArtifactDetails
inputArtifactDetails :: ActionTypeArtifactDetails
$sel:inputArtifactDetails:ActionTypeDeclaration' :: ActionTypeDeclaration -> ActionTypeArtifactDetails
inputArtifactDetails} -> ActionTypeArtifactDetails
inputArtifactDetails) (\s :: ActionTypeDeclaration
s@ActionTypeDeclaration' {} ActionTypeArtifactDetails
a -> ActionTypeDeclaration
s {$sel:inputArtifactDetails:ActionTypeDeclaration' :: ActionTypeArtifactDetails
inputArtifactDetails = ActionTypeArtifactDetails
a} :: ActionTypeDeclaration)

-- | Details for the output artifacts, such as a built application, that are
-- the result of the action. For example, the minimum and maximum number of
-- output artifacts allowed.
actionTypeDeclaration_outputArtifactDetails :: Lens.Lens' ActionTypeDeclaration ActionTypeArtifactDetails
actionTypeDeclaration_outputArtifactDetails :: Lens' ActionTypeDeclaration ActionTypeArtifactDetails
actionTypeDeclaration_outputArtifactDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ActionTypeDeclaration' {ActionTypeArtifactDetails
outputArtifactDetails :: ActionTypeArtifactDetails
$sel:outputArtifactDetails:ActionTypeDeclaration' :: ActionTypeDeclaration -> ActionTypeArtifactDetails
outputArtifactDetails} -> ActionTypeArtifactDetails
outputArtifactDetails) (\s :: ActionTypeDeclaration
s@ActionTypeDeclaration' {} ActionTypeArtifactDetails
a -> ActionTypeDeclaration
s {$sel:outputArtifactDetails:ActionTypeDeclaration' :: ActionTypeArtifactDetails
outputArtifactDetails = ActionTypeArtifactDetails
a} :: ActionTypeDeclaration)

instance Data.FromJSON ActionTypeDeclaration where
  parseJSON :: Value -> Parser ActionTypeDeclaration
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"ActionTypeDeclaration"
      ( \Object
x ->
          Maybe Text
-> Maybe ActionTypePermissions
-> Maybe [ActionTypeProperty]
-> Maybe ActionTypeUrls
-> ActionTypeExecutor
-> ActionTypeIdentifier
-> ActionTypeArtifactDetails
-> ActionTypeArtifactDetails
-> ActionTypeDeclaration
ActionTypeDeclaration'
            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
"description")
            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
"permissions")
            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
"properties" 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
"urls")
            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
"executor")
            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
"id")
            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
"inputArtifactDetails")
            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
"outputArtifactDetails")
      )

instance Prelude.Hashable ActionTypeDeclaration where
  hashWithSalt :: Int -> ActionTypeDeclaration -> Int
hashWithSalt Int
_salt ActionTypeDeclaration' {Maybe [ActionTypeProperty]
Maybe Text
Maybe ActionTypePermissions
Maybe ActionTypeUrls
ActionTypeArtifactDetails
ActionTypeIdentifier
ActionTypeExecutor
outputArtifactDetails :: ActionTypeArtifactDetails
inputArtifactDetails :: ActionTypeArtifactDetails
id :: ActionTypeIdentifier
executor :: ActionTypeExecutor
urls :: Maybe ActionTypeUrls
properties :: Maybe [ActionTypeProperty]
permissions :: Maybe ActionTypePermissions
description :: Maybe Text
$sel:outputArtifactDetails:ActionTypeDeclaration' :: ActionTypeDeclaration -> ActionTypeArtifactDetails
$sel:inputArtifactDetails:ActionTypeDeclaration' :: ActionTypeDeclaration -> ActionTypeArtifactDetails
$sel:id:ActionTypeDeclaration' :: ActionTypeDeclaration -> ActionTypeIdentifier
$sel:executor:ActionTypeDeclaration' :: ActionTypeDeclaration -> ActionTypeExecutor
$sel:urls:ActionTypeDeclaration' :: ActionTypeDeclaration -> Maybe ActionTypeUrls
$sel:properties:ActionTypeDeclaration' :: ActionTypeDeclaration -> Maybe [ActionTypeProperty]
$sel:permissions:ActionTypeDeclaration' :: ActionTypeDeclaration -> Maybe ActionTypePermissions
$sel:description:ActionTypeDeclaration' :: ActionTypeDeclaration -> 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 ActionTypePermissions
permissions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [ActionTypeProperty]
properties
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ActionTypeUrls
urls
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ActionTypeExecutor
executor
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ActionTypeIdentifier
id
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ActionTypeArtifactDetails
inputArtifactDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ActionTypeArtifactDetails
outputArtifactDetails

instance Prelude.NFData ActionTypeDeclaration where
  rnf :: ActionTypeDeclaration -> ()
rnf ActionTypeDeclaration' {Maybe [ActionTypeProperty]
Maybe Text
Maybe ActionTypePermissions
Maybe ActionTypeUrls
ActionTypeArtifactDetails
ActionTypeIdentifier
ActionTypeExecutor
outputArtifactDetails :: ActionTypeArtifactDetails
inputArtifactDetails :: ActionTypeArtifactDetails
id :: ActionTypeIdentifier
executor :: ActionTypeExecutor
urls :: Maybe ActionTypeUrls
properties :: Maybe [ActionTypeProperty]
permissions :: Maybe ActionTypePermissions
description :: Maybe Text
$sel:outputArtifactDetails:ActionTypeDeclaration' :: ActionTypeDeclaration -> ActionTypeArtifactDetails
$sel:inputArtifactDetails:ActionTypeDeclaration' :: ActionTypeDeclaration -> ActionTypeArtifactDetails
$sel:id:ActionTypeDeclaration' :: ActionTypeDeclaration -> ActionTypeIdentifier
$sel:executor:ActionTypeDeclaration' :: ActionTypeDeclaration -> ActionTypeExecutor
$sel:urls:ActionTypeDeclaration' :: ActionTypeDeclaration -> Maybe ActionTypeUrls
$sel:properties:ActionTypeDeclaration' :: ActionTypeDeclaration -> Maybe [ActionTypeProperty]
$sel:permissions:ActionTypeDeclaration' :: ActionTypeDeclaration -> Maybe ActionTypePermissions
$sel:description:ActionTypeDeclaration' :: ActionTypeDeclaration -> 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 ActionTypePermissions
permissions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ActionTypeProperty]
properties
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ActionTypeUrls
urls
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ActionTypeExecutor
executor
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ActionTypeIdentifier
id
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ActionTypeArtifactDetails
inputArtifactDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ActionTypeArtifactDetails
outputArtifactDetails

instance Data.ToJSON ActionTypeDeclaration where
  toJSON :: ActionTypeDeclaration -> Value
toJSON ActionTypeDeclaration' {Maybe [ActionTypeProperty]
Maybe Text
Maybe ActionTypePermissions
Maybe ActionTypeUrls
ActionTypeArtifactDetails
ActionTypeIdentifier
ActionTypeExecutor
outputArtifactDetails :: ActionTypeArtifactDetails
inputArtifactDetails :: ActionTypeArtifactDetails
id :: ActionTypeIdentifier
executor :: ActionTypeExecutor
urls :: Maybe ActionTypeUrls
properties :: Maybe [ActionTypeProperty]
permissions :: Maybe ActionTypePermissions
description :: Maybe Text
$sel:outputArtifactDetails:ActionTypeDeclaration' :: ActionTypeDeclaration -> ActionTypeArtifactDetails
$sel:inputArtifactDetails:ActionTypeDeclaration' :: ActionTypeDeclaration -> ActionTypeArtifactDetails
$sel:id:ActionTypeDeclaration' :: ActionTypeDeclaration -> ActionTypeIdentifier
$sel:executor:ActionTypeDeclaration' :: ActionTypeDeclaration -> ActionTypeExecutor
$sel:urls:ActionTypeDeclaration' :: ActionTypeDeclaration -> Maybe ActionTypeUrls
$sel:properties:ActionTypeDeclaration' :: ActionTypeDeclaration -> Maybe [ActionTypeProperty]
$sel:permissions:ActionTypeDeclaration' :: ActionTypeDeclaration -> Maybe ActionTypePermissions
$sel:description:ActionTypeDeclaration' :: ActionTypeDeclaration -> 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
"permissions" 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 ActionTypePermissions
permissions,
            (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 [ActionTypeProperty]
properties,
            (Key
"urls" 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 ActionTypeUrls
urls,
            forall a. a -> Maybe a
Prelude.Just (Key
"executor" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ActionTypeExecutor
executor),
            forall a. a -> Maybe a
Prelude.Just (Key
"id" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ActionTypeIdentifier
id),
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"inputArtifactDetails"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ActionTypeArtifactDetails
inputArtifactDetails
              ),
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"outputArtifactDetails"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ActionTypeArtifactDetails
outputArtifactDetails
              )
          ]
      )