{-# 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.ExportEarthObservationJob
(
ExportEarthObservationJob (..),
newExportEarthObservationJob,
exportEarthObservationJob_exportSourceImages,
exportEarthObservationJob_arn,
exportEarthObservationJob_executionRoleArn,
exportEarthObservationJob_outputConfig,
ExportEarthObservationJobResponse (..),
newExportEarthObservationJobResponse,
exportEarthObservationJobResponse_exportSourceImages,
exportEarthObservationJobResponse_httpStatus,
exportEarthObservationJobResponse_arn,
exportEarthObservationJobResponse_creationTime,
exportEarthObservationJobResponse_executionRoleArn,
exportEarthObservationJobResponse_exportStatus,
exportEarthObservationJobResponse_outputConfig,
)
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 ExportEarthObservationJob = ExportEarthObservationJob'
{
ExportEarthObservationJob -> Maybe Bool
exportSourceImages :: Prelude.Maybe Prelude.Bool,
ExportEarthObservationJob -> Text
arn :: Prelude.Text,
ExportEarthObservationJob -> Text
executionRoleArn :: Prelude.Text,
ExportEarthObservationJob -> OutputConfigInput
outputConfig :: OutputConfigInput
}
deriving (ExportEarthObservationJob -> ExportEarthObservationJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExportEarthObservationJob -> ExportEarthObservationJob -> Bool
$c/= :: ExportEarthObservationJob -> ExportEarthObservationJob -> Bool
== :: ExportEarthObservationJob -> ExportEarthObservationJob -> Bool
$c== :: ExportEarthObservationJob -> ExportEarthObservationJob -> Bool
Prelude.Eq, ReadPrec [ExportEarthObservationJob]
ReadPrec ExportEarthObservationJob
Int -> ReadS ExportEarthObservationJob
ReadS [ExportEarthObservationJob]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ExportEarthObservationJob]
$creadListPrec :: ReadPrec [ExportEarthObservationJob]
readPrec :: ReadPrec ExportEarthObservationJob
$creadPrec :: ReadPrec ExportEarthObservationJob
readList :: ReadS [ExportEarthObservationJob]
$creadList :: ReadS [ExportEarthObservationJob]
readsPrec :: Int -> ReadS ExportEarthObservationJob
$creadsPrec :: Int -> ReadS ExportEarthObservationJob
Prelude.Read, Int -> ExportEarthObservationJob -> ShowS
[ExportEarthObservationJob] -> ShowS
ExportEarthObservationJob -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExportEarthObservationJob] -> ShowS
$cshowList :: [ExportEarthObservationJob] -> ShowS
show :: ExportEarthObservationJob -> String
$cshow :: ExportEarthObservationJob -> String
showsPrec :: Int -> ExportEarthObservationJob -> ShowS
$cshowsPrec :: Int -> ExportEarthObservationJob -> ShowS
Prelude.Show, forall x.
Rep ExportEarthObservationJob x -> ExportEarthObservationJob
forall x.
ExportEarthObservationJob -> Rep ExportEarthObservationJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ExportEarthObservationJob x -> ExportEarthObservationJob
$cfrom :: forall x.
ExportEarthObservationJob -> Rep ExportEarthObservationJob x
Prelude.Generic)
newExportEarthObservationJob ::
Prelude.Text ->
Prelude.Text ->
OutputConfigInput ->
ExportEarthObservationJob
newExportEarthObservationJob :: Text -> Text -> OutputConfigInput -> ExportEarthObservationJob
newExportEarthObservationJob
Text
pArn_
Text
pExecutionRoleArn_
OutputConfigInput
pOutputConfig_ =
ExportEarthObservationJob'
{ $sel:exportSourceImages:ExportEarthObservationJob' :: Maybe Bool
exportSourceImages =
forall a. Maybe a
Prelude.Nothing,
$sel:arn:ExportEarthObservationJob' :: Text
arn = Text
pArn_,
$sel:executionRoleArn:ExportEarthObservationJob' :: Text
executionRoleArn = Text
pExecutionRoleArn_,
$sel:outputConfig:ExportEarthObservationJob' :: OutputConfigInput
outputConfig = OutputConfigInput
pOutputConfig_
}
exportEarthObservationJob_exportSourceImages :: Lens.Lens' ExportEarthObservationJob (Prelude.Maybe Prelude.Bool)
exportEarthObservationJob_exportSourceImages :: Lens' ExportEarthObservationJob (Maybe Bool)
exportEarthObservationJob_exportSourceImages = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportEarthObservationJob' {Maybe Bool
exportSourceImages :: Maybe Bool
$sel:exportSourceImages:ExportEarthObservationJob' :: ExportEarthObservationJob -> Maybe Bool
exportSourceImages} -> Maybe Bool
exportSourceImages) (\s :: ExportEarthObservationJob
s@ExportEarthObservationJob' {} Maybe Bool
a -> ExportEarthObservationJob
s {$sel:exportSourceImages:ExportEarthObservationJob' :: Maybe Bool
exportSourceImages = Maybe Bool
a} :: ExportEarthObservationJob)
exportEarthObservationJob_arn :: Lens.Lens' ExportEarthObservationJob Prelude.Text
exportEarthObservationJob_arn :: Lens' ExportEarthObservationJob Text
exportEarthObservationJob_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportEarthObservationJob' {Text
arn :: Text
$sel:arn:ExportEarthObservationJob' :: ExportEarthObservationJob -> Text
arn} -> Text
arn) (\s :: ExportEarthObservationJob
s@ExportEarthObservationJob' {} Text
a -> ExportEarthObservationJob
s {$sel:arn:ExportEarthObservationJob' :: Text
arn = Text
a} :: ExportEarthObservationJob)
exportEarthObservationJob_executionRoleArn :: Lens.Lens' ExportEarthObservationJob Prelude.Text
exportEarthObservationJob_executionRoleArn :: Lens' ExportEarthObservationJob Text
exportEarthObservationJob_executionRoleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportEarthObservationJob' {Text
executionRoleArn :: Text
$sel:executionRoleArn:ExportEarthObservationJob' :: ExportEarthObservationJob -> Text
executionRoleArn} -> Text
executionRoleArn) (\s :: ExportEarthObservationJob
s@ExportEarthObservationJob' {} Text
a -> ExportEarthObservationJob
s {$sel:executionRoleArn:ExportEarthObservationJob' :: Text
executionRoleArn = Text
a} :: ExportEarthObservationJob)
exportEarthObservationJob_outputConfig :: Lens.Lens' ExportEarthObservationJob OutputConfigInput
exportEarthObservationJob_outputConfig :: Lens' ExportEarthObservationJob OutputConfigInput
exportEarthObservationJob_outputConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportEarthObservationJob' {OutputConfigInput
outputConfig :: OutputConfigInput
$sel:outputConfig:ExportEarthObservationJob' :: ExportEarthObservationJob -> OutputConfigInput
outputConfig} -> OutputConfigInput
outputConfig) (\s :: ExportEarthObservationJob
s@ExportEarthObservationJob' {} OutputConfigInput
a -> ExportEarthObservationJob
s {$sel:outputConfig:ExportEarthObservationJob' :: OutputConfigInput
outputConfig = OutputConfigInput
a} :: ExportEarthObservationJob)
instance Core.AWSRequest ExportEarthObservationJob where
type
AWSResponse ExportEarthObservationJob =
ExportEarthObservationJobResponse
request :: (Service -> Service)
-> ExportEarthObservationJob -> Request ExportEarthObservationJob
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 ExportEarthObservationJob
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse ExportEarthObservationJob)))
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 Bool
-> Int
-> Text
-> POSIX
-> Text
-> EarthObservationJobExportStatus
-> OutputConfigInput
-> ExportEarthObservationJobResponse
ExportEarthObservationJobResponse'
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
"ExportSourceImages")
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
"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 a
Data..:> Key
"ExecutionRoleArn")
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
"ExportStatus")
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
"OutputConfig")
)
instance Prelude.Hashable ExportEarthObservationJob where
hashWithSalt :: Int -> ExportEarthObservationJob -> Int
hashWithSalt Int
_salt ExportEarthObservationJob' {Maybe Bool
Text
OutputConfigInput
outputConfig :: OutputConfigInput
executionRoleArn :: Text
arn :: Text
exportSourceImages :: Maybe Bool
$sel:outputConfig:ExportEarthObservationJob' :: ExportEarthObservationJob -> OutputConfigInput
$sel:executionRoleArn:ExportEarthObservationJob' :: ExportEarthObservationJob -> Text
$sel:arn:ExportEarthObservationJob' :: ExportEarthObservationJob -> Text
$sel:exportSourceImages:ExportEarthObservationJob' :: ExportEarthObservationJob -> Maybe Bool
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
exportSourceImages
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
arn
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
executionRoleArn
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` OutputConfigInput
outputConfig
instance Prelude.NFData ExportEarthObservationJob where
rnf :: ExportEarthObservationJob -> ()
rnf ExportEarthObservationJob' {Maybe Bool
Text
OutputConfigInput
outputConfig :: OutputConfigInput
executionRoleArn :: Text
arn :: Text
exportSourceImages :: Maybe Bool
$sel:outputConfig:ExportEarthObservationJob' :: ExportEarthObservationJob -> OutputConfigInput
$sel:executionRoleArn:ExportEarthObservationJob' :: ExportEarthObservationJob -> Text
$sel:arn:ExportEarthObservationJob' :: ExportEarthObservationJob -> Text
$sel:exportSourceImages:ExportEarthObservationJob' :: ExportEarthObservationJob -> Maybe Bool
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
exportSourceImages
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
executionRoleArn
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf OutputConfigInput
outputConfig
instance Data.ToHeaders ExportEarthObservationJob where
toHeaders :: ExportEarthObservationJob -> 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.ToJSON ExportEarthObservationJob where
toJSON :: ExportEarthObservationJob -> Value
toJSON ExportEarthObservationJob' {Maybe Bool
Text
OutputConfigInput
outputConfig :: OutputConfigInput
executionRoleArn :: Text
arn :: Text
exportSourceImages :: Maybe Bool
$sel:outputConfig:ExportEarthObservationJob' :: ExportEarthObservationJob -> OutputConfigInput
$sel:executionRoleArn:ExportEarthObservationJob' :: ExportEarthObservationJob -> Text
$sel:arn:ExportEarthObservationJob' :: ExportEarthObservationJob -> Text
$sel:exportSourceImages:ExportEarthObservationJob' :: ExportEarthObservationJob -> Maybe Bool
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ (Key
"ExportSourceImages" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Bool
exportSourceImages,
forall a. a -> Maybe a
Prelude.Just (Key
"Arn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
arn),
forall a. a -> Maybe a
Prelude.Just
(Key
"ExecutionRoleArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
executionRoleArn),
forall a. a -> Maybe a
Prelude.Just (Key
"OutputConfig" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= OutputConfigInput
outputConfig)
]
)
instance Data.ToPath ExportEarthObservationJob where
toPath :: ExportEarthObservationJob -> ByteString
toPath =
forall a b. a -> b -> a
Prelude.const ByteString
"/export-earth-observation-job"
instance Data.ToQuery ExportEarthObservationJob where
toQuery :: ExportEarthObservationJob -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data ExportEarthObservationJobResponse = ExportEarthObservationJobResponse'
{
ExportEarthObservationJobResponse -> Maybe Bool
exportSourceImages :: Prelude.Maybe Prelude.Bool,
ExportEarthObservationJobResponse -> Int
httpStatus :: Prelude.Int,
ExportEarthObservationJobResponse -> Text
arn :: Prelude.Text,
ExportEarthObservationJobResponse -> POSIX
creationTime :: Data.POSIX,
ExportEarthObservationJobResponse -> Text
executionRoleArn :: Prelude.Text,
ExportEarthObservationJobResponse
-> EarthObservationJobExportStatus
exportStatus :: EarthObservationJobExportStatus,
ExportEarthObservationJobResponse -> OutputConfigInput
outputConfig :: OutputConfigInput
}
deriving (ExportEarthObservationJobResponse
-> ExportEarthObservationJobResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExportEarthObservationJobResponse
-> ExportEarthObservationJobResponse -> Bool
$c/= :: ExportEarthObservationJobResponse
-> ExportEarthObservationJobResponse -> Bool
== :: ExportEarthObservationJobResponse
-> ExportEarthObservationJobResponse -> Bool
$c== :: ExportEarthObservationJobResponse
-> ExportEarthObservationJobResponse -> Bool
Prelude.Eq, ReadPrec [ExportEarthObservationJobResponse]
ReadPrec ExportEarthObservationJobResponse
Int -> ReadS ExportEarthObservationJobResponse
ReadS [ExportEarthObservationJobResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ExportEarthObservationJobResponse]
$creadListPrec :: ReadPrec [ExportEarthObservationJobResponse]
readPrec :: ReadPrec ExportEarthObservationJobResponse
$creadPrec :: ReadPrec ExportEarthObservationJobResponse
readList :: ReadS [ExportEarthObservationJobResponse]
$creadList :: ReadS [ExportEarthObservationJobResponse]
readsPrec :: Int -> ReadS ExportEarthObservationJobResponse
$creadsPrec :: Int -> ReadS ExportEarthObservationJobResponse
Prelude.Read, Int -> ExportEarthObservationJobResponse -> ShowS
[ExportEarthObservationJobResponse] -> ShowS
ExportEarthObservationJobResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExportEarthObservationJobResponse] -> ShowS
$cshowList :: [ExportEarthObservationJobResponse] -> ShowS
show :: ExportEarthObservationJobResponse -> String
$cshow :: ExportEarthObservationJobResponse -> String
showsPrec :: Int -> ExportEarthObservationJobResponse -> ShowS
$cshowsPrec :: Int -> ExportEarthObservationJobResponse -> ShowS
Prelude.Show, forall x.
Rep ExportEarthObservationJobResponse x
-> ExportEarthObservationJobResponse
forall x.
ExportEarthObservationJobResponse
-> Rep ExportEarthObservationJobResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ExportEarthObservationJobResponse x
-> ExportEarthObservationJobResponse
$cfrom :: forall x.
ExportEarthObservationJobResponse
-> Rep ExportEarthObservationJobResponse x
Prelude.Generic)
newExportEarthObservationJobResponse ::
Prelude.Int ->
Prelude.Text ->
Prelude.UTCTime ->
Prelude.Text ->
EarthObservationJobExportStatus ->
OutputConfigInput ->
ExportEarthObservationJobResponse
newExportEarthObservationJobResponse :: Int
-> Text
-> UTCTime
-> Text
-> EarthObservationJobExportStatus
-> OutputConfigInput
-> ExportEarthObservationJobResponse
newExportEarthObservationJobResponse
Int
pHttpStatus_
Text
pArn_
UTCTime
pCreationTime_
Text
pExecutionRoleArn_
EarthObservationJobExportStatus
pExportStatus_
OutputConfigInput
pOutputConfig_ =
ExportEarthObservationJobResponse'
{ $sel:exportSourceImages:ExportEarthObservationJobResponse' :: Maybe Bool
exportSourceImages =
forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:ExportEarthObservationJobResponse' :: Int
httpStatus = Int
pHttpStatus_,
$sel:arn:ExportEarthObservationJobResponse' :: Text
arn = Text
pArn_,
$sel:creationTime:ExportEarthObservationJobResponse' :: POSIX
creationTime =
forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pCreationTime_,
$sel:executionRoleArn:ExportEarthObservationJobResponse' :: Text
executionRoleArn = Text
pExecutionRoleArn_,
$sel:exportStatus:ExportEarthObservationJobResponse' :: EarthObservationJobExportStatus
exportStatus = EarthObservationJobExportStatus
pExportStatus_,
$sel:outputConfig:ExportEarthObservationJobResponse' :: OutputConfigInput
outputConfig = OutputConfigInput
pOutputConfig_
}
exportEarthObservationJobResponse_exportSourceImages :: Lens.Lens' ExportEarthObservationJobResponse (Prelude.Maybe Prelude.Bool)
exportEarthObservationJobResponse_exportSourceImages :: Lens' ExportEarthObservationJobResponse (Maybe Bool)
exportEarthObservationJobResponse_exportSourceImages = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportEarthObservationJobResponse' {Maybe Bool
exportSourceImages :: Maybe Bool
$sel:exportSourceImages:ExportEarthObservationJobResponse' :: ExportEarthObservationJobResponse -> Maybe Bool
exportSourceImages} -> Maybe Bool
exportSourceImages) (\s :: ExportEarthObservationJobResponse
s@ExportEarthObservationJobResponse' {} Maybe Bool
a -> ExportEarthObservationJobResponse
s {$sel:exportSourceImages:ExportEarthObservationJobResponse' :: Maybe Bool
exportSourceImages = Maybe Bool
a} :: ExportEarthObservationJobResponse)
exportEarthObservationJobResponse_httpStatus :: Lens.Lens' ExportEarthObservationJobResponse Prelude.Int
exportEarthObservationJobResponse_httpStatus :: Lens' ExportEarthObservationJobResponse Int
exportEarthObservationJobResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportEarthObservationJobResponse' {Int
httpStatus :: Int
$sel:httpStatus:ExportEarthObservationJobResponse' :: ExportEarthObservationJobResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ExportEarthObservationJobResponse
s@ExportEarthObservationJobResponse' {} Int
a -> ExportEarthObservationJobResponse
s {$sel:httpStatus:ExportEarthObservationJobResponse' :: Int
httpStatus = Int
a} :: ExportEarthObservationJobResponse)
exportEarthObservationJobResponse_arn :: Lens.Lens' ExportEarthObservationJobResponse Prelude.Text
exportEarthObservationJobResponse_arn :: Lens' ExportEarthObservationJobResponse Text
exportEarthObservationJobResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportEarthObservationJobResponse' {Text
arn :: Text
$sel:arn:ExportEarthObservationJobResponse' :: ExportEarthObservationJobResponse -> Text
arn} -> Text
arn) (\s :: ExportEarthObservationJobResponse
s@ExportEarthObservationJobResponse' {} Text
a -> ExportEarthObservationJobResponse
s {$sel:arn:ExportEarthObservationJobResponse' :: Text
arn = Text
a} :: ExportEarthObservationJobResponse)
exportEarthObservationJobResponse_creationTime :: Lens.Lens' ExportEarthObservationJobResponse Prelude.UTCTime
exportEarthObservationJobResponse_creationTime :: Lens' ExportEarthObservationJobResponse UTCTime
exportEarthObservationJobResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportEarthObservationJobResponse' {POSIX
creationTime :: POSIX
$sel:creationTime:ExportEarthObservationJobResponse' :: ExportEarthObservationJobResponse -> POSIX
creationTime} -> POSIX
creationTime) (\s :: ExportEarthObservationJobResponse
s@ExportEarthObservationJobResponse' {} POSIX
a -> ExportEarthObservationJobResponse
s {$sel:creationTime:ExportEarthObservationJobResponse' :: POSIX
creationTime = POSIX
a} :: ExportEarthObservationJobResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time
exportEarthObservationJobResponse_executionRoleArn :: Lens.Lens' ExportEarthObservationJobResponse Prelude.Text
exportEarthObservationJobResponse_executionRoleArn :: Lens' ExportEarthObservationJobResponse Text
exportEarthObservationJobResponse_executionRoleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportEarthObservationJobResponse' {Text
executionRoleArn :: Text
$sel:executionRoleArn:ExportEarthObservationJobResponse' :: ExportEarthObservationJobResponse -> Text
executionRoleArn} -> Text
executionRoleArn) (\s :: ExportEarthObservationJobResponse
s@ExportEarthObservationJobResponse' {} Text
a -> ExportEarthObservationJobResponse
s {$sel:executionRoleArn:ExportEarthObservationJobResponse' :: Text
executionRoleArn = Text
a} :: ExportEarthObservationJobResponse)
exportEarthObservationJobResponse_exportStatus :: Lens.Lens' ExportEarthObservationJobResponse EarthObservationJobExportStatus
exportEarthObservationJobResponse_exportStatus :: Lens'
ExportEarthObservationJobResponse EarthObservationJobExportStatus
exportEarthObservationJobResponse_exportStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportEarthObservationJobResponse' {EarthObservationJobExportStatus
exportStatus :: EarthObservationJobExportStatus
$sel:exportStatus:ExportEarthObservationJobResponse' :: ExportEarthObservationJobResponse
-> EarthObservationJobExportStatus
exportStatus} -> EarthObservationJobExportStatus
exportStatus) (\s :: ExportEarthObservationJobResponse
s@ExportEarthObservationJobResponse' {} EarthObservationJobExportStatus
a -> ExportEarthObservationJobResponse
s {$sel:exportStatus:ExportEarthObservationJobResponse' :: EarthObservationJobExportStatus
exportStatus = EarthObservationJobExportStatus
a} :: ExportEarthObservationJobResponse)
exportEarthObservationJobResponse_outputConfig :: Lens.Lens' ExportEarthObservationJobResponse OutputConfigInput
exportEarthObservationJobResponse_outputConfig :: Lens' ExportEarthObservationJobResponse OutputConfigInput
exportEarthObservationJobResponse_outputConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportEarthObservationJobResponse' {OutputConfigInput
outputConfig :: OutputConfigInput
$sel:outputConfig:ExportEarthObservationJobResponse' :: ExportEarthObservationJobResponse -> OutputConfigInput
outputConfig} -> OutputConfigInput
outputConfig) (\s :: ExportEarthObservationJobResponse
s@ExportEarthObservationJobResponse' {} OutputConfigInput
a -> ExportEarthObservationJobResponse
s {$sel:outputConfig:ExportEarthObservationJobResponse' :: OutputConfigInput
outputConfig = OutputConfigInput
a} :: ExportEarthObservationJobResponse)
instance
Prelude.NFData
ExportEarthObservationJobResponse
where
rnf :: ExportEarthObservationJobResponse -> ()
rnf ExportEarthObservationJobResponse' {Int
Maybe Bool
Text
POSIX
EarthObservationJobExportStatus
OutputConfigInput
outputConfig :: OutputConfigInput
exportStatus :: EarthObservationJobExportStatus
executionRoleArn :: Text
creationTime :: POSIX
arn :: Text
httpStatus :: Int
exportSourceImages :: Maybe Bool
$sel:outputConfig:ExportEarthObservationJobResponse' :: ExportEarthObservationJobResponse -> OutputConfigInput
$sel:exportStatus:ExportEarthObservationJobResponse' :: ExportEarthObservationJobResponse
-> EarthObservationJobExportStatus
$sel:executionRoleArn:ExportEarthObservationJobResponse' :: ExportEarthObservationJobResponse -> Text
$sel:creationTime:ExportEarthObservationJobResponse' :: ExportEarthObservationJobResponse -> POSIX
$sel:arn:ExportEarthObservationJobResponse' :: ExportEarthObservationJobResponse -> Text
$sel:httpStatus:ExportEarthObservationJobResponse' :: ExportEarthObservationJobResponse -> Int
$sel:exportSourceImages:ExportEarthObservationJobResponse' :: ExportEarthObservationJobResponse -> Maybe Bool
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
exportSourceImages
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 POSIX
creationTime
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
executionRoleArn
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf EarthObservationJobExportStatus
exportStatus
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf OutputConfigInput
outputConfig