{-# 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.ServiceCatalog.CopyProduct
(
CopyProduct (..),
newCopyProduct,
copyProduct_acceptLanguage,
copyProduct_copyOptions,
copyProduct_sourceProvisioningArtifactIdentifiers,
copyProduct_targetProductId,
copyProduct_targetProductName,
copyProduct_sourceProductArn,
copyProduct_idempotencyToken,
CopyProductResponse (..),
newCopyProductResponse,
copyProductResponse_copyProductToken,
copyProductResponse_httpStatus,
)
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.ServiceCatalog.Types
data CopyProduct = CopyProduct'
{
CopyProduct -> Maybe Text
acceptLanguage :: Prelude.Maybe Prelude.Text,
CopyProduct -> Maybe [CopyOption]
copyOptions :: Prelude.Maybe [CopyOption],
CopyProduct
-> Maybe [HashMap ProvisioningArtifactPropertyName Text]
sourceProvisioningArtifactIdentifiers :: Prelude.Maybe [Prelude.HashMap ProvisioningArtifactPropertyName Prelude.Text],
CopyProduct -> Maybe Text
targetProductId :: Prelude.Maybe Prelude.Text,
CopyProduct -> Maybe Text
targetProductName :: Prelude.Maybe Prelude.Text,
CopyProduct -> Text
sourceProductArn :: Prelude.Text,
CopyProduct -> Text
idempotencyToken :: Prelude.Text
}
deriving (CopyProduct -> CopyProduct -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CopyProduct -> CopyProduct -> Bool
$c/= :: CopyProduct -> CopyProduct -> Bool
== :: CopyProduct -> CopyProduct -> Bool
$c== :: CopyProduct -> CopyProduct -> Bool
Prelude.Eq, ReadPrec [CopyProduct]
ReadPrec CopyProduct
Int -> ReadS CopyProduct
ReadS [CopyProduct]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CopyProduct]
$creadListPrec :: ReadPrec [CopyProduct]
readPrec :: ReadPrec CopyProduct
$creadPrec :: ReadPrec CopyProduct
readList :: ReadS [CopyProduct]
$creadList :: ReadS [CopyProduct]
readsPrec :: Int -> ReadS CopyProduct
$creadsPrec :: Int -> ReadS CopyProduct
Prelude.Read, Int -> CopyProduct -> ShowS
[CopyProduct] -> ShowS
CopyProduct -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CopyProduct] -> ShowS
$cshowList :: [CopyProduct] -> ShowS
show :: CopyProduct -> String
$cshow :: CopyProduct -> String
showsPrec :: Int -> CopyProduct -> ShowS
$cshowsPrec :: Int -> CopyProduct -> ShowS
Prelude.Show, forall x. Rep CopyProduct x -> CopyProduct
forall x. CopyProduct -> Rep CopyProduct x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CopyProduct x -> CopyProduct
$cfrom :: forall x. CopyProduct -> Rep CopyProduct x
Prelude.Generic)
newCopyProduct ::
Prelude.Text ->
Prelude.Text ->
CopyProduct
newCopyProduct :: Text -> Text -> CopyProduct
newCopyProduct Text
pSourceProductArn_ Text
pIdempotencyToken_ =
CopyProduct'
{ $sel:acceptLanguage:CopyProduct' :: Maybe Text
acceptLanguage = forall a. Maybe a
Prelude.Nothing,
$sel:copyOptions:CopyProduct' :: Maybe [CopyOption]
copyOptions = forall a. Maybe a
Prelude.Nothing,
$sel:sourceProvisioningArtifactIdentifiers:CopyProduct' :: Maybe [HashMap ProvisioningArtifactPropertyName Text]
sourceProvisioningArtifactIdentifiers =
forall a. Maybe a
Prelude.Nothing,
$sel:targetProductId:CopyProduct' :: Maybe Text
targetProductId = forall a. Maybe a
Prelude.Nothing,
$sel:targetProductName:CopyProduct' :: Maybe Text
targetProductName = forall a. Maybe a
Prelude.Nothing,
$sel:sourceProductArn:CopyProduct' :: Text
sourceProductArn = Text
pSourceProductArn_,
$sel:idempotencyToken:CopyProduct' :: Text
idempotencyToken = Text
pIdempotencyToken_
}
copyProduct_acceptLanguage :: Lens.Lens' CopyProduct (Prelude.Maybe Prelude.Text)
copyProduct_acceptLanguage :: Lens' CopyProduct (Maybe Text)
copyProduct_acceptLanguage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyProduct' {Maybe Text
acceptLanguage :: Maybe Text
$sel:acceptLanguage:CopyProduct' :: CopyProduct -> Maybe Text
acceptLanguage} -> Maybe Text
acceptLanguage) (\s :: CopyProduct
s@CopyProduct' {} Maybe Text
a -> CopyProduct
s {$sel:acceptLanguage:CopyProduct' :: Maybe Text
acceptLanguage = Maybe Text
a} :: CopyProduct)
copyProduct_copyOptions :: Lens.Lens' CopyProduct (Prelude.Maybe [CopyOption])
copyProduct_copyOptions :: Lens' CopyProduct (Maybe [CopyOption])
copyProduct_copyOptions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyProduct' {Maybe [CopyOption]
copyOptions :: Maybe [CopyOption]
$sel:copyOptions:CopyProduct' :: CopyProduct -> Maybe [CopyOption]
copyOptions} -> Maybe [CopyOption]
copyOptions) (\s :: CopyProduct
s@CopyProduct' {} Maybe [CopyOption]
a -> CopyProduct
s {$sel:copyOptions:CopyProduct' :: Maybe [CopyOption]
copyOptions = Maybe [CopyOption]
a} :: CopyProduct) 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
copyProduct_sourceProvisioningArtifactIdentifiers :: Lens.Lens' CopyProduct (Prelude.Maybe [Prelude.HashMap ProvisioningArtifactPropertyName Prelude.Text])
copyProduct_sourceProvisioningArtifactIdentifiers :: Lens'
CopyProduct (Maybe [HashMap ProvisioningArtifactPropertyName Text])
copyProduct_sourceProvisioningArtifactIdentifiers = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyProduct' {Maybe [HashMap ProvisioningArtifactPropertyName Text]
sourceProvisioningArtifactIdentifiers :: Maybe [HashMap ProvisioningArtifactPropertyName Text]
$sel:sourceProvisioningArtifactIdentifiers:CopyProduct' :: CopyProduct
-> Maybe [HashMap ProvisioningArtifactPropertyName Text]
sourceProvisioningArtifactIdentifiers} -> Maybe [HashMap ProvisioningArtifactPropertyName Text]
sourceProvisioningArtifactIdentifiers) (\s :: CopyProduct
s@CopyProduct' {} Maybe [HashMap ProvisioningArtifactPropertyName Text]
a -> CopyProduct
s {$sel:sourceProvisioningArtifactIdentifiers:CopyProduct' :: Maybe [HashMap ProvisioningArtifactPropertyName Text]
sourceProvisioningArtifactIdentifiers = Maybe [HashMap ProvisioningArtifactPropertyName Text]
a} :: CopyProduct) 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
copyProduct_targetProductId :: Lens.Lens' CopyProduct (Prelude.Maybe Prelude.Text)
copyProduct_targetProductId :: Lens' CopyProduct (Maybe Text)
copyProduct_targetProductId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyProduct' {Maybe Text
targetProductId :: Maybe Text
$sel:targetProductId:CopyProduct' :: CopyProduct -> Maybe Text
targetProductId} -> Maybe Text
targetProductId) (\s :: CopyProduct
s@CopyProduct' {} Maybe Text
a -> CopyProduct
s {$sel:targetProductId:CopyProduct' :: Maybe Text
targetProductId = Maybe Text
a} :: CopyProduct)
copyProduct_targetProductName :: Lens.Lens' CopyProduct (Prelude.Maybe Prelude.Text)
copyProduct_targetProductName :: Lens' CopyProduct (Maybe Text)
copyProduct_targetProductName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyProduct' {Maybe Text
targetProductName :: Maybe Text
$sel:targetProductName:CopyProduct' :: CopyProduct -> Maybe Text
targetProductName} -> Maybe Text
targetProductName) (\s :: CopyProduct
s@CopyProduct' {} Maybe Text
a -> CopyProduct
s {$sel:targetProductName:CopyProduct' :: Maybe Text
targetProductName = Maybe Text
a} :: CopyProduct)
copyProduct_sourceProductArn :: Lens.Lens' CopyProduct Prelude.Text
copyProduct_sourceProductArn :: Lens' CopyProduct Text
copyProduct_sourceProductArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyProduct' {Text
sourceProductArn :: Text
$sel:sourceProductArn:CopyProduct' :: CopyProduct -> Text
sourceProductArn} -> Text
sourceProductArn) (\s :: CopyProduct
s@CopyProduct' {} Text
a -> CopyProduct
s {$sel:sourceProductArn:CopyProduct' :: Text
sourceProductArn = Text
a} :: CopyProduct)
copyProduct_idempotencyToken :: Lens.Lens' CopyProduct Prelude.Text
copyProduct_idempotencyToken :: Lens' CopyProduct Text
copyProduct_idempotencyToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyProduct' {Text
idempotencyToken :: Text
$sel:idempotencyToken:CopyProduct' :: CopyProduct -> Text
idempotencyToken} -> Text
idempotencyToken) (\s :: CopyProduct
s@CopyProduct' {} Text
a -> CopyProduct
s {$sel:idempotencyToken:CopyProduct' :: Text
idempotencyToken = Text
a} :: CopyProduct)
instance Core.AWSRequest CopyProduct where
type AWSResponse CopyProduct = CopyProductResponse
request :: (Service -> Service) -> CopyProduct -> Request CopyProduct
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 CopyProduct
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CopyProduct)))
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 -> CopyProductResponse
CopyProductResponse'
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
"CopyProductToken")
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 CopyProduct where
hashWithSalt :: Int -> CopyProduct -> Int
hashWithSalt Int
_salt CopyProduct' {Maybe [HashMap ProvisioningArtifactPropertyName Text]
Maybe [CopyOption]
Maybe Text
Text
idempotencyToken :: Text
sourceProductArn :: Text
targetProductName :: Maybe Text
targetProductId :: Maybe Text
sourceProvisioningArtifactIdentifiers :: Maybe [HashMap ProvisioningArtifactPropertyName Text]
copyOptions :: Maybe [CopyOption]
acceptLanguage :: Maybe Text
$sel:idempotencyToken:CopyProduct' :: CopyProduct -> Text
$sel:sourceProductArn:CopyProduct' :: CopyProduct -> Text
$sel:targetProductName:CopyProduct' :: CopyProduct -> Maybe Text
$sel:targetProductId:CopyProduct' :: CopyProduct -> Maybe Text
$sel:sourceProvisioningArtifactIdentifiers:CopyProduct' :: CopyProduct
-> Maybe [HashMap ProvisioningArtifactPropertyName Text]
$sel:copyOptions:CopyProduct' :: CopyProduct -> Maybe [CopyOption]
$sel:acceptLanguage:CopyProduct' :: CopyProduct -> Maybe Text
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
acceptLanguage
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [CopyOption]
copyOptions
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [HashMap ProvisioningArtifactPropertyName Text]
sourceProvisioningArtifactIdentifiers
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
targetProductId
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
targetProductName
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
sourceProductArn
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
idempotencyToken
instance Prelude.NFData CopyProduct where
rnf :: CopyProduct -> ()
rnf CopyProduct' {Maybe [HashMap ProvisioningArtifactPropertyName Text]
Maybe [CopyOption]
Maybe Text
Text
idempotencyToken :: Text
sourceProductArn :: Text
targetProductName :: Maybe Text
targetProductId :: Maybe Text
sourceProvisioningArtifactIdentifiers :: Maybe [HashMap ProvisioningArtifactPropertyName Text]
copyOptions :: Maybe [CopyOption]
acceptLanguage :: Maybe Text
$sel:idempotencyToken:CopyProduct' :: CopyProduct -> Text
$sel:sourceProductArn:CopyProduct' :: CopyProduct -> Text
$sel:targetProductName:CopyProduct' :: CopyProduct -> Maybe Text
$sel:targetProductId:CopyProduct' :: CopyProduct -> Maybe Text
$sel:sourceProvisioningArtifactIdentifiers:CopyProduct' :: CopyProduct
-> Maybe [HashMap ProvisioningArtifactPropertyName Text]
$sel:copyOptions:CopyProduct' :: CopyProduct -> Maybe [CopyOption]
$sel:acceptLanguage:CopyProduct' :: CopyProduct -> Maybe Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
acceptLanguage
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [CopyOption]
copyOptions
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [HashMap ProvisioningArtifactPropertyName Text]
sourceProvisioningArtifactIdentifiers
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
targetProductId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
targetProductName
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
sourceProductArn
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
idempotencyToken
instance Data.ToHeaders CopyProduct where
toHeaders :: CopyProduct -> 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
"AWS242ServiceCatalogService.CopyProduct" ::
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 CopyProduct where
toJSON :: CopyProduct -> Value
toJSON CopyProduct' {Maybe [HashMap ProvisioningArtifactPropertyName Text]
Maybe [CopyOption]
Maybe Text
Text
idempotencyToken :: Text
sourceProductArn :: Text
targetProductName :: Maybe Text
targetProductId :: Maybe Text
sourceProvisioningArtifactIdentifiers :: Maybe [HashMap ProvisioningArtifactPropertyName Text]
copyOptions :: Maybe [CopyOption]
acceptLanguage :: Maybe Text
$sel:idempotencyToken:CopyProduct' :: CopyProduct -> Text
$sel:sourceProductArn:CopyProduct' :: CopyProduct -> Text
$sel:targetProductName:CopyProduct' :: CopyProduct -> Maybe Text
$sel:targetProductId:CopyProduct' :: CopyProduct -> Maybe Text
$sel:sourceProvisioningArtifactIdentifiers:CopyProduct' :: CopyProduct
-> Maybe [HashMap ProvisioningArtifactPropertyName Text]
$sel:copyOptions:CopyProduct' :: CopyProduct -> Maybe [CopyOption]
$sel:acceptLanguage:CopyProduct' :: CopyProduct -> Maybe Text
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ (Key
"AcceptLanguage" 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
acceptLanguage,
(Key
"CopyOptions" 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 [CopyOption]
copyOptions,
(Key
"SourceProvisioningArtifactIdentifiers" 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 [HashMap ProvisioningArtifactPropertyName Text]
sourceProvisioningArtifactIdentifiers,
(Key
"TargetProductId" 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
targetProductId,
(Key
"TargetProductName" 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
targetProductName,
forall a. a -> Maybe a
Prelude.Just
(Key
"SourceProductArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
sourceProductArn),
forall a. a -> Maybe a
Prelude.Just
(Key
"IdempotencyToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
idempotencyToken)
]
)
instance Data.ToPath CopyProduct where
toPath :: CopyProduct -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery CopyProduct where
toQuery :: CopyProduct -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data CopyProductResponse = CopyProductResponse'
{
CopyProductResponse -> Maybe Text
copyProductToken :: Prelude.Maybe Prelude.Text,
CopyProductResponse -> Int
httpStatus :: Prelude.Int
}
deriving (CopyProductResponse -> CopyProductResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CopyProductResponse -> CopyProductResponse -> Bool
$c/= :: CopyProductResponse -> CopyProductResponse -> Bool
== :: CopyProductResponse -> CopyProductResponse -> Bool
$c== :: CopyProductResponse -> CopyProductResponse -> Bool
Prelude.Eq, ReadPrec [CopyProductResponse]
ReadPrec CopyProductResponse
Int -> ReadS CopyProductResponse
ReadS [CopyProductResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CopyProductResponse]
$creadListPrec :: ReadPrec [CopyProductResponse]
readPrec :: ReadPrec CopyProductResponse
$creadPrec :: ReadPrec CopyProductResponse
readList :: ReadS [CopyProductResponse]
$creadList :: ReadS [CopyProductResponse]
readsPrec :: Int -> ReadS CopyProductResponse
$creadsPrec :: Int -> ReadS CopyProductResponse
Prelude.Read, Int -> CopyProductResponse -> ShowS
[CopyProductResponse] -> ShowS
CopyProductResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CopyProductResponse] -> ShowS
$cshowList :: [CopyProductResponse] -> ShowS
show :: CopyProductResponse -> String
$cshow :: CopyProductResponse -> String
showsPrec :: Int -> CopyProductResponse -> ShowS
$cshowsPrec :: Int -> CopyProductResponse -> ShowS
Prelude.Show, forall x. Rep CopyProductResponse x -> CopyProductResponse
forall x. CopyProductResponse -> Rep CopyProductResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CopyProductResponse x -> CopyProductResponse
$cfrom :: forall x. CopyProductResponse -> Rep CopyProductResponse x
Prelude.Generic)
newCopyProductResponse ::
Prelude.Int ->
CopyProductResponse
newCopyProductResponse :: Int -> CopyProductResponse
newCopyProductResponse Int
pHttpStatus_ =
CopyProductResponse'
{ $sel:copyProductToken:CopyProductResponse' :: Maybe Text
copyProductToken =
forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:CopyProductResponse' :: Int
httpStatus = Int
pHttpStatus_
}
copyProductResponse_copyProductToken :: Lens.Lens' CopyProductResponse (Prelude.Maybe Prelude.Text)
copyProductResponse_copyProductToken :: Lens' CopyProductResponse (Maybe Text)
copyProductResponse_copyProductToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyProductResponse' {Maybe Text
copyProductToken :: Maybe Text
$sel:copyProductToken:CopyProductResponse' :: CopyProductResponse -> Maybe Text
copyProductToken} -> Maybe Text
copyProductToken) (\s :: CopyProductResponse
s@CopyProductResponse' {} Maybe Text
a -> CopyProductResponse
s {$sel:copyProductToken:CopyProductResponse' :: Maybe Text
copyProductToken = Maybe Text
a} :: CopyProductResponse)
copyProductResponse_httpStatus :: Lens.Lens' CopyProductResponse Prelude.Int
copyProductResponse_httpStatus :: Lens' CopyProductResponse Int
copyProductResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyProductResponse' {Int
httpStatus :: Int
$sel:httpStatus:CopyProductResponse' :: CopyProductResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: CopyProductResponse
s@CopyProductResponse' {} Int
a -> CopyProductResponse
s {$sel:httpStatus:CopyProductResponse' :: Int
httpStatus = Int
a} :: CopyProductResponse)
instance Prelude.NFData CopyProductResponse where
rnf :: CopyProductResponse -> ()
rnf CopyProductResponse' {Int
Maybe Text
httpStatus :: Int
copyProductToken :: Maybe Text
$sel:httpStatus:CopyProductResponse' :: CopyProductResponse -> Int
$sel:copyProductToken:CopyProductResponse' :: CopyProductResponse -> Maybe Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
copyProductToken
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus