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

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

-- |
-- Module      : Amazonka.AppFlow.DescribeFlow
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Provides a description of the specified flow.
module Amazonka.AppFlow.DescribeFlow
  ( -- * Creating a Request
    DescribeFlow (..),
    newDescribeFlow,

    -- * Request Lenses
    describeFlow_flowName,

    -- * Destructuring the Response
    DescribeFlowResponse (..),
    newDescribeFlowResponse,

    -- * Response Lenses
    describeFlowResponse_createdAt,
    describeFlowResponse_createdBy,
    describeFlowResponse_description,
    describeFlowResponse_destinationFlowConfigList,
    describeFlowResponse_flowArn,
    describeFlowResponse_flowName,
    describeFlowResponse_flowStatus,
    describeFlowResponse_flowStatusMessage,
    describeFlowResponse_kmsArn,
    describeFlowResponse_lastRunExecutionDetails,
    describeFlowResponse_lastRunMetadataCatalogDetails,
    describeFlowResponse_lastUpdatedAt,
    describeFlowResponse_lastUpdatedBy,
    describeFlowResponse_metadataCatalogConfig,
    describeFlowResponse_schemaVersion,
    describeFlowResponse_sourceFlowConfig,
    describeFlowResponse_tags,
    describeFlowResponse_tasks,
    describeFlowResponse_triggerConfig,
    describeFlowResponse_httpStatus,
  )
where

import Amazonka.AppFlow.Types
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newDescribeFlow' smart constructor.
data DescribeFlow = DescribeFlow'
  { -- | The specified name of the flow. Spaces are not allowed. Use underscores
    -- (_) or hyphens (-) only.
    DescribeFlow -> Text
flowName :: Prelude.Text
  }
  deriving (DescribeFlow -> DescribeFlow -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeFlow -> DescribeFlow -> Bool
$c/= :: DescribeFlow -> DescribeFlow -> Bool
== :: DescribeFlow -> DescribeFlow -> Bool
$c== :: DescribeFlow -> DescribeFlow -> Bool
Prelude.Eq, ReadPrec [DescribeFlow]
ReadPrec DescribeFlow
Int -> ReadS DescribeFlow
ReadS [DescribeFlow]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeFlow]
$creadListPrec :: ReadPrec [DescribeFlow]
readPrec :: ReadPrec DescribeFlow
$creadPrec :: ReadPrec DescribeFlow
readList :: ReadS [DescribeFlow]
$creadList :: ReadS [DescribeFlow]
readsPrec :: Int -> ReadS DescribeFlow
$creadsPrec :: Int -> ReadS DescribeFlow
Prelude.Read, Int -> DescribeFlow -> ShowS
[DescribeFlow] -> ShowS
DescribeFlow -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeFlow] -> ShowS
$cshowList :: [DescribeFlow] -> ShowS
show :: DescribeFlow -> String
$cshow :: DescribeFlow -> String
showsPrec :: Int -> DescribeFlow -> ShowS
$cshowsPrec :: Int -> DescribeFlow -> ShowS
Prelude.Show, forall x. Rep DescribeFlow x -> DescribeFlow
forall x. DescribeFlow -> Rep DescribeFlow x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeFlow x -> DescribeFlow
$cfrom :: forall x. DescribeFlow -> Rep DescribeFlow x
Prelude.Generic)

-- |
-- Create a value of 'DescribeFlow' 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:
--
-- 'flowName', 'describeFlow_flowName' - The specified name of the flow. Spaces are not allowed. Use underscores
-- (_) or hyphens (-) only.
newDescribeFlow ::
  -- | 'flowName'
  Prelude.Text ->
  DescribeFlow
newDescribeFlow :: Text -> DescribeFlow
newDescribeFlow Text
pFlowName_ =
  DescribeFlow' {$sel:flowName:DescribeFlow' :: Text
flowName = Text
pFlowName_}

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

instance Core.AWSRequest DescribeFlow where
  type AWSResponse DescribeFlow = DescribeFlowResponse
  request :: (Service -> Service) -> DescribeFlow -> Request DescribeFlow
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DescribeFlow
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DescribeFlow)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe POSIX
-> Maybe Text
-> Maybe Text
-> Maybe [DestinationFlowConfig]
-> Maybe Text
-> Maybe Text
-> Maybe FlowStatus
-> Maybe Text
-> Maybe Text
-> Maybe ExecutionDetails
-> Maybe [MetadataCatalogDetail]
-> Maybe POSIX
-> Maybe Text
-> Maybe MetadataCatalogConfig
-> Maybe Integer
-> Maybe SourceFlowConfig
-> Maybe (HashMap Text Text)
-> Maybe [Task]
-> Maybe TriggerConfig
-> Int
-> DescribeFlowResponse
DescribeFlowResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"createdAt")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (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 -> Either String (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 -> Either String (Maybe a)
Data..?> Key
"destinationFlowConfigList"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ 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 -> Either String (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 -> Either String (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 -> Either String (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 -> Either String (Maybe a)
Data..?> Key
"flowStatusMessage")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"kmsArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (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 -> Either String (Maybe a)
Data..?> Key
"lastRunMetadataCatalogDetails"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ 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 -> Either String (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 -> Either String (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 -> Either String (Maybe a)
Data..?> Key
"metadataCatalogConfig")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"schemaVersion")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"sourceFlowConfig")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"tags" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ 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 -> Either String (Maybe a)
Data..?> Key
"tasks" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ 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 -> Either String (Maybe a)
Data..?> Key
"triggerConfig")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable DescribeFlow where
  hashWithSalt :: Int -> DescribeFlow -> Int
hashWithSalt Int
_salt DescribeFlow' {Text
flowName :: Text
$sel:flowName:DescribeFlow' :: DescribeFlow -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
flowName

instance Prelude.NFData DescribeFlow where
  rnf :: DescribeFlow -> ()
rnf DescribeFlow' {Text
flowName :: Text
$sel:flowName:DescribeFlow' :: DescribeFlow -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
flowName

instance Data.ToHeaders DescribeFlow where
  toHeaders :: DescribeFlow -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON DescribeFlow where
  toJSON :: DescribeFlow -> Value
toJSON DescribeFlow' {Text
flowName :: Text
$sel:flowName:DescribeFlow' :: DescribeFlow -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"flowName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
flowName)]
      )

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

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

-- | /See:/ 'newDescribeFlowResponse' smart constructor.
data DescribeFlowResponse = DescribeFlowResponse'
  { -- | Specifies when the flow was created.
    DescribeFlowResponse -> Maybe POSIX
createdAt :: Prelude.Maybe Data.POSIX,
    -- | The ARN of the user who created the flow.
    DescribeFlowResponse -> Maybe Text
createdBy :: Prelude.Maybe Prelude.Text,
    -- | A description of the flow.
    DescribeFlowResponse -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The configuration that controls how Amazon AppFlow transfers data to the
    -- destination connector.
    DescribeFlowResponse -> Maybe [DestinationFlowConfig]
destinationFlowConfigList :: Prelude.Maybe [DestinationFlowConfig],
    -- | The flow\'s Amazon Resource Name (ARN).
    DescribeFlowResponse -> Maybe Text
flowArn :: Prelude.Maybe Prelude.Text,
    -- | The specified name of the flow. Spaces are not allowed. Use underscores
    -- (_) or hyphens (-) only.
    DescribeFlowResponse -> Maybe Text
flowName :: Prelude.Maybe Prelude.Text,
    -- | Indicates the current status of the flow.
    DescribeFlowResponse -> Maybe FlowStatus
flowStatus :: Prelude.Maybe FlowStatus,
    -- | Contains an error message if the flow status is in a suspended or error
    -- state. This applies only to scheduled or event-triggered flows.
    DescribeFlowResponse -> Maybe Text
flowStatusMessage :: Prelude.Maybe Prelude.Text,
    -- | The ARN (Amazon Resource Name) of the Key Management Service (KMS) key
    -- you provide for encryption. This is required if you do not want to use
    -- the Amazon AppFlow-managed KMS key. If you don\'t provide anything here,
    -- Amazon AppFlow uses the Amazon AppFlow-managed KMS key.
    DescribeFlowResponse -> Maybe Text
kmsArn :: Prelude.Maybe Prelude.Text,
    -- | Describes the details of the most recent flow run.
    DescribeFlowResponse -> Maybe ExecutionDetails
lastRunExecutionDetails :: Prelude.Maybe ExecutionDetails,
    -- | Describes the metadata catalog, metadata table, and data partitions that
    -- Amazon AppFlow used for the associated flow run.
    DescribeFlowResponse -> Maybe [MetadataCatalogDetail]
lastRunMetadataCatalogDetails :: Prelude.Maybe [MetadataCatalogDetail],
    -- | Specifies when the flow was last updated.
    DescribeFlowResponse -> Maybe POSIX
lastUpdatedAt :: Prelude.Maybe Data.POSIX,
    -- | Specifies the user name of the account that performed the most recent
    -- update.
    DescribeFlowResponse -> Maybe Text
lastUpdatedBy :: Prelude.Maybe Prelude.Text,
    -- | Specifies the configuration that Amazon AppFlow uses when it catalogs
    -- the data that\'s transferred by the associated flow. When Amazon AppFlow
    -- catalogs the data from a flow, it stores metadata in a data catalog.
    DescribeFlowResponse -> Maybe MetadataCatalogConfig
metadataCatalogConfig :: Prelude.Maybe MetadataCatalogConfig,
    -- | The version number of your data schema. Amazon AppFlow assigns this
    -- version number. The version number increases by one when you change any
    -- of the following settings in your flow configuration:
    --
    -- -   Source-to-destination field mappings
    --
    -- -   Field data types
    --
    -- -   Partition keys
    DescribeFlowResponse -> Maybe Integer
schemaVersion :: Prelude.Maybe Prelude.Integer,
    -- | The configuration that controls how Amazon AppFlow retrieves data from
    -- the source connector.
    DescribeFlowResponse -> Maybe SourceFlowConfig
sourceFlowConfig :: Prelude.Maybe SourceFlowConfig,
    -- | The tags used to organize, track, or control access for your flow.
    DescribeFlowResponse -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | A list of tasks that Amazon AppFlow performs while transferring the data
    -- in the flow run.
    DescribeFlowResponse -> Maybe [Task]
tasks :: Prelude.Maybe [Task],
    -- | The trigger settings that determine how and when the flow runs.
    DescribeFlowResponse -> Maybe TriggerConfig
triggerConfig :: Prelude.Maybe TriggerConfig,
    -- | The response's http status code.
    DescribeFlowResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeFlowResponse -> DescribeFlowResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeFlowResponse -> DescribeFlowResponse -> Bool
$c/= :: DescribeFlowResponse -> DescribeFlowResponse -> Bool
== :: DescribeFlowResponse -> DescribeFlowResponse -> Bool
$c== :: DescribeFlowResponse -> DescribeFlowResponse -> Bool
Prelude.Eq, ReadPrec [DescribeFlowResponse]
ReadPrec DescribeFlowResponse
Int -> ReadS DescribeFlowResponse
ReadS [DescribeFlowResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeFlowResponse]
$creadListPrec :: ReadPrec [DescribeFlowResponse]
readPrec :: ReadPrec DescribeFlowResponse
$creadPrec :: ReadPrec DescribeFlowResponse
readList :: ReadS [DescribeFlowResponse]
$creadList :: ReadS [DescribeFlowResponse]
readsPrec :: Int -> ReadS DescribeFlowResponse
$creadsPrec :: Int -> ReadS DescribeFlowResponse
Prelude.Read, Int -> DescribeFlowResponse -> ShowS
[DescribeFlowResponse] -> ShowS
DescribeFlowResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeFlowResponse] -> ShowS
$cshowList :: [DescribeFlowResponse] -> ShowS
show :: DescribeFlowResponse -> String
$cshow :: DescribeFlowResponse -> String
showsPrec :: Int -> DescribeFlowResponse -> ShowS
$cshowsPrec :: Int -> DescribeFlowResponse -> ShowS
Prelude.Show, forall x. Rep DescribeFlowResponse x -> DescribeFlowResponse
forall x. DescribeFlowResponse -> Rep DescribeFlowResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeFlowResponse x -> DescribeFlowResponse
$cfrom :: forall x. DescribeFlowResponse -> Rep DescribeFlowResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeFlowResponse' 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', 'describeFlowResponse_createdAt' - Specifies when the flow was created.
--
-- 'createdBy', 'describeFlowResponse_createdBy' - The ARN of the user who created the flow.
--
-- 'description', 'describeFlowResponse_description' - A description of the flow.
--
-- 'destinationFlowConfigList', 'describeFlowResponse_destinationFlowConfigList' - The configuration that controls how Amazon AppFlow transfers data to the
-- destination connector.
--
-- 'flowArn', 'describeFlowResponse_flowArn' - The flow\'s Amazon Resource Name (ARN).
--
-- 'flowName', 'describeFlowResponse_flowName' - The specified name of the flow. Spaces are not allowed. Use underscores
-- (_) or hyphens (-) only.
--
-- 'flowStatus', 'describeFlowResponse_flowStatus' - Indicates the current status of the flow.
--
-- 'flowStatusMessage', 'describeFlowResponse_flowStatusMessage' - Contains an error message if the flow status is in a suspended or error
-- state. This applies only to scheduled or event-triggered flows.
--
-- 'kmsArn', 'describeFlowResponse_kmsArn' - The ARN (Amazon Resource Name) of the Key Management Service (KMS) key
-- you provide for encryption. This is required if you do not want to use
-- the Amazon AppFlow-managed KMS key. If you don\'t provide anything here,
-- Amazon AppFlow uses the Amazon AppFlow-managed KMS key.
--
-- 'lastRunExecutionDetails', 'describeFlowResponse_lastRunExecutionDetails' - Describes the details of the most recent flow run.
--
-- 'lastRunMetadataCatalogDetails', 'describeFlowResponse_lastRunMetadataCatalogDetails' - Describes the metadata catalog, metadata table, and data partitions that
-- Amazon AppFlow used for the associated flow run.
--
-- 'lastUpdatedAt', 'describeFlowResponse_lastUpdatedAt' - Specifies when the flow was last updated.
--
-- 'lastUpdatedBy', 'describeFlowResponse_lastUpdatedBy' - Specifies the user name of the account that performed the most recent
-- update.
--
-- 'metadataCatalogConfig', 'describeFlowResponse_metadataCatalogConfig' - Specifies the configuration that Amazon AppFlow uses when it catalogs
-- the data that\'s transferred by the associated flow. When Amazon AppFlow
-- catalogs the data from a flow, it stores metadata in a data catalog.
--
-- 'schemaVersion', 'describeFlowResponse_schemaVersion' - The version number of your data schema. Amazon AppFlow assigns this
-- version number. The version number increases by one when you change any
-- of the following settings in your flow configuration:
--
-- -   Source-to-destination field mappings
--
-- -   Field data types
--
-- -   Partition keys
--
-- 'sourceFlowConfig', 'describeFlowResponse_sourceFlowConfig' - The configuration that controls how Amazon AppFlow retrieves data from
-- the source connector.
--
-- 'tags', 'describeFlowResponse_tags' - The tags used to organize, track, or control access for your flow.
--
-- 'tasks', 'describeFlowResponse_tasks' - A list of tasks that Amazon AppFlow performs while transferring the data
-- in the flow run.
--
-- 'triggerConfig', 'describeFlowResponse_triggerConfig' - The trigger settings that determine how and when the flow runs.
--
-- 'httpStatus', 'describeFlowResponse_httpStatus' - The response's http status code.
newDescribeFlowResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeFlowResponse
newDescribeFlowResponse :: Int -> DescribeFlowResponse
newDescribeFlowResponse Int
pHttpStatus_ =
  DescribeFlowResponse'
    { $sel:createdAt:DescribeFlowResponse' :: Maybe POSIX
createdAt = forall a. Maybe a
Prelude.Nothing,
      $sel:createdBy:DescribeFlowResponse' :: Maybe Text
createdBy = forall a. Maybe a
Prelude.Nothing,
      $sel:description:DescribeFlowResponse' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:destinationFlowConfigList:DescribeFlowResponse' :: Maybe [DestinationFlowConfig]
destinationFlowConfigList = forall a. Maybe a
Prelude.Nothing,
      $sel:flowArn:DescribeFlowResponse' :: Maybe Text
flowArn = forall a. Maybe a
Prelude.Nothing,
      $sel:flowName:DescribeFlowResponse' :: Maybe Text
flowName = forall a. Maybe a
Prelude.Nothing,
      $sel:flowStatus:DescribeFlowResponse' :: Maybe FlowStatus
flowStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:flowStatusMessage:DescribeFlowResponse' :: Maybe Text
flowStatusMessage = forall a. Maybe a
Prelude.Nothing,
      $sel:kmsArn:DescribeFlowResponse' :: Maybe Text
kmsArn = forall a. Maybe a
Prelude.Nothing,
      $sel:lastRunExecutionDetails:DescribeFlowResponse' :: Maybe ExecutionDetails
lastRunExecutionDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:lastRunMetadataCatalogDetails:DescribeFlowResponse' :: Maybe [MetadataCatalogDetail]
lastRunMetadataCatalogDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:lastUpdatedAt:DescribeFlowResponse' :: Maybe POSIX
lastUpdatedAt = forall a. Maybe a
Prelude.Nothing,
      $sel:lastUpdatedBy:DescribeFlowResponse' :: Maybe Text
lastUpdatedBy = forall a. Maybe a
Prelude.Nothing,
      $sel:metadataCatalogConfig:DescribeFlowResponse' :: Maybe MetadataCatalogConfig
metadataCatalogConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:schemaVersion:DescribeFlowResponse' :: Maybe Integer
schemaVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceFlowConfig:DescribeFlowResponse' :: Maybe SourceFlowConfig
sourceFlowConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:DescribeFlowResponse' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:tasks:DescribeFlowResponse' :: Maybe [Task]
tasks = forall a. Maybe a
Prelude.Nothing,
      $sel:triggerConfig:DescribeFlowResponse' :: Maybe TriggerConfig
triggerConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeFlowResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Specifies when the flow was created.
describeFlowResponse_createdAt :: Lens.Lens' DescribeFlowResponse (Prelude.Maybe Prelude.UTCTime)
describeFlowResponse_createdAt :: Lens' DescribeFlowResponse (Maybe UTCTime)
describeFlowResponse_createdAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFlowResponse' {Maybe POSIX
createdAt :: Maybe POSIX
$sel:createdAt:DescribeFlowResponse' :: DescribeFlowResponse -> Maybe POSIX
createdAt} -> Maybe POSIX
createdAt) (\s :: DescribeFlowResponse
s@DescribeFlowResponse' {} Maybe POSIX
a -> DescribeFlowResponse
s {$sel:createdAt:DescribeFlowResponse' :: Maybe POSIX
createdAt = Maybe POSIX
a} :: DescribeFlowResponse) 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.
describeFlowResponse_createdBy :: Lens.Lens' DescribeFlowResponse (Prelude.Maybe Prelude.Text)
describeFlowResponse_createdBy :: Lens' DescribeFlowResponse (Maybe Text)
describeFlowResponse_createdBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFlowResponse' {Maybe Text
createdBy :: Maybe Text
$sel:createdBy:DescribeFlowResponse' :: DescribeFlowResponse -> Maybe Text
createdBy} -> Maybe Text
createdBy) (\s :: DescribeFlowResponse
s@DescribeFlowResponse' {} Maybe Text
a -> DescribeFlowResponse
s {$sel:createdBy:DescribeFlowResponse' :: Maybe Text
createdBy = Maybe Text
a} :: DescribeFlowResponse)

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

-- | The configuration that controls how Amazon AppFlow transfers data to the
-- destination connector.
describeFlowResponse_destinationFlowConfigList :: Lens.Lens' DescribeFlowResponse (Prelude.Maybe [DestinationFlowConfig])
describeFlowResponse_destinationFlowConfigList :: Lens' DescribeFlowResponse (Maybe [DestinationFlowConfig])
describeFlowResponse_destinationFlowConfigList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFlowResponse' {Maybe [DestinationFlowConfig]
destinationFlowConfigList :: Maybe [DestinationFlowConfig]
$sel:destinationFlowConfigList:DescribeFlowResponse' :: DescribeFlowResponse -> Maybe [DestinationFlowConfig]
destinationFlowConfigList} -> Maybe [DestinationFlowConfig]
destinationFlowConfigList) (\s :: DescribeFlowResponse
s@DescribeFlowResponse' {} Maybe [DestinationFlowConfig]
a -> DescribeFlowResponse
s {$sel:destinationFlowConfigList:DescribeFlowResponse' :: Maybe [DestinationFlowConfig]
destinationFlowConfigList = Maybe [DestinationFlowConfig]
a} :: DescribeFlowResponse) 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 flow\'s Amazon Resource Name (ARN).
describeFlowResponse_flowArn :: Lens.Lens' DescribeFlowResponse (Prelude.Maybe Prelude.Text)
describeFlowResponse_flowArn :: Lens' DescribeFlowResponse (Maybe Text)
describeFlowResponse_flowArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFlowResponse' {Maybe Text
flowArn :: Maybe Text
$sel:flowArn:DescribeFlowResponse' :: DescribeFlowResponse -> Maybe Text
flowArn} -> Maybe Text
flowArn) (\s :: DescribeFlowResponse
s@DescribeFlowResponse' {} Maybe Text
a -> DescribeFlowResponse
s {$sel:flowArn:DescribeFlowResponse' :: Maybe Text
flowArn = Maybe Text
a} :: DescribeFlowResponse)

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

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

-- | Contains an error message if the flow status is in a suspended or error
-- state. This applies only to scheduled or event-triggered flows.
describeFlowResponse_flowStatusMessage :: Lens.Lens' DescribeFlowResponse (Prelude.Maybe Prelude.Text)
describeFlowResponse_flowStatusMessage :: Lens' DescribeFlowResponse (Maybe Text)
describeFlowResponse_flowStatusMessage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFlowResponse' {Maybe Text
flowStatusMessage :: Maybe Text
$sel:flowStatusMessage:DescribeFlowResponse' :: DescribeFlowResponse -> Maybe Text
flowStatusMessage} -> Maybe Text
flowStatusMessage) (\s :: DescribeFlowResponse
s@DescribeFlowResponse' {} Maybe Text
a -> DescribeFlowResponse
s {$sel:flowStatusMessage:DescribeFlowResponse' :: Maybe Text
flowStatusMessage = Maybe Text
a} :: DescribeFlowResponse)

-- | The ARN (Amazon Resource Name) of the Key Management Service (KMS) key
-- you provide for encryption. This is required if you do not want to use
-- the Amazon AppFlow-managed KMS key. If you don\'t provide anything here,
-- Amazon AppFlow uses the Amazon AppFlow-managed KMS key.
describeFlowResponse_kmsArn :: Lens.Lens' DescribeFlowResponse (Prelude.Maybe Prelude.Text)
describeFlowResponse_kmsArn :: Lens' DescribeFlowResponse (Maybe Text)
describeFlowResponse_kmsArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFlowResponse' {Maybe Text
kmsArn :: Maybe Text
$sel:kmsArn:DescribeFlowResponse' :: DescribeFlowResponse -> Maybe Text
kmsArn} -> Maybe Text
kmsArn) (\s :: DescribeFlowResponse
s@DescribeFlowResponse' {} Maybe Text
a -> DescribeFlowResponse
s {$sel:kmsArn:DescribeFlowResponse' :: Maybe Text
kmsArn = Maybe Text
a} :: DescribeFlowResponse)

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

-- | Describes the metadata catalog, metadata table, and data partitions that
-- Amazon AppFlow used for the associated flow run.
describeFlowResponse_lastRunMetadataCatalogDetails :: Lens.Lens' DescribeFlowResponse (Prelude.Maybe [MetadataCatalogDetail])
describeFlowResponse_lastRunMetadataCatalogDetails :: Lens' DescribeFlowResponse (Maybe [MetadataCatalogDetail])
describeFlowResponse_lastRunMetadataCatalogDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFlowResponse' {Maybe [MetadataCatalogDetail]
lastRunMetadataCatalogDetails :: Maybe [MetadataCatalogDetail]
$sel:lastRunMetadataCatalogDetails:DescribeFlowResponse' :: DescribeFlowResponse -> Maybe [MetadataCatalogDetail]
lastRunMetadataCatalogDetails} -> Maybe [MetadataCatalogDetail]
lastRunMetadataCatalogDetails) (\s :: DescribeFlowResponse
s@DescribeFlowResponse' {} Maybe [MetadataCatalogDetail]
a -> DescribeFlowResponse
s {$sel:lastRunMetadataCatalogDetails:DescribeFlowResponse' :: Maybe [MetadataCatalogDetail]
lastRunMetadataCatalogDetails = Maybe [MetadataCatalogDetail]
a} :: DescribeFlowResponse) 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 when the flow was last updated.
describeFlowResponse_lastUpdatedAt :: Lens.Lens' DescribeFlowResponse (Prelude.Maybe Prelude.UTCTime)
describeFlowResponse_lastUpdatedAt :: Lens' DescribeFlowResponse (Maybe UTCTime)
describeFlowResponse_lastUpdatedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFlowResponse' {Maybe POSIX
lastUpdatedAt :: Maybe POSIX
$sel:lastUpdatedAt:DescribeFlowResponse' :: DescribeFlowResponse -> Maybe POSIX
lastUpdatedAt} -> Maybe POSIX
lastUpdatedAt) (\s :: DescribeFlowResponse
s@DescribeFlowResponse' {} Maybe POSIX
a -> DescribeFlowResponse
s {$sel:lastUpdatedAt:DescribeFlowResponse' :: Maybe POSIX
lastUpdatedAt = Maybe POSIX
a} :: DescribeFlowResponse) 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 user name of the account that performed the most recent
-- update.
describeFlowResponse_lastUpdatedBy :: Lens.Lens' DescribeFlowResponse (Prelude.Maybe Prelude.Text)
describeFlowResponse_lastUpdatedBy :: Lens' DescribeFlowResponse (Maybe Text)
describeFlowResponse_lastUpdatedBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFlowResponse' {Maybe Text
lastUpdatedBy :: Maybe Text
$sel:lastUpdatedBy:DescribeFlowResponse' :: DescribeFlowResponse -> Maybe Text
lastUpdatedBy} -> Maybe Text
lastUpdatedBy) (\s :: DescribeFlowResponse
s@DescribeFlowResponse' {} Maybe Text
a -> DescribeFlowResponse
s {$sel:lastUpdatedBy:DescribeFlowResponse' :: Maybe Text
lastUpdatedBy = Maybe Text
a} :: DescribeFlowResponse)

-- | Specifies the configuration that Amazon AppFlow uses when it catalogs
-- the data that\'s transferred by the associated flow. When Amazon AppFlow
-- catalogs the data from a flow, it stores metadata in a data catalog.
describeFlowResponse_metadataCatalogConfig :: Lens.Lens' DescribeFlowResponse (Prelude.Maybe MetadataCatalogConfig)
describeFlowResponse_metadataCatalogConfig :: Lens' DescribeFlowResponse (Maybe MetadataCatalogConfig)
describeFlowResponse_metadataCatalogConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFlowResponse' {Maybe MetadataCatalogConfig
metadataCatalogConfig :: Maybe MetadataCatalogConfig
$sel:metadataCatalogConfig:DescribeFlowResponse' :: DescribeFlowResponse -> Maybe MetadataCatalogConfig
metadataCatalogConfig} -> Maybe MetadataCatalogConfig
metadataCatalogConfig) (\s :: DescribeFlowResponse
s@DescribeFlowResponse' {} Maybe MetadataCatalogConfig
a -> DescribeFlowResponse
s {$sel:metadataCatalogConfig:DescribeFlowResponse' :: Maybe MetadataCatalogConfig
metadataCatalogConfig = Maybe MetadataCatalogConfig
a} :: DescribeFlowResponse)

-- | The version number of your data schema. Amazon AppFlow assigns this
-- version number. The version number increases by one when you change any
-- of the following settings in your flow configuration:
--
-- -   Source-to-destination field mappings
--
-- -   Field data types
--
-- -   Partition keys
describeFlowResponse_schemaVersion :: Lens.Lens' DescribeFlowResponse (Prelude.Maybe Prelude.Integer)
describeFlowResponse_schemaVersion :: Lens' DescribeFlowResponse (Maybe Integer)
describeFlowResponse_schemaVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFlowResponse' {Maybe Integer
schemaVersion :: Maybe Integer
$sel:schemaVersion:DescribeFlowResponse' :: DescribeFlowResponse -> Maybe Integer
schemaVersion} -> Maybe Integer
schemaVersion) (\s :: DescribeFlowResponse
s@DescribeFlowResponse' {} Maybe Integer
a -> DescribeFlowResponse
s {$sel:schemaVersion:DescribeFlowResponse' :: Maybe Integer
schemaVersion = Maybe Integer
a} :: DescribeFlowResponse)

-- | The configuration that controls how Amazon AppFlow retrieves data from
-- the source connector.
describeFlowResponse_sourceFlowConfig :: Lens.Lens' DescribeFlowResponse (Prelude.Maybe SourceFlowConfig)
describeFlowResponse_sourceFlowConfig :: Lens' DescribeFlowResponse (Maybe SourceFlowConfig)
describeFlowResponse_sourceFlowConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFlowResponse' {Maybe SourceFlowConfig
sourceFlowConfig :: Maybe SourceFlowConfig
$sel:sourceFlowConfig:DescribeFlowResponse' :: DescribeFlowResponse -> Maybe SourceFlowConfig
sourceFlowConfig} -> Maybe SourceFlowConfig
sourceFlowConfig) (\s :: DescribeFlowResponse
s@DescribeFlowResponse' {} Maybe SourceFlowConfig
a -> DescribeFlowResponse
s {$sel:sourceFlowConfig:DescribeFlowResponse' :: Maybe SourceFlowConfig
sourceFlowConfig = Maybe SourceFlowConfig
a} :: DescribeFlowResponse)

-- | The tags used to organize, track, or control access for your flow.
describeFlowResponse_tags :: Lens.Lens' DescribeFlowResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
describeFlowResponse_tags :: Lens' DescribeFlowResponse (Maybe (HashMap Text Text))
describeFlowResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFlowResponse' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:DescribeFlowResponse' :: DescribeFlowResponse -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: DescribeFlowResponse
s@DescribeFlowResponse' {} Maybe (HashMap Text Text)
a -> DescribeFlowResponse
s {$sel:tags:DescribeFlowResponse' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: DescribeFlowResponse) 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

-- | A list of tasks that Amazon AppFlow performs while transferring the data
-- in the flow run.
describeFlowResponse_tasks :: Lens.Lens' DescribeFlowResponse (Prelude.Maybe [Task])
describeFlowResponse_tasks :: Lens' DescribeFlowResponse (Maybe [Task])
describeFlowResponse_tasks = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFlowResponse' {Maybe [Task]
tasks :: Maybe [Task]
$sel:tasks:DescribeFlowResponse' :: DescribeFlowResponse -> Maybe [Task]
tasks} -> Maybe [Task]
tasks) (\s :: DescribeFlowResponse
s@DescribeFlowResponse' {} Maybe [Task]
a -> DescribeFlowResponse
s {$sel:tasks:DescribeFlowResponse' :: Maybe [Task]
tasks = Maybe [Task]
a} :: DescribeFlowResponse) 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 trigger settings that determine how and when the flow runs.
describeFlowResponse_triggerConfig :: Lens.Lens' DescribeFlowResponse (Prelude.Maybe TriggerConfig)
describeFlowResponse_triggerConfig :: Lens' DescribeFlowResponse (Maybe TriggerConfig)
describeFlowResponse_triggerConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFlowResponse' {Maybe TriggerConfig
triggerConfig :: Maybe TriggerConfig
$sel:triggerConfig:DescribeFlowResponse' :: DescribeFlowResponse -> Maybe TriggerConfig
triggerConfig} -> Maybe TriggerConfig
triggerConfig) (\s :: DescribeFlowResponse
s@DescribeFlowResponse' {} Maybe TriggerConfig
a -> DescribeFlowResponse
s {$sel:triggerConfig:DescribeFlowResponse' :: Maybe TriggerConfig
triggerConfig = Maybe TriggerConfig
a} :: DescribeFlowResponse)

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

instance Prelude.NFData DescribeFlowResponse where
  rnf :: DescribeFlowResponse -> ()
rnf DescribeFlowResponse' {Int
Maybe Integer
Maybe [MetadataCatalogDetail]
Maybe [Task]
Maybe [DestinationFlowConfig]
Maybe Text
Maybe (HashMap Text Text)
Maybe POSIX
Maybe ExecutionDetails
Maybe FlowStatus
Maybe MetadataCatalogConfig
Maybe TriggerConfig
Maybe SourceFlowConfig
httpStatus :: Int
triggerConfig :: Maybe TriggerConfig
tasks :: Maybe [Task]
tags :: Maybe (HashMap Text Text)
sourceFlowConfig :: Maybe SourceFlowConfig
schemaVersion :: Maybe Integer
metadataCatalogConfig :: Maybe MetadataCatalogConfig
lastUpdatedBy :: Maybe Text
lastUpdatedAt :: Maybe POSIX
lastRunMetadataCatalogDetails :: Maybe [MetadataCatalogDetail]
lastRunExecutionDetails :: Maybe ExecutionDetails
kmsArn :: Maybe Text
flowStatusMessage :: Maybe Text
flowStatus :: Maybe FlowStatus
flowName :: Maybe Text
flowArn :: Maybe Text
destinationFlowConfigList :: Maybe [DestinationFlowConfig]
description :: Maybe Text
createdBy :: Maybe Text
createdAt :: Maybe POSIX
$sel:httpStatus:DescribeFlowResponse' :: DescribeFlowResponse -> Int
$sel:triggerConfig:DescribeFlowResponse' :: DescribeFlowResponse -> Maybe TriggerConfig
$sel:tasks:DescribeFlowResponse' :: DescribeFlowResponse -> Maybe [Task]
$sel:tags:DescribeFlowResponse' :: DescribeFlowResponse -> Maybe (HashMap Text Text)
$sel:sourceFlowConfig:DescribeFlowResponse' :: DescribeFlowResponse -> Maybe SourceFlowConfig
$sel:schemaVersion:DescribeFlowResponse' :: DescribeFlowResponse -> Maybe Integer
$sel:metadataCatalogConfig:DescribeFlowResponse' :: DescribeFlowResponse -> Maybe MetadataCatalogConfig
$sel:lastUpdatedBy:DescribeFlowResponse' :: DescribeFlowResponse -> Maybe Text
$sel:lastUpdatedAt:DescribeFlowResponse' :: DescribeFlowResponse -> Maybe POSIX
$sel:lastRunMetadataCatalogDetails:DescribeFlowResponse' :: DescribeFlowResponse -> Maybe [MetadataCatalogDetail]
$sel:lastRunExecutionDetails:DescribeFlowResponse' :: DescribeFlowResponse -> Maybe ExecutionDetails
$sel:kmsArn:DescribeFlowResponse' :: DescribeFlowResponse -> Maybe Text
$sel:flowStatusMessage:DescribeFlowResponse' :: DescribeFlowResponse -> Maybe Text
$sel:flowStatus:DescribeFlowResponse' :: DescribeFlowResponse -> Maybe FlowStatus
$sel:flowName:DescribeFlowResponse' :: DescribeFlowResponse -> Maybe Text
$sel:flowArn:DescribeFlowResponse' :: DescribeFlowResponse -> Maybe Text
$sel:destinationFlowConfigList:DescribeFlowResponse' :: DescribeFlowResponse -> Maybe [DestinationFlowConfig]
$sel:description:DescribeFlowResponse' :: DescribeFlowResponse -> Maybe Text
$sel:createdBy:DescribeFlowResponse' :: DescribeFlowResponse -> Maybe Text
$sel:createdAt:DescribeFlowResponse' :: DescribeFlowResponse -> 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 [DestinationFlowConfig]
destinationFlowConfigList
      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 Text
flowStatusMessage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
kmsArn
      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 [MetadataCatalogDetail]
lastRunMetadataCatalogDetails
      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 MetadataCatalogConfig
metadataCatalogConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
schemaVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SourceFlowConfig
sourceFlowConfig
      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 [Task]
tasks
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TriggerConfig
triggerConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus