{-# 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.AmplifyUiBuilder.Types.ActionParameters
-- 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.AmplifyUiBuilder.Types.ActionParameters where

import Amazonka.AmplifyUiBuilder.Types.ComponentProperty
import Amazonka.AmplifyUiBuilder.Types.MutationActionSetStateParameter
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 the event action configuration for an element of a
-- @Component@ or @ComponentChild@. Use for the workflow feature in Amplify
-- Studio that allows you to bind events and actions to components.
-- @ActionParameters@ defines the action that is performed when an event
-- occurs on the component.
--
-- /See:/ 'newActionParameters' smart constructor.
data ActionParameters = ActionParameters'
  { -- | The HTML anchor link to the location to open. Specify this value for a
    -- navigation action.
    ActionParameters -> Maybe ComponentProperty
anchor :: Prelude.Maybe ComponentProperty,
    -- | A dictionary of key-value pairs mapping Amplify Studio properties to
    -- fields in a data model. Use when the action performs an operation on an
    -- Amplify DataStore model.
    ActionParameters -> Maybe (HashMap Text ComponentProperty)
fields :: Prelude.Maybe (Prelude.HashMap Prelude.Text ComponentProperty),
    -- | Specifies whether the user should be signed out globally. Specify this
    -- value for an auth sign out action.
    ActionParameters -> Maybe ComponentProperty
global :: Prelude.Maybe ComponentProperty,
    -- | The unique ID of the component that the @ActionParameters@ apply to.
    ActionParameters -> Maybe ComponentProperty
id :: Prelude.Maybe ComponentProperty,
    -- | The name of the data model. Use when the action performs an operation on
    -- an Amplify DataStore model.
    ActionParameters -> Maybe Text
model :: Prelude.Maybe Prelude.Text,
    -- | A key-value pair that specifies the state property name and its initial
    -- value.
    ActionParameters -> Maybe MutationActionSetStateParameter
state :: Prelude.Maybe MutationActionSetStateParameter,
    -- | The element within the same component to modify when the action occurs.
    ActionParameters -> Maybe ComponentProperty
target :: Prelude.Maybe ComponentProperty,
    -- | The type of navigation action. Valid values are @url@ and @anchor@. This
    -- value is required for a navigation action.
    ActionParameters -> Maybe ComponentProperty
type' :: Prelude.Maybe ComponentProperty,
    -- | The URL to the location to open. Specify this value for a navigation
    -- action.
    ActionParameters -> Maybe ComponentProperty
url :: Prelude.Maybe ComponentProperty
  }
  deriving (ActionParameters -> ActionParameters -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ActionParameters -> ActionParameters -> Bool
$c/= :: ActionParameters -> ActionParameters -> Bool
== :: ActionParameters -> ActionParameters -> Bool
$c== :: ActionParameters -> ActionParameters -> Bool
Prelude.Eq, ReadPrec [ActionParameters]
ReadPrec ActionParameters
Int -> ReadS ActionParameters
ReadS [ActionParameters]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ActionParameters]
$creadListPrec :: ReadPrec [ActionParameters]
readPrec :: ReadPrec ActionParameters
$creadPrec :: ReadPrec ActionParameters
readList :: ReadS [ActionParameters]
$creadList :: ReadS [ActionParameters]
readsPrec :: Int -> ReadS ActionParameters
$creadsPrec :: Int -> ReadS ActionParameters
Prelude.Read, Int -> ActionParameters -> ShowS
[ActionParameters] -> ShowS
ActionParameters -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ActionParameters] -> ShowS
$cshowList :: [ActionParameters] -> ShowS
show :: ActionParameters -> String
$cshow :: ActionParameters -> String
showsPrec :: Int -> ActionParameters -> ShowS
$cshowsPrec :: Int -> ActionParameters -> ShowS
Prelude.Show, forall x. Rep ActionParameters x -> ActionParameters
forall x. ActionParameters -> Rep ActionParameters x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ActionParameters x -> ActionParameters
$cfrom :: forall x. ActionParameters -> Rep ActionParameters x
Prelude.Generic)

-- |
-- Create a value of 'ActionParameters' 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:
--
-- 'anchor', 'actionParameters_anchor' - The HTML anchor link to the location to open. Specify this value for a
-- navigation action.
--
-- 'fields', 'actionParameters_fields' - A dictionary of key-value pairs mapping Amplify Studio properties to
-- fields in a data model. Use when the action performs an operation on an
-- Amplify DataStore model.
--
-- 'global', 'actionParameters_global' - Specifies whether the user should be signed out globally. Specify this
-- value for an auth sign out action.
--
-- 'id', 'actionParameters_id' - The unique ID of the component that the @ActionParameters@ apply to.
--
-- 'model', 'actionParameters_model' - The name of the data model. Use when the action performs an operation on
-- an Amplify DataStore model.
--
-- 'state', 'actionParameters_state' - A key-value pair that specifies the state property name and its initial
-- value.
--
-- 'target', 'actionParameters_target' - The element within the same component to modify when the action occurs.
--
-- 'type'', 'actionParameters_type' - The type of navigation action. Valid values are @url@ and @anchor@. This
-- value is required for a navigation action.
--
-- 'url', 'actionParameters_url' - The URL to the location to open. Specify this value for a navigation
-- action.
newActionParameters ::
  ActionParameters
newActionParameters :: ActionParameters
newActionParameters =
  ActionParameters'
    { $sel:anchor:ActionParameters' :: Maybe ComponentProperty
anchor = forall a. Maybe a
Prelude.Nothing,
      $sel:fields:ActionParameters' :: Maybe (HashMap Text ComponentProperty)
fields = forall a. Maybe a
Prelude.Nothing,
      $sel:global:ActionParameters' :: Maybe ComponentProperty
global = forall a. Maybe a
Prelude.Nothing,
      $sel:id:ActionParameters' :: Maybe ComponentProperty
id = forall a. Maybe a
Prelude.Nothing,
      $sel:model:ActionParameters' :: Maybe Text
model = forall a. Maybe a
Prelude.Nothing,
      $sel:state:ActionParameters' :: Maybe MutationActionSetStateParameter
state = forall a. Maybe a
Prelude.Nothing,
      $sel:target:ActionParameters' :: Maybe ComponentProperty
target = forall a. Maybe a
Prelude.Nothing,
      $sel:type':ActionParameters' :: Maybe ComponentProperty
type' = forall a. Maybe a
Prelude.Nothing,
      $sel:url:ActionParameters' :: Maybe ComponentProperty
url = forall a. Maybe a
Prelude.Nothing
    }

-- | The HTML anchor link to the location to open. Specify this value for a
-- navigation action.
actionParameters_anchor :: Lens.Lens' ActionParameters (Prelude.Maybe ComponentProperty)
actionParameters_anchor :: Lens' ActionParameters (Maybe ComponentProperty)
actionParameters_anchor = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ActionParameters' {Maybe ComponentProperty
anchor :: Maybe ComponentProperty
$sel:anchor:ActionParameters' :: ActionParameters -> Maybe ComponentProperty
anchor} -> Maybe ComponentProperty
anchor) (\s :: ActionParameters
s@ActionParameters' {} Maybe ComponentProperty
a -> ActionParameters
s {$sel:anchor:ActionParameters' :: Maybe ComponentProperty
anchor = Maybe ComponentProperty
a} :: ActionParameters)

-- | A dictionary of key-value pairs mapping Amplify Studio properties to
-- fields in a data model. Use when the action performs an operation on an
-- Amplify DataStore model.
actionParameters_fields :: Lens.Lens' ActionParameters (Prelude.Maybe (Prelude.HashMap Prelude.Text ComponentProperty))
actionParameters_fields :: Lens' ActionParameters (Maybe (HashMap Text ComponentProperty))
actionParameters_fields = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ActionParameters' {Maybe (HashMap Text ComponentProperty)
fields :: Maybe (HashMap Text ComponentProperty)
$sel:fields:ActionParameters' :: ActionParameters -> Maybe (HashMap Text ComponentProperty)
fields} -> Maybe (HashMap Text ComponentProperty)
fields) (\s :: ActionParameters
s@ActionParameters' {} Maybe (HashMap Text ComponentProperty)
a -> ActionParameters
s {$sel:fields:ActionParameters' :: Maybe (HashMap Text ComponentProperty)
fields = Maybe (HashMap Text ComponentProperty)
a} :: ActionParameters) 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

-- | Specifies whether the user should be signed out globally. Specify this
-- value for an auth sign out action.
actionParameters_global :: Lens.Lens' ActionParameters (Prelude.Maybe ComponentProperty)
actionParameters_global :: Lens' ActionParameters (Maybe ComponentProperty)
actionParameters_global = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ActionParameters' {Maybe ComponentProperty
global :: Maybe ComponentProperty
$sel:global:ActionParameters' :: ActionParameters -> Maybe ComponentProperty
global} -> Maybe ComponentProperty
global) (\s :: ActionParameters
s@ActionParameters' {} Maybe ComponentProperty
a -> ActionParameters
s {$sel:global:ActionParameters' :: Maybe ComponentProperty
global = Maybe ComponentProperty
a} :: ActionParameters)

-- | The unique ID of the component that the @ActionParameters@ apply to.
actionParameters_id :: Lens.Lens' ActionParameters (Prelude.Maybe ComponentProperty)
actionParameters_id :: Lens' ActionParameters (Maybe ComponentProperty)
actionParameters_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ActionParameters' {Maybe ComponentProperty
id :: Maybe ComponentProperty
$sel:id:ActionParameters' :: ActionParameters -> Maybe ComponentProperty
id} -> Maybe ComponentProperty
id) (\s :: ActionParameters
s@ActionParameters' {} Maybe ComponentProperty
a -> ActionParameters
s {$sel:id:ActionParameters' :: Maybe ComponentProperty
id = Maybe ComponentProperty
a} :: ActionParameters)

-- | The name of the data model. Use when the action performs an operation on
-- an Amplify DataStore model.
actionParameters_model :: Lens.Lens' ActionParameters (Prelude.Maybe Prelude.Text)
actionParameters_model :: Lens' ActionParameters (Maybe Text)
actionParameters_model = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ActionParameters' {Maybe Text
model :: Maybe Text
$sel:model:ActionParameters' :: ActionParameters -> Maybe Text
model} -> Maybe Text
model) (\s :: ActionParameters
s@ActionParameters' {} Maybe Text
a -> ActionParameters
s {$sel:model:ActionParameters' :: Maybe Text
model = Maybe Text
a} :: ActionParameters)

-- | A key-value pair that specifies the state property name and its initial
-- value.
actionParameters_state :: Lens.Lens' ActionParameters (Prelude.Maybe MutationActionSetStateParameter)
actionParameters_state :: Lens' ActionParameters (Maybe MutationActionSetStateParameter)
actionParameters_state = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ActionParameters' {Maybe MutationActionSetStateParameter
state :: Maybe MutationActionSetStateParameter
$sel:state:ActionParameters' :: ActionParameters -> Maybe MutationActionSetStateParameter
state} -> Maybe MutationActionSetStateParameter
state) (\s :: ActionParameters
s@ActionParameters' {} Maybe MutationActionSetStateParameter
a -> ActionParameters
s {$sel:state:ActionParameters' :: Maybe MutationActionSetStateParameter
state = Maybe MutationActionSetStateParameter
a} :: ActionParameters)

-- | The element within the same component to modify when the action occurs.
actionParameters_target :: Lens.Lens' ActionParameters (Prelude.Maybe ComponentProperty)
actionParameters_target :: Lens' ActionParameters (Maybe ComponentProperty)
actionParameters_target = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ActionParameters' {Maybe ComponentProperty
target :: Maybe ComponentProperty
$sel:target:ActionParameters' :: ActionParameters -> Maybe ComponentProperty
target} -> Maybe ComponentProperty
target) (\s :: ActionParameters
s@ActionParameters' {} Maybe ComponentProperty
a -> ActionParameters
s {$sel:target:ActionParameters' :: Maybe ComponentProperty
target = Maybe ComponentProperty
a} :: ActionParameters)

-- | The type of navigation action. Valid values are @url@ and @anchor@. This
-- value is required for a navigation action.
actionParameters_type :: Lens.Lens' ActionParameters (Prelude.Maybe ComponentProperty)
actionParameters_type :: Lens' ActionParameters (Maybe ComponentProperty)
actionParameters_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ActionParameters' {Maybe ComponentProperty
type' :: Maybe ComponentProperty
$sel:type':ActionParameters' :: ActionParameters -> Maybe ComponentProperty
type'} -> Maybe ComponentProperty
type') (\s :: ActionParameters
s@ActionParameters' {} Maybe ComponentProperty
a -> ActionParameters
s {$sel:type':ActionParameters' :: Maybe ComponentProperty
type' = Maybe ComponentProperty
a} :: ActionParameters)

-- | The URL to the location to open. Specify this value for a navigation
-- action.
actionParameters_url :: Lens.Lens' ActionParameters (Prelude.Maybe ComponentProperty)
actionParameters_url :: Lens' ActionParameters (Maybe ComponentProperty)
actionParameters_url = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ActionParameters' {Maybe ComponentProperty
url :: Maybe ComponentProperty
$sel:url:ActionParameters' :: ActionParameters -> Maybe ComponentProperty
url} -> Maybe ComponentProperty
url) (\s :: ActionParameters
s@ActionParameters' {} Maybe ComponentProperty
a -> ActionParameters
s {$sel:url:ActionParameters' :: Maybe ComponentProperty
url = Maybe ComponentProperty
a} :: ActionParameters)

instance Data.FromJSON ActionParameters where
  parseJSON :: Value -> Parser ActionParameters
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"ActionParameters"
      ( \Object
x ->
          Maybe ComponentProperty
-> Maybe (HashMap Text ComponentProperty)
-> Maybe ComponentProperty
-> Maybe ComponentProperty
-> Maybe Text
-> Maybe MutationActionSetStateParameter
-> Maybe ComponentProperty
-> Maybe ComponentProperty
-> Maybe ComponentProperty
-> ActionParameters
ActionParameters'
            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
"anchor")
            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
"fields" 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
"global")
            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
"id")
            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
"model")
            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
"state")
            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
"target")
            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
"type")
            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
"url")
      )

instance Prelude.Hashable ActionParameters where
  hashWithSalt :: Int -> ActionParameters -> Int
hashWithSalt Int
_salt ActionParameters' {Maybe Text
Maybe (HashMap Text ComponentProperty)
Maybe ComponentProperty
Maybe MutationActionSetStateParameter
url :: Maybe ComponentProperty
type' :: Maybe ComponentProperty
target :: Maybe ComponentProperty
state :: Maybe MutationActionSetStateParameter
model :: Maybe Text
id :: Maybe ComponentProperty
global :: Maybe ComponentProperty
fields :: Maybe (HashMap Text ComponentProperty)
anchor :: Maybe ComponentProperty
$sel:url:ActionParameters' :: ActionParameters -> Maybe ComponentProperty
$sel:type':ActionParameters' :: ActionParameters -> Maybe ComponentProperty
$sel:target:ActionParameters' :: ActionParameters -> Maybe ComponentProperty
$sel:state:ActionParameters' :: ActionParameters -> Maybe MutationActionSetStateParameter
$sel:model:ActionParameters' :: ActionParameters -> Maybe Text
$sel:id:ActionParameters' :: ActionParameters -> Maybe ComponentProperty
$sel:global:ActionParameters' :: ActionParameters -> Maybe ComponentProperty
$sel:fields:ActionParameters' :: ActionParameters -> Maybe (HashMap Text ComponentProperty)
$sel:anchor:ActionParameters' :: ActionParameters -> Maybe ComponentProperty
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ComponentProperty
anchor
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text ComponentProperty)
fields
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ComponentProperty
global
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ComponentProperty
id
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
model
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe MutationActionSetStateParameter
state
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ComponentProperty
target
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ComponentProperty
type'
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ComponentProperty
url

instance Prelude.NFData ActionParameters where
  rnf :: ActionParameters -> ()
rnf ActionParameters' {Maybe Text
Maybe (HashMap Text ComponentProperty)
Maybe ComponentProperty
Maybe MutationActionSetStateParameter
url :: Maybe ComponentProperty
type' :: Maybe ComponentProperty
target :: Maybe ComponentProperty
state :: Maybe MutationActionSetStateParameter
model :: Maybe Text
id :: Maybe ComponentProperty
global :: Maybe ComponentProperty
fields :: Maybe (HashMap Text ComponentProperty)
anchor :: Maybe ComponentProperty
$sel:url:ActionParameters' :: ActionParameters -> Maybe ComponentProperty
$sel:type':ActionParameters' :: ActionParameters -> Maybe ComponentProperty
$sel:target:ActionParameters' :: ActionParameters -> Maybe ComponentProperty
$sel:state:ActionParameters' :: ActionParameters -> Maybe MutationActionSetStateParameter
$sel:model:ActionParameters' :: ActionParameters -> Maybe Text
$sel:id:ActionParameters' :: ActionParameters -> Maybe ComponentProperty
$sel:global:ActionParameters' :: ActionParameters -> Maybe ComponentProperty
$sel:fields:ActionParameters' :: ActionParameters -> Maybe (HashMap Text ComponentProperty)
$sel:anchor:ActionParameters' :: ActionParameters -> Maybe ComponentProperty
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ComponentProperty
anchor
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text ComponentProperty)
fields
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ComponentProperty
global
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ComponentProperty
id
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
model
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe MutationActionSetStateParameter
state
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ComponentProperty
target
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ComponentProperty
type'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ComponentProperty
url

instance Data.ToJSON ActionParameters where
  toJSON :: ActionParameters -> Value
toJSON ActionParameters' {Maybe Text
Maybe (HashMap Text ComponentProperty)
Maybe ComponentProperty
Maybe MutationActionSetStateParameter
url :: Maybe ComponentProperty
type' :: Maybe ComponentProperty
target :: Maybe ComponentProperty
state :: Maybe MutationActionSetStateParameter
model :: Maybe Text
id :: Maybe ComponentProperty
global :: Maybe ComponentProperty
fields :: Maybe (HashMap Text ComponentProperty)
anchor :: Maybe ComponentProperty
$sel:url:ActionParameters' :: ActionParameters -> Maybe ComponentProperty
$sel:type':ActionParameters' :: ActionParameters -> Maybe ComponentProperty
$sel:target:ActionParameters' :: ActionParameters -> Maybe ComponentProperty
$sel:state:ActionParameters' :: ActionParameters -> Maybe MutationActionSetStateParameter
$sel:model:ActionParameters' :: ActionParameters -> Maybe Text
$sel:id:ActionParameters' :: ActionParameters -> Maybe ComponentProperty
$sel:global:ActionParameters' :: ActionParameters -> Maybe ComponentProperty
$sel:fields:ActionParameters' :: ActionParameters -> Maybe (HashMap Text ComponentProperty)
$sel:anchor:ActionParameters' :: ActionParameters -> Maybe ComponentProperty
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"anchor" 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 ComponentProperty
anchor,
            (Key
"fields" 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 ComponentProperty)
fields,
            (Key
"global" 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 ComponentProperty
global,
            (Key
"id" 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 ComponentProperty
id,
            (Key
"model" 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
model,
            (Key
"state" 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 MutationActionSetStateParameter
state,
            (Key
"target" 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 ComponentProperty
target,
            (Key
"type" 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 ComponentProperty
type',
            (Key
"url" 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 ComponentProperty
url
          ]
      )