{-# 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.M2.GetDataSetDetails
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets the details of a specific data set.
module Amazonka.M2.GetDataSetDetails
  ( -- * Creating a Request
    GetDataSetDetails (..),
    newGetDataSetDetails,

    -- * Request Lenses
    getDataSetDetails_applicationId,
    getDataSetDetails_dataSetName,

    -- * Destructuring the Response
    GetDataSetDetailsResponse (..),
    newGetDataSetDetailsResponse,

    -- * Response Lenses
    getDataSetDetailsResponse_blocksize,
    getDataSetDetailsResponse_creationTime,
    getDataSetDetailsResponse_dataSetOrg,
    getDataSetDetailsResponse_lastReferencedTime,
    getDataSetDetailsResponse_lastUpdatedTime,
    getDataSetDetailsResponse_location,
    getDataSetDetailsResponse_recordLength,
    getDataSetDetailsResponse_httpStatus,
    getDataSetDetailsResponse_dataSetName,
  )
where

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

-- | /See:/ 'newGetDataSetDetails' smart constructor.
data GetDataSetDetails = GetDataSetDetails'
  { -- | The unique identifier of the application that this data set is
    -- associated with.
    GetDataSetDetails -> Text
applicationId :: Prelude.Text,
    -- | The name of the data set.
    GetDataSetDetails -> Text
dataSetName :: Prelude.Text
  }
  deriving (GetDataSetDetails -> GetDataSetDetails -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDataSetDetails -> GetDataSetDetails -> Bool
$c/= :: GetDataSetDetails -> GetDataSetDetails -> Bool
== :: GetDataSetDetails -> GetDataSetDetails -> Bool
$c== :: GetDataSetDetails -> GetDataSetDetails -> Bool
Prelude.Eq, ReadPrec [GetDataSetDetails]
ReadPrec GetDataSetDetails
Int -> ReadS GetDataSetDetails
ReadS [GetDataSetDetails]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetDataSetDetails]
$creadListPrec :: ReadPrec [GetDataSetDetails]
readPrec :: ReadPrec GetDataSetDetails
$creadPrec :: ReadPrec GetDataSetDetails
readList :: ReadS [GetDataSetDetails]
$creadList :: ReadS [GetDataSetDetails]
readsPrec :: Int -> ReadS GetDataSetDetails
$creadsPrec :: Int -> ReadS GetDataSetDetails
Prelude.Read, Int -> GetDataSetDetails -> ShowS
[GetDataSetDetails] -> ShowS
GetDataSetDetails -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetDataSetDetails] -> ShowS
$cshowList :: [GetDataSetDetails] -> ShowS
show :: GetDataSetDetails -> String
$cshow :: GetDataSetDetails -> String
showsPrec :: Int -> GetDataSetDetails -> ShowS
$cshowsPrec :: Int -> GetDataSetDetails -> ShowS
Prelude.Show, forall x. Rep GetDataSetDetails x -> GetDataSetDetails
forall x. GetDataSetDetails -> Rep GetDataSetDetails x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetDataSetDetails x -> GetDataSetDetails
$cfrom :: forall x. GetDataSetDetails -> Rep GetDataSetDetails x
Prelude.Generic)

-- |
-- Create a value of 'GetDataSetDetails' 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:
--
-- 'applicationId', 'getDataSetDetails_applicationId' - The unique identifier of the application that this data set is
-- associated with.
--
-- 'dataSetName', 'getDataSetDetails_dataSetName' - The name of the data set.
newGetDataSetDetails ::
  -- | 'applicationId'
  Prelude.Text ->
  -- | 'dataSetName'
  Prelude.Text ->
  GetDataSetDetails
newGetDataSetDetails :: Text -> Text -> GetDataSetDetails
newGetDataSetDetails Text
pApplicationId_ Text
pDataSetName_ =
  GetDataSetDetails'
    { $sel:applicationId:GetDataSetDetails' :: Text
applicationId = Text
pApplicationId_,
      $sel:dataSetName:GetDataSetDetails' :: Text
dataSetName = Text
pDataSetName_
    }

-- | The unique identifier of the application that this data set is
-- associated with.
getDataSetDetails_applicationId :: Lens.Lens' GetDataSetDetails Prelude.Text
getDataSetDetails_applicationId :: Lens' GetDataSetDetails Text
getDataSetDetails_applicationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataSetDetails' {Text
applicationId :: Text
$sel:applicationId:GetDataSetDetails' :: GetDataSetDetails -> Text
applicationId} -> Text
applicationId) (\s :: GetDataSetDetails
s@GetDataSetDetails' {} Text
a -> GetDataSetDetails
s {$sel:applicationId:GetDataSetDetails' :: Text
applicationId = Text
a} :: GetDataSetDetails)

-- | The name of the data set.
getDataSetDetails_dataSetName :: Lens.Lens' GetDataSetDetails Prelude.Text
getDataSetDetails_dataSetName :: Lens' GetDataSetDetails Text
getDataSetDetails_dataSetName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataSetDetails' {Text
dataSetName :: Text
$sel:dataSetName:GetDataSetDetails' :: GetDataSetDetails -> Text
dataSetName} -> Text
dataSetName) (\s :: GetDataSetDetails
s@GetDataSetDetails' {} Text
a -> GetDataSetDetails
s {$sel:dataSetName:GetDataSetDetails' :: Text
dataSetName = Text
a} :: GetDataSetDetails)

instance Core.AWSRequest GetDataSetDetails where
  type
    AWSResponse GetDataSetDetails =
      GetDataSetDetailsResponse
  request :: (Service -> Service)
-> GetDataSetDetails -> Request GetDataSetDetails
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetDataSetDetails
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetDataSetDetails)))
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 Int
-> Maybe POSIX
-> Maybe DatasetDetailOrgAttributes
-> Maybe POSIX
-> Maybe POSIX
-> Maybe Text
-> Maybe Int
-> Int
-> Text
-> GetDataSetDetailsResponse
GetDataSetDetailsResponse'
            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
"blocksize")
            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
"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
"dataSetOrg")
            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
"lastReferencedTime")
            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
"lastUpdatedTime")
            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
"location")
            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
"recordLength")
            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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"dataSetName")
      )

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

instance Prelude.NFData GetDataSetDetails where
  rnf :: GetDataSetDetails -> ()
rnf GetDataSetDetails' {Text
dataSetName :: Text
applicationId :: Text
$sel:dataSetName:GetDataSetDetails' :: GetDataSetDetails -> Text
$sel:applicationId:GetDataSetDetails' :: GetDataSetDetails -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
applicationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
dataSetName

instance Data.ToHeaders GetDataSetDetails where
  toHeaders :: GetDataSetDetails -> 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.ToPath GetDataSetDetails where
  toPath :: GetDataSetDetails -> ByteString
toPath GetDataSetDetails' {Text
dataSetName :: Text
applicationId :: Text
$sel:dataSetName:GetDataSetDetails' :: GetDataSetDetails -> Text
$sel:applicationId:GetDataSetDetails' :: GetDataSetDetails -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/applications/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
applicationId,
        ByteString
"/datasets/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
dataSetName
      ]

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

-- | /See:/ 'newGetDataSetDetailsResponse' smart constructor.
data GetDataSetDetailsResponse = GetDataSetDetailsResponse'
  { -- | The size of the block on disk.
    GetDataSetDetailsResponse -> Maybe Int
blocksize :: Prelude.Maybe Prelude.Int,
    -- | The timestamp when the data set was created.
    GetDataSetDetailsResponse -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
    -- | The type of data set. The only supported value is VSAM.
    GetDataSetDetailsResponse -> Maybe DatasetDetailOrgAttributes
dataSetOrg :: Prelude.Maybe DatasetDetailOrgAttributes,
    -- | The last time the data set was referenced.
    GetDataSetDetailsResponse -> Maybe POSIX
lastReferencedTime :: Prelude.Maybe Data.POSIX,
    -- | The last time the data set was updated.
    GetDataSetDetailsResponse -> Maybe POSIX
lastUpdatedTime :: Prelude.Maybe Data.POSIX,
    -- | The location where the data set is stored.
    GetDataSetDetailsResponse -> Maybe Text
location :: Prelude.Maybe Prelude.Text,
    -- | The length of records in the data set.
    GetDataSetDetailsResponse -> Maybe Int
recordLength :: Prelude.Maybe Prelude.Int,
    -- | The response's http status code.
    GetDataSetDetailsResponse -> Int
httpStatus :: Prelude.Int,
    -- | The name of the data set.
    GetDataSetDetailsResponse -> Text
dataSetName :: Prelude.Text
  }
  deriving (GetDataSetDetailsResponse -> GetDataSetDetailsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDataSetDetailsResponse -> GetDataSetDetailsResponse -> Bool
$c/= :: GetDataSetDetailsResponse -> GetDataSetDetailsResponse -> Bool
== :: GetDataSetDetailsResponse -> GetDataSetDetailsResponse -> Bool
$c== :: GetDataSetDetailsResponse -> GetDataSetDetailsResponse -> Bool
Prelude.Eq, ReadPrec [GetDataSetDetailsResponse]
ReadPrec GetDataSetDetailsResponse
Int -> ReadS GetDataSetDetailsResponse
ReadS [GetDataSetDetailsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetDataSetDetailsResponse]
$creadListPrec :: ReadPrec [GetDataSetDetailsResponse]
readPrec :: ReadPrec GetDataSetDetailsResponse
$creadPrec :: ReadPrec GetDataSetDetailsResponse
readList :: ReadS [GetDataSetDetailsResponse]
$creadList :: ReadS [GetDataSetDetailsResponse]
readsPrec :: Int -> ReadS GetDataSetDetailsResponse
$creadsPrec :: Int -> ReadS GetDataSetDetailsResponse
Prelude.Read, Int -> GetDataSetDetailsResponse -> ShowS
[GetDataSetDetailsResponse] -> ShowS
GetDataSetDetailsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetDataSetDetailsResponse] -> ShowS
$cshowList :: [GetDataSetDetailsResponse] -> ShowS
show :: GetDataSetDetailsResponse -> String
$cshow :: GetDataSetDetailsResponse -> String
showsPrec :: Int -> GetDataSetDetailsResponse -> ShowS
$cshowsPrec :: Int -> GetDataSetDetailsResponse -> ShowS
Prelude.Show, forall x.
Rep GetDataSetDetailsResponse x -> GetDataSetDetailsResponse
forall x.
GetDataSetDetailsResponse -> Rep GetDataSetDetailsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetDataSetDetailsResponse x -> GetDataSetDetailsResponse
$cfrom :: forall x.
GetDataSetDetailsResponse -> Rep GetDataSetDetailsResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetDataSetDetailsResponse' 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:
--
-- 'blocksize', 'getDataSetDetailsResponse_blocksize' - The size of the block on disk.
--
-- 'creationTime', 'getDataSetDetailsResponse_creationTime' - The timestamp when the data set was created.
--
-- 'dataSetOrg', 'getDataSetDetailsResponse_dataSetOrg' - The type of data set. The only supported value is VSAM.
--
-- 'lastReferencedTime', 'getDataSetDetailsResponse_lastReferencedTime' - The last time the data set was referenced.
--
-- 'lastUpdatedTime', 'getDataSetDetailsResponse_lastUpdatedTime' - The last time the data set was updated.
--
-- 'location', 'getDataSetDetailsResponse_location' - The location where the data set is stored.
--
-- 'recordLength', 'getDataSetDetailsResponse_recordLength' - The length of records in the data set.
--
-- 'httpStatus', 'getDataSetDetailsResponse_httpStatus' - The response's http status code.
--
-- 'dataSetName', 'getDataSetDetailsResponse_dataSetName' - The name of the data set.
newGetDataSetDetailsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'dataSetName'
  Prelude.Text ->
  GetDataSetDetailsResponse
newGetDataSetDetailsResponse :: Int -> Text -> GetDataSetDetailsResponse
newGetDataSetDetailsResponse
  Int
pHttpStatus_
  Text
pDataSetName_ =
    GetDataSetDetailsResponse'
      { $sel:blocksize:GetDataSetDetailsResponse' :: Maybe Int
blocksize =
          forall a. Maybe a
Prelude.Nothing,
        $sel:creationTime:GetDataSetDetailsResponse' :: Maybe POSIX
creationTime = forall a. Maybe a
Prelude.Nothing,
        $sel:dataSetOrg:GetDataSetDetailsResponse' :: Maybe DatasetDetailOrgAttributes
dataSetOrg = forall a. Maybe a
Prelude.Nothing,
        $sel:lastReferencedTime:GetDataSetDetailsResponse' :: Maybe POSIX
lastReferencedTime = forall a. Maybe a
Prelude.Nothing,
        $sel:lastUpdatedTime:GetDataSetDetailsResponse' :: Maybe POSIX
lastUpdatedTime = forall a. Maybe a
Prelude.Nothing,
        $sel:location:GetDataSetDetailsResponse' :: Maybe Text
location = forall a. Maybe a
Prelude.Nothing,
        $sel:recordLength:GetDataSetDetailsResponse' :: Maybe Int
recordLength = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:GetDataSetDetailsResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:dataSetName:GetDataSetDetailsResponse' :: Text
dataSetName = Text
pDataSetName_
      }

-- | The size of the block on disk.
getDataSetDetailsResponse_blocksize :: Lens.Lens' GetDataSetDetailsResponse (Prelude.Maybe Prelude.Int)
getDataSetDetailsResponse_blocksize :: Lens' GetDataSetDetailsResponse (Maybe Int)
getDataSetDetailsResponse_blocksize = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataSetDetailsResponse' {Maybe Int
blocksize :: Maybe Int
$sel:blocksize:GetDataSetDetailsResponse' :: GetDataSetDetailsResponse -> Maybe Int
blocksize} -> Maybe Int
blocksize) (\s :: GetDataSetDetailsResponse
s@GetDataSetDetailsResponse' {} Maybe Int
a -> GetDataSetDetailsResponse
s {$sel:blocksize:GetDataSetDetailsResponse' :: Maybe Int
blocksize = Maybe Int
a} :: GetDataSetDetailsResponse)

-- | The timestamp when the data set was created.
getDataSetDetailsResponse_creationTime :: Lens.Lens' GetDataSetDetailsResponse (Prelude.Maybe Prelude.UTCTime)
getDataSetDetailsResponse_creationTime :: Lens' GetDataSetDetailsResponse (Maybe UTCTime)
getDataSetDetailsResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataSetDetailsResponse' {Maybe POSIX
creationTime :: Maybe POSIX
$sel:creationTime:GetDataSetDetailsResponse' :: GetDataSetDetailsResponse -> Maybe POSIX
creationTime} -> Maybe POSIX
creationTime) (\s :: GetDataSetDetailsResponse
s@GetDataSetDetailsResponse' {} Maybe POSIX
a -> GetDataSetDetailsResponse
s {$sel:creationTime:GetDataSetDetailsResponse' :: Maybe POSIX
creationTime = Maybe POSIX
a} :: GetDataSetDetailsResponse) 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 type of data set. The only supported value is VSAM.
getDataSetDetailsResponse_dataSetOrg :: Lens.Lens' GetDataSetDetailsResponse (Prelude.Maybe DatasetDetailOrgAttributes)
getDataSetDetailsResponse_dataSetOrg :: Lens' GetDataSetDetailsResponse (Maybe DatasetDetailOrgAttributes)
getDataSetDetailsResponse_dataSetOrg = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataSetDetailsResponse' {Maybe DatasetDetailOrgAttributes
dataSetOrg :: Maybe DatasetDetailOrgAttributes
$sel:dataSetOrg:GetDataSetDetailsResponse' :: GetDataSetDetailsResponse -> Maybe DatasetDetailOrgAttributes
dataSetOrg} -> Maybe DatasetDetailOrgAttributes
dataSetOrg) (\s :: GetDataSetDetailsResponse
s@GetDataSetDetailsResponse' {} Maybe DatasetDetailOrgAttributes
a -> GetDataSetDetailsResponse
s {$sel:dataSetOrg:GetDataSetDetailsResponse' :: Maybe DatasetDetailOrgAttributes
dataSetOrg = Maybe DatasetDetailOrgAttributes
a} :: GetDataSetDetailsResponse)

-- | The last time the data set was referenced.
getDataSetDetailsResponse_lastReferencedTime :: Lens.Lens' GetDataSetDetailsResponse (Prelude.Maybe Prelude.UTCTime)
getDataSetDetailsResponse_lastReferencedTime :: Lens' GetDataSetDetailsResponse (Maybe UTCTime)
getDataSetDetailsResponse_lastReferencedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataSetDetailsResponse' {Maybe POSIX
lastReferencedTime :: Maybe POSIX
$sel:lastReferencedTime:GetDataSetDetailsResponse' :: GetDataSetDetailsResponse -> Maybe POSIX
lastReferencedTime} -> Maybe POSIX
lastReferencedTime) (\s :: GetDataSetDetailsResponse
s@GetDataSetDetailsResponse' {} Maybe POSIX
a -> GetDataSetDetailsResponse
s {$sel:lastReferencedTime:GetDataSetDetailsResponse' :: Maybe POSIX
lastReferencedTime = Maybe POSIX
a} :: GetDataSetDetailsResponse) 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 last time the data set was updated.
getDataSetDetailsResponse_lastUpdatedTime :: Lens.Lens' GetDataSetDetailsResponse (Prelude.Maybe Prelude.UTCTime)
getDataSetDetailsResponse_lastUpdatedTime :: Lens' GetDataSetDetailsResponse (Maybe UTCTime)
getDataSetDetailsResponse_lastUpdatedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataSetDetailsResponse' {Maybe POSIX
lastUpdatedTime :: Maybe POSIX
$sel:lastUpdatedTime:GetDataSetDetailsResponse' :: GetDataSetDetailsResponse -> Maybe POSIX
lastUpdatedTime} -> Maybe POSIX
lastUpdatedTime) (\s :: GetDataSetDetailsResponse
s@GetDataSetDetailsResponse' {} Maybe POSIX
a -> GetDataSetDetailsResponse
s {$sel:lastUpdatedTime:GetDataSetDetailsResponse' :: Maybe POSIX
lastUpdatedTime = Maybe POSIX
a} :: GetDataSetDetailsResponse) 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 location where the data set is stored.
getDataSetDetailsResponse_location :: Lens.Lens' GetDataSetDetailsResponse (Prelude.Maybe Prelude.Text)
getDataSetDetailsResponse_location :: Lens' GetDataSetDetailsResponse (Maybe Text)
getDataSetDetailsResponse_location = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataSetDetailsResponse' {Maybe Text
location :: Maybe Text
$sel:location:GetDataSetDetailsResponse' :: GetDataSetDetailsResponse -> Maybe Text
location} -> Maybe Text
location) (\s :: GetDataSetDetailsResponse
s@GetDataSetDetailsResponse' {} Maybe Text
a -> GetDataSetDetailsResponse
s {$sel:location:GetDataSetDetailsResponse' :: Maybe Text
location = Maybe Text
a} :: GetDataSetDetailsResponse)

-- | The length of records in the data set.
getDataSetDetailsResponse_recordLength :: Lens.Lens' GetDataSetDetailsResponse (Prelude.Maybe Prelude.Int)
getDataSetDetailsResponse_recordLength :: Lens' GetDataSetDetailsResponse (Maybe Int)
getDataSetDetailsResponse_recordLength = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataSetDetailsResponse' {Maybe Int
recordLength :: Maybe Int
$sel:recordLength:GetDataSetDetailsResponse' :: GetDataSetDetailsResponse -> Maybe Int
recordLength} -> Maybe Int
recordLength) (\s :: GetDataSetDetailsResponse
s@GetDataSetDetailsResponse' {} Maybe Int
a -> GetDataSetDetailsResponse
s {$sel:recordLength:GetDataSetDetailsResponse' :: Maybe Int
recordLength = Maybe Int
a} :: GetDataSetDetailsResponse)

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

-- | The name of the data set.
getDataSetDetailsResponse_dataSetName :: Lens.Lens' GetDataSetDetailsResponse Prelude.Text
getDataSetDetailsResponse_dataSetName :: Lens' GetDataSetDetailsResponse Text
getDataSetDetailsResponse_dataSetName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataSetDetailsResponse' {Text
dataSetName :: Text
$sel:dataSetName:GetDataSetDetailsResponse' :: GetDataSetDetailsResponse -> Text
dataSetName} -> Text
dataSetName) (\s :: GetDataSetDetailsResponse
s@GetDataSetDetailsResponse' {} Text
a -> GetDataSetDetailsResponse
s {$sel:dataSetName:GetDataSetDetailsResponse' :: Text
dataSetName = Text
a} :: GetDataSetDetailsResponse)

instance Prelude.NFData GetDataSetDetailsResponse where
  rnf :: GetDataSetDetailsResponse -> ()
rnf GetDataSetDetailsResponse' {Int
Maybe Int
Maybe Text
Maybe POSIX
Maybe DatasetDetailOrgAttributes
Text
dataSetName :: Text
httpStatus :: Int
recordLength :: Maybe Int
location :: Maybe Text
lastUpdatedTime :: Maybe POSIX
lastReferencedTime :: Maybe POSIX
dataSetOrg :: Maybe DatasetDetailOrgAttributes
creationTime :: Maybe POSIX
blocksize :: Maybe Int
$sel:dataSetName:GetDataSetDetailsResponse' :: GetDataSetDetailsResponse -> Text
$sel:httpStatus:GetDataSetDetailsResponse' :: GetDataSetDetailsResponse -> Int
$sel:recordLength:GetDataSetDetailsResponse' :: GetDataSetDetailsResponse -> Maybe Int
$sel:location:GetDataSetDetailsResponse' :: GetDataSetDetailsResponse -> Maybe Text
$sel:lastUpdatedTime:GetDataSetDetailsResponse' :: GetDataSetDetailsResponse -> Maybe POSIX
$sel:lastReferencedTime:GetDataSetDetailsResponse' :: GetDataSetDetailsResponse -> Maybe POSIX
$sel:dataSetOrg:GetDataSetDetailsResponse' :: GetDataSetDetailsResponse -> Maybe DatasetDetailOrgAttributes
$sel:creationTime:GetDataSetDetailsResponse' :: GetDataSetDetailsResponse -> Maybe POSIX
$sel:blocksize:GetDataSetDetailsResponse' :: GetDataSetDetailsResponse -> Maybe Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
blocksize
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 DatasetDetailOrgAttributes
dataSetOrg
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastReferencedTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastUpdatedTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
location
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
recordLength
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
dataSetName