{-# 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.SSM.DeletePatchBaseline
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Deletes a patch baseline.
module Amazonka.SSM.DeletePatchBaseline
  ( -- * Creating a Request
    DeletePatchBaseline (..),
    newDeletePatchBaseline,

    -- * Request Lenses
    deletePatchBaseline_baselineId,

    -- * Destructuring the Response
    DeletePatchBaselineResponse (..),
    newDeletePatchBaselineResponse,

    -- * Response Lenses
    deletePatchBaselineResponse_baselineId,
    deletePatchBaselineResponse_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.SSM.Types

-- | /See:/ 'newDeletePatchBaseline' smart constructor.
data DeletePatchBaseline = DeletePatchBaseline'
  { -- | The ID of the patch baseline to delete.
    DeletePatchBaseline -> Text
baselineId :: Prelude.Text
  }
  deriving (DeletePatchBaseline -> DeletePatchBaseline -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeletePatchBaseline -> DeletePatchBaseline -> Bool
$c/= :: DeletePatchBaseline -> DeletePatchBaseline -> Bool
== :: DeletePatchBaseline -> DeletePatchBaseline -> Bool
$c== :: DeletePatchBaseline -> DeletePatchBaseline -> Bool
Prelude.Eq, ReadPrec [DeletePatchBaseline]
ReadPrec DeletePatchBaseline
Int -> ReadS DeletePatchBaseline
ReadS [DeletePatchBaseline]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeletePatchBaseline]
$creadListPrec :: ReadPrec [DeletePatchBaseline]
readPrec :: ReadPrec DeletePatchBaseline
$creadPrec :: ReadPrec DeletePatchBaseline
readList :: ReadS [DeletePatchBaseline]
$creadList :: ReadS [DeletePatchBaseline]
readsPrec :: Int -> ReadS DeletePatchBaseline
$creadsPrec :: Int -> ReadS DeletePatchBaseline
Prelude.Read, Int -> DeletePatchBaseline -> ShowS
[DeletePatchBaseline] -> ShowS
DeletePatchBaseline -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeletePatchBaseline] -> ShowS
$cshowList :: [DeletePatchBaseline] -> ShowS
show :: DeletePatchBaseline -> String
$cshow :: DeletePatchBaseline -> String
showsPrec :: Int -> DeletePatchBaseline -> ShowS
$cshowsPrec :: Int -> DeletePatchBaseline -> ShowS
Prelude.Show, forall x. Rep DeletePatchBaseline x -> DeletePatchBaseline
forall x. DeletePatchBaseline -> Rep DeletePatchBaseline x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeletePatchBaseline x -> DeletePatchBaseline
$cfrom :: forall x. DeletePatchBaseline -> Rep DeletePatchBaseline x
Prelude.Generic)

-- |
-- Create a value of 'DeletePatchBaseline' 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:
--
-- 'baselineId', 'deletePatchBaseline_baselineId' - The ID of the patch baseline to delete.
newDeletePatchBaseline ::
  -- | 'baselineId'
  Prelude.Text ->
  DeletePatchBaseline
newDeletePatchBaseline :: Text -> DeletePatchBaseline
newDeletePatchBaseline Text
pBaselineId_ =
  DeletePatchBaseline' {$sel:baselineId:DeletePatchBaseline' :: Text
baselineId = Text
pBaselineId_}

-- | The ID of the patch baseline to delete.
deletePatchBaseline_baselineId :: Lens.Lens' DeletePatchBaseline Prelude.Text
deletePatchBaseline_baselineId :: Lens' DeletePatchBaseline Text
deletePatchBaseline_baselineId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeletePatchBaseline' {Text
baselineId :: Text
$sel:baselineId:DeletePatchBaseline' :: DeletePatchBaseline -> Text
baselineId} -> Text
baselineId) (\s :: DeletePatchBaseline
s@DeletePatchBaseline' {} Text
a -> DeletePatchBaseline
s {$sel:baselineId:DeletePatchBaseline' :: Text
baselineId = Text
a} :: DeletePatchBaseline)

instance Core.AWSRequest DeletePatchBaseline where
  type
    AWSResponse DeletePatchBaseline =
      DeletePatchBaselineResponse
  request :: (Service -> Service)
-> DeletePatchBaseline -> Request DeletePatchBaseline
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 DeletePatchBaseline
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeletePatchBaseline)))
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 -> DeletePatchBaselineResponse
DeletePatchBaselineResponse'
            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
"BaselineId")
            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 DeletePatchBaseline where
  hashWithSalt :: Int -> DeletePatchBaseline -> Int
hashWithSalt Int
_salt DeletePatchBaseline' {Text
baselineId :: Text
$sel:baselineId:DeletePatchBaseline' :: DeletePatchBaseline -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
baselineId

instance Prelude.NFData DeletePatchBaseline where
  rnf :: DeletePatchBaseline -> ()
rnf DeletePatchBaseline' {Text
baselineId :: Text
$sel:baselineId:DeletePatchBaseline' :: DeletePatchBaseline -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
baselineId

instance Data.ToHeaders DeletePatchBaseline where
  toHeaders :: DeletePatchBaseline -> 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
"AmazonSSM.DeletePatchBaseline" ::
                          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 DeletePatchBaseline where
  toJSON :: DeletePatchBaseline -> Value
toJSON DeletePatchBaseline' {Text
baselineId :: Text
$sel:baselineId:DeletePatchBaseline' :: DeletePatchBaseline -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"BaselineId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
baselineId)]
      )

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

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

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

-- |
-- Create a value of 'DeletePatchBaselineResponse' 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:
--
-- 'baselineId', 'deletePatchBaselineResponse_baselineId' - The ID of the deleted patch baseline.
--
-- 'httpStatus', 'deletePatchBaselineResponse_httpStatus' - The response's http status code.
newDeletePatchBaselineResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeletePatchBaselineResponse
newDeletePatchBaselineResponse :: Int -> DeletePatchBaselineResponse
newDeletePatchBaselineResponse Int
pHttpStatus_ =
  DeletePatchBaselineResponse'
    { $sel:baselineId:DeletePatchBaselineResponse' :: Maybe Text
baselineId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeletePatchBaselineResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The ID of the deleted patch baseline.
deletePatchBaselineResponse_baselineId :: Lens.Lens' DeletePatchBaselineResponse (Prelude.Maybe Prelude.Text)
deletePatchBaselineResponse_baselineId :: Lens' DeletePatchBaselineResponse (Maybe Text)
deletePatchBaselineResponse_baselineId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeletePatchBaselineResponse' {Maybe Text
baselineId :: Maybe Text
$sel:baselineId:DeletePatchBaselineResponse' :: DeletePatchBaselineResponse -> Maybe Text
baselineId} -> Maybe Text
baselineId) (\s :: DeletePatchBaselineResponse
s@DeletePatchBaselineResponse' {} Maybe Text
a -> DeletePatchBaselineResponse
s {$sel:baselineId:DeletePatchBaselineResponse' :: Maybe Text
baselineId = Maybe Text
a} :: DeletePatchBaselineResponse)

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

instance Prelude.NFData DeletePatchBaselineResponse where
  rnf :: DeletePatchBaselineResponse -> ()
rnf DeletePatchBaselineResponse' {Int
Maybe Text
httpStatus :: Int
baselineId :: Maybe Text
$sel:httpStatus:DeletePatchBaselineResponse' :: DeletePatchBaselineResponse -> Int
$sel:baselineId:DeletePatchBaselineResponse' :: DeletePatchBaselineResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
baselineId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus