{-# 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 #-}
module Amazonka.FinSpaceData.GetDataView
(
GetDataView (..),
newGetDataView,
getDataView_dataViewId,
getDataView_datasetId,
GetDataViewResponse (..),
newGetDataViewResponse,
getDataViewResponse_asOfTimestamp,
getDataViewResponse_autoUpdate,
getDataViewResponse_createTime,
getDataViewResponse_dataViewArn,
getDataViewResponse_dataViewId,
getDataViewResponse_datasetId,
getDataViewResponse_destinationTypeParams,
getDataViewResponse_errorInfo,
getDataViewResponse_lastModifiedTime,
getDataViewResponse_partitionColumns,
getDataViewResponse_sortColumns,
getDataViewResponse_status,
getDataViewResponse_httpStatus,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.FinSpaceData.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
data GetDataView = GetDataView'
{
GetDataView -> Text
dataViewId :: Prelude.Text,
GetDataView -> Text
datasetId :: Prelude.Text
}
deriving (GetDataView -> GetDataView -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDataView -> GetDataView -> Bool
$c/= :: GetDataView -> GetDataView -> Bool
== :: GetDataView -> GetDataView -> Bool
$c== :: GetDataView -> GetDataView -> Bool
Prelude.Eq, ReadPrec [GetDataView]
ReadPrec GetDataView
Int -> ReadS GetDataView
ReadS [GetDataView]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetDataView]
$creadListPrec :: ReadPrec [GetDataView]
readPrec :: ReadPrec GetDataView
$creadPrec :: ReadPrec GetDataView
readList :: ReadS [GetDataView]
$creadList :: ReadS [GetDataView]
readsPrec :: Int -> ReadS GetDataView
$creadsPrec :: Int -> ReadS GetDataView
Prelude.Read, Int -> GetDataView -> ShowS
[GetDataView] -> ShowS
GetDataView -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetDataView] -> ShowS
$cshowList :: [GetDataView] -> ShowS
show :: GetDataView -> String
$cshow :: GetDataView -> String
showsPrec :: Int -> GetDataView -> ShowS
$cshowsPrec :: Int -> GetDataView -> ShowS
Prelude.Show, forall x. Rep GetDataView x -> GetDataView
forall x. GetDataView -> Rep GetDataView x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetDataView x -> GetDataView
$cfrom :: forall x. GetDataView -> Rep GetDataView x
Prelude.Generic)
newGetDataView ::
Prelude.Text ->
Prelude.Text ->
GetDataView
newGetDataView :: Text -> Text -> GetDataView
newGetDataView Text
pDataViewId_ Text
pDatasetId_ =
GetDataView'
{ $sel:dataViewId:GetDataView' :: Text
dataViewId = Text
pDataViewId_,
$sel:datasetId:GetDataView' :: Text
datasetId = Text
pDatasetId_
}
getDataView_dataViewId :: Lens.Lens' GetDataView Prelude.Text
getDataView_dataViewId :: Lens' GetDataView Text
getDataView_dataViewId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataView' {Text
dataViewId :: Text
$sel:dataViewId:GetDataView' :: GetDataView -> Text
dataViewId} -> Text
dataViewId) (\s :: GetDataView
s@GetDataView' {} Text
a -> GetDataView
s {$sel:dataViewId:GetDataView' :: Text
dataViewId = Text
a} :: GetDataView)
getDataView_datasetId :: Lens.Lens' GetDataView Prelude.Text
getDataView_datasetId :: Lens' GetDataView Text
getDataView_datasetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataView' {Text
datasetId :: Text
$sel:datasetId:GetDataView' :: GetDataView -> Text
datasetId} -> Text
datasetId) (\s :: GetDataView
s@GetDataView' {} Text
a -> GetDataView
s {$sel:datasetId:GetDataView' :: Text
datasetId = Text
a} :: GetDataView)
instance Core.AWSRequest GetDataView where
type AWSResponse GetDataView = GetDataViewResponse
request :: (Service -> Service) -> GetDataView -> Request GetDataView
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 GetDataView
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetDataView)))
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 Integer
-> Maybe Bool
-> Maybe Integer
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe DataViewDestinationTypeParams
-> Maybe DataViewErrorInfo
-> Maybe Integer
-> Maybe [Text]
-> Maybe [Text]
-> Maybe DataViewStatus
-> Int
-> GetDataViewResponse
GetDataViewResponse'
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
"asOfTimestamp")
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
"autoUpdate")
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
"createTime")
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
"dataViewArn")
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
"dataViewId")
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
"datasetId")
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
"destinationTypeParams")
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
"errorInfo")
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
"lastModifiedTime")
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
"partitionColumns"
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
"sortColumns" 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
"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 GetDataView where
hashWithSalt :: Int -> GetDataView -> Int
hashWithSalt Int
_salt GetDataView' {Text
datasetId :: Text
dataViewId :: Text
$sel:datasetId:GetDataView' :: GetDataView -> Text
$sel:dataViewId:GetDataView' :: GetDataView -> Text
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
dataViewId
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
datasetId
instance Prelude.NFData GetDataView where
rnf :: GetDataView -> ()
rnf GetDataView' {Text
datasetId :: Text
dataViewId :: Text
$sel:datasetId:GetDataView' :: GetDataView -> Text
$sel:dataViewId:GetDataView' :: GetDataView -> Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Text
dataViewId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
datasetId
instance Data.ToHeaders GetDataView where
toHeaders :: GetDataView -> 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 GetDataView where
toPath :: GetDataView -> ByteString
toPath GetDataView' {Text
datasetId :: Text
dataViewId :: Text
$sel:datasetId:GetDataView' :: GetDataView -> Text
$sel:dataViewId:GetDataView' :: GetDataView -> Text
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ ByteString
"/datasets/",
forall a. ToByteString a => a -> ByteString
Data.toBS Text
datasetId,
ByteString
"/dataviewsv2/",
forall a. ToByteString a => a -> ByteString
Data.toBS Text
dataViewId
]
instance Data.ToQuery GetDataView where
toQuery :: GetDataView -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data GetDataViewResponse = GetDataViewResponse'
{
GetDataViewResponse -> Maybe Integer
asOfTimestamp :: Prelude.Maybe Prelude.Integer,
GetDataViewResponse -> Maybe Bool
autoUpdate :: Prelude.Maybe Prelude.Bool,
GetDataViewResponse -> Maybe Integer
createTime :: Prelude.Maybe Prelude.Integer,
GetDataViewResponse -> Maybe Text
dataViewArn :: Prelude.Maybe Prelude.Text,
GetDataViewResponse -> Maybe Text
dataViewId :: Prelude.Maybe Prelude.Text,
GetDataViewResponse -> Maybe Text
datasetId :: Prelude.Maybe Prelude.Text,
GetDataViewResponse -> Maybe DataViewDestinationTypeParams
destinationTypeParams :: Prelude.Maybe DataViewDestinationTypeParams,
GetDataViewResponse -> Maybe DataViewErrorInfo
errorInfo :: Prelude.Maybe DataViewErrorInfo,
GetDataViewResponse -> Maybe Integer
lastModifiedTime :: Prelude.Maybe Prelude.Integer,
GetDataViewResponse -> Maybe [Text]
partitionColumns :: Prelude.Maybe [Prelude.Text],
GetDataViewResponse -> Maybe [Text]
sortColumns :: Prelude.Maybe [Prelude.Text],
GetDataViewResponse -> Maybe DataViewStatus
status :: Prelude.Maybe DataViewStatus,
GetDataViewResponse -> Int
httpStatus :: Prelude.Int
}
deriving (GetDataViewResponse -> GetDataViewResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDataViewResponse -> GetDataViewResponse -> Bool
$c/= :: GetDataViewResponse -> GetDataViewResponse -> Bool
== :: GetDataViewResponse -> GetDataViewResponse -> Bool
$c== :: GetDataViewResponse -> GetDataViewResponse -> Bool
Prelude.Eq, ReadPrec [GetDataViewResponse]
ReadPrec GetDataViewResponse
Int -> ReadS GetDataViewResponse
ReadS [GetDataViewResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetDataViewResponse]
$creadListPrec :: ReadPrec [GetDataViewResponse]
readPrec :: ReadPrec GetDataViewResponse
$creadPrec :: ReadPrec GetDataViewResponse
readList :: ReadS [GetDataViewResponse]
$creadList :: ReadS [GetDataViewResponse]
readsPrec :: Int -> ReadS GetDataViewResponse
$creadsPrec :: Int -> ReadS GetDataViewResponse
Prelude.Read, Int -> GetDataViewResponse -> ShowS
[GetDataViewResponse] -> ShowS
GetDataViewResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetDataViewResponse] -> ShowS
$cshowList :: [GetDataViewResponse] -> ShowS
show :: GetDataViewResponse -> String
$cshow :: GetDataViewResponse -> String
showsPrec :: Int -> GetDataViewResponse -> ShowS
$cshowsPrec :: Int -> GetDataViewResponse -> ShowS
Prelude.Show, forall x. Rep GetDataViewResponse x -> GetDataViewResponse
forall x. GetDataViewResponse -> Rep GetDataViewResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetDataViewResponse x -> GetDataViewResponse
$cfrom :: forall x. GetDataViewResponse -> Rep GetDataViewResponse x
Prelude.Generic)
newGetDataViewResponse ::
Prelude.Int ->
GetDataViewResponse
newGetDataViewResponse :: Int -> GetDataViewResponse
newGetDataViewResponse Int
pHttpStatus_ =
GetDataViewResponse'
{ $sel:asOfTimestamp:GetDataViewResponse' :: Maybe Integer
asOfTimestamp =
forall a. Maybe a
Prelude.Nothing,
$sel:autoUpdate:GetDataViewResponse' :: Maybe Bool
autoUpdate = forall a. Maybe a
Prelude.Nothing,
$sel:createTime:GetDataViewResponse' :: Maybe Integer
createTime = forall a. Maybe a
Prelude.Nothing,
$sel:dataViewArn:GetDataViewResponse' :: Maybe Text
dataViewArn = forall a. Maybe a
Prelude.Nothing,
$sel:dataViewId:GetDataViewResponse' :: Maybe Text
dataViewId = forall a. Maybe a
Prelude.Nothing,
$sel:datasetId:GetDataViewResponse' :: Maybe Text
datasetId = forall a. Maybe a
Prelude.Nothing,
$sel:destinationTypeParams:GetDataViewResponse' :: Maybe DataViewDestinationTypeParams
destinationTypeParams = forall a. Maybe a
Prelude.Nothing,
$sel:errorInfo:GetDataViewResponse' :: Maybe DataViewErrorInfo
errorInfo = forall a. Maybe a
Prelude.Nothing,
$sel:lastModifiedTime:GetDataViewResponse' :: Maybe Integer
lastModifiedTime = forall a. Maybe a
Prelude.Nothing,
$sel:partitionColumns:GetDataViewResponse' :: Maybe [Text]
partitionColumns = forall a. Maybe a
Prelude.Nothing,
$sel:sortColumns:GetDataViewResponse' :: Maybe [Text]
sortColumns = forall a. Maybe a
Prelude.Nothing,
$sel:status:GetDataViewResponse' :: Maybe DataViewStatus
status = forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:GetDataViewResponse' :: Int
httpStatus = Int
pHttpStatus_
}
getDataViewResponse_asOfTimestamp :: Lens.Lens' GetDataViewResponse (Prelude.Maybe Prelude.Integer)
getDataViewResponse_asOfTimestamp :: Lens' GetDataViewResponse (Maybe Integer)
getDataViewResponse_asOfTimestamp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataViewResponse' {Maybe Integer
asOfTimestamp :: Maybe Integer
$sel:asOfTimestamp:GetDataViewResponse' :: GetDataViewResponse -> Maybe Integer
asOfTimestamp} -> Maybe Integer
asOfTimestamp) (\s :: GetDataViewResponse
s@GetDataViewResponse' {} Maybe Integer
a -> GetDataViewResponse
s {$sel:asOfTimestamp:GetDataViewResponse' :: Maybe Integer
asOfTimestamp = Maybe Integer
a} :: GetDataViewResponse)
getDataViewResponse_autoUpdate :: Lens.Lens' GetDataViewResponse (Prelude.Maybe Prelude.Bool)
getDataViewResponse_autoUpdate :: Lens' GetDataViewResponse (Maybe Bool)
getDataViewResponse_autoUpdate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataViewResponse' {Maybe Bool
autoUpdate :: Maybe Bool
$sel:autoUpdate:GetDataViewResponse' :: GetDataViewResponse -> Maybe Bool
autoUpdate} -> Maybe Bool
autoUpdate) (\s :: GetDataViewResponse
s@GetDataViewResponse' {} Maybe Bool
a -> GetDataViewResponse
s {$sel:autoUpdate:GetDataViewResponse' :: Maybe Bool
autoUpdate = Maybe Bool
a} :: GetDataViewResponse)
getDataViewResponse_createTime :: Lens.Lens' GetDataViewResponse (Prelude.Maybe Prelude.Integer)
getDataViewResponse_createTime :: Lens' GetDataViewResponse (Maybe Integer)
getDataViewResponse_createTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataViewResponse' {Maybe Integer
createTime :: Maybe Integer
$sel:createTime:GetDataViewResponse' :: GetDataViewResponse -> Maybe Integer
createTime} -> Maybe Integer
createTime) (\s :: GetDataViewResponse
s@GetDataViewResponse' {} Maybe Integer
a -> GetDataViewResponse
s {$sel:createTime:GetDataViewResponse' :: Maybe Integer
createTime = Maybe Integer
a} :: GetDataViewResponse)
getDataViewResponse_dataViewArn :: Lens.Lens' GetDataViewResponse (Prelude.Maybe Prelude.Text)
getDataViewResponse_dataViewArn :: Lens' GetDataViewResponse (Maybe Text)
getDataViewResponse_dataViewArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataViewResponse' {Maybe Text
dataViewArn :: Maybe Text
$sel:dataViewArn:GetDataViewResponse' :: GetDataViewResponse -> Maybe Text
dataViewArn} -> Maybe Text
dataViewArn) (\s :: GetDataViewResponse
s@GetDataViewResponse' {} Maybe Text
a -> GetDataViewResponse
s {$sel:dataViewArn:GetDataViewResponse' :: Maybe Text
dataViewArn = Maybe Text
a} :: GetDataViewResponse)
getDataViewResponse_dataViewId :: Lens.Lens' GetDataViewResponse (Prelude.Maybe Prelude.Text)
getDataViewResponse_dataViewId :: Lens' GetDataViewResponse (Maybe Text)
getDataViewResponse_dataViewId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataViewResponse' {Maybe Text
dataViewId :: Maybe Text
$sel:dataViewId:GetDataViewResponse' :: GetDataViewResponse -> Maybe Text
dataViewId} -> Maybe Text
dataViewId) (\s :: GetDataViewResponse
s@GetDataViewResponse' {} Maybe Text
a -> GetDataViewResponse
s {$sel:dataViewId:GetDataViewResponse' :: Maybe Text
dataViewId = Maybe Text
a} :: GetDataViewResponse)
getDataViewResponse_datasetId :: Lens.Lens' GetDataViewResponse (Prelude.Maybe Prelude.Text)
getDataViewResponse_datasetId :: Lens' GetDataViewResponse (Maybe Text)
getDataViewResponse_datasetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataViewResponse' {Maybe Text
datasetId :: Maybe Text
$sel:datasetId:GetDataViewResponse' :: GetDataViewResponse -> Maybe Text
datasetId} -> Maybe Text
datasetId) (\s :: GetDataViewResponse
s@GetDataViewResponse' {} Maybe Text
a -> GetDataViewResponse
s {$sel:datasetId:GetDataViewResponse' :: Maybe Text
datasetId = Maybe Text
a} :: GetDataViewResponse)
getDataViewResponse_destinationTypeParams :: Lens.Lens' GetDataViewResponse (Prelude.Maybe DataViewDestinationTypeParams)
getDataViewResponse_destinationTypeParams :: Lens' GetDataViewResponse (Maybe DataViewDestinationTypeParams)
getDataViewResponse_destinationTypeParams = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataViewResponse' {Maybe DataViewDestinationTypeParams
destinationTypeParams :: Maybe DataViewDestinationTypeParams
$sel:destinationTypeParams:GetDataViewResponse' :: GetDataViewResponse -> Maybe DataViewDestinationTypeParams
destinationTypeParams} -> Maybe DataViewDestinationTypeParams
destinationTypeParams) (\s :: GetDataViewResponse
s@GetDataViewResponse' {} Maybe DataViewDestinationTypeParams
a -> GetDataViewResponse
s {$sel:destinationTypeParams:GetDataViewResponse' :: Maybe DataViewDestinationTypeParams
destinationTypeParams = Maybe DataViewDestinationTypeParams
a} :: GetDataViewResponse)
getDataViewResponse_errorInfo :: Lens.Lens' GetDataViewResponse (Prelude.Maybe DataViewErrorInfo)
getDataViewResponse_errorInfo :: Lens' GetDataViewResponse (Maybe DataViewErrorInfo)
getDataViewResponse_errorInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataViewResponse' {Maybe DataViewErrorInfo
errorInfo :: Maybe DataViewErrorInfo
$sel:errorInfo:GetDataViewResponse' :: GetDataViewResponse -> Maybe DataViewErrorInfo
errorInfo} -> Maybe DataViewErrorInfo
errorInfo) (\s :: GetDataViewResponse
s@GetDataViewResponse' {} Maybe DataViewErrorInfo
a -> GetDataViewResponse
s {$sel:errorInfo:GetDataViewResponse' :: Maybe DataViewErrorInfo
errorInfo = Maybe DataViewErrorInfo
a} :: GetDataViewResponse)
getDataViewResponse_lastModifiedTime :: Lens.Lens' GetDataViewResponse (Prelude.Maybe Prelude.Integer)
getDataViewResponse_lastModifiedTime :: Lens' GetDataViewResponse (Maybe Integer)
getDataViewResponse_lastModifiedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataViewResponse' {Maybe Integer
lastModifiedTime :: Maybe Integer
$sel:lastModifiedTime:GetDataViewResponse' :: GetDataViewResponse -> Maybe Integer
lastModifiedTime} -> Maybe Integer
lastModifiedTime) (\s :: GetDataViewResponse
s@GetDataViewResponse' {} Maybe Integer
a -> GetDataViewResponse
s {$sel:lastModifiedTime:GetDataViewResponse' :: Maybe Integer
lastModifiedTime = Maybe Integer
a} :: GetDataViewResponse)
getDataViewResponse_partitionColumns :: Lens.Lens' GetDataViewResponse (Prelude.Maybe [Prelude.Text])
getDataViewResponse_partitionColumns :: Lens' GetDataViewResponse (Maybe [Text])
getDataViewResponse_partitionColumns = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataViewResponse' {Maybe [Text]
partitionColumns :: Maybe [Text]
$sel:partitionColumns:GetDataViewResponse' :: GetDataViewResponse -> Maybe [Text]
partitionColumns} -> Maybe [Text]
partitionColumns) (\s :: GetDataViewResponse
s@GetDataViewResponse' {} Maybe [Text]
a -> GetDataViewResponse
s {$sel:partitionColumns:GetDataViewResponse' :: Maybe [Text]
partitionColumns = Maybe [Text]
a} :: GetDataViewResponse) 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
getDataViewResponse_sortColumns :: Lens.Lens' GetDataViewResponse (Prelude.Maybe [Prelude.Text])
getDataViewResponse_sortColumns :: Lens' GetDataViewResponse (Maybe [Text])
getDataViewResponse_sortColumns = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataViewResponse' {Maybe [Text]
sortColumns :: Maybe [Text]
$sel:sortColumns:GetDataViewResponse' :: GetDataViewResponse -> Maybe [Text]
sortColumns} -> Maybe [Text]
sortColumns) (\s :: GetDataViewResponse
s@GetDataViewResponse' {} Maybe [Text]
a -> GetDataViewResponse
s {$sel:sortColumns:GetDataViewResponse' :: Maybe [Text]
sortColumns = Maybe [Text]
a} :: GetDataViewResponse) 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
getDataViewResponse_status :: Lens.Lens' GetDataViewResponse (Prelude.Maybe DataViewStatus)
getDataViewResponse_status :: Lens' GetDataViewResponse (Maybe DataViewStatus)
getDataViewResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataViewResponse' {Maybe DataViewStatus
status :: Maybe DataViewStatus
$sel:status:GetDataViewResponse' :: GetDataViewResponse -> Maybe DataViewStatus
status} -> Maybe DataViewStatus
status) (\s :: GetDataViewResponse
s@GetDataViewResponse' {} Maybe DataViewStatus
a -> GetDataViewResponse
s {$sel:status:GetDataViewResponse' :: Maybe DataViewStatus
status = Maybe DataViewStatus
a} :: GetDataViewResponse)
getDataViewResponse_httpStatus :: Lens.Lens' GetDataViewResponse Prelude.Int
getDataViewResponse_httpStatus :: Lens' GetDataViewResponse Int
getDataViewResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataViewResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetDataViewResponse' :: GetDataViewResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetDataViewResponse
s@GetDataViewResponse' {} Int
a -> GetDataViewResponse
s {$sel:httpStatus:GetDataViewResponse' :: Int
httpStatus = Int
a} :: GetDataViewResponse)
instance Prelude.NFData GetDataViewResponse where
rnf :: GetDataViewResponse -> ()
rnf GetDataViewResponse' {Int
Maybe Bool
Maybe Integer
Maybe [Text]
Maybe Text
Maybe DataViewStatus
Maybe DataViewErrorInfo
Maybe DataViewDestinationTypeParams
httpStatus :: Int
status :: Maybe DataViewStatus
sortColumns :: Maybe [Text]
partitionColumns :: Maybe [Text]
lastModifiedTime :: Maybe Integer
errorInfo :: Maybe DataViewErrorInfo
destinationTypeParams :: Maybe DataViewDestinationTypeParams
datasetId :: Maybe Text
dataViewId :: Maybe Text
dataViewArn :: Maybe Text
createTime :: Maybe Integer
autoUpdate :: Maybe Bool
asOfTimestamp :: Maybe Integer
$sel:httpStatus:GetDataViewResponse' :: GetDataViewResponse -> Int
$sel:status:GetDataViewResponse' :: GetDataViewResponse -> Maybe DataViewStatus
$sel:sortColumns:GetDataViewResponse' :: GetDataViewResponse -> Maybe [Text]
$sel:partitionColumns:GetDataViewResponse' :: GetDataViewResponse -> Maybe [Text]
$sel:lastModifiedTime:GetDataViewResponse' :: GetDataViewResponse -> Maybe Integer
$sel:errorInfo:GetDataViewResponse' :: GetDataViewResponse -> Maybe DataViewErrorInfo
$sel:destinationTypeParams:GetDataViewResponse' :: GetDataViewResponse -> Maybe DataViewDestinationTypeParams
$sel:datasetId:GetDataViewResponse' :: GetDataViewResponse -> Maybe Text
$sel:dataViewId:GetDataViewResponse' :: GetDataViewResponse -> Maybe Text
$sel:dataViewArn:GetDataViewResponse' :: GetDataViewResponse -> Maybe Text
$sel:createTime:GetDataViewResponse' :: GetDataViewResponse -> Maybe Integer
$sel:autoUpdate:GetDataViewResponse' :: GetDataViewResponse -> Maybe Bool
$sel:asOfTimestamp:GetDataViewResponse' :: GetDataViewResponse -> Maybe Integer
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
asOfTimestamp
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
autoUpdate
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
createTime
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
dataViewArn
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
dataViewId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
datasetId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DataViewDestinationTypeParams
destinationTypeParams
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DataViewErrorInfo
errorInfo
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
lastModifiedTime
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
partitionColumns
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
sortColumns
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DataViewStatus
status
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus