{-# 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.Forecast.DescribeWhatIfForecastExport
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Describes the what-if forecast export created using the
-- CreateWhatIfForecastExport operation.
--
-- In addition to listing the properties provided in the
-- @CreateWhatIfForecastExport@ request, this operation lists the following
-- properties:
--
-- -   @CreationTime@
--
-- -   @LastModificationTime@
--
-- -   @Message@ - If an error occurred, information about the error.
--
-- -   @Status@
module Amazonka.Forecast.DescribeWhatIfForecastExport
  ( -- * Creating a Request
    DescribeWhatIfForecastExport (..),
    newDescribeWhatIfForecastExport,

    -- * Request Lenses
    describeWhatIfForecastExport_whatIfForecastExportArn,

    -- * Destructuring the Response
    DescribeWhatIfForecastExportResponse (..),
    newDescribeWhatIfForecastExportResponse,

    -- * Response Lenses
    describeWhatIfForecastExportResponse_creationTime,
    describeWhatIfForecastExportResponse_destination,
    describeWhatIfForecastExportResponse_estimatedTimeRemainingInMinutes,
    describeWhatIfForecastExportResponse_format,
    describeWhatIfForecastExportResponse_lastModificationTime,
    describeWhatIfForecastExportResponse_message,
    describeWhatIfForecastExportResponse_status,
    describeWhatIfForecastExportResponse_whatIfForecastArns,
    describeWhatIfForecastExportResponse_whatIfForecastExportArn,
    describeWhatIfForecastExportResponse_whatIfForecastExportName,
    describeWhatIfForecastExportResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDescribeWhatIfForecastExport' smart constructor.
data DescribeWhatIfForecastExport = DescribeWhatIfForecastExport'
  { -- | The Amazon Resource Name (ARN) of the what-if forecast export that you
    -- are interested in.
    DescribeWhatIfForecastExport -> Text
whatIfForecastExportArn :: Prelude.Text
  }
  deriving (DescribeWhatIfForecastExport
-> DescribeWhatIfForecastExport -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeWhatIfForecastExport
-> DescribeWhatIfForecastExport -> Bool
$c/= :: DescribeWhatIfForecastExport
-> DescribeWhatIfForecastExport -> Bool
== :: DescribeWhatIfForecastExport
-> DescribeWhatIfForecastExport -> Bool
$c== :: DescribeWhatIfForecastExport
-> DescribeWhatIfForecastExport -> Bool
Prelude.Eq, ReadPrec [DescribeWhatIfForecastExport]
ReadPrec DescribeWhatIfForecastExport
Int -> ReadS DescribeWhatIfForecastExport
ReadS [DescribeWhatIfForecastExport]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeWhatIfForecastExport]
$creadListPrec :: ReadPrec [DescribeWhatIfForecastExport]
readPrec :: ReadPrec DescribeWhatIfForecastExport
$creadPrec :: ReadPrec DescribeWhatIfForecastExport
readList :: ReadS [DescribeWhatIfForecastExport]
$creadList :: ReadS [DescribeWhatIfForecastExport]
readsPrec :: Int -> ReadS DescribeWhatIfForecastExport
$creadsPrec :: Int -> ReadS DescribeWhatIfForecastExport
Prelude.Read, Int -> DescribeWhatIfForecastExport -> ShowS
[DescribeWhatIfForecastExport] -> ShowS
DescribeWhatIfForecastExport -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeWhatIfForecastExport] -> ShowS
$cshowList :: [DescribeWhatIfForecastExport] -> ShowS
show :: DescribeWhatIfForecastExport -> String
$cshow :: DescribeWhatIfForecastExport -> String
showsPrec :: Int -> DescribeWhatIfForecastExport -> ShowS
$cshowsPrec :: Int -> DescribeWhatIfForecastExport -> ShowS
Prelude.Show, forall x.
Rep DescribeWhatIfForecastExport x -> DescribeWhatIfForecastExport
forall x.
DescribeWhatIfForecastExport -> Rep DescribeWhatIfForecastExport x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeWhatIfForecastExport x -> DescribeWhatIfForecastExport
$cfrom :: forall x.
DescribeWhatIfForecastExport -> Rep DescribeWhatIfForecastExport x
Prelude.Generic)

-- |
-- Create a value of 'DescribeWhatIfForecastExport' 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:
--
-- 'whatIfForecastExportArn', 'describeWhatIfForecastExport_whatIfForecastExportArn' - The Amazon Resource Name (ARN) of the what-if forecast export that you
-- are interested in.
newDescribeWhatIfForecastExport ::
  -- | 'whatIfForecastExportArn'
  Prelude.Text ->
  DescribeWhatIfForecastExport
newDescribeWhatIfForecastExport :: Text -> DescribeWhatIfForecastExport
newDescribeWhatIfForecastExport
  Text
pWhatIfForecastExportArn_ =
    DescribeWhatIfForecastExport'
      { $sel:whatIfForecastExportArn:DescribeWhatIfForecastExport' :: Text
whatIfForecastExportArn =
          Text
pWhatIfForecastExportArn_
      }

-- | The Amazon Resource Name (ARN) of the what-if forecast export that you
-- are interested in.
describeWhatIfForecastExport_whatIfForecastExportArn :: Lens.Lens' DescribeWhatIfForecastExport Prelude.Text
describeWhatIfForecastExport_whatIfForecastExportArn :: Lens' DescribeWhatIfForecastExport Text
describeWhatIfForecastExport_whatIfForecastExportArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeWhatIfForecastExport' {Text
whatIfForecastExportArn :: Text
$sel:whatIfForecastExportArn:DescribeWhatIfForecastExport' :: DescribeWhatIfForecastExport -> Text
whatIfForecastExportArn} -> Text
whatIfForecastExportArn) (\s :: DescribeWhatIfForecastExport
s@DescribeWhatIfForecastExport' {} Text
a -> DescribeWhatIfForecastExport
s {$sel:whatIfForecastExportArn:DescribeWhatIfForecastExport' :: Text
whatIfForecastExportArn = Text
a} :: DescribeWhatIfForecastExport)

instance Core.AWSRequest DescribeWhatIfForecastExport where
  type
    AWSResponse DescribeWhatIfForecastExport =
      DescribeWhatIfForecastExportResponse
  request :: (Service -> Service)
-> DescribeWhatIfForecastExport
-> Request DescribeWhatIfForecastExport
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 DescribeWhatIfForecastExport
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeWhatIfForecastExport)))
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 DataDestination
-> Maybe Integer
-> Maybe Text
-> Maybe POSIX
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe Text
-> Maybe Text
-> Int
-> DescribeWhatIfForecastExportResponse
DescribeWhatIfForecastExportResponse'
            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
"CreationTime")
            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
"Destination")
            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
"EstimatedTimeRemainingInMinutes")
            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
"Format")
            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
"LastModificationTime")
            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
"Message")
            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
"Status")
            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
"WhatIfForecastArns"
                            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
"WhatIfForecastExportArn")
            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
"WhatIfForecastExportName")
            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
    DescribeWhatIfForecastExport
  where
  hashWithSalt :: Int -> DescribeWhatIfForecastExport -> Int
hashWithSalt Int
_salt DescribeWhatIfForecastExport' {Text
whatIfForecastExportArn :: Text
$sel:whatIfForecastExportArn:DescribeWhatIfForecastExport' :: DescribeWhatIfForecastExport -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
whatIfForecastExportArn

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

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

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

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

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

-- | /See:/ 'newDescribeWhatIfForecastExportResponse' smart constructor.
data DescribeWhatIfForecastExportResponse = DescribeWhatIfForecastExportResponse'
  { -- | When the what-if forecast export was created.
    DescribeWhatIfForecastExportResponse -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
    DescribeWhatIfForecastExportResponse -> Maybe DataDestination
destination :: Prelude.Maybe DataDestination,
    -- | The approximate time remaining to complete the what-if forecast export,
    -- in minutes.
    DescribeWhatIfForecastExportResponse -> Maybe Integer
estimatedTimeRemainingInMinutes :: Prelude.Maybe Prelude.Integer,
    -- | The format of the exported data, CSV or PARQUET.
    DescribeWhatIfForecastExportResponse -> Maybe Text
format :: Prelude.Maybe Prelude.Text,
    -- | The last time the resource was modified. The timestamp depends on the
    -- status of the job:
    --
    -- -   @CREATE_PENDING@ - The @CreationTime@.
    --
    -- -   @CREATE_IN_PROGRESS@ - The current timestamp.
    --
    -- -   @CREATE_STOPPING@ - The current timestamp.
    --
    -- -   @CREATE_STOPPED@ - When the job stopped.
    --
    -- -   @ACTIVE@ or @CREATE_FAILED@ - When the job finished or failed.
    DescribeWhatIfForecastExportResponse -> Maybe POSIX
lastModificationTime :: Prelude.Maybe Data.POSIX,
    -- | If an error occurred, an informational message about the error.
    DescribeWhatIfForecastExportResponse -> Maybe Text
message :: Prelude.Maybe Prelude.Text,
    -- | The status of the what-if forecast. States include:
    --
    -- -   @ACTIVE@
    --
    -- -   @CREATE_PENDING@, @CREATE_IN_PROGRESS@, @CREATE_FAILED@
    --
    -- -   @CREATE_STOPPING@, @CREATE_STOPPED@
    --
    -- -   @DELETE_PENDING@, @DELETE_IN_PROGRESS@, @DELETE_FAILED@
    --
    -- The @Status@ of the what-if forecast export must be @ACTIVE@ before you
    -- can access the forecast export.
    DescribeWhatIfForecastExportResponse -> Maybe Text
status :: Prelude.Maybe Prelude.Text,
    -- | An array of Amazon Resource Names (ARNs) that represent all of the
    -- what-if forecasts exported in this resource.
    DescribeWhatIfForecastExportResponse -> Maybe [Text]
whatIfForecastArns :: Prelude.Maybe [Prelude.Text],
    -- | The Amazon Resource Name (ARN) of the what-if forecast export.
    DescribeWhatIfForecastExportResponse -> Maybe Text
whatIfForecastExportArn :: Prelude.Maybe Prelude.Text,
    -- | The name of the what-if forecast export.
    DescribeWhatIfForecastExportResponse -> Maybe Text
whatIfForecastExportName :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DescribeWhatIfForecastExportResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeWhatIfForecastExportResponse
-> DescribeWhatIfForecastExportResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeWhatIfForecastExportResponse
-> DescribeWhatIfForecastExportResponse -> Bool
$c/= :: DescribeWhatIfForecastExportResponse
-> DescribeWhatIfForecastExportResponse -> Bool
== :: DescribeWhatIfForecastExportResponse
-> DescribeWhatIfForecastExportResponse -> Bool
$c== :: DescribeWhatIfForecastExportResponse
-> DescribeWhatIfForecastExportResponse -> Bool
Prelude.Eq, ReadPrec [DescribeWhatIfForecastExportResponse]
ReadPrec DescribeWhatIfForecastExportResponse
Int -> ReadS DescribeWhatIfForecastExportResponse
ReadS [DescribeWhatIfForecastExportResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeWhatIfForecastExportResponse]
$creadListPrec :: ReadPrec [DescribeWhatIfForecastExportResponse]
readPrec :: ReadPrec DescribeWhatIfForecastExportResponse
$creadPrec :: ReadPrec DescribeWhatIfForecastExportResponse
readList :: ReadS [DescribeWhatIfForecastExportResponse]
$creadList :: ReadS [DescribeWhatIfForecastExportResponse]
readsPrec :: Int -> ReadS DescribeWhatIfForecastExportResponse
$creadsPrec :: Int -> ReadS DescribeWhatIfForecastExportResponse
Prelude.Read, Int -> DescribeWhatIfForecastExportResponse -> ShowS
[DescribeWhatIfForecastExportResponse] -> ShowS
DescribeWhatIfForecastExportResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeWhatIfForecastExportResponse] -> ShowS
$cshowList :: [DescribeWhatIfForecastExportResponse] -> ShowS
show :: DescribeWhatIfForecastExportResponse -> String
$cshow :: DescribeWhatIfForecastExportResponse -> String
showsPrec :: Int -> DescribeWhatIfForecastExportResponse -> ShowS
$cshowsPrec :: Int -> DescribeWhatIfForecastExportResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeWhatIfForecastExportResponse x
-> DescribeWhatIfForecastExportResponse
forall x.
DescribeWhatIfForecastExportResponse
-> Rep DescribeWhatIfForecastExportResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeWhatIfForecastExportResponse x
-> DescribeWhatIfForecastExportResponse
$cfrom :: forall x.
DescribeWhatIfForecastExportResponse
-> Rep DescribeWhatIfForecastExportResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeWhatIfForecastExportResponse' 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:
--
-- 'creationTime', 'describeWhatIfForecastExportResponse_creationTime' - When the what-if forecast export was created.
--
-- 'destination', 'describeWhatIfForecastExportResponse_destination' - Undocumented member.
--
-- 'estimatedTimeRemainingInMinutes', 'describeWhatIfForecastExportResponse_estimatedTimeRemainingInMinutes' - The approximate time remaining to complete the what-if forecast export,
-- in minutes.
--
-- 'format', 'describeWhatIfForecastExportResponse_format' - The format of the exported data, CSV or PARQUET.
--
-- 'lastModificationTime', 'describeWhatIfForecastExportResponse_lastModificationTime' - The last time the resource was modified. The timestamp depends on the
-- status of the job:
--
-- -   @CREATE_PENDING@ - The @CreationTime@.
--
-- -   @CREATE_IN_PROGRESS@ - The current timestamp.
--
-- -   @CREATE_STOPPING@ - The current timestamp.
--
-- -   @CREATE_STOPPED@ - When the job stopped.
--
-- -   @ACTIVE@ or @CREATE_FAILED@ - When the job finished or failed.
--
-- 'message', 'describeWhatIfForecastExportResponse_message' - If an error occurred, an informational message about the error.
--
-- 'status', 'describeWhatIfForecastExportResponse_status' - The status of the what-if forecast. States include:
--
-- -   @ACTIVE@
--
-- -   @CREATE_PENDING@, @CREATE_IN_PROGRESS@, @CREATE_FAILED@
--
-- -   @CREATE_STOPPING@, @CREATE_STOPPED@
--
-- -   @DELETE_PENDING@, @DELETE_IN_PROGRESS@, @DELETE_FAILED@
--
-- The @Status@ of the what-if forecast export must be @ACTIVE@ before you
-- can access the forecast export.
--
-- 'whatIfForecastArns', 'describeWhatIfForecastExportResponse_whatIfForecastArns' - An array of Amazon Resource Names (ARNs) that represent all of the
-- what-if forecasts exported in this resource.
--
-- 'whatIfForecastExportArn', 'describeWhatIfForecastExportResponse_whatIfForecastExportArn' - The Amazon Resource Name (ARN) of the what-if forecast export.
--
-- 'whatIfForecastExportName', 'describeWhatIfForecastExportResponse_whatIfForecastExportName' - The name of the what-if forecast export.
--
-- 'httpStatus', 'describeWhatIfForecastExportResponse_httpStatus' - The response's http status code.
newDescribeWhatIfForecastExportResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeWhatIfForecastExportResponse
newDescribeWhatIfForecastExportResponse :: Int -> DescribeWhatIfForecastExportResponse
newDescribeWhatIfForecastExportResponse Int
pHttpStatus_ =
  DescribeWhatIfForecastExportResponse'
    { $sel:creationTime:DescribeWhatIfForecastExportResponse' :: Maybe POSIX
creationTime =
        forall a. Maybe a
Prelude.Nothing,
      $sel:destination:DescribeWhatIfForecastExportResponse' :: Maybe DataDestination
destination = forall a. Maybe a
Prelude.Nothing,
      $sel:estimatedTimeRemainingInMinutes:DescribeWhatIfForecastExportResponse' :: Maybe Integer
estimatedTimeRemainingInMinutes =
        forall a. Maybe a
Prelude.Nothing,
      $sel:format:DescribeWhatIfForecastExportResponse' :: Maybe Text
format = forall a. Maybe a
Prelude.Nothing,
      $sel:lastModificationTime:DescribeWhatIfForecastExportResponse' :: Maybe POSIX
lastModificationTime =
        forall a. Maybe a
Prelude.Nothing,
      $sel:message:DescribeWhatIfForecastExportResponse' :: Maybe Text
message = forall a. Maybe a
Prelude.Nothing,
      $sel:status:DescribeWhatIfForecastExportResponse' :: Maybe Text
status = forall a. Maybe a
Prelude.Nothing,
      $sel:whatIfForecastArns:DescribeWhatIfForecastExportResponse' :: Maybe [Text]
whatIfForecastArns = forall a. Maybe a
Prelude.Nothing,
      $sel:whatIfForecastExportArn:DescribeWhatIfForecastExportResponse' :: Maybe Text
whatIfForecastExportArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:whatIfForecastExportName:DescribeWhatIfForecastExportResponse' :: Maybe Text
whatIfForecastExportName =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeWhatIfForecastExportResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | When the what-if forecast export was created.
describeWhatIfForecastExportResponse_creationTime :: Lens.Lens' DescribeWhatIfForecastExportResponse (Prelude.Maybe Prelude.UTCTime)
describeWhatIfForecastExportResponse_creationTime :: Lens' DescribeWhatIfForecastExportResponse (Maybe UTCTime)
describeWhatIfForecastExportResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeWhatIfForecastExportResponse' {Maybe POSIX
creationTime :: Maybe POSIX
$sel:creationTime:DescribeWhatIfForecastExportResponse' :: DescribeWhatIfForecastExportResponse -> Maybe POSIX
creationTime} -> Maybe POSIX
creationTime) (\s :: DescribeWhatIfForecastExportResponse
s@DescribeWhatIfForecastExportResponse' {} Maybe POSIX
a -> DescribeWhatIfForecastExportResponse
s {$sel:creationTime:DescribeWhatIfForecastExportResponse' :: Maybe POSIX
creationTime = Maybe POSIX
a} :: DescribeWhatIfForecastExportResponse) 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

-- | Undocumented member.
describeWhatIfForecastExportResponse_destination :: Lens.Lens' DescribeWhatIfForecastExportResponse (Prelude.Maybe DataDestination)
describeWhatIfForecastExportResponse_destination :: Lens' DescribeWhatIfForecastExportResponse (Maybe DataDestination)
describeWhatIfForecastExportResponse_destination = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeWhatIfForecastExportResponse' {Maybe DataDestination
destination :: Maybe DataDestination
$sel:destination:DescribeWhatIfForecastExportResponse' :: DescribeWhatIfForecastExportResponse -> Maybe DataDestination
destination} -> Maybe DataDestination
destination) (\s :: DescribeWhatIfForecastExportResponse
s@DescribeWhatIfForecastExportResponse' {} Maybe DataDestination
a -> DescribeWhatIfForecastExportResponse
s {$sel:destination:DescribeWhatIfForecastExportResponse' :: Maybe DataDestination
destination = Maybe DataDestination
a} :: DescribeWhatIfForecastExportResponse)

-- | The approximate time remaining to complete the what-if forecast export,
-- in minutes.
describeWhatIfForecastExportResponse_estimatedTimeRemainingInMinutes :: Lens.Lens' DescribeWhatIfForecastExportResponse (Prelude.Maybe Prelude.Integer)
describeWhatIfForecastExportResponse_estimatedTimeRemainingInMinutes :: Lens' DescribeWhatIfForecastExportResponse (Maybe Integer)
describeWhatIfForecastExportResponse_estimatedTimeRemainingInMinutes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeWhatIfForecastExportResponse' {Maybe Integer
estimatedTimeRemainingInMinutes :: Maybe Integer
$sel:estimatedTimeRemainingInMinutes:DescribeWhatIfForecastExportResponse' :: DescribeWhatIfForecastExportResponse -> Maybe Integer
estimatedTimeRemainingInMinutes} -> Maybe Integer
estimatedTimeRemainingInMinutes) (\s :: DescribeWhatIfForecastExportResponse
s@DescribeWhatIfForecastExportResponse' {} Maybe Integer
a -> DescribeWhatIfForecastExportResponse
s {$sel:estimatedTimeRemainingInMinutes:DescribeWhatIfForecastExportResponse' :: Maybe Integer
estimatedTimeRemainingInMinutes = Maybe Integer
a} :: DescribeWhatIfForecastExportResponse)

-- | The format of the exported data, CSV or PARQUET.
describeWhatIfForecastExportResponse_format :: Lens.Lens' DescribeWhatIfForecastExportResponse (Prelude.Maybe Prelude.Text)
describeWhatIfForecastExportResponse_format :: Lens' DescribeWhatIfForecastExportResponse (Maybe Text)
describeWhatIfForecastExportResponse_format = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeWhatIfForecastExportResponse' {Maybe Text
format :: Maybe Text
$sel:format:DescribeWhatIfForecastExportResponse' :: DescribeWhatIfForecastExportResponse -> Maybe Text
format} -> Maybe Text
format) (\s :: DescribeWhatIfForecastExportResponse
s@DescribeWhatIfForecastExportResponse' {} Maybe Text
a -> DescribeWhatIfForecastExportResponse
s {$sel:format:DescribeWhatIfForecastExportResponse' :: Maybe Text
format = Maybe Text
a} :: DescribeWhatIfForecastExportResponse)

-- | The last time the resource was modified. The timestamp depends on the
-- status of the job:
--
-- -   @CREATE_PENDING@ - The @CreationTime@.
--
-- -   @CREATE_IN_PROGRESS@ - The current timestamp.
--
-- -   @CREATE_STOPPING@ - The current timestamp.
--
-- -   @CREATE_STOPPED@ - When the job stopped.
--
-- -   @ACTIVE@ or @CREATE_FAILED@ - When the job finished or failed.
describeWhatIfForecastExportResponse_lastModificationTime :: Lens.Lens' DescribeWhatIfForecastExportResponse (Prelude.Maybe Prelude.UTCTime)
describeWhatIfForecastExportResponse_lastModificationTime :: Lens' DescribeWhatIfForecastExportResponse (Maybe UTCTime)
describeWhatIfForecastExportResponse_lastModificationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeWhatIfForecastExportResponse' {Maybe POSIX
lastModificationTime :: Maybe POSIX
$sel:lastModificationTime:DescribeWhatIfForecastExportResponse' :: DescribeWhatIfForecastExportResponse -> Maybe POSIX
lastModificationTime} -> Maybe POSIX
lastModificationTime) (\s :: DescribeWhatIfForecastExportResponse
s@DescribeWhatIfForecastExportResponse' {} Maybe POSIX
a -> DescribeWhatIfForecastExportResponse
s {$sel:lastModificationTime:DescribeWhatIfForecastExportResponse' :: Maybe POSIX
lastModificationTime = Maybe POSIX
a} :: DescribeWhatIfForecastExportResponse) 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

-- | If an error occurred, an informational message about the error.
describeWhatIfForecastExportResponse_message :: Lens.Lens' DescribeWhatIfForecastExportResponse (Prelude.Maybe Prelude.Text)
describeWhatIfForecastExportResponse_message :: Lens' DescribeWhatIfForecastExportResponse (Maybe Text)
describeWhatIfForecastExportResponse_message = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeWhatIfForecastExportResponse' {Maybe Text
message :: Maybe Text
$sel:message:DescribeWhatIfForecastExportResponse' :: DescribeWhatIfForecastExportResponse -> Maybe Text
message} -> Maybe Text
message) (\s :: DescribeWhatIfForecastExportResponse
s@DescribeWhatIfForecastExportResponse' {} Maybe Text
a -> DescribeWhatIfForecastExportResponse
s {$sel:message:DescribeWhatIfForecastExportResponse' :: Maybe Text
message = Maybe Text
a} :: DescribeWhatIfForecastExportResponse)

-- | The status of the what-if forecast. States include:
--
-- -   @ACTIVE@
--
-- -   @CREATE_PENDING@, @CREATE_IN_PROGRESS@, @CREATE_FAILED@
--
-- -   @CREATE_STOPPING@, @CREATE_STOPPED@
--
-- -   @DELETE_PENDING@, @DELETE_IN_PROGRESS@, @DELETE_FAILED@
--
-- The @Status@ of the what-if forecast export must be @ACTIVE@ before you
-- can access the forecast export.
describeWhatIfForecastExportResponse_status :: Lens.Lens' DescribeWhatIfForecastExportResponse (Prelude.Maybe Prelude.Text)
describeWhatIfForecastExportResponse_status :: Lens' DescribeWhatIfForecastExportResponse (Maybe Text)
describeWhatIfForecastExportResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeWhatIfForecastExportResponse' {Maybe Text
status :: Maybe Text
$sel:status:DescribeWhatIfForecastExportResponse' :: DescribeWhatIfForecastExportResponse -> Maybe Text
status} -> Maybe Text
status) (\s :: DescribeWhatIfForecastExportResponse
s@DescribeWhatIfForecastExportResponse' {} Maybe Text
a -> DescribeWhatIfForecastExportResponse
s {$sel:status:DescribeWhatIfForecastExportResponse' :: Maybe Text
status = Maybe Text
a} :: DescribeWhatIfForecastExportResponse)

-- | An array of Amazon Resource Names (ARNs) that represent all of the
-- what-if forecasts exported in this resource.
describeWhatIfForecastExportResponse_whatIfForecastArns :: Lens.Lens' DescribeWhatIfForecastExportResponse (Prelude.Maybe [Prelude.Text])
describeWhatIfForecastExportResponse_whatIfForecastArns :: Lens' DescribeWhatIfForecastExportResponse (Maybe [Text])
describeWhatIfForecastExportResponse_whatIfForecastArns = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeWhatIfForecastExportResponse' {Maybe [Text]
whatIfForecastArns :: Maybe [Text]
$sel:whatIfForecastArns:DescribeWhatIfForecastExportResponse' :: DescribeWhatIfForecastExportResponse -> Maybe [Text]
whatIfForecastArns} -> Maybe [Text]
whatIfForecastArns) (\s :: DescribeWhatIfForecastExportResponse
s@DescribeWhatIfForecastExportResponse' {} Maybe [Text]
a -> DescribeWhatIfForecastExportResponse
s {$sel:whatIfForecastArns:DescribeWhatIfForecastExportResponse' :: Maybe [Text]
whatIfForecastArns = Maybe [Text]
a} :: DescribeWhatIfForecastExportResponse) 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 Amazon Resource Name (ARN) of the what-if forecast export.
describeWhatIfForecastExportResponse_whatIfForecastExportArn :: Lens.Lens' DescribeWhatIfForecastExportResponse (Prelude.Maybe Prelude.Text)
describeWhatIfForecastExportResponse_whatIfForecastExportArn :: Lens' DescribeWhatIfForecastExportResponse (Maybe Text)
describeWhatIfForecastExportResponse_whatIfForecastExportArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeWhatIfForecastExportResponse' {Maybe Text
whatIfForecastExportArn :: Maybe Text
$sel:whatIfForecastExportArn:DescribeWhatIfForecastExportResponse' :: DescribeWhatIfForecastExportResponse -> Maybe Text
whatIfForecastExportArn} -> Maybe Text
whatIfForecastExportArn) (\s :: DescribeWhatIfForecastExportResponse
s@DescribeWhatIfForecastExportResponse' {} Maybe Text
a -> DescribeWhatIfForecastExportResponse
s {$sel:whatIfForecastExportArn:DescribeWhatIfForecastExportResponse' :: Maybe Text
whatIfForecastExportArn = Maybe Text
a} :: DescribeWhatIfForecastExportResponse)

-- | The name of the what-if forecast export.
describeWhatIfForecastExportResponse_whatIfForecastExportName :: Lens.Lens' DescribeWhatIfForecastExportResponse (Prelude.Maybe Prelude.Text)
describeWhatIfForecastExportResponse_whatIfForecastExportName :: Lens' DescribeWhatIfForecastExportResponse (Maybe Text)
describeWhatIfForecastExportResponse_whatIfForecastExportName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeWhatIfForecastExportResponse' {Maybe Text
whatIfForecastExportName :: Maybe Text
$sel:whatIfForecastExportName:DescribeWhatIfForecastExportResponse' :: DescribeWhatIfForecastExportResponse -> Maybe Text
whatIfForecastExportName} -> Maybe Text
whatIfForecastExportName) (\s :: DescribeWhatIfForecastExportResponse
s@DescribeWhatIfForecastExportResponse' {} Maybe Text
a -> DescribeWhatIfForecastExportResponse
s {$sel:whatIfForecastExportName:DescribeWhatIfForecastExportResponse' :: Maybe Text
whatIfForecastExportName = Maybe Text
a} :: DescribeWhatIfForecastExportResponse)

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

instance
  Prelude.NFData
    DescribeWhatIfForecastExportResponse
  where
  rnf :: DescribeWhatIfForecastExportResponse -> ()
rnf DescribeWhatIfForecastExportResponse' {Int
Maybe Integer
Maybe [Text]
Maybe Text
Maybe POSIX
Maybe DataDestination
httpStatus :: Int
whatIfForecastExportName :: Maybe Text
whatIfForecastExportArn :: Maybe Text
whatIfForecastArns :: Maybe [Text]
status :: Maybe Text
message :: Maybe Text
lastModificationTime :: Maybe POSIX
format :: Maybe Text
estimatedTimeRemainingInMinutes :: Maybe Integer
destination :: Maybe DataDestination
creationTime :: Maybe POSIX
$sel:httpStatus:DescribeWhatIfForecastExportResponse' :: DescribeWhatIfForecastExportResponse -> Int
$sel:whatIfForecastExportName:DescribeWhatIfForecastExportResponse' :: DescribeWhatIfForecastExportResponse -> Maybe Text
$sel:whatIfForecastExportArn:DescribeWhatIfForecastExportResponse' :: DescribeWhatIfForecastExportResponse -> Maybe Text
$sel:whatIfForecastArns:DescribeWhatIfForecastExportResponse' :: DescribeWhatIfForecastExportResponse -> Maybe [Text]
$sel:status:DescribeWhatIfForecastExportResponse' :: DescribeWhatIfForecastExportResponse -> Maybe Text
$sel:message:DescribeWhatIfForecastExportResponse' :: DescribeWhatIfForecastExportResponse -> Maybe Text
$sel:lastModificationTime:DescribeWhatIfForecastExportResponse' :: DescribeWhatIfForecastExportResponse -> Maybe POSIX
$sel:format:DescribeWhatIfForecastExportResponse' :: DescribeWhatIfForecastExportResponse -> Maybe Text
$sel:estimatedTimeRemainingInMinutes:DescribeWhatIfForecastExportResponse' :: DescribeWhatIfForecastExportResponse -> Maybe Integer
$sel:destination:DescribeWhatIfForecastExportResponse' :: DescribeWhatIfForecastExportResponse -> Maybe DataDestination
$sel:creationTime:DescribeWhatIfForecastExportResponse' :: DescribeWhatIfForecastExportResponse -> Maybe POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DataDestination
destination
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
estimatedTimeRemainingInMinutes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
format
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastModificationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
message
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
whatIfForecastArns
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
whatIfForecastExportArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
whatIfForecastExportName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus