{-# 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 #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.MigrationHub.DisassociateCreatedArtifact
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Disassociates a created artifact of an AWS resource with a migration
-- task performed by a migration tool that was previously associated. This
-- API has the following traits:
--
-- -   A migration user can call the @DisassociateCreatedArtifacts@
--     operation to disassociate a created AWS Artifact from a migration
--     task.
--
-- -   The created artifact name must be provided in ARN (Amazon Resource
--     Name) format which will contain information about type and region;
--     for example:
--     @arn:aws:ec2:us-east-1:488216288981:image\/ami-6d0ba87b@.
--
-- -   Examples of the AWS resource behind the created artifact are,
--     AMI\'s, EC2 instance, or RDS instance, etc.
module Amazonka.MigrationHub.DisassociateCreatedArtifact
  ( -- * Creating a Request
    DisassociateCreatedArtifact (..),
    newDisassociateCreatedArtifact,

    -- * Request Lenses
    disassociateCreatedArtifact_dryRun,
    disassociateCreatedArtifact_progressUpdateStream,
    disassociateCreatedArtifact_migrationTaskName,
    disassociateCreatedArtifact_createdArtifactName,

    -- * Destructuring the Response
    DisassociateCreatedArtifactResponse (..),
    newDisassociateCreatedArtifactResponse,

    -- * Response Lenses
    disassociateCreatedArtifactResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.MigrationHub.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newDisassociateCreatedArtifact' smart constructor.
data DisassociateCreatedArtifact = DisassociateCreatedArtifact'
  { -- | Optional boolean flag to indicate whether any effect should take place.
    -- Used to test if the caller has permission to make the call.
    DisassociateCreatedArtifact -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The name of the ProgressUpdateStream.
    DisassociateCreatedArtifact -> Text
progressUpdateStream :: Prelude.Text,
    -- | Unique identifier that references the migration task to be disassociated
    -- with the artifact. /Do not store personal data in this field./
    DisassociateCreatedArtifact -> Text
migrationTaskName :: Prelude.Text,
    -- | An ARN of the AWS resource related to the migration (e.g., AMI, EC2
    -- instance, RDS instance, etc.)
    DisassociateCreatedArtifact -> Text
createdArtifactName :: Prelude.Text
  }
  deriving (DisassociateCreatedArtifact -> DisassociateCreatedArtifact -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisassociateCreatedArtifact -> DisassociateCreatedArtifact -> Bool
$c/= :: DisassociateCreatedArtifact -> DisassociateCreatedArtifact -> Bool
== :: DisassociateCreatedArtifact -> DisassociateCreatedArtifact -> Bool
$c== :: DisassociateCreatedArtifact -> DisassociateCreatedArtifact -> Bool
Prelude.Eq, ReadPrec [DisassociateCreatedArtifact]
ReadPrec DisassociateCreatedArtifact
Int -> ReadS DisassociateCreatedArtifact
ReadS [DisassociateCreatedArtifact]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DisassociateCreatedArtifact]
$creadListPrec :: ReadPrec [DisassociateCreatedArtifact]
readPrec :: ReadPrec DisassociateCreatedArtifact
$creadPrec :: ReadPrec DisassociateCreatedArtifact
readList :: ReadS [DisassociateCreatedArtifact]
$creadList :: ReadS [DisassociateCreatedArtifact]
readsPrec :: Int -> ReadS DisassociateCreatedArtifact
$creadsPrec :: Int -> ReadS DisassociateCreatedArtifact
Prelude.Read, Int -> DisassociateCreatedArtifact -> ShowS
[DisassociateCreatedArtifact] -> ShowS
DisassociateCreatedArtifact -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisassociateCreatedArtifact] -> ShowS
$cshowList :: [DisassociateCreatedArtifact] -> ShowS
show :: DisassociateCreatedArtifact -> String
$cshow :: DisassociateCreatedArtifact -> String
showsPrec :: Int -> DisassociateCreatedArtifact -> ShowS
$cshowsPrec :: Int -> DisassociateCreatedArtifact -> ShowS
Prelude.Show, forall x.
Rep DisassociateCreatedArtifact x -> DisassociateCreatedArtifact
forall x.
DisassociateCreatedArtifact -> Rep DisassociateCreatedArtifact x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DisassociateCreatedArtifact x -> DisassociateCreatedArtifact
$cfrom :: forall x.
DisassociateCreatedArtifact -> Rep DisassociateCreatedArtifact x
Prelude.Generic)

-- |
-- Create a value of 'DisassociateCreatedArtifact' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'dryRun', 'disassociateCreatedArtifact_dryRun' - Optional boolean flag to indicate whether any effect should take place.
-- Used to test if the caller has permission to make the call.
--
-- 'progressUpdateStream', 'disassociateCreatedArtifact_progressUpdateStream' - The name of the ProgressUpdateStream.
--
-- 'migrationTaskName', 'disassociateCreatedArtifact_migrationTaskName' - Unique identifier that references the migration task to be disassociated
-- with the artifact. /Do not store personal data in this field./
--
-- 'createdArtifactName', 'disassociateCreatedArtifact_createdArtifactName' - An ARN of the AWS resource related to the migration (e.g., AMI, EC2
-- instance, RDS instance, etc.)
newDisassociateCreatedArtifact ::
  -- | 'progressUpdateStream'
  Prelude.Text ->
  -- | 'migrationTaskName'
  Prelude.Text ->
  -- | 'createdArtifactName'
  Prelude.Text ->
  DisassociateCreatedArtifact
newDisassociateCreatedArtifact :: Text -> Text -> Text -> DisassociateCreatedArtifact
newDisassociateCreatedArtifact
  Text
pProgressUpdateStream_
  Text
pMigrationTaskName_
  Text
pCreatedArtifactName_ =
    DisassociateCreatedArtifact'
      { $sel:dryRun:DisassociateCreatedArtifact' :: Maybe Bool
dryRun =
          forall a. Maybe a
Prelude.Nothing,
        $sel:progressUpdateStream:DisassociateCreatedArtifact' :: Text
progressUpdateStream = Text
pProgressUpdateStream_,
        $sel:migrationTaskName:DisassociateCreatedArtifact' :: Text
migrationTaskName = Text
pMigrationTaskName_,
        $sel:createdArtifactName:DisassociateCreatedArtifact' :: Text
createdArtifactName = Text
pCreatedArtifactName_
      }

-- | Optional boolean flag to indicate whether any effect should take place.
-- Used to test if the caller has permission to make the call.
disassociateCreatedArtifact_dryRun :: Lens.Lens' DisassociateCreatedArtifact (Prelude.Maybe Prelude.Bool)
disassociateCreatedArtifact_dryRun :: Lens' DisassociateCreatedArtifact (Maybe Bool)
disassociateCreatedArtifact_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateCreatedArtifact' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:DisassociateCreatedArtifact' :: DisassociateCreatedArtifact -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: DisassociateCreatedArtifact
s@DisassociateCreatedArtifact' {} Maybe Bool
a -> DisassociateCreatedArtifact
s {$sel:dryRun:DisassociateCreatedArtifact' :: Maybe Bool
dryRun = Maybe Bool
a} :: DisassociateCreatedArtifact)

-- | The name of the ProgressUpdateStream.
disassociateCreatedArtifact_progressUpdateStream :: Lens.Lens' DisassociateCreatedArtifact Prelude.Text
disassociateCreatedArtifact_progressUpdateStream :: Lens' DisassociateCreatedArtifact Text
disassociateCreatedArtifact_progressUpdateStream = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateCreatedArtifact' {Text
progressUpdateStream :: Text
$sel:progressUpdateStream:DisassociateCreatedArtifact' :: DisassociateCreatedArtifact -> Text
progressUpdateStream} -> Text
progressUpdateStream) (\s :: DisassociateCreatedArtifact
s@DisassociateCreatedArtifact' {} Text
a -> DisassociateCreatedArtifact
s {$sel:progressUpdateStream:DisassociateCreatedArtifact' :: Text
progressUpdateStream = Text
a} :: DisassociateCreatedArtifact)

-- | Unique identifier that references the migration task to be disassociated
-- with the artifact. /Do not store personal data in this field./
disassociateCreatedArtifact_migrationTaskName :: Lens.Lens' DisassociateCreatedArtifact Prelude.Text
disassociateCreatedArtifact_migrationTaskName :: Lens' DisassociateCreatedArtifact Text
disassociateCreatedArtifact_migrationTaskName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateCreatedArtifact' {Text
migrationTaskName :: Text
$sel:migrationTaskName:DisassociateCreatedArtifact' :: DisassociateCreatedArtifact -> Text
migrationTaskName} -> Text
migrationTaskName) (\s :: DisassociateCreatedArtifact
s@DisassociateCreatedArtifact' {} Text
a -> DisassociateCreatedArtifact
s {$sel:migrationTaskName:DisassociateCreatedArtifact' :: Text
migrationTaskName = Text
a} :: DisassociateCreatedArtifact)

-- | An ARN of the AWS resource related to the migration (e.g., AMI, EC2
-- instance, RDS instance, etc.)
disassociateCreatedArtifact_createdArtifactName :: Lens.Lens' DisassociateCreatedArtifact Prelude.Text
disassociateCreatedArtifact_createdArtifactName :: Lens' DisassociateCreatedArtifact Text
disassociateCreatedArtifact_createdArtifactName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateCreatedArtifact' {Text
createdArtifactName :: Text
$sel:createdArtifactName:DisassociateCreatedArtifact' :: DisassociateCreatedArtifact -> Text
createdArtifactName} -> Text
createdArtifactName) (\s :: DisassociateCreatedArtifact
s@DisassociateCreatedArtifact' {} Text
a -> DisassociateCreatedArtifact
s {$sel:createdArtifactName:DisassociateCreatedArtifact' :: Text
createdArtifactName = Text
a} :: DisassociateCreatedArtifact)

instance Core.AWSRequest DisassociateCreatedArtifact where
  type
    AWSResponse DisassociateCreatedArtifact =
      DisassociateCreatedArtifactResponse
  request :: (Service -> Service)
-> DisassociateCreatedArtifact
-> Request DisassociateCreatedArtifact
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 DisassociateCreatedArtifact
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DisassociateCreatedArtifact)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> DisassociateCreatedArtifactResponse
DisassociateCreatedArtifactResponse'
            forall (f :: * -> *) a b. Functor 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 DisassociateCreatedArtifact where
  hashWithSalt :: Int -> DisassociateCreatedArtifact -> Int
hashWithSalt Int
_salt DisassociateCreatedArtifact' {Maybe Bool
Text
createdArtifactName :: Text
migrationTaskName :: Text
progressUpdateStream :: Text
dryRun :: Maybe Bool
$sel:createdArtifactName:DisassociateCreatedArtifact' :: DisassociateCreatedArtifact -> Text
$sel:migrationTaskName:DisassociateCreatedArtifact' :: DisassociateCreatedArtifact -> Text
$sel:progressUpdateStream:DisassociateCreatedArtifact' :: DisassociateCreatedArtifact -> Text
$sel:dryRun:DisassociateCreatedArtifact' :: DisassociateCreatedArtifact -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
dryRun
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
progressUpdateStream
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
migrationTaskName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
createdArtifactName

instance Prelude.NFData DisassociateCreatedArtifact where
  rnf :: DisassociateCreatedArtifact -> ()
rnf DisassociateCreatedArtifact' {Maybe Bool
Text
createdArtifactName :: Text
migrationTaskName :: Text
progressUpdateStream :: Text
dryRun :: Maybe Bool
$sel:createdArtifactName:DisassociateCreatedArtifact' :: DisassociateCreatedArtifact -> Text
$sel:migrationTaskName:DisassociateCreatedArtifact' :: DisassociateCreatedArtifact -> Text
$sel:progressUpdateStream:DisassociateCreatedArtifact' :: DisassociateCreatedArtifact -> Text
$sel:dryRun:DisassociateCreatedArtifact' :: DisassociateCreatedArtifact -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
dryRun
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
progressUpdateStream
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
migrationTaskName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
createdArtifactName

instance Data.ToHeaders DisassociateCreatedArtifact where
  toHeaders :: DisassociateCreatedArtifact -> 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
"AWSMigrationHub.DisassociateCreatedArtifact" ::
                          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 DisassociateCreatedArtifact where
  toJSON :: DisassociateCreatedArtifact -> Value
toJSON DisassociateCreatedArtifact' {Maybe Bool
Text
createdArtifactName :: Text
migrationTaskName :: Text
progressUpdateStream :: Text
dryRun :: Maybe Bool
$sel:createdArtifactName:DisassociateCreatedArtifact' :: DisassociateCreatedArtifact -> Text
$sel:migrationTaskName:DisassociateCreatedArtifact' :: DisassociateCreatedArtifact -> Text
$sel:progressUpdateStream:DisassociateCreatedArtifact' :: DisassociateCreatedArtifact -> Text
$sel:dryRun:DisassociateCreatedArtifact' :: DisassociateCreatedArtifact -> Maybe Bool
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"DryRun" 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
dryRun,
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"ProgressUpdateStream"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
progressUpdateStream
              ),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"MigrationTaskName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
migrationTaskName),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"CreatedArtifactName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
createdArtifactName)
          ]
      )

instance Data.ToPath DisassociateCreatedArtifact where
  toPath :: DisassociateCreatedArtifact -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

instance Data.ToQuery DisassociateCreatedArtifact where
  toQuery :: DisassociateCreatedArtifact -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newDisassociateCreatedArtifactResponse' smart constructor.
data DisassociateCreatedArtifactResponse = DisassociateCreatedArtifactResponse'
  { -- | The response's http status code.
    DisassociateCreatedArtifactResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DisassociateCreatedArtifactResponse
-> DisassociateCreatedArtifactResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisassociateCreatedArtifactResponse
-> DisassociateCreatedArtifactResponse -> Bool
$c/= :: DisassociateCreatedArtifactResponse
-> DisassociateCreatedArtifactResponse -> Bool
== :: DisassociateCreatedArtifactResponse
-> DisassociateCreatedArtifactResponse -> Bool
$c== :: DisassociateCreatedArtifactResponse
-> DisassociateCreatedArtifactResponse -> Bool
Prelude.Eq, ReadPrec [DisassociateCreatedArtifactResponse]
ReadPrec DisassociateCreatedArtifactResponse
Int -> ReadS DisassociateCreatedArtifactResponse
ReadS [DisassociateCreatedArtifactResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DisassociateCreatedArtifactResponse]
$creadListPrec :: ReadPrec [DisassociateCreatedArtifactResponse]
readPrec :: ReadPrec DisassociateCreatedArtifactResponse
$creadPrec :: ReadPrec DisassociateCreatedArtifactResponse
readList :: ReadS [DisassociateCreatedArtifactResponse]
$creadList :: ReadS [DisassociateCreatedArtifactResponse]
readsPrec :: Int -> ReadS DisassociateCreatedArtifactResponse
$creadsPrec :: Int -> ReadS DisassociateCreatedArtifactResponse
Prelude.Read, Int -> DisassociateCreatedArtifactResponse -> ShowS
[DisassociateCreatedArtifactResponse] -> ShowS
DisassociateCreatedArtifactResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisassociateCreatedArtifactResponse] -> ShowS
$cshowList :: [DisassociateCreatedArtifactResponse] -> ShowS
show :: DisassociateCreatedArtifactResponse -> String
$cshow :: DisassociateCreatedArtifactResponse -> String
showsPrec :: Int -> DisassociateCreatedArtifactResponse -> ShowS
$cshowsPrec :: Int -> DisassociateCreatedArtifactResponse -> ShowS
Prelude.Show, forall x.
Rep DisassociateCreatedArtifactResponse x
-> DisassociateCreatedArtifactResponse
forall x.
DisassociateCreatedArtifactResponse
-> Rep DisassociateCreatedArtifactResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DisassociateCreatedArtifactResponse x
-> DisassociateCreatedArtifactResponse
$cfrom :: forall x.
DisassociateCreatedArtifactResponse
-> Rep DisassociateCreatedArtifactResponse x
Prelude.Generic)

-- |
-- Create a value of 'DisassociateCreatedArtifactResponse' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'httpStatus', 'disassociateCreatedArtifactResponse_httpStatus' - The response's http status code.
newDisassociateCreatedArtifactResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DisassociateCreatedArtifactResponse
newDisassociateCreatedArtifactResponse :: Int -> DisassociateCreatedArtifactResponse
newDisassociateCreatedArtifactResponse Int
pHttpStatus_ =
  DisassociateCreatedArtifactResponse'
    { $sel:httpStatus:DisassociateCreatedArtifactResponse' :: Int
httpStatus =
        Int
pHttpStatus_
    }

-- | The response's http status code.
disassociateCreatedArtifactResponse_httpStatus :: Lens.Lens' DisassociateCreatedArtifactResponse Prelude.Int
disassociateCreatedArtifactResponse_httpStatus :: Lens' DisassociateCreatedArtifactResponse Int
disassociateCreatedArtifactResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateCreatedArtifactResponse' {Int
httpStatus :: Int
$sel:httpStatus:DisassociateCreatedArtifactResponse' :: DisassociateCreatedArtifactResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DisassociateCreatedArtifactResponse
s@DisassociateCreatedArtifactResponse' {} Int
a -> DisassociateCreatedArtifactResponse
s {$sel:httpStatus:DisassociateCreatedArtifactResponse' :: Int
httpStatus = Int
a} :: DisassociateCreatedArtifactResponse)

instance
  Prelude.NFData
    DisassociateCreatedArtifactResponse
  where
  rnf :: DisassociateCreatedArtifactResponse -> ()
rnf DisassociateCreatedArtifactResponse' {Int
httpStatus :: Int
$sel:httpStatus:DisassociateCreatedArtifactResponse' :: DisassociateCreatedArtifactResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus