{-# 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.AccessAnalyzer.CancelPolicyGeneration
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Cancels the requested policy generation.
module Amazonka.AccessAnalyzer.CancelPolicyGeneration
  ( -- * Creating a Request
    CancelPolicyGeneration (..),
    newCancelPolicyGeneration,

    -- * Request Lenses
    cancelPolicyGeneration_jobId,

    -- * Destructuring the Response
    CancelPolicyGenerationResponse (..),
    newCancelPolicyGenerationResponse,

    -- * Response Lenses
    cancelPolicyGenerationResponse_httpStatus,
  )
where

import Amazonka.AccessAnalyzer.Types
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

-- | /See:/ 'newCancelPolicyGeneration' smart constructor.
data CancelPolicyGeneration = CancelPolicyGeneration'
  { -- | The @JobId@ that is returned by the @StartPolicyGeneration@ operation.
    -- The @JobId@ can be used with @GetGeneratedPolicy@ to retrieve the
    -- generated policies or used with @CancelPolicyGeneration@ to cancel the
    -- policy generation request.
    CancelPolicyGeneration -> Text
jobId :: Prelude.Text
  }
  deriving (CancelPolicyGeneration -> CancelPolicyGeneration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CancelPolicyGeneration -> CancelPolicyGeneration -> Bool
$c/= :: CancelPolicyGeneration -> CancelPolicyGeneration -> Bool
== :: CancelPolicyGeneration -> CancelPolicyGeneration -> Bool
$c== :: CancelPolicyGeneration -> CancelPolicyGeneration -> Bool
Prelude.Eq, ReadPrec [CancelPolicyGeneration]
ReadPrec CancelPolicyGeneration
Int -> ReadS CancelPolicyGeneration
ReadS [CancelPolicyGeneration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CancelPolicyGeneration]
$creadListPrec :: ReadPrec [CancelPolicyGeneration]
readPrec :: ReadPrec CancelPolicyGeneration
$creadPrec :: ReadPrec CancelPolicyGeneration
readList :: ReadS [CancelPolicyGeneration]
$creadList :: ReadS [CancelPolicyGeneration]
readsPrec :: Int -> ReadS CancelPolicyGeneration
$creadsPrec :: Int -> ReadS CancelPolicyGeneration
Prelude.Read, Int -> CancelPolicyGeneration -> ShowS
[CancelPolicyGeneration] -> ShowS
CancelPolicyGeneration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CancelPolicyGeneration] -> ShowS
$cshowList :: [CancelPolicyGeneration] -> ShowS
show :: CancelPolicyGeneration -> String
$cshow :: CancelPolicyGeneration -> String
showsPrec :: Int -> CancelPolicyGeneration -> ShowS
$cshowsPrec :: Int -> CancelPolicyGeneration -> ShowS
Prelude.Show, forall x. Rep CancelPolicyGeneration x -> CancelPolicyGeneration
forall x. CancelPolicyGeneration -> Rep CancelPolicyGeneration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CancelPolicyGeneration x -> CancelPolicyGeneration
$cfrom :: forall x. CancelPolicyGeneration -> Rep CancelPolicyGeneration x
Prelude.Generic)

-- |
-- Create a value of 'CancelPolicyGeneration' 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:
--
-- 'jobId', 'cancelPolicyGeneration_jobId' - The @JobId@ that is returned by the @StartPolicyGeneration@ operation.
-- The @JobId@ can be used with @GetGeneratedPolicy@ to retrieve the
-- generated policies or used with @CancelPolicyGeneration@ to cancel the
-- policy generation request.
newCancelPolicyGeneration ::
  -- | 'jobId'
  Prelude.Text ->
  CancelPolicyGeneration
newCancelPolicyGeneration :: Text -> CancelPolicyGeneration
newCancelPolicyGeneration Text
pJobId_ =
  CancelPolicyGeneration' {$sel:jobId:CancelPolicyGeneration' :: Text
jobId = Text
pJobId_}

-- | The @JobId@ that is returned by the @StartPolicyGeneration@ operation.
-- The @JobId@ can be used with @GetGeneratedPolicy@ to retrieve the
-- generated policies or used with @CancelPolicyGeneration@ to cancel the
-- policy generation request.
cancelPolicyGeneration_jobId :: Lens.Lens' CancelPolicyGeneration Prelude.Text
cancelPolicyGeneration_jobId :: Lens' CancelPolicyGeneration Text
cancelPolicyGeneration_jobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CancelPolicyGeneration' {Text
jobId :: Text
$sel:jobId:CancelPolicyGeneration' :: CancelPolicyGeneration -> Text
jobId} -> Text
jobId) (\s :: CancelPolicyGeneration
s@CancelPolicyGeneration' {} Text
a -> CancelPolicyGeneration
s {$sel:jobId:CancelPolicyGeneration' :: Text
jobId = Text
a} :: CancelPolicyGeneration)

instance Core.AWSRequest CancelPolicyGeneration where
  type
    AWSResponse CancelPolicyGeneration =
      CancelPolicyGenerationResponse
  request :: (Service -> Service)
-> CancelPolicyGeneration -> Request CancelPolicyGeneration
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy CancelPolicyGeneration
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CancelPolicyGeneration)))
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 -> CancelPolicyGenerationResponse
CancelPolicyGenerationResponse'
            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 CancelPolicyGeneration where
  hashWithSalt :: Int -> CancelPolicyGeneration -> Int
hashWithSalt Int
_salt CancelPolicyGeneration' {Text
jobId :: Text
$sel:jobId:CancelPolicyGeneration' :: CancelPolicyGeneration -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
jobId

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

instance Data.ToHeaders CancelPolicyGeneration where
  toHeaders :: CancelPolicyGeneration -> 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 CancelPolicyGeneration where
  toJSON :: CancelPolicyGeneration -> Value
toJSON = forall a b. a -> b -> a
Prelude.const (Object -> Value
Data.Object forall a. Monoid a => a
Prelude.mempty)

instance Data.ToPath CancelPolicyGeneration where
  toPath :: CancelPolicyGeneration -> ByteString
toPath CancelPolicyGeneration' {Text
jobId :: Text
$sel:jobId:CancelPolicyGeneration' :: CancelPolicyGeneration -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/policy/generation/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
jobId]

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

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

-- |
-- Create a value of 'CancelPolicyGenerationResponse' 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', 'cancelPolicyGenerationResponse_httpStatus' - The response's http status code.
newCancelPolicyGenerationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CancelPolicyGenerationResponse
newCancelPolicyGenerationResponse :: Int -> CancelPolicyGenerationResponse
newCancelPolicyGenerationResponse Int
pHttpStatus_ =
  CancelPolicyGenerationResponse'
    { $sel:httpStatus:CancelPolicyGenerationResponse' :: Int
httpStatus =
        Int
pHttpStatus_
    }

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

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