{-# 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.DescribeDataset
-- 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 an Amazon Forecast dataset created using the
-- <https://docs.aws.amazon.com/forecast/latest/dg/API_CreateDataset.html CreateDataset>
-- operation.
--
-- In addition to listing the parameters specified in the @CreateDataset@
-- request, this operation includes the following dataset properties:
--
-- -   @CreationTime@
--
-- -   @LastModificationTime@
--
-- -   @Status@
module Amazonka.Forecast.DescribeDataset
  ( -- * Creating a Request
    DescribeDataset (..),
    newDescribeDataset,

    -- * Request Lenses
    describeDataset_datasetArn,

    -- * Destructuring the Response
    DescribeDatasetResponse (..),
    newDescribeDatasetResponse,

    -- * Response Lenses
    describeDatasetResponse_creationTime,
    describeDatasetResponse_dataFrequency,
    describeDatasetResponse_datasetArn,
    describeDatasetResponse_datasetName,
    describeDatasetResponse_datasetType,
    describeDatasetResponse_domain,
    describeDatasetResponse_encryptionConfig,
    describeDatasetResponse_lastModificationTime,
    describeDatasetResponse_schema,
    describeDatasetResponse_status,
    describeDatasetResponse_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:/ 'newDescribeDataset' smart constructor.
data DescribeDataset = DescribeDataset'
  { -- | The Amazon Resource Name (ARN) of the dataset.
    DescribeDataset -> Text
datasetArn :: Prelude.Text
  }
  deriving (DescribeDataset -> DescribeDataset -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeDataset -> DescribeDataset -> Bool
$c/= :: DescribeDataset -> DescribeDataset -> Bool
== :: DescribeDataset -> DescribeDataset -> Bool
$c== :: DescribeDataset -> DescribeDataset -> Bool
Prelude.Eq, ReadPrec [DescribeDataset]
ReadPrec DescribeDataset
Int -> ReadS DescribeDataset
ReadS [DescribeDataset]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeDataset]
$creadListPrec :: ReadPrec [DescribeDataset]
readPrec :: ReadPrec DescribeDataset
$creadPrec :: ReadPrec DescribeDataset
readList :: ReadS [DescribeDataset]
$creadList :: ReadS [DescribeDataset]
readsPrec :: Int -> ReadS DescribeDataset
$creadsPrec :: Int -> ReadS DescribeDataset
Prelude.Read, Int -> DescribeDataset -> ShowS
[DescribeDataset] -> ShowS
DescribeDataset -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeDataset] -> ShowS
$cshowList :: [DescribeDataset] -> ShowS
show :: DescribeDataset -> String
$cshow :: DescribeDataset -> String
showsPrec :: Int -> DescribeDataset -> ShowS
$cshowsPrec :: Int -> DescribeDataset -> ShowS
Prelude.Show, forall x. Rep DescribeDataset x -> DescribeDataset
forall x. DescribeDataset -> Rep DescribeDataset x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeDataset x -> DescribeDataset
$cfrom :: forall x. DescribeDataset -> Rep DescribeDataset x
Prelude.Generic)

-- |
-- Create a value of 'DescribeDataset' 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:
--
-- 'datasetArn', 'describeDataset_datasetArn' - The Amazon Resource Name (ARN) of the dataset.
newDescribeDataset ::
  -- | 'datasetArn'
  Prelude.Text ->
  DescribeDataset
newDescribeDataset :: Text -> DescribeDataset
newDescribeDataset Text
pDatasetArn_ =
  DescribeDataset' {$sel:datasetArn:DescribeDataset' :: Text
datasetArn = Text
pDatasetArn_}

-- | The Amazon Resource Name (ARN) of the dataset.
describeDataset_datasetArn :: Lens.Lens' DescribeDataset Prelude.Text
describeDataset_datasetArn :: Lens' DescribeDataset Text
describeDataset_datasetArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDataset' {Text
datasetArn :: Text
$sel:datasetArn:DescribeDataset' :: DescribeDataset -> Text
datasetArn} -> Text
datasetArn) (\s :: DescribeDataset
s@DescribeDataset' {} Text
a -> DescribeDataset
s {$sel:datasetArn:DescribeDataset' :: Text
datasetArn = Text
a} :: DescribeDataset)

instance Core.AWSRequest DescribeDataset where
  type
    AWSResponse DescribeDataset =
      DescribeDatasetResponse
  request :: (Service -> Service) -> DescribeDataset -> Request DescribeDataset
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 DescribeDataset
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DescribeDataset)))
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 Text
-> Maybe DatasetType
-> Maybe Domain
-> Maybe EncryptionConfig
-> Maybe POSIX
-> Maybe Schema
-> Maybe Text
-> Int
-> DescribeDatasetResponse
DescribeDatasetResponse'
            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
"DataFrequency")
            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
"DatasetArn")
            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
"DatasetName")
            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
"DatasetType")
            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
"Domain")
            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
"EncryptionConfig")
            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
"Schema")
            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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

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

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

instance Data.ToHeaders DescribeDataset where
  toHeaders :: DescribeDataset -> 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.DescribeDataset" ::
                          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 DescribeDataset where
  toJSON :: DescribeDataset -> Value
toJSON DescribeDataset' {Text
datasetArn :: Text
$sel:datasetArn:DescribeDataset' :: DescribeDataset -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"DatasetArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
datasetArn)]
      )

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

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

-- | /See:/ 'newDescribeDatasetResponse' smart constructor.
data DescribeDatasetResponse = DescribeDatasetResponse'
  { -- | When the dataset was created.
    DescribeDatasetResponse -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
    -- | The frequency of data collection.
    --
    -- Valid intervals are Y (Year), M (Month), W (Week), D (Day), H (Hour),
    -- 30min (30 minutes), 15min (15 minutes), 10min (10 minutes), 5min (5
    -- minutes), and 1min (1 minute). For example, \"M\" indicates every month
    -- and \"30min\" indicates every 30 minutes.
    DescribeDatasetResponse -> Maybe Text
dataFrequency :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the dataset.
    DescribeDatasetResponse -> Maybe Text
datasetArn :: Prelude.Maybe Prelude.Text,
    -- | The name of the dataset.
    DescribeDatasetResponse -> Maybe Text
datasetName :: Prelude.Maybe Prelude.Text,
    -- | The dataset type.
    DescribeDatasetResponse -> Maybe DatasetType
datasetType :: Prelude.Maybe DatasetType,
    -- | The domain associated with the dataset.
    DescribeDatasetResponse -> Maybe Domain
domain :: Prelude.Maybe Domain,
    -- | The AWS Key Management Service (KMS) key and the AWS Identity and Access
    -- Management (IAM) role that Amazon Forecast can assume to access the key.
    DescribeDatasetResponse -> Maybe EncryptionConfig
encryptionConfig :: Prelude.Maybe EncryptionConfig,
    -- | When you create a dataset, @LastModificationTime@ is the same as
    -- @CreationTime@. While data is being imported to the dataset,
    -- @LastModificationTime@ is the current time of the @DescribeDataset@
    -- call. After a
    -- <https://docs.aws.amazon.com/forecast/latest/dg/API_CreateDatasetImportJob.html CreateDatasetImportJob>
    -- operation has finished, @LastModificationTime@ is when the import job
    -- completed or failed.
    DescribeDatasetResponse -> Maybe POSIX
lastModificationTime :: Prelude.Maybe Data.POSIX,
    -- | An array of @SchemaAttribute@ objects that specify the dataset fields.
    -- Each @SchemaAttribute@ specifies the name and data type of a field.
    DescribeDatasetResponse -> Maybe Schema
schema :: Prelude.Maybe Schema,
    -- | The status of the dataset. States include:
    --
    -- -   @ACTIVE@
    --
    -- -   @CREATE_PENDING@, @CREATE_IN_PROGRESS@, @CREATE_FAILED@
    --
    -- -   @DELETE_PENDING@, @DELETE_IN_PROGRESS@, @DELETE_FAILED@
    --
    -- -   @UPDATE_PENDING@, @UPDATE_IN_PROGRESS@, @UPDATE_FAILED@
    --
    -- The @UPDATE@ states apply while data is imported to the dataset from a
    -- call to the
    -- <https://docs.aws.amazon.com/forecast/latest/dg/API_CreateDatasetImportJob.html CreateDatasetImportJob>
    -- operation and reflect the status of the dataset import job. For example,
    -- when the import job status is @CREATE_IN_PROGRESS@, the status of the
    -- dataset is @UPDATE_IN_PROGRESS@.
    --
    -- The @Status@ of the dataset must be @ACTIVE@ before you can import
    -- training data.
    DescribeDatasetResponse -> Maybe Text
status :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DescribeDatasetResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeDatasetResponse -> DescribeDatasetResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeDatasetResponse -> DescribeDatasetResponse -> Bool
$c/= :: DescribeDatasetResponse -> DescribeDatasetResponse -> Bool
== :: DescribeDatasetResponse -> DescribeDatasetResponse -> Bool
$c== :: DescribeDatasetResponse -> DescribeDatasetResponse -> Bool
Prelude.Eq, ReadPrec [DescribeDatasetResponse]
ReadPrec DescribeDatasetResponse
Int -> ReadS DescribeDatasetResponse
ReadS [DescribeDatasetResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeDatasetResponse]
$creadListPrec :: ReadPrec [DescribeDatasetResponse]
readPrec :: ReadPrec DescribeDatasetResponse
$creadPrec :: ReadPrec DescribeDatasetResponse
readList :: ReadS [DescribeDatasetResponse]
$creadList :: ReadS [DescribeDatasetResponse]
readsPrec :: Int -> ReadS DescribeDatasetResponse
$creadsPrec :: Int -> ReadS DescribeDatasetResponse
Prelude.Read, Int -> DescribeDatasetResponse -> ShowS
[DescribeDatasetResponse] -> ShowS
DescribeDatasetResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeDatasetResponse] -> ShowS
$cshowList :: [DescribeDatasetResponse] -> ShowS
show :: DescribeDatasetResponse -> String
$cshow :: DescribeDatasetResponse -> String
showsPrec :: Int -> DescribeDatasetResponse -> ShowS
$cshowsPrec :: Int -> DescribeDatasetResponse -> ShowS
Prelude.Show, forall x. Rep DescribeDatasetResponse x -> DescribeDatasetResponse
forall x. DescribeDatasetResponse -> Rep DescribeDatasetResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeDatasetResponse x -> DescribeDatasetResponse
$cfrom :: forall x. DescribeDatasetResponse -> Rep DescribeDatasetResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeDatasetResponse' 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', 'describeDatasetResponse_creationTime' - When the dataset was created.
--
-- 'dataFrequency', 'describeDatasetResponse_dataFrequency' - The frequency of data collection.
--
-- Valid intervals are Y (Year), M (Month), W (Week), D (Day), H (Hour),
-- 30min (30 minutes), 15min (15 minutes), 10min (10 minutes), 5min (5
-- minutes), and 1min (1 minute). For example, \"M\" indicates every month
-- and \"30min\" indicates every 30 minutes.
--
-- 'datasetArn', 'describeDatasetResponse_datasetArn' - The Amazon Resource Name (ARN) of the dataset.
--
-- 'datasetName', 'describeDatasetResponse_datasetName' - The name of the dataset.
--
-- 'datasetType', 'describeDatasetResponse_datasetType' - The dataset type.
--
-- 'domain', 'describeDatasetResponse_domain' - The domain associated with the dataset.
--
-- 'encryptionConfig', 'describeDatasetResponse_encryptionConfig' - The AWS Key Management Service (KMS) key and the AWS Identity and Access
-- Management (IAM) role that Amazon Forecast can assume to access the key.
--
-- 'lastModificationTime', 'describeDatasetResponse_lastModificationTime' - When you create a dataset, @LastModificationTime@ is the same as
-- @CreationTime@. While data is being imported to the dataset,
-- @LastModificationTime@ is the current time of the @DescribeDataset@
-- call. After a
-- <https://docs.aws.amazon.com/forecast/latest/dg/API_CreateDatasetImportJob.html CreateDatasetImportJob>
-- operation has finished, @LastModificationTime@ is when the import job
-- completed or failed.
--
-- 'schema', 'describeDatasetResponse_schema' - An array of @SchemaAttribute@ objects that specify the dataset fields.
-- Each @SchemaAttribute@ specifies the name and data type of a field.
--
-- 'status', 'describeDatasetResponse_status' - The status of the dataset. States include:
--
-- -   @ACTIVE@
--
-- -   @CREATE_PENDING@, @CREATE_IN_PROGRESS@, @CREATE_FAILED@
--
-- -   @DELETE_PENDING@, @DELETE_IN_PROGRESS@, @DELETE_FAILED@
--
-- -   @UPDATE_PENDING@, @UPDATE_IN_PROGRESS@, @UPDATE_FAILED@
--
-- The @UPDATE@ states apply while data is imported to the dataset from a
-- call to the
-- <https://docs.aws.amazon.com/forecast/latest/dg/API_CreateDatasetImportJob.html CreateDatasetImportJob>
-- operation and reflect the status of the dataset import job. For example,
-- when the import job status is @CREATE_IN_PROGRESS@, the status of the
-- dataset is @UPDATE_IN_PROGRESS@.
--
-- The @Status@ of the dataset must be @ACTIVE@ before you can import
-- training data.
--
-- 'httpStatus', 'describeDatasetResponse_httpStatus' - The response's http status code.
newDescribeDatasetResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeDatasetResponse
newDescribeDatasetResponse :: Int -> DescribeDatasetResponse
newDescribeDatasetResponse Int
pHttpStatus_ =
  DescribeDatasetResponse'
    { $sel:creationTime:DescribeDatasetResponse' :: Maybe POSIX
creationTime =
        forall a. Maybe a
Prelude.Nothing,
      $sel:dataFrequency:DescribeDatasetResponse' :: Maybe Text
dataFrequency = forall a. Maybe a
Prelude.Nothing,
      $sel:datasetArn:DescribeDatasetResponse' :: Maybe Text
datasetArn = forall a. Maybe a
Prelude.Nothing,
      $sel:datasetName:DescribeDatasetResponse' :: Maybe Text
datasetName = forall a. Maybe a
Prelude.Nothing,
      $sel:datasetType:DescribeDatasetResponse' :: Maybe DatasetType
datasetType = forall a. Maybe a
Prelude.Nothing,
      $sel:domain:DescribeDatasetResponse' :: Maybe Domain
domain = forall a. Maybe a
Prelude.Nothing,
      $sel:encryptionConfig:DescribeDatasetResponse' :: Maybe EncryptionConfig
encryptionConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:lastModificationTime:DescribeDatasetResponse' :: Maybe POSIX
lastModificationTime = forall a. Maybe a
Prelude.Nothing,
      $sel:schema:DescribeDatasetResponse' :: Maybe Schema
schema = forall a. Maybe a
Prelude.Nothing,
      $sel:status:DescribeDatasetResponse' :: Maybe Text
status = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeDatasetResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | When the dataset was created.
describeDatasetResponse_creationTime :: Lens.Lens' DescribeDatasetResponse (Prelude.Maybe Prelude.UTCTime)
describeDatasetResponse_creationTime :: Lens' DescribeDatasetResponse (Maybe UTCTime)
describeDatasetResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDatasetResponse' {Maybe POSIX
creationTime :: Maybe POSIX
$sel:creationTime:DescribeDatasetResponse' :: DescribeDatasetResponse -> Maybe POSIX
creationTime} -> Maybe POSIX
creationTime) (\s :: DescribeDatasetResponse
s@DescribeDatasetResponse' {} Maybe POSIX
a -> DescribeDatasetResponse
s {$sel:creationTime:DescribeDatasetResponse' :: Maybe POSIX
creationTime = Maybe POSIX
a} :: DescribeDatasetResponse) 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 frequency of data collection.
--
-- Valid intervals are Y (Year), M (Month), W (Week), D (Day), H (Hour),
-- 30min (30 minutes), 15min (15 minutes), 10min (10 minutes), 5min (5
-- minutes), and 1min (1 minute). For example, \"M\" indicates every month
-- and \"30min\" indicates every 30 minutes.
describeDatasetResponse_dataFrequency :: Lens.Lens' DescribeDatasetResponse (Prelude.Maybe Prelude.Text)
describeDatasetResponse_dataFrequency :: Lens' DescribeDatasetResponse (Maybe Text)
describeDatasetResponse_dataFrequency = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDatasetResponse' {Maybe Text
dataFrequency :: Maybe Text
$sel:dataFrequency:DescribeDatasetResponse' :: DescribeDatasetResponse -> Maybe Text
dataFrequency} -> Maybe Text
dataFrequency) (\s :: DescribeDatasetResponse
s@DescribeDatasetResponse' {} Maybe Text
a -> DescribeDatasetResponse
s {$sel:dataFrequency:DescribeDatasetResponse' :: Maybe Text
dataFrequency = Maybe Text
a} :: DescribeDatasetResponse)

-- | The Amazon Resource Name (ARN) of the dataset.
describeDatasetResponse_datasetArn :: Lens.Lens' DescribeDatasetResponse (Prelude.Maybe Prelude.Text)
describeDatasetResponse_datasetArn :: Lens' DescribeDatasetResponse (Maybe Text)
describeDatasetResponse_datasetArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDatasetResponse' {Maybe Text
datasetArn :: Maybe Text
$sel:datasetArn:DescribeDatasetResponse' :: DescribeDatasetResponse -> Maybe Text
datasetArn} -> Maybe Text
datasetArn) (\s :: DescribeDatasetResponse
s@DescribeDatasetResponse' {} Maybe Text
a -> DescribeDatasetResponse
s {$sel:datasetArn:DescribeDatasetResponse' :: Maybe Text
datasetArn = Maybe Text
a} :: DescribeDatasetResponse)

-- | The name of the dataset.
describeDatasetResponse_datasetName :: Lens.Lens' DescribeDatasetResponse (Prelude.Maybe Prelude.Text)
describeDatasetResponse_datasetName :: Lens' DescribeDatasetResponse (Maybe Text)
describeDatasetResponse_datasetName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDatasetResponse' {Maybe Text
datasetName :: Maybe Text
$sel:datasetName:DescribeDatasetResponse' :: DescribeDatasetResponse -> Maybe Text
datasetName} -> Maybe Text
datasetName) (\s :: DescribeDatasetResponse
s@DescribeDatasetResponse' {} Maybe Text
a -> DescribeDatasetResponse
s {$sel:datasetName:DescribeDatasetResponse' :: Maybe Text
datasetName = Maybe Text
a} :: DescribeDatasetResponse)

-- | The dataset type.
describeDatasetResponse_datasetType :: Lens.Lens' DescribeDatasetResponse (Prelude.Maybe DatasetType)
describeDatasetResponse_datasetType :: Lens' DescribeDatasetResponse (Maybe DatasetType)
describeDatasetResponse_datasetType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDatasetResponse' {Maybe DatasetType
datasetType :: Maybe DatasetType
$sel:datasetType:DescribeDatasetResponse' :: DescribeDatasetResponse -> Maybe DatasetType
datasetType} -> Maybe DatasetType
datasetType) (\s :: DescribeDatasetResponse
s@DescribeDatasetResponse' {} Maybe DatasetType
a -> DescribeDatasetResponse
s {$sel:datasetType:DescribeDatasetResponse' :: Maybe DatasetType
datasetType = Maybe DatasetType
a} :: DescribeDatasetResponse)

-- | The domain associated with the dataset.
describeDatasetResponse_domain :: Lens.Lens' DescribeDatasetResponse (Prelude.Maybe Domain)
describeDatasetResponse_domain :: Lens' DescribeDatasetResponse (Maybe Domain)
describeDatasetResponse_domain = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDatasetResponse' {Maybe Domain
domain :: Maybe Domain
$sel:domain:DescribeDatasetResponse' :: DescribeDatasetResponse -> Maybe Domain
domain} -> Maybe Domain
domain) (\s :: DescribeDatasetResponse
s@DescribeDatasetResponse' {} Maybe Domain
a -> DescribeDatasetResponse
s {$sel:domain:DescribeDatasetResponse' :: Maybe Domain
domain = Maybe Domain
a} :: DescribeDatasetResponse)

-- | The AWS Key Management Service (KMS) key and the AWS Identity and Access
-- Management (IAM) role that Amazon Forecast can assume to access the key.
describeDatasetResponse_encryptionConfig :: Lens.Lens' DescribeDatasetResponse (Prelude.Maybe EncryptionConfig)
describeDatasetResponse_encryptionConfig :: Lens' DescribeDatasetResponse (Maybe EncryptionConfig)
describeDatasetResponse_encryptionConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDatasetResponse' {Maybe EncryptionConfig
encryptionConfig :: Maybe EncryptionConfig
$sel:encryptionConfig:DescribeDatasetResponse' :: DescribeDatasetResponse -> Maybe EncryptionConfig
encryptionConfig} -> Maybe EncryptionConfig
encryptionConfig) (\s :: DescribeDatasetResponse
s@DescribeDatasetResponse' {} Maybe EncryptionConfig
a -> DescribeDatasetResponse
s {$sel:encryptionConfig:DescribeDatasetResponse' :: Maybe EncryptionConfig
encryptionConfig = Maybe EncryptionConfig
a} :: DescribeDatasetResponse)

-- | When you create a dataset, @LastModificationTime@ is the same as
-- @CreationTime@. While data is being imported to the dataset,
-- @LastModificationTime@ is the current time of the @DescribeDataset@
-- call. After a
-- <https://docs.aws.amazon.com/forecast/latest/dg/API_CreateDatasetImportJob.html CreateDatasetImportJob>
-- operation has finished, @LastModificationTime@ is when the import job
-- completed or failed.
describeDatasetResponse_lastModificationTime :: Lens.Lens' DescribeDatasetResponse (Prelude.Maybe Prelude.UTCTime)
describeDatasetResponse_lastModificationTime :: Lens' DescribeDatasetResponse (Maybe UTCTime)
describeDatasetResponse_lastModificationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDatasetResponse' {Maybe POSIX
lastModificationTime :: Maybe POSIX
$sel:lastModificationTime:DescribeDatasetResponse' :: DescribeDatasetResponse -> Maybe POSIX
lastModificationTime} -> Maybe POSIX
lastModificationTime) (\s :: DescribeDatasetResponse
s@DescribeDatasetResponse' {} Maybe POSIX
a -> DescribeDatasetResponse
s {$sel:lastModificationTime:DescribeDatasetResponse' :: Maybe POSIX
lastModificationTime = Maybe POSIX
a} :: DescribeDatasetResponse) 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

-- | An array of @SchemaAttribute@ objects that specify the dataset fields.
-- Each @SchemaAttribute@ specifies the name and data type of a field.
describeDatasetResponse_schema :: Lens.Lens' DescribeDatasetResponse (Prelude.Maybe Schema)
describeDatasetResponse_schema :: Lens' DescribeDatasetResponse (Maybe Schema)
describeDatasetResponse_schema = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDatasetResponse' {Maybe Schema
schema :: Maybe Schema
$sel:schema:DescribeDatasetResponse' :: DescribeDatasetResponse -> Maybe Schema
schema} -> Maybe Schema
schema) (\s :: DescribeDatasetResponse
s@DescribeDatasetResponse' {} Maybe Schema
a -> DescribeDatasetResponse
s {$sel:schema:DescribeDatasetResponse' :: Maybe Schema
schema = Maybe Schema
a} :: DescribeDatasetResponse)

-- | The status of the dataset. States include:
--
-- -   @ACTIVE@
--
-- -   @CREATE_PENDING@, @CREATE_IN_PROGRESS@, @CREATE_FAILED@
--
-- -   @DELETE_PENDING@, @DELETE_IN_PROGRESS@, @DELETE_FAILED@
--
-- -   @UPDATE_PENDING@, @UPDATE_IN_PROGRESS@, @UPDATE_FAILED@
--
-- The @UPDATE@ states apply while data is imported to the dataset from a
-- call to the
-- <https://docs.aws.amazon.com/forecast/latest/dg/API_CreateDatasetImportJob.html CreateDatasetImportJob>
-- operation and reflect the status of the dataset import job. For example,
-- when the import job status is @CREATE_IN_PROGRESS@, the status of the
-- dataset is @UPDATE_IN_PROGRESS@.
--
-- The @Status@ of the dataset must be @ACTIVE@ before you can import
-- training data.
describeDatasetResponse_status :: Lens.Lens' DescribeDatasetResponse (Prelude.Maybe Prelude.Text)
describeDatasetResponse_status :: Lens' DescribeDatasetResponse (Maybe Text)
describeDatasetResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDatasetResponse' {Maybe Text
status :: Maybe Text
$sel:status:DescribeDatasetResponse' :: DescribeDatasetResponse -> Maybe Text
status} -> Maybe Text
status) (\s :: DescribeDatasetResponse
s@DescribeDatasetResponse' {} Maybe Text
a -> DescribeDatasetResponse
s {$sel:status:DescribeDatasetResponse' :: Maybe Text
status = Maybe Text
a} :: DescribeDatasetResponse)

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

instance Prelude.NFData DescribeDatasetResponse where
  rnf :: DescribeDatasetResponse -> ()
rnf DescribeDatasetResponse' {Int
Maybe Text
Maybe POSIX
Maybe DatasetType
Maybe Domain
Maybe EncryptionConfig
Maybe Schema
httpStatus :: Int
status :: Maybe Text
schema :: Maybe Schema
lastModificationTime :: Maybe POSIX
encryptionConfig :: Maybe EncryptionConfig
domain :: Maybe Domain
datasetType :: Maybe DatasetType
datasetName :: Maybe Text
datasetArn :: Maybe Text
dataFrequency :: Maybe Text
creationTime :: Maybe POSIX
$sel:httpStatus:DescribeDatasetResponse' :: DescribeDatasetResponse -> Int
$sel:status:DescribeDatasetResponse' :: DescribeDatasetResponse -> Maybe Text
$sel:schema:DescribeDatasetResponse' :: DescribeDatasetResponse -> Maybe Schema
$sel:lastModificationTime:DescribeDatasetResponse' :: DescribeDatasetResponse -> Maybe POSIX
$sel:encryptionConfig:DescribeDatasetResponse' :: DescribeDatasetResponse -> Maybe EncryptionConfig
$sel:domain:DescribeDatasetResponse' :: DescribeDatasetResponse -> Maybe Domain
$sel:datasetType:DescribeDatasetResponse' :: DescribeDatasetResponse -> Maybe DatasetType
$sel:datasetName:DescribeDatasetResponse' :: DescribeDatasetResponse -> Maybe Text
$sel:datasetArn:DescribeDatasetResponse' :: DescribeDatasetResponse -> Maybe Text
$sel:dataFrequency:DescribeDatasetResponse' :: DescribeDatasetResponse -> Maybe Text
$sel:creationTime:DescribeDatasetResponse' :: DescribeDatasetResponse -> 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 Text
dataFrequency
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
datasetArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
datasetName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DatasetType
datasetType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Domain
domain
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EncryptionConfig
encryptionConfig
      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 Schema
schema
      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 Int
httpStatus