{-# 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.Personalize.CreateBatchSegmentJob
(
CreateBatchSegmentJob (..),
newCreateBatchSegmentJob,
createBatchSegmentJob_filterArn,
createBatchSegmentJob_numResults,
createBatchSegmentJob_tags,
createBatchSegmentJob_jobName,
createBatchSegmentJob_solutionVersionArn,
createBatchSegmentJob_jobInput,
createBatchSegmentJob_jobOutput,
createBatchSegmentJob_roleArn,
CreateBatchSegmentJobResponse (..),
newCreateBatchSegmentJobResponse,
createBatchSegmentJobResponse_batchSegmentJobArn,
createBatchSegmentJobResponse_httpStatus,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Personalize.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
data CreateBatchSegmentJob = CreateBatchSegmentJob'
{
CreateBatchSegmentJob -> Maybe Text
filterArn :: Prelude.Maybe Prelude.Text,
CreateBatchSegmentJob -> Maybe Int
numResults :: Prelude.Maybe Prelude.Int,
CreateBatchSegmentJob -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
CreateBatchSegmentJob -> Text
jobName :: Prelude.Text,
CreateBatchSegmentJob -> Text
solutionVersionArn :: Prelude.Text,
CreateBatchSegmentJob -> BatchSegmentJobInput
jobInput :: BatchSegmentJobInput,
CreateBatchSegmentJob -> BatchSegmentJobOutput
jobOutput :: BatchSegmentJobOutput,
CreateBatchSegmentJob -> Text
roleArn :: Prelude.Text
}
deriving (CreateBatchSegmentJob -> CreateBatchSegmentJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateBatchSegmentJob -> CreateBatchSegmentJob -> Bool
$c/= :: CreateBatchSegmentJob -> CreateBatchSegmentJob -> Bool
== :: CreateBatchSegmentJob -> CreateBatchSegmentJob -> Bool
$c== :: CreateBatchSegmentJob -> CreateBatchSegmentJob -> Bool
Prelude.Eq, ReadPrec [CreateBatchSegmentJob]
ReadPrec CreateBatchSegmentJob
Int -> ReadS CreateBatchSegmentJob
ReadS [CreateBatchSegmentJob]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateBatchSegmentJob]
$creadListPrec :: ReadPrec [CreateBatchSegmentJob]
readPrec :: ReadPrec CreateBatchSegmentJob
$creadPrec :: ReadPrec CreateBatchSegmentJob
readList :: ReadS [CreateBatchSegmentJob]
$creadList :: ReadS [CreateBatchSegmentJob]
readsPrec :: Int -> ReadS CreateBatchSegmentJob
$creadsPrec :: Int -> ReadS CreateBatchSegmentJob
Prelude.Read, Int -> CreateBatchSegmentJob -> ShowS
[CreateBatchSegmentJob] -> ShowS
CreateBatchSegmentJob -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateBatchSegmentJob] -> ShowS
$cshowList :: [CreateBatchSegmentJob] -> ShowS
show :: CreateBatchSegmentJob -> String
$cshow :: CreateBatchSegmentJob -> String
showsPrec :: Int -> CreateBatchSegmentJob -> ShowS
$cshowsPrec :: Int -> CreateBatchSegmentJob -> ShowS
Prelude.Show, forall x. Rep CreateBatchSegmentJob x -> CreateBatchSegmentJob
forall x. CreateBatchSegmentJob -> Rep CreateBatchSegmentJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateBatchSegmentJob x -> CreateBatchSegmentJob
$cfrom :: forall x. CreateBatchSegmentJob -> Rep CreateBatchSegmentJob x
Prelude.Generic)
newCreateBatchSegmentJob ::
Prelude.Text ->
Prelude.Text ->
BatchSegmentJobInput ->
BatchSegmentJobOutput ->
Prelude.Text ->
CreateBatchSegmentJob
newCreateBatchSegmentJob :: Text
-> Text
-> BatchSegmentJobInput
-> BatchSegmentJobOutput
-> Text
-> CreateBatchSegmentJob
newCreateBatchSegmentJob
Text
pJobName_
Text
pSolutionVersionArn_
BatchSegmentJobInput
pJobInput_
BatchSegmentJobOutput
pJobOutput_
Text
pRoleArn_ =
CreateBatchSegmentJob'
{ $sel:filterArn:CreateBatchSegmentJob' :: Maybe Text
filterArn = forall a. Maybe a
Prelude.Nothing,
$sel:numResults:CreateBatchSegmentJob' :: Maybe Int
numResults = forall a. Maybe a
Prelude.Nothing,
$sel:tags:CreateBatchSegmentJob' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
$sel:jobName:CreateBatchSegmentJob' :: Text
jobName = Text
pJobName_,
$sel:solutionVersionArn:CreateBatchSegmentJob' :: Text
solutionVersionArn = Text
pSolutionVersionArn_,
$sel:jobInput:CreateBatchSegmentJob' :: BatchSegmentJobInput
jobInput = BatchSegmentJobInput
pJobInput_,
$sel:jobOutput:CreateBatchSegmentJob' :: BatchSegmentJobOutput
jobOutput = BatchSegmentJobOutput
pJobOutput_,
$sel:roleArn:CreateBatchSegmentJob' :: Text
roleArn = Text
pRoleArn_
}
createBatchSegmentJob_filterArn :: Lens.Lens' CreateBatchSegmentJob (Prelude.Maybe Prelude.Text)
createBatchSegmentJob_filterArn :: Lens' CreateBatchSegmentJob (Maybe Text)
createBatchSegmentJob_filterArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateBatchSegmentJob' {Maybe Text
filterArn :: Maybe Text
$sel:filterArn:CreateBatchSegmentJob' :: CreateBatchSegmentJob -> Maybe Text
filterArn} -> Maybe Text
filterArn) (\s :: CreateBatchSegmentJob
s@CreateBatchSegmentJob' {} Maybe Text
a -> CreateBatchSegmentJob
s {$sel:filterArn:CreateBatchSegmentJob' :: Maybe Text
filterArn = Maybe Text
a} :: CreateBatchSegmentJob)
createBatchSegmentJob_numResults :: Lens.Lens' CreateBatchSegmentJob (Prelude.Maybe Prelude.Int)
createBatchSegmentJob_numResults :: Lens' CreateBatchSegmentJob (Maybe Int)
createBatchSegmentJob_numResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateBatchSegmentJob' {Maybe Int
numResults :: Maybe Int
$sel:numResults:CreateBatchSegmentJob' :: CreateBatchSegmentJob -> Maybe Int
numResults} -> Maybe Int
numResults) (\s :: CreateBatchSegmentJob
s@CreateBatchSegmentJob' {} Maybe Int
a -> CreateBatchSegmentJob
s {$sel:numResults:CreateBatchSegmentJob' :: Maybe Int
numResults = Maybe Int
a} :: CreateBatchSegmentJob)
createBatchSegmentJob_tags :: Lens.Lens' CreateBatchSegmentJob (Prelude.Maybe [Tag])
createBatchSegmentJob_tags :: Lens' CreateBatchSegmentJob (Maybe [Tag])
createBatchSegmentJob_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateBatchSegmentJob' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreateBatchSegmentJob' :: CreateBatchSegmentJob -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreateBatchSegmentJob
s@CreateBatchSegmentJob' {} Maybe [Tag]
a -> CreateBatchSegmentJob
s {$sel:tags:CreateBatchSegmentJob' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: CreateBatchSegmentJob) 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
createBatchSegmentJob_jobName :: Lens.Lens' CreateBatchSegmentJob Prelude.Text
createBatchSegmentJob_jobName :: Lens' CreateBatchSegmentJob Text
createBatchSegmentJob_jobName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateBatchSegmentJob' {Text
jobName :: Text
$sel:jobName:CreateBatchSegmentJob' :: CreateBatchSegmentJob -> Text
jobName} -> Text
jobName) (\s :: CreateBatchSegmentJob
s@CreateBatchSegmentJob' {} Text
a -> CreateBatchSegmentJob
s {$sel:jobName:CreateBatchSegmentJob' :: Text
jobName = Text
a} :: CreateBatchSegmentJob)
createBatchSegmentJob_solutionVersionArn :: Lens.Lens' CreateBatchSegmentJob Prelude.Text
createBatchSegmentJob_solutionVersionArn :: Lens' CreateBatchSegmentJob Text
createBatchSegmentJob_solutionVersionArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateBatchSegmentJob' {Text
solutionVersionArn :: Text
$sel:solutionVersionArn:CreateBatchSegmentJob' :: CreateBatchSegmentJob -> Text
solutionVersionArn} -> Text
solutionVersionArn) (\s :: CreateBatchSegmentJob
s@CreateBatchSegmentJob' {} Text
a -> CreateBatchSegmentJob
s {$sel:solutionVersionArn:CreateBatchSegmentJob' :: Text
solutionVersionArn = Text
a} :: CreateBatchSegmentJob)
createBatchSegmentJob_jobInput :: Lens.Lens' CreateBatchSegmentJob BatchSegmentJobInput
createBatchSegmentJob_jobInput :: Lens' CreateBatchSegmentJob BatchSegmentJobInput
createBatchSegmentJob_jobInput = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateBatchSegmentJob' {BatchSegmentJobInput
jobInput :: BatchSegmentJobInput
$sel:jobInput:CreateBatchSegmentJob' :: CreateBatchSegmentJob -> BatchSegmentJobInput
jobInput} -> BatchSegmentJobInput
jobInput) (\s :: CreateBatchSegmentJob
s@CreateBatchSegmentJob' {} BatchSegmentJobInput
a -> CreateBatchSegmentJob
s {$sel:jobInput:CreateBatchSegmentJob' :: BatchSegmentJobInput
jobInput = BatchSegmentJobInput
a} :: CreateBatchSegmentJob)
createBatchSegmentJob_jobOutput :: Lens.Lens' CreateBatchSegmentJob BatchSegmentJobOutput
createBatchSegmentJob_jobOutput :: Lens' CreateBatchSegmentJob BatchSegmentJobOutput
createBatchSegmentJob_jobOutput = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateBatchSegmentJob' {BatchSegmentJobOutput
jobOutput :: BatchSegmentJobOutput
$sel:jobOutput:CreateBatchSegmentJob' :: CreateBatchSegmentJob -> BatchSegmentJobOutput
jobOutput} -> BatchSegmentJobOutput
jobOutput) (\s :: CreateBatchSegmentJob
s@CreateBatchSegmentJob' {} BatchSegmentJobOutput
a -> CreateBatchSegmentJob
s {$sel:jobOutput:CreateBatchSegmentJob' :: BatchSegmentJobOutput
jobOutput = BatchSegmentJobOutput
a} :: CreateBatchSegmentJob)
createBatchSegmentJob_roleArn :: Lens.Lens' CreateBatchSegmentJob Prelude.Text
createBatchSegmentJob_roleArn :: Lens' CreateBatchSegmentJob Text
createBatchSegmentJob_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateBatchSegmentJob' {Text
roleArn :: Text
$sel:roleArn:CreateBatchSegmentJob' :: CreateBatchSegmentJob -> Text
roleArn} -> Text
roleArn) (\s :: CreateBatchSegmentJob
s@CreateBatchSegmentJob' {} Text
a -> CreateBatchSegmentJob
s {$sel:roleArn:CreateBatchSegmentJob' :: Text
roleArn = Text
a} :: CreateBatchSegmentJob)
instance Core.AWSRequest CreateBatchSegmentJob where
type
AWSResponse CreateBatchSegmentJob =
CreateBatchSegmentJobResponse
request :: (Service -> Service)
-> CreateBatchSegmentJob -> Request CreateBatchSegmentJob
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 CreateBatchSegmentJob
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse CreateBatchSegmentJob)))
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 Text -> Int -> CreateBatchSegmentJobResponse
CreateBatchSegmentJobResponse'
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
"batchSegmentJobArn")
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 CreateBatchSegmentJob where
hashWithSalt :: Int -> CreateBatchSegmentJob -> Int
hashWithSalt Int
_salt CreateBatchSegmentJob' {Maybe Int
Maybe [Tag]
Maybe Text
Text
BatchSegmentJobOutput
BatchSegmentJobInput
roleArn :: Text
jobOutput :: BatchSegmentJobOutput
jobInput :: BatchSegmentJobInput
solutionVersionArn :: Text
jobName :: Text
tags :: Maybe [Tag]
numResults :: Maybe Int
filterArn :: Maybe Text
$sel:roleArn:CreateBatchSegmentJob' :: CreateBatchSegmentJob -> Text
$sel:jobOutput:CreateBatchSegmentJob' :: CreateBatchSegmentJob -> BatchSegmentJobOutput
$sel:jobInput:CreateBatchSegmentJob' :: CreateBatchSegmentJob -> BatchSegmentJobInput
$sel:solutionVersionArn:CreateBatchSegmentJob' :: CreateBatchSegmentJob -> Text
$sel:jobName:CreateBatchSegmentJob' :: CreateBatchSegmentJob -> Text
$sel:tags:CreateBatchSegmentJob' :: CreateBatchSegmentJob -> Maybe [Tag]
$sel:numResults:CreateBatchSegmentJob' :: CreateBatchSegmentJob -> Maybe Int
$sel:filterArn:CreateBatchSegmentJob' :: CreateBatchSegmentJob -> Maybe Text
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
filterArn
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
numResults
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
jobName
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
solutionVersionArn
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` BatchSegmentJobInput
jobInput
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` BatchSegmentJobOutput
jobOutput
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
roleArn
instance Prelude.NFData CreateBatchSegmentJob where
rnf :: CreateBatchSegmentJob -> ()
rnf CreateBatchSegmentJob' {Maybe Int
Maybe [Tag]
Maybe Text
Text
BatchSegmentJobOutput
BatchSegmentJobInput
roleArn :: Text
jobOutput :: BatchSegmentJobOutput
jobInput :: BatchSegmentJobInput
solutionVersionArn :: Text
jobName :: Text
tags :: Maybe [Tag]
numResults :: Maybe Int
filterArn :: Maybe Text
$sel:roleArn:CreateBatchSegmentJob' :: CreateBatchSegmentJob -> Text
$sel:jobOutput:CreateBatchSegmentJob' :: CreateBatchSegmentJob -> BatchSegmentJobOutput
$sel:jobInput:CreateBatchSegmentJob' :: CreateBatchSegmentJob -> BatchSegmentJobInput
$sel:solutionVersionArn:CreateBatchSegmentJob' :: CreateBatchSegmentJob -> Text
$sel:jobName:CreateBatchSegmentJob' :: CreateBatchSegmentJob -> Text
$sel:tags:CreateBatchSegmentJob' :: CreateBatchSegmentJob -> Maybe [Tag]
$sel:numResults:CreateBatchSegmentJob' :: CreateBatchSegmentJob -> Maybe Int
$sel:filterArn:CreateBatchSegmentJob' :: CreateBatchSegmentJob -> Maybe Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
filterArn
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
numResults
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
jobName
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
solutionVersionArn
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf BatchSegmentJobInput
jobInput
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf BatchSegmentJobOutput
jobOutput
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
roleArn
instance Data.ToHeaders CreateBatchSegmentJob where
toHeaders :: CreateBatchSegmentJob -> ResponseHeaders
toHeaders =
forall a b. a -> b -> a
Prelude.const
( forall a. Monoid a => [a] -> a
Prelude.mconcat
[ HeaderName
"X-Amz-Target"
forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"AmazonPersonalize.CreateBatchSegmentJob" ::
Prelude.ByteString
),
HeaderName
"Content-Type"
forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
Prelude.ByteString
)
]
)
instance Data.ToJSON CreateBatchSegmentJob where
toJSON :: CreateBatchSegmentJob -> Value
toJSON CreateBatchSegmentJob' {Maybe Int
Maybe [Tag]
Maybe Text
Text
BatchSegmentJobOutput
BatchSegmentJobInput
roleArn :: Text
jobOutput :: BatchSegmentJobOutput
jobInput :: BatchSegmentJobInput
solutionVersionArn :: Text
jobName :: Text
tags :: Maybe [Tag]
numResults :: Maybe Int
filterArn :: Maybe Text
$sel:roleArn:CreateBatchSegmentJob' :: CreateBatchSegmentJob -> Text
$sel:jobOutput:CreateBatchSegmentJob' :: CreateBatchSegmentJob -> BatchSegmentJobOutput
$sel:jobInput:CreateBatchSegmentJob' :: CreateBatchSegmentJob -> BatchSegmentJobInput
$sel:solutionVersionArn:CreateBatchSegmentJob' :: CreateBatchSegmentJob -> Text
$sel:jobName:CreateBatchSegmentJob' :: CreateBatchSegmentJob -> Text
$sel:tags:CreateBatchSegmentJob' :: CreateBatchSegmentJob -> Maybe [Tag]
$sel:numResults:CreateBatchSegmentJob' :: CreateBatchSegmentJob -> Maybe Int
$sel:filterArn:CreateBatchSegmentJob' :: CreateBatchSegmentJob -> Maybe Text
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ (Key
"filterArn" 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 Text
filterArn,
(Key
"numResults" 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 Int
numResults,
(Key
"tags" 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 [Tag]
tags,
forall a. a -> Maybe a
Prelude.Just (Key
"jobName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
jobName),
forall a. a -> Maybe a
Prelude.Just
(Key
"solutionVersionArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
solutionVersionArn),
forall a. a -> Maybe a
Prelude.Just (Key
"jobInput" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= BatchSegmentJobInput
jobInput),
forall a. a -> Maybe a
Prelude.Just (Key
"jobOutput" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= BatchSegmentJobOutput
jobOutput),
forall a. a -> Maybe a
Prelude.Just (Key
"roleArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
roleArn)
]
)
instance Data.ToPath CreateBatchSegmentJob where
toPath :: CreateBatchSegmentJob -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery CreateBatchSegmentJob where
toQuery :: CreateBatchSegmentJob -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data CreateBatchSegmentJobResponse = CreateBatchSegmentJobResponse'
{
CreateBatchSegmentJobResponse -> Maybe Text
batchSegmentJobArn :: Prelude.Maybe Prelude.Text,
CreateBatchSegmentJobResponse -> Int
httpStatus :: Prelude.Int
}
deriving (CreateBatchSegmentJobResponse
-> CreateBatchSegmentJobResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateBatchSegmentJobResponse
-> CreateBatchSegmentJobResponse -> Bool
$c/= :: CreateBatchSegmentJobResponse
-> CreateBatchSegmentJobResponse -> Bool
== :: CreateBatchSegmentJobResponse
-> CreateBatchSegmentJobResponse -> Bool
$c== :: CreateBatchSegmentJobResponse
-> CreateBatchSegmentJobResponse -> Bool
Prelude.Eq, ReadPrec [CreateBatchSegmentJobResponse]
ReadPrec CreateBatchSegmentJobResponse
Int -> ReadS CreateBatchSegmentJobResponse
ReadS [CreateBatchSegmentJobResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateBatchSegmentJobResponse]
$creadListPrec :: ReadPrec [CreateBatchSegmentJobResponse]
readPrec :: ReadPrec CreateBatchSegmentJobResponse
$creadPrec :: ReadPrec CreateBatchSegmentJobResponse
readList :: ReadS [CreateBatchSegmentJobResponse]
$creadList :: ReadS [CreateBatchSegmentJobResponse]
readsPrec :: Int -> ReadS CreateBatchSegmentJobResponse
$creadsPrec :: Int -> ReadS CreateBatchSegmentJobResponse
Prelude.Read, Int -> CreateBatchSegmentJobResponse -> ShowS
[CreateBatchSegmentJobResponse] -> ShowS
CreateBatchSegmentJobResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateBatchSegmentJobResponse] -> ShowS
$cshowList :: [CreateBatchSegmentJobResponse] -> ShowS
show :: CreateBatchSegmentJobResponse -> String
$cshow :: CreateBatchSegmentJobResponse -> String
showsPrec :: Int -> CreateBatchSegmentJobResponse -> ShowS
$cshowsPrec :: Int -> CreateBatchSegmentJobResponse -> ShowS
Prelude.Show, forall x.
Rep CreateBatchSegmentJobResponse x
-> CreateBatchSegmentJobResponse
forall x.
CreateBatchSegmentJobResponse
-> Rep CreateBatchSegmentJobResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateBatchSegmentJobResponse x
-> CreateBatchSegmentJobResponse
$cfrom :: forall x.
CreateBatchSegmentJobResponse
-> Rep CreateBatchSegmentJobResponse x
Prelude.Generic)
newCreateBatchSegmentJobResponse ::
Prelude.Int ->
CreateBatchSegmentJobResponse
newCreateBatchSegmentJobResponse :: Int -> CreateBatchSegmentJobResponse
newCreateBatchSegmentJobResponse Int
pHttpStatus_ =
CreateBatchSegmentJobResponse'
{ $sel:batchSegmentJobArn:CreateBatchSegmentJobResponse' :: Maybe Text
batchSegmentJobArn =
forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:CreateBatchSegmentJobResponse' :: Int
httpStatus = Int
pHttpStatus_
}
createBatchSegmentJobResponse_batchSegmentJobArn :: Lens.Lens' CreateBatchSegmentJobResponse (Prelude.Maybe Prelude.Text)
createBatchSegmentJobResponse_batchSegmentJobArn :: Lens' CreateBatchSegmentJobResponse (Maybe Text)
createBatchSegmentJobResponse_batchSegmentJobArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateBatchSegmentJobResponse' {Maybe Text
batchSegmentJobArn :: Maybe Text
$sel:batchSegmentJobArn:CreateBatchSegmentJobResponse' :: CreateBatchSegmentJobResponse -> Maybe Text
batchSegmentJobArn} -> Maybe Text
batchSegmentJobArn) (\s :: CreateBatchSegmentJobResponse
s@CreateBatchSegmentJobResponse' {} Maybe Text
a -> CreateBatchSegmentJobResponse
s {$sel:batchSegmentJobArn:CreateBatchSegmentJobResponse' :: Maybe Text
batchSegmentJobArn = Maybe Text
a} :: CreateBatchSegmentJobResponse)
createBatchSegmentJobResponse_httpStatus :: Lens.Lens' CreateBatchSegmentJobResponse Prelude.Int
createBatchSegmentJobResponse_httpStatus :: Lens' CreateBatchSegmentJobResponse Int
createBatchSegmentJobResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateBatchSegmentJobResponse' {Int
httpStatus :: Int
$sel:httpStatus:CreateBatchSegmentJobResponse' :: CreateBatchSegmentJobResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: CreateBatchSegmentJobResponse
s@CreateBatchSegmentJobResponse' {} Int
a -> CreateBatchSegmentJobResponse
s {$sel:httpStatus:CreateBatchSegmentJobResponse' :: Int
httpStatus = Int
a} :: CreateBatchSegmentJobResponse)
instance Prelude.NFData CreateBatchSegmentJobResponse where
rnf :: CreateBatchSegmentJobResponse -> ()
rnf CreateBatchSegmentJobResponse' {Int
Maybe Text
httpStatus :: Int
batchSegmentJobArn :: Maybe Text
$sel:httpStatus:CreateBatchSegmentJobResponse' :: CreateBatchSegmentJobResponse -> Int
$sel:batchSegmentJobArn:CreateBatchSegmentJobResponse' :: CreateBatchSegmentJobResponse -> Maybe Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
batchSegmentJobArn
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus