{-# 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.AppFlow.Types.FlowDefinition
-- 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.AppFlow.Types.FlowDefinition where

import Amazonka.AppFlow.Types.ConnectorType
import Amazonka.AppFlow.Types.ExecutionDetails
import Amazonka.AppFlow.Types.FlowStatus
import Amazonka.AppFlow.Types.TriggerType
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 properties of the flow, such as its source, destination, trigger
-- type, and so on.
--
-- /See:/ 'newFlowDefinition' smart constructor.
data FlowDefinition = FlowDefinition'
  { -- | Specifies when the flow was created.
    FlowDefinition -> Maybe POSIX
createdAt :: Prelude.Maybe Data.POSIX,
    -- | The ARN of the user who created the flow.
    FlowDefinition -> Maybe Text
createdBy :: Prelude.Maybe Prelude.Text,
    -- | A user-entered description of the flow.
    FlowDefinition -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The label of the destination connector in the flow.
    FlowDefinition -> Maybe Text
destinationConnectorLabel :: Prelude.Maybe Prelude.Text,
    -- | Specifies the destination connector type, such as Salesforce, Amazon S3,
    -- Amplitude, and so on.
    FlowDefinition -> Maybe ConnectorType
destinationConnectorType :: Prelude.Maybe ConnectorType,
    -- | The flow\'s Amazon Resource Name (ARN).
    FlowDefinition -> Maybe Text
flowArn :: Prelude.Maybe Prelude.Text,
    -- | The specified name of the flow. Spaces are not allowed. Use underscores
    -- (_) or hyphens (-) only.
    FlowDefinition -> Maybe Text
flowName :: Prelude.Maybe Prelude.Text,
    -- | Indicates the current status of the flow.
    FlowDefinition -> Maybe FlowStatus
flowStatus :: Prelude.Maybe FlowStatus,
    -- | Describes the details of the most recent flow run.
    FlowDefinition -> Maybe ExecutionDetails
lastRunExecutionDetails :: Prelude.Maybe ExecutionDetails,
    -- | Specifies when the flow was last updated.
    FlowDefinition -> Maybe POSIX
lastUpdatedAt :: Prelude.Maybe Data.POSIX,
    -- | Specifies the account user name that most recently updated the flow.
    FlowDefinition -> Maybe Text
lastUpdatedBy :: Prelude.Maybe Prelude.Text,
    -- | The label of the source connector in the flow.
    FlowDefinition -> Maybe Text
sourceConnectorLabel :: Prelude.Maybe Prelude.Text,
    -- | Specifies the source connector type, such as Salesforce, Amazon S3,
    -- Amplitude, and so on.
    FlowDefinition -> Maybe ConnectorType
sourceConnectorType :: Prelude.Maybe ConnectorType,
    -- | The tags used to organize, track, or control access for your flow.
    FlowDefinition -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | Specifies the type of flow trigger. This can be @OnDemand@, @Scheduled@,
    -- or @Event@.
    FlowDefinition -> Maybe TriggerType
triggerType :: Prelude.Maybe TriggerType
  }
  deriving (FlowDefinition -> FlowDefinition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FlowDefinition -> FlowDefinition -> Bool
$c/= :: FlowDefinition -> FlowDefinition -> Bool
== :: FlowDefinition -> FlowDefinition -> Bool
$c== :: FlowDefinition -> FlowDefinition -> Bool
Prelude.Eq, ReadPrec [FlowDefinition]
ReadPrec FlowDefinition
Int -> ReadS FlowDefinition
ReadS [FlowDefinition]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FlowDefinition]
$creadListPrec :: ReadPrec [FlowDefinition]
readPrec :: ReadPrec FlowDefinition
$creadPrec :: ReadPrec FlowDefinition
readList :: ReadS [FlowDefinition]
$creadList :: ReadS [FlowDefinition]
readsPrec :: Int -> ReadS FlowDefinition
$creadsPrec :: Int -> ReadS FlowDefinition
Prelude.Read, Int -> FlowDefinition -> ShowS
[FlowDefinition] -> ShowS
FlowDefinition -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FlowDefinition] -> ShowS
$cshowList :: [FlowDefinition] -> ShowS
show :: FlowDefinition -> String
$cshow :: FlowDefinition -> String
showsPrec :: Int -> FlowDefinition -> ShowS
$cshowsPrec :: Int -> FlowDefinition -> ShowS
Prelude.Show, forall x. Rep FlowDefinition x -> FlowDefinition
forall x. FlowDefinition -> Rep FlowDefinition x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FlowDefinition x -> FlowDefinition
$cfrom :: forall x. FlowDefinition -> Rep FlowDefinition x
Prelude.Generic)

-- |
-- Create a value of 'FlowDefinition' 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:
--
-- 'createdAt', 'flowDefinition_createdAt' - Specifies when the flow was created.
--
-- 'createdBy', 'flowDefinition_createdBy' - The ARN of the user who created the flow.
--
-- 'description', 'flowDefinition_description' - A user-entered description of the flow.
--
-- 'destinationConnectorLabel', 'flowDefinition_destinationConnectorLabel' - The label of the destination connector in the flow.
--
-- 'destinationConnectorType', 'flowDefinition_destinationConnectorType' - Specifies the destination connector type, such as Salesforce, Amazon S3,
-- Amplitude, and so on.
--
-- 'flowArn', 'flowDefinition_flowArn' - The flow\'s Amazon Resource Name (ARN).
--
-- 'flowName', 'flowDefinition_flowName' - The specified name of the flow. Spaces are not allowed. Use underscores
-- (_) or hyphens (-) only.
--
-- 'flowStatus', 'flowDefinition_flowStatus' - Indicates the current status of the flow.
--
-- 'lastRunExecutionDetails', 'flowDefinition_lastRunExecutionDetails' - Describes the details of the most recent flow run.
--
-- 'lastUpdatedAt', 'flowDefinition_lastUpdatedAt' - Specifies when the flow was last updated.
--
-- 'lastUpdatedBy', 'flowDefinition_lastUpdatedBy' - Specifies the account user name that most recently updated the flow.
--
-- 'sourceConnectorLabel', 'flowDefinition_sourceConnectorLabel' - The label of the source connector in the flow.
--
-- 'sourceConnectorType', 'flowDefinition_sourceConnectorType' - Specifies the source connector type, such as Salesforce, Amazon S3,
-- Amplitude, and so on.
--
-- 'tags', 'flowDefinition_tags' - The tags used to organize, track, or control access for your flow.
--
-- 'triggerType', 'flowDefinition_triggerType' - Specifies the type of flow trigger. This can be @OnDemand@, @Scheduled@,
-- or @Event@.
newFlowDefinition ::
  FlowDefinition
newFlowDefinition :: FlowDefinition
newFlowDefinition =
  FlowDefinition'
    { $sel:createdAt:FlowDefinition' :: Maybe POSIX
createdAt = forall a. Maybe a
Prelude.Nothing,
      $sel:createdBy:FlowDefinition' :: Maybe Text
createdBy = forall a. Maybe a
Prelude.Nothing,
      $sel:description:FlowDefinition' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:destinationConnectorLabel:FlowDefinition' :: Maybe Text
destinationConnectorLabel = forall a. Maybe a
Prelude.Nothing,
      $sel:destinationConnectorType:FlowDefinition' :: Maybe ConnectorType
destinationConnectorType = forall a. Maybe a
Prelude.Nothing,
      $sel:flowArn:FlowDefinition' :: Maybe Text
flowArn = forall a. Maybe a
Prelude.Nothing,
      $sel:flowName:FlowDefinition' :: Maybe Text
flowName = forall a. Maybe a
Prelude.Nothing,
      $sel:flowStatus:FlowDefinition' :: Maybe FlowStatus
flowStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:lastRunExecutionDetails:FlowDefinition' :: Maybe ExecutionDetails
lastRunExecutionDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:lastUpdatedAt:FlowDefinition' :: Maybe POSIX
lastUpdatedAt = forall a. Maybe a
Prelude.Nothing,
      $sel:lastUpdatedBy:FlowDefinition' :: Maybe Text
lastUpdatedBy = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceConnectorLabel:FlowDefinition' :: Maybe Text
sourceConnectorLabel = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceConnectorType:FlowDefinition' :: Maybe ConnectorType
sourceConnectorType = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:FlowDefinition' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:triggerType:FlowDefinition' :: Maybe TriggerType
triggerType = forall a. Maybe a
Prelude.Nothing
    }

-- | Specifies when the flow was created.
flowDefinition_createdAt :: Lens.Lens' FlowDefinition (Prelude.Maybe Prelude.UTCTime)
flowDefinition_createdAt :: Lens' FlowDefinition (Maybe UTCTime)
flowDefinition_createdAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FlowDefinition' {Maybe POSIX
createdAt :: Maybe POSIX
$sel:createdAt:FlowDefinition' :: FlowDefinition -> Maybe POSIX
createdAt} -> Maybe POSIX
createdAt) (\s :: FlowDefinition
s@FlowDefinition' {} Maybe POSIX
a -> FlowDefinition
s {$sel:createdAt:FlowDefinition' :: Maybe POSIX
createdAt = Maybe POSIX
a} :: FlowDefinition) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The ARN of the user who created the flow.
flowDefinition_createdBy :: Lens.Lens' FlowDefinition (Prelude.Maybe Prelude.Text)
flowDefinition_createdBy :: Lens' FlowDefinition (Maybe Text)
flowDefinition_createdBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FlowDefinition' {Maybe Text
createdBy :: Maybe Text
$sel:createdBy:FlowDefinition' :: FlowDefinition -> Maybe Text
createdBy} -> Maybe Text
createdBy) (\s :: FlowDefinition
s@FlowDefinition' {} Maybe Text
a -> FlowDefinition
s {$sel:createdBy:FlowDefinition' :: Maybe Text
createdBy = Maybe Text
a} :: FlowDefinition)

-- | A user-entered description of the flow.
flowDefinition_description :: Lens.Lens' FlowDefinition (Prelude.Maybe Prelude.Text)
flowDefinition_description :: Lens' FlowDefinition (Maybe Text)
flowDefinition_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FlowDefinition' {Maybe Text
description :: Maybe Text
$sel:description:FlowDefinition' :: FlowDefinition -> Maybe Text
description} -> Maybe Text
description) (\s :: FlowDefinition
s@FlowDefinition' {} Maybe Text
a -> FlowDefinition
s {$sel:description:FlowDefinition' :: Maybe Text
description = Maybe Text
a} :: FlowDefinition)

-- | The label of the destination connector in the flow.
flowDefinition_destinationConnectorLabel :: Lens.Lens' FlowDefinition (Prelude.Maybe Prelude.Text)
flowDefinition_destinationConnectorLabel :: Lens' FlowDefinition (Maybe Text)
flowDefinition_destinationConnectorLabel = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FlowDefinition' {Maybe Text
destinationConnectorLabel :: Maybe Text
$sel:destinationConnectorLabel:FlowDefinition' :: FlowDefinition -> Maybe Text
destinationConnectorLabel} -> Maybe Text
destinationConnectorLabel) (\s :: FlowDefinition
s@FlowDefinition' {} Maybe Text
a -> FlowDefinition
s {$sel:destinationConnectorLabel:FlowDefinition' :: Maybe Text
destinationConnectorLabel = Maybe Text
a} :: FlowDefinition)

-- | Specifies the destination connector type, such as Salesforce, Amazon S3,
-- Amplitude, and so on.
flowDefinition_destinationConnectorType :: Lens.Lens' FlowDefinition (Prelude.Maybe ConnectorType)
flowDefinition_destinationConnectorType :: Lens' FlowDefinition (Maybe ConnectorType)
flowDefinition_destinationConnectorType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FlowDefinition' {Maybe ConnectorType
destinationConnectorType :: Maybe ConnectorType
$sel:destinationConnectorType:FlowDefinition' :: FlowDefinition -> Maybe ConnectorType
destinationConnectorType} -> Maybe ConnectorType
destinationConnectorType) (\s :: FlowDefinition
s@FlowDefinition' {} Maybe ConnectorType
a -> FlowDefinition
s {$sel:destinationConnectorType:FlowDefinition' :: Maybe ConnectorType
destinationConnectorType = Maybe ConnectorType
a} :: FlowDefinition)

-- | The flow\'s Amazon Resource Name (ARN).
flowDefinition_flowArn :: Lens.Lens' FlowDefinition (Prelude.Maybe Prelude.Text)
flowDefinition_flowArn :: Lens' FlowDefinition (Maybe Text)
flowDefinition_flowArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FlowDefinition' {Maybe Text
flowArn :: Maybe Text
$sel:flowArn:FlowDefinition' :: FlowDefinition -> Maybe Text
flowArn} -> Maybe Text
flowArn) (\s :: FlowDefinition
s@FlowDefinition' {} Maybe Text
a -> FlowDefinition
s {$sel:flowArn:FlowDefinition' :: Maybe Text
flowArn = Maybe Text
a} :: FlowDefinition)

-- | The specified name of the flow. Spaces are not allowed. Use underscores
-- (_) or hyphens (-) only.
flowDefinition_flowName :: Lens.Lens' FlowDefinition (Prelude.Maybe Prelude.Text)
flowDefinition_flowName :: Lens' FlowDefinition (Maybe Text)
flowDefinition_flowName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FlowDefinition' {Maybe Text
flowName :: Maybe Text
$sel:flowName:FlowDefinition' :: FlowDefinition -> Maybe Text
flowName} -> Maybe Text
flowName) (\s :: FlowDefinition
s@FlowDefinition' {} Maybe Text
a -> FlowDefinition
s {$sel:flowName:FlowDefinition' :: Maybe Text
flowName = Maybe Text
a} :: FlowDefinition)

-- | Indicates the current status of the flow.
flowDefinition_flowStatus :: Lens.Lens' FlowDefinition (Prelude.Maybe FlowStatus)
flowDefinition_flowStatus :: Lens' FlowDefinition (Maybe FlowStatus)
flowDefinition_flowStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FlowDefinition' {Maybe FlowStatus
flowStatus :: Maybe FlowStatus
$sel:flowStatus:FlowDefinition' :: FlowDefinition -> Maybe FlowStatus
flowStatus} -> Maybe FlowStatus
flowStatus) (\s :: FlowDefinition
s@FlowDefinition' {} Maybe FlowStatus
a -> FlowDefinition
s {$sel:flowStatus:FlowDefinition' :: Maybe FlowStatus
flowStatus = Maybe FlowStatus
a} :: FlowDefinition)

-- | Describes the details of the most recent flow run.
flowDefinition_lastRunExecutionDetails :: Lens.Lens' FlowDefinition (Prelude.Maybe ExecutionDetails)
flowDefinition_lastRunExecutionDetails :: Lens' FlowDefinition (Maybe ExecutionDetails)
flowDefinition_lastRunExecutionDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FlowDefinition' {Maybe ExecutionDetails
lastRunExecutionDetails :: Maybe ExecutionDetails
$sel:lastRunExecutionDetails:FlowDefinition' :: FlowDefinition -> Maybe ExecutionDetails
lastRunExecutionDetails} -> Maybe ExecutionDetails
lastRunExecutionDetails) (\s :: FlowDefinition
s@FlowDefinition' {} Maybe ExecutionDetails
a -> FlowDefinition
s {$sel:lastRunExecutionDetails:FlowDefinition' :: Maybe ExecutionDetails
lastRunExecutionDetails = Maybe ExecutionDetails
a} :: FlowDefinition)

-- | Specifies when the flow was last updated.
flowDefinition_lastUpdatedAt :: Lens.Lens' FlowDefinition (Prelude.Maybe Prelude.UTCTime)
flowDefinition_lastUpdatedAt :: Lens' FlowDefinition (Maybe UTCTime)
flowDefinition_lastUpdatedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FlowDefinition' {Maybe POSIX
lastUpdatedAt :: Maybe POSIX
$sel:lastUpdatedAt:FlowDefinition' :: FlowDefinition -> Maybe POSIX
lastUpdatedAt} -> Maybe POSIX
lastUpdatedAt) (\s :: FlowDefinition
s@FlowDefinition' {} Maybe POSIX
a -> FlowDefinition
s {$sel:lastUpdatedAt:FlowDefinition' :: Maybe POSIX
lastUpdatedAt = Maybe POSIX
a} :: FlowDefinition) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | Specifies the account user name that most recently updated the flow.
flowDefinition_lastUpdatedBy :: Lens.Lens' FlowDefinition (Prelude.Maybe Prelude.Text)
flowDefinition_lastUpdatedBy :: Lens' FlowDefinition (Maybe Text)
flowDefinition_lastUpdatedBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FlowDefinition' {Maybe Text
lastUpdatedBy :: Maybe Text
$sel:lastUpdatedBy:FlowDefinition' :: FlowDefinition -> Maybe Text
lastUpdatedBy} -> Maybe Text
lastUpdatedBy) (\s :: FlowDefinition
s@FlowDefinition' {} Maybe Text
a -> FlowDefinition
s {$sel:lastUpdatedBy:FlowDefinition' :: Maybe Text
lastUpdatedBy = Maybe Text
a} :: FlowDefinition)

-- | The label of the source connector in the flow.
flowDefinition_sourceConnectorLabel :: Lens.Lens' FlowDefinition (Prelude.Maybe Prelude.Text)
flowDefinition_sourceConnectorLabel :: Lens' FlowDefinition (Maybe Text)
flowDefinition_sourceConnectorLabel = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FlowDefinition' {Maybe Text
sourceConnectorLabel :: Maybe Text
$sel:sourceConnectorLabel:FlowDefinition' :: FlowDefinition -> Maybe Text
sourceConnectorLabel} -> Maybe Text
sourceConnectorLabel) (\s :: FlowDefinition
s@FlowDefinition' {} Maybe Text
a -> FlowDefinition
s {$sel:sourceConnectorLabel:FlowDefinition' :: Maybe Text
sourceConnectorLabel = Maybe Text
a} :: FlowDefinition)

-- | Specifies the source connector type, such as Salesforce, Amazon S3,
-- Amplitude, and so on.
flowDefinition_sourceConnectorType :: Lens.Lens' FlowDefinition (Prelude.Maybe ConnectorType)
flowDefinition_sourceConnectorType :: Lens' FlowDefinition (Maybe ConnectorType)
flowDefinition_sourceConnectorType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FlowDefinition' {Maybe ConnectorType
sourceConnectorType :: Maybe ConnectorType
$sel:sourceConnectorType:FlowDefinition' :: FlowDefinition -> Maybe ConnectorType
sourceConnectorType} -> Maybe ConnectorType
sourceConnectorType) (\s :: FlowDefinition
s@FlowDefinition' {} Maybe ConnectorType
a -> FlowDefinition
s {$sel:sourceConnectorType:FlowDefinition' :: Maybe ConnectorType
sourceConnectorType = Maybe ConnectorType
a} :: FlowDefinition)

-- | The tags used to organize, track, or control access for your flow.
flowDefinition_tags :: Lens.Lens' FlowDefinition (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
flowDefinition_tags :: Lens' FlowDefinition (Maybe (HashMap Text Text))
flowDefinition_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FlowDefinition' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:FlowDefinition' :: FlowDefinition -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: FlowDefinition
s@FlowDefinition' {} Maybe (HashMap Text Text)
a -> FlowDefinition
s {$sel:tags:FlowDefinition' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: FlowDefinition) 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 the type of flow trigger. This can be @OnDemand@, @Scheduled@,
-- or @Event@.
flowDefinition_triggerType :: Lens.Lens' FlowDefinition (Prelude.Maybe TriggerType)
flowDefinition_triggerType :: Lens' FlowDefinition (Maybe TriggerType)
flowDefinition_triggerType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FlowDefinition' {Maybe TriggerType
triggerType :: Maybe TriggerType
$sel:triggerType:FlowDefinition' :: FlowDefinition -> Maybe TriggerType
triggerType} -> Maybe TriggerType
triggerType) (\s :: FlowDefinition
s@FlowDefinition' {} Maybe TriggerType
a -> FlowDefinition
s {$sel:triggerType:FlowDefinition' :: Maybe TriggerType
triggerType = Maybe TriggerType
a} :: FlowDefinition)

instance Data.FromJSON FlowDefinition where
  parseJSON :: Value -> Parser FlowDefinition
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"FlowDefinition"
      ( \Object
x ->
          Maybe POSIX
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe ConnectorType
-> Maybe Text
-> Maybe Text
-> Maybe FlowStatus
-> Maybe ExecutionDetails
-> Maybe POSIX
-> Maybe Text
-> Maybe Text
-> Maybe ConnectorType
-> Maybe (HashMap Text Text)
-> Maybe TriggerType
-> FlowDefinition
FlowDefinition'
            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
"createdAt")
            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
"createdBy")
            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
"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
"destinationConnectorLabel")
            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
"destinationConnectorType")
            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
"flowArn")
            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
"flowName")
            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
"flowStatus")
            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
"lastRunExecutionDetails")
            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
"lastUpdatedAt")
            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
"lastUpdatedBy")
            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
"sourceConnectorLabel")
            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
"sourceConnectorType")
            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
"tags" 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
"triggerType")
      )

instance Prelude.Hashable FlowDefinition where
  hashWithSalt :: Int -> FlowDefinition -> Int
hashWithSalt Int
_salt FlowDefinition' {Maybe Text
Maybe (HashMap Text Text)
Maybe POSIX
Maybe ConnectorType
Maybe ExecutionDetails
Maybe FlowStatus
Maybe TriggerType
triggerType :: Maybe TriggerType
tags :: Maybe (HashMap Text Text)
sourceConnectorType :: Maybe ConnectorType
sourceConnectorLabel :: Maybe Text
lastUpdatedBy :: Maybe Text
lastUpdatedAt :: Maybe POSIX
lastRunExecutionDetails :: Maybe ExecutionDetails
flowStatus :: Maybe FlowStatus
flowName :: Maybe Text
flowArn :: Maybe Text
destinationConnectorType :: Maybe ConnectorType
destinationConnectorLabel :: Maybe Text
description :: Maybe Text
createdBy :: Maybe Text
createdAt :: Maybe POSIX
$sel:triggerType:FlowDefinition' :: FlowDefinition -> Maybe TriggerType
$sel:tags:FlowDefinition' :: FlowDefinition -> Maybe (HashMap Text Text)
$sel:sourceConnectorType:FlowDefinition' :: FlowDefinition -> Maybe ConnectorType
$sel:sourceConnectorLabel:FlowDefinition' :: FlowDefinition -> Maybe Text
$sel:lastUpdatedBy:FlowDefinition' :: FlowDefinition -> Maybe Text
$sel:lastUpdatedAt:FlowDefinition' :: FlowDefinition -> Maybe POSIX
$sel:lastRunExecutionDetails:FlowDefinition' :: FlowDefinition -> Maybe ExecutionDetails
$sel:flowStatus:FlowDefinition' :: FlowDefinition -> Maybe FlowStatus
$sel:flowName:FlowDefinition' :: FlowDefinition -> Maybe Text
$sel:flowArn:FlowDefinition' :: FlowDefinition -> Maybe Text
$sel:destinationConnectorType:FlowDefinition' :: FlowDefinition -> Maybe ConnectorType
$sel:destinationConnectorLabel:FlowDefinition' :: FlowDefinition -> Maybe Text
$sel:description:FlowDefinition' :: FlowDefinition -> Maybe Text
$sel:createdBy:FlowDefinition' :: FlowDefinition -> Maybe Text
$sel:createdAt:FlowDefinition' :: FlowDefinition -> Maybe POSIX
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
createdAt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
createdBy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
destinationConnectorLabel
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ConnectorType
destinationConnectorType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
flowArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
flowName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe FlowStatus
flowStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ExecutionDetails
lastRunExecutionDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
lastUpdatedAt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
lastUpdatedBy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
sourceConnectorLabel
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ConnectorType
sourceConnectorType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TriggerType
triggerType

instance Prelude.NFData FlowDefinition where
  rnf :: FlowDefinition -> ()
rnf FlowDefinition' {Maybe Text
Maybe (HashMap Text Text)
Maybe POSIX
Maybe ConnectorType
Maybe ExecutionDetails
Maybe FlowStatus
Maybe TriggerType
triggerType :: Maybe TriggerType
tags :: Maybe (HashMap Text Text)
sourceConnectorType :: Maybe ConnectorType
sourceConnectorLabel :: Maybe Text
lastUpdatedBy :: Maybe Text
lastUpdatedAt :: Maybe POSIX
lastRunExecutionDetails :: Maybe ExecutionDetails
flowStatus :: Maybe FlowStatus
flowName :: Maybe Text
flowArn :: Maybe Text
destinationConnectorType :: Maybe ConnectorType
destinationConnectorLabel :: Maybe Text
description :: Maybe Text
createdBy :: Maybe Text
createdAt :: Maybe POSIX
$sel:triggerType:FlowDefinition' :: FlowDefinition -> Maybe TriggerType
$sel:tags:FlowDefinition' :: FlowDefinition -> Maybe (HashMap Text Text)
$sel:sourceConnectorType:FlowDefinition' :: FlowDefinition -> Maybe ConnectorType
$sel:sourceConnectorLabel:FlowDefinition' :: FlowDefinition -> Maybe Text
$sel:lastUpdatedBy:FlowDefinition' :: FlowDefinition -> Maybe Text
$sel:lastUpdatedAt:FlowDefinition' :: FlowDefinition -> Maybe POSIX
$sel:lastRunExecutionDetails:FlowDefinition' :: FlowDefinition -> Maybe ExecutionDetails
$sel:flowStatus:FlowDefinition' :: FlowDefinition -> Maybe FlowStatus
$sel:flowName:FlowDefinition' :: FlowDefinition -> Maybe Text
$sel:flowArn:FlowDefinition' :: FlowDefinition -> Maybe Text
$sel:destinationConnectorType:FlowDefinition' :: FlowDefinition -> Maybe ConnectorType
$sel:destinationConnectorLabel:FlowDefinition' :: FlowDefinition -> Maybe Text
$sel:description:FlowDefinition' :: FlowDefinition -> Maybe Text
$sel:createdBy:FlowDefinition' :: FlowDefinition -> Maybe Text
$sel:createdAt:FlowDefinition' :: FlowDefinition -> Maybe POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createdAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
createdBy
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 Text
destinationConnectorLabel
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ConnectorType
destinationConnectorType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
flowArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
flowName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe FlowStatus
flowStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ExecutionDetails
lastRunExecutionDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastUpdatedAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
lastUpdatedBy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
sourceConnectorLabel
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ConnectorType
sourceConnectorType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TriggerType
triggerType