{-# 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.SageMakerGeoSpatial.GetRasterDataCollection
(
GetRasterDataCollection (..),
newGetRasterDataCollection,
getRasterDataCollection_arn,
GetRasterDataCollectionResponse (..),
newGetRasterDataCollectionResponse,
getRasterDataCollectionResponse_tags,
getRasterDataCollectionResponse_httpStatus,
getRasterDataCollectionResponse_arn,
getRasterDataCollectionResponse_description,
getRasterDataCollectionResponse_descriptionPageUrl,
getRasterDataCollectionResponse_imageSourceBands,
getRasterDataCollectionResponse_name,
getRasterDataCollectionResponse_supportedFilters,
getRasterDataCollectionResponse_type,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.SageMakerGeoSpatial.Types
data GetRasterDataCollection = GetRasterDataCollection'
{
GetRasterDataCollection -> Text
arn :: Prelude.Text
}
deriving (GetRasterDataCollection -> GetRasterDataCollection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetRasterDataCollection -> GetRasterDataCollection -> Bool
$c/= :: GetRasterDataCollection -> GetRasterDataCollection -> Bool
== :: GetRasterDataCollection -> GetRasterDataCollection -> Bool
$c== :: GetRasterDataCollection -> GetRasterDataCollection -> Bool
Prelude.Eq, ReadPrec [GetRasterDataCollection]
ReadPrec GetRasterDataCollection
Int -> ReadS GetRasterDataCollection
ReadS [GetRasterDataCollection]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetRasterDataCollection]
$creadListPrec :: ReadPrec [GetRasterDataCollection]
readPrec :: ReadPrec GetRasterDataCollection
$creadPrec :: ReadPrec GetRasterDataCollection
readList :: ReadS [GetRasterDataCollection]
$creadList :: ReadS [GetRasterDataCollection]
readsPrec :: Int -> ReadS GetRasterDataCollection
$creadsPrec :: Int -> ReadS GetRasterDataCollection
Prelude.Read, Int -> GetRasterDataCollection -> ShowS
[GetRasterDataCollection] -> ShowS
GetRasterDataCollection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetRasterDataCollection] -> ShowS
$cshowList :: [GetRasterDataCollection] -> ShowS
show :: GetRasterDataCollection -> String
$cshow :: GetRasterDataCollection -> String
showsPrec :: Int -> GetRasterDataCollection -> ShowS
$cshowsPrec :: Int -> GetRasterDataCollection -> ShowS
Prelude.Show, forall x. Rep GetRasterDataCollection x -> GetRasterDataCollection
forall x. GetRasterDataCollection -> Rep GetRasterDataCollection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetRasterDataCollection x -> GetRasterDataCollection
$cfrom :: forall x. GetRasterDataCollection -> Rep GetRasterDataCollection x
Prelude.Generic)
newGetRasterDataCollection ::
Prelude.Text ->
GetRasterDataCollection
newGetRasterDataCollection :: Text -> GetRasterDataCollection
newGetRasterDataCollection Text
pArn_ =
GetRasterDataCollection' {$sel:arn:GetRasterDataCollection' :: Text
arn = Text
pArn_}
getRasterDataCollection_arn :: Lens.Lens' GetRasterDataCollection Prelude.Text
getRasterDataCollection_arn :: Lens' GetRasterDataCollection Text
getRasterDataCollection_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRasterDataCollection' {Text
arn :: Text
$sel:arn:GetRasterDataCollection' :: GetRasterDataCollection -> Text
arn} -> Text
arn) (\s :: GetRasterDataCollection
s@GetRasterDataCollection' {} Text
a -> GetRasterDataCollection
s {$sel:arn:GetRasterDataCollection' :: Text
arn = Text
a} :: GetRasterDataCollection)
instance Core.AWSRequest GetRasterDataCollection where
type
AWSResponse GetRasterDataCollection =
GetRasterDataCollectionResponse
request :: (Service -> Service)
-> GetRasterDataCollection -> Request GetRasterDataCollection
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 GetRasterDataCollection
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse GetRasterDataCollection)))
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 (HashMap Text Text)
-> Int
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> [Filter]
-> DataCollectionType
-> GetRasterDataCollectionResponse
GetRasterDataCollectionResponse'
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
"Tags" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (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
"Arn")
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
"Description")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"DescriptionPageUrl")
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
"ImageSourceBands"
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 a
Data..:> Key
"Name")
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
"SupportedFilters"
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 a
Data..:> Key
"Type")
)
instance Prelude.Hashable GetRasterDataCollection where
hashWithSalt :: Int -> GetRasterDataCollection -> Int
hashWithSalt Int
_salt GetRasterDataCollection' {Text
arn :: Text
$sel:arn:GetRasterDataCollection' :: GetRasterDataCollection -> Text
..} =
Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
arn
instance Prelude.NFData GetRasterDataCollection where
rnf :: GetRasterDataCollection -> ()
rnf GetRasterDataCollection' {Text
arn :: Text
$sel:arn:GetRasterDataCollection' :: GetRasterDataCollection -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
arn
instance Data.ToHeaders GetRasterDataCollection where
toHeaders :: GetRasterDataCollection -> 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 GetRasterDataCollection where
toPath :: GetRasterDataCollection -> ByteString
toPath GetRasterDataCollection' {Text
arn :: Text
$sel:arn:GetRasterDataCollection' :: GetRasterDataCollection -> Text
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ByteString
"/raster-data-collection/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
arn]
instance Data.ToQuery GetRasterDataCollection where
toQuery :: GetRasterDataCollection -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data GetRasterDataCollectionResponse = GetRasterDataCollectionResponse'
{
GetRasterDataCollectionResponse -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
GetRasterDataCollectionResponse -> Int
httpStatus :: Prelude.Int,
GetRasterDataCollectionResponse -> Text
arn :: Prelude.Text,
GetRasterDataCollectionResponse -> Text
description :: Prelude.Text,
GetRasterDataCollectionResponse -> Text
descriptionPageUrl :: Prelude.Text,
GetRasterDataCollectionResponse -> [Text]
imageSourceBands :: [Prelude.Text],
GetRasterDataCollectionResponse -> Text
name :: Prelude.Text,
GetRasterDataCollectionResponse -> [Filter]
supportedFilters :: [Filter],
GetRasterDataCollectionResponse -> DataCollectionType
type' :: DataCollectionType
}
deriving (GetRasterDataCollectionResponse
-> GetRasterDataCollectionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetRasterDataCollectionResponse
-> GetRasterDataCollectionResponse -> Bool
$c/= :: GetRasterDataCollectionResponse
-> GetRasterDataCollectionResponse -> Bool
== :: GetRasterDataCollectionResponse
-> GetRasterDataCollectionResponse -> Bool
$c== :: GetRasterDataCollectionResponse
-> GetRasterDataCollectionResponse -> Bool
Prelude.Eq, ReadPrec [GetRasterDataCollectionResponse]
ReadPrec GetRasterDataCollectionResponse
Int -> ReadS GetRasterDataCollectionResponse
ReadS [GetRasterDataCollectionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetRasterDataCollectionResponse]
$creadListPrec :: ReadPrec [GetRasterDataCollectionResponse]
readPrec :: ReadPrec GetRasterDataCollectionResponse
$creadPrec :: ReadPrec GetRasterDataCollectionResponse
readList :: ReadS [GetRasterDataCollectionResponse]
$creadList :: ReadS [GetRasterDataCollectionResponse]
readsPrec :: Int -> ReadS GetRasterDataCollectionResponse
$creadsPrec :: Int -> ReadS GetRasterDataCollectionResponse
Prelude.Read, Int -> GetRasterDataCollectionResponse -> ShowS
[GetRasterDataCollectionResponse] -> ShowS
GetRasterDataCollectionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetRasterDataCollectionResponse] -> ShowS
$cshowList :: [GetRasterDataCollectionResponse] -> ShowS
show :: GetRasterDataCollectionResponse -> String
$cshow :: GetRasterDataCollectionResponse -> String
showsPrec :: Int -> GetRasterDataCollectionResponse -> ShowS
$cshowsPrec :: Int -> GetRasterDataCollectionResponse -> ShowS
Prelude.Show, forall x.
Rep GetRasterDataCollectionResponse x
-> GetRasterDataCollectionResponse
forall x.
GetRasterDataCollectionResponse
-> Rep GetRasterDataCollectionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetRasterDataCollectionResponse x
-> GetRasterDataCollectionResponse
$cfrom :: forall x.
GetRasterDataCollectionResponse
-> Rep GetRasterDataCollectionResponse x
Prelude.Generic)
newGetRasterDataCollectionResponse ::
Prelude.Int ->
Prelude.Text ->
Prelude.Text ->
Prelude.Text ->
Prelude.Text ->
DataCollectionType ->
GetRasterDataCollectionResponse
newGetRasterDataCollectionResponse :: Int
-> Text
-> Text
-> Text
-> Text
-> DataCollectionType
-> GetRasterDataCollectionResponse
newGetRasterDataCollectionResponse
Int
pHttpStatus_
Text
pArn_
Text
pDescription_
Text
pDescriptionPageUrl_
Text
pName_
DataCollectionType
pType_ =
GetRasterDataCollectionResponse'
{ $sel:tags:GetRasterDataCollectionResponse' :: Maybe (HashMap Text Text)
tags =
forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:GetRasterDataCollectionResponse' :: Int
httpStatus = Int
pHttpStatus_,
$sel:arn:GetRasterDataCollectionResponse' :: Text
arn = Text
pArn_,
$sel:description:GetRasterDataCollectionResponse' :: Text
description = Text
pDescription_,
$sel:descriptionPageUrl:GetRasterDataCollectionResponse' :: Text
descriptionPageUrl = Text
pDescriptionPageUrl_,
$sel:imageSourceBands:GetRasterDataCollectionResponse' :: [Text]
imageSourceBands = forall a. Monoid a => a
Prelude.mempty,
$sel:name:GetRasterDataCollectionResponse' :: Text
name = Text
pName_,
$sel:supportedFilters:GetRasterDataCollectionResponse' :: [Filter]
supportedFilters = forall a. Monoid a => a
Prelude.mempty,
$sel:type':GetRasterDataCollectionResponse' :: DataCollectionType
type' = DataCollectionType
pType_
}
getRasterDataCollectionResponse_tags :: Lens.Lens' GetRasterDataCollectionResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
getRasterDataCollectionResponse_tags :: Lens' GetRasterDataCollectionResponse (Maybe (HashMap Text Text))
getRasterDataCollectionResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRasterDataCollectionResponse' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:GetRasterDataCollectionResponse' :: GetRasterDataCollectionResponse -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: GetRasterDataCollectionResponse
s@GetRasterDataCollectionResponse' {} Maybe (HashMap Text Text)
a -> GetRasterDataCollectionResponse
s {$sel:tags:GetRasterDataCollectionResponse' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: GetRasterDataCollectionResponse) 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
getRasterDataCollectionResponse_httpStatus :: Lens.Lens' GetRasterDataCollectionResponse Prelude.Int
getRasterDataCollectionResponse_httpStatus :: Lens' GetRasterDataCollectionResponse Int
getRasterDataCollectionResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRasterDataCollectionResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetRasterDataCollectionResponse' :: GetRasterDataCollectionResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetRasterDataCollectionResponse
s@GetRasterDataCollectionResponse' {} Int
a -> GetRasterDataCollectionResponse
s {$sel:httpStatus:GetRasterDataCollectionResponse' :: Int
httpStatus = Int
a} :: GetRasterDataCollectionResponse)
getRasterDataCollectionResponse_arn :: Lens.Lens' GetRasterDataCollectionResponse Prelude.Text
getRasterDataCollectionResponse_arn :: Lens' GetRasterDataCollectionResponse Text
getRasterDataCollectionResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRasterDataCollectionResponse' {Text
arn :: Text
$sel:arn:GetRasterDataCollectionResponse' :: GetRasterDataCollectionResponse -> Text
arn} -> Text
arn) (\s :: GetRasterDataCollectionResponse
s@GetRasterDataCollectionResponse' {} Text
a -> GetRasterDataCollectionResponse
s {$sel:arn:GetRasterDataCollectionResponse' :: Text
arn = Text
a} :: GetRasterDataCollectionResponse)
getRasterDataCollectionResponse_description :: Lens.Lens' GetRasterDataCollectionResponse Prelude.Text
getRasterDataCollectionResponse_description :: Lens' GetRasterDataCollectionResponse Text
getRasterDataCollectionResponse_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRasterDataCollectionResponse' {Text
description :: Text
$sel:description:GetRasterDataCollectionResponse' :: GetRasterDataCollectionResponse -> Text
description} -> Text
description) (\s :: GetRasterDataCollectionResponse
s@GetRasterDataCollectionResponse' {} Text
a -> GetRasterDataCollectionResponse
s {$sel:description:GetRasterDataCollectionResponse' :: Text
description = Text
a} :: GetRasterDataCollectionResponse)
getRasterDataCollectionResponse_descriptionPageUrl :: Lens.Lens' GetRasterDataCollectionResponse Prelude.Text
getRasterDataCollectionResponse_descriptionPageUrl :: Lens' GetRasterDataCollectionResponse Text
getRasterDataCollectionResponse_descriptionPageUrl = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRasterDataCollectionResponse' {Text
descriptionPageUrl :: Text
$sel:descriptionPageUrl:GetRasterDataCollectionResponse' :: GetRasterDataCollectionResponse -> Text
descriptionPageUrl} -> Text
descriptionPageUrl) (\s :: GetRasterDataCollectionResponse
s@GetRasterDataCollectionResponse' {} Text
a -> GetRasterDataCollectionResponse
s {$sel:descriptionPageUrl:GetRasterDataCollectionResponse' :: Text
descriptionPageUrl = Text
a} :: GetRasterDataCollectionResponse)
getRasterDataCollectionResponse_imageSourceBands :: Lens.Lens' GetRasterDataCollectionResponse [Prelude.Text]
getRasterDataCollectionResponse_imageSourceBands :: Lens' GetRasterDataCollectionResponse [Text]
getRasterDataCollectionResponse_imageSourceBands = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRasterDataCollectionResponse' {[Text]
imageSourceBands :: [Text]
$sel:imageSourceBands:GetRasterDataCollectionResponse' :: GetRasterDataCollectionResponse -> [Text]
imageSourceBands} -> [Text]
imageSourceBands) (\s :: GetRasterDataCollectionResponse
s@GetRasterDataCollectionResponse' {} [Text]
a -> GetRasterDataCollectionResponse
s {$sel:imageSourceBands:GetRasterDataCollectionResponse' :: [Text]
imageSourceBands = [Text]
a} :: GetRasterDataCollectionResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
getRasterDataCollectionResponse_name :: Lens.Lens' GetRasterDataCollectionResponse Prelude.Text
getRasterDataCollectionResponse_name :: Lens' GetRasterDataCollectionResponse Text
getRasterDataCollectionResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRasterDataCollectionResponse' {Text
name :: Text
$sel:name:GetRasterDataCollectionResponse' :: GetRasterDataCollectionResponse -> Text
name} -> Text
name) (\s :: GetRasterDataCollectionResponse
s@GetRasterDataCollectionResponse' {} Text
a -> GetRasterDataCollectionResponse
s {$sel:name:GetRasterDataCollectionResponse' :: Text
name = Text
a} :: GetRasterDataCollectionResponse)
getRasterDataCollectionResponse_supportedFilters :: Lens.Lens' GetRasterDataCollectionResponse [Filter]
getRasterDataCollectionResponse_supportedFilters :: Lens' GetRasterDataCollectionResponse [Filter]
getRasterDataCollectionResponse_supportedFilters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRasterDataCollectionResponse' {[Filter]
supportedFilters :: [Filter]
$sel:supportedFilters:GetRasterDataCollectionResponse' :: GetRasterDataCollectionResponse -> [Filter]
supportedFilters} -> [Filter]
supportedFilters) (\s :: GetRasterDataCollectionResponse
s@GetRasterDataCollectionResponse' {} [Filter]
a -> GetRasterDataCollectionResponse
s {$sel:supportedFilters:GetRasterDataCollectionResponse' :: [Filter]
supportedFilters = [Filter]
a} :: GetRasterDataCollectionResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
getRasterDataCollectionResponse_type :: Lens.Lens' GetRasterDataCollectionResponse DataCollectionType
getRasterDataCollectionResponse_type :: Lens' GetRasterDataCollectionResponse DataCollectionType
getRasterDataCollectionResponse_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRasterDataCollectionResponse' {DataCollectionType
type' :: DataCollectionType
$sel:type':GetRasterDataCollectionResponse' :: GetRasterDataCollectionResponse -> DataCollectionType
type'} -> DataCollectionType
type') (\s :: GetRasterDataCollectionResponse
s@GetRasterDataCollectionResponse' {} DataCollectionType
a -> GetRasterDataCollectionResponse
s {$sel:type':GetRasterDataCollectionResponse' :: DataCollectionType
type' = DataCollectionType
a} :: GetRasterDataCollectionResponse)
instance
Prelude.NFData
GetRasterDataCollectionResponse
where
rnf :: GetRasterDataCollectionResponse -> ()
rnf GetRasterDataCollectionResponse' {Int
[Text]
[Filter]
Maybe (HashMap Text Text)
Text
DataCollectionType
type' :: DataCollectionType
supportedFilters :: [Filter]
name :: Text
imageSourceBands :: [Text]
descriptionPageUrl :: Text
description :: Text
arn :: Text
httpStatus :: Int
tags :: Maybe (HashMap Text Text)
$sel:type':GetRasterDataCollectionResponse' :: GetRasterDataCollectionResponse -> DataCollectionType
$sel:supportedFilters:GetRasterDataCollectionResponse' :: GetRasterDataCollectionResponse -> [Filter]
$sel:name:GetRasterDataCollectionResponse' :: GetRasterDataCollectionResponse -> Text
$sel:imageSourceBands:GetRasterDataCollectionResponse' :: GetRasterDataCollectionResponse -> [Text]
$sel:descriptionPageUrl:GetRasterDataCollectionResponse' :: GetRasterDataCollectionResponse -> Text
$sel:description:GetRasterDataCollectionResponse' :: GetRasterDataCollectionResponse -> Text
$sel:arn:GetRasterDataCollectionResponse' :: GetRasterDataCollectionResponse -> Text
$sel:httpStatus:GetRasterDataCollectionResponse' :: GetRasterDataCollectionResponse -> Int
$sel:tags:GetRasterDataCollectionResponse' :: GetRasterDataCollectionResponse -> Maybe (HashMap Text Text)
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
arn
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
description
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
descriptionPageUrl
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Text]
imageSourceBands
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Filter]
supportedFilters
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf DataCollectionType
type'