{-# 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.IoT.DeletePolicyVersion
  ( 
    DeletePolicyVersion (..),
    newDeletePolicyVersion,
    
    deletePolicyVersion_policyName,
    deletePolicyVersion_policyVersionId,
    
    DeletePolicyVersionResponse (..),
    newDeletePolicyVersionResponse,
  )
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.IoT.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
data DeletePolicyVersion = DeletePolicyVersion'
  { 
    DeletePolicyVersion -> Text
policyName :: Prelude.Text,
    
    DeletePolicyVersion -> Text
policyVersionId :: Prelude.Text
  }
  deriving (DeletePolicyVersion -> DeletePolicyVersion -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeletePolicyVersion -> DeletePolicyVersion -> Bool
$c/= :: DeletePolicyVersion -> DeletePolicyVersion -> Bool
== :: DeletePolicyVersion -> DeletePolicyVersion -> Bool
$c== :: DeletePolicyVersion -> DeletePolicyVersion -> Bool
Prelude.Eq, ReadPrec [DeletePolicyVersion]
ReadPrec DeletePolicyVersion
Int -> ReadS DeletePolicyVersion
ReadS [DeletePolicyVersion]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeletePolicyVersion]
$creadListPrec :: ReadPrec [DeletePolicyVersion]
readPrec :: ReadPrec DeletePolicyVersion
$creadPrec :: ReadPrec DeletePolicyVersion
readList :: ReadS [DeletePolicyVersion]
$creadList :: ReadS [DeletePolicyVersion]
readsPrec :: Int -> ReadS DeletePolicyVersion
$creadsPrec :: Int -> ReadS DeletePolicyVersion
Prelude.Read, Int -> DeletePolicyVersion -> ShowS
[DeletePolicyVersion] -> ShowS
DeletePolicyVersion -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeletePolicyVersion] -> ShowS
$cshowList :: [DeletePolicyVersion] -> ShowS
show :: DeletePolicyVersion -> String
$cshow :: DeletePolicyVersion -> String
showsPrec :: Int -> DeletePolicyVersion -> ShowS
$cshowsPrec :: Int -> DeletePolicyVersion -> ShowS
Prelude.Show, forall x. Rep DeletePolicyVersion x -> DeletePolicyVersion
forall x. DeletePolicyVersion -> Rep DeletePolicyVersion x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeletePolicyVersion x -> DeletePolicyVersion
$cfrom :: forall x. DeletePolicyVersion -> Rep DeletePolicyVersion x
Prelude.Generic)
newDeletePolicyVersion ::
  
  Prelude.Text ->
  
  Prelude.Text ->
  DeletePolicyVersion
newDeletePolicyVersion :: Text -> Text -> DeletePolicyVersion
newDeletePolicyVersion Text
pPolicyName_ Text
pPolicyVersionId_ =
  DeletePolicyVersion'
    { $sel:policyName:DeletePolicyVersion' :: Text
policyName = Text
pPolicyName_,
      $sel:policyVersionId:DeletePolicyVersion' :: Text
policyVersionId = Text
pPolicyVersionId_
    }
deletePolicyVersion_policyName :: Lens.Lens' DeletePolicyVersion Prelude.Text
deletePolicyVersion_policyName :: Lens' DeletePolicyVersion Text
deletePolicyVersion_policyName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeletePolicyVersion' {Text
policyName :: Text
$sel:policyName:DeletePolicyVersion' :: DeletePolicyVersion -> Text
policyName} -> Text
policyName) (\s :: DeletePolicyVersion
s@DeletePolicyVersion' {} Text
a -> DeletePolicyVersion
s {$sel:policyName:DeletePolicyVersion' :: Text
policyName = Text
a} :: DeletePolicyVersion)
deletePolicyVersion_policyVersionId :: Lens.Lens' DeletePolicyVersion Prelude.Text
deletePolicyVersion_policyVersionId :: Lens' DeletePolicyVersion Text
deletePolicyVersion_policyVersionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeletePolicyVersion' {Text
policyVersionId :: Text
$sel:policyVersionId:DeletePolicyVersion' :: DeletePolicyVersion -> Text
policyVersionId} -> Text
policyVersionId) (\s :: DeletePolicyVersion
s@DeletePolicyVersion' {} Text
a -> DeletePolicyVersion
s {$sel:policyVersionId:DeletePolicyVersion' :: Text
policyVersionId = Text
a} :: DeletePolicyVersion)
instance Core.AWSRequest DeletePolicyVersion where
  type
    AWSResponse DeletePolicyVersion =
      DeletePolicyVersionResponse
  request :: (Service -> Service)
-> DeletePolicyVersion -> Request DeletePolicyVersion
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.delete (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeletePolicyVersion
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeletePolicyVersion)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull DeletePolicyVersionResponse
DeletePolicyVersionResponse'
instance Prelude.Hashable DeletePolicyVersion where
  hashWithSalt :: Int -> DeletePolicyVersion -> Int
hashWithSalt Int
_salt DeletePolicyVersion' {Text
policyVersionId :: Text
policyName :: Text
$sel:policyVersionId:DeletePolicyVersion' :: DeletePolicyVersion -> Text
$sel:policyName:DeletePolicyVersion' :: DeletePolicyVersion -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
policyName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
policyVersionId
instance Prelude.NFData DeletePolicyVersion where
  rnf :: DeletePolicyVersion -> ()
rnf DeletePolicyVersion' {Text
policyVersionId :: Text
policyName :: Text
$sel:policyVersionId:DeletePolicyVersion' :: DeletePolicyVersion -> Text
$sel:policyName:DeletePolicyVersion' :: DeletePolicyVersion -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
policyName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
policyVersionId
instance Data.ToHeaders DeletePolicyVersion where
  toHeaders :: DeletePolicyVersion -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
instance Data.ToPath DeletePolicyVersion where
  toPath :: DeletePolicyVersion -> ByteString
toPath DeletePolicyVersion' {Text
policyVersionId :: Text
policyName :: Text
$sel:policyVersionId:DeletePolicyVersion' :: DeletePolicyVersion -> Text
$sel:policyName:DeletePolicyVersion' :: DeletePolicyVersion -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/policies/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
policyName,
        ByteString
"/version/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
policyVersionId
      ]
instance Data.ToQuery DeletePolicyVersion where
  toQuery :: DeletePolicyVersion -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data DeletePolicyVersionResponse = DeletePolicyVersionResponse'
  {
  }
  deriving (DeletePolicyVersionResponse -> DeletePolicyVersionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeletePolicyVersionResponse -> DeletePolicyVersionResponse -> Bool
$c/= :: DeletePolicyVersionResponse -> DeletePolicyVersionResponse -> Bool
== :: DeletePolicyVersionResponse -> DeletePolicyVersionResponse -> Bool
$c== :: DeletePolicyVersionResponse -> DeletePolicyVersionResponse -> Bool
Prelude.Eq, ReadPrec [DeletePolicyVersionResponse]
ReadPrec DeletePolicyVersionResponse
Int -> ReadS DeletePolicyVersionResponse
ReadS [DeletePolicyVersionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeletePolicyVersionResponse]
$creadListPrec :: ReadPrec [DeletePolicyVersionResponse]
readPrec :: ReadPrec DeletePolicyVersionResponse
$creadPrec :: ReadPrec DeletePolicyVersionResponse
readList :: ReadS [DeletePolicyVersionResponse]
$creadList :: ReadS [DeletePolicyVersionResponse]
readsPrec :: Int -> ReadS DeletePolicyVersionResponse
$creadsPrec :: Int -> ReadS DeletePolicyVersionResponse
Prelude.Read, Int -> DeletePolicyVersionResponse -> ShowS
[DeletePolicyVersionResponse] -> ShowS
DeletePolicyVersionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeletePolicyVersionResponse] -> ShowS
$cshowList :: [DeletePolicyVersionResponse] -> ShowS
show :: DeletePolicyVersionResponse -> String
$cshow :: DeletePolicyVersionResponse -> String
showsPrec :: Int -> DeletePolicyVersionResponse -> ShowS
$cshowsPrec :: Int -> DeletePolicyVersionResponse -> ShowS
Prelude.Show, forall x.
Rep DeletePolicyVersionResponse x -> DeletePolicyVersionResponse
forall x.
DeletePolicyVersionResponse -> Rep DeletePolicyVersionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeletePolicyVersionResponse x -> DeletePolicyVersionResponse
$cfrom :: forall x.
DeletePolicyVersionResponse -> Rep DeletePolicyVersionResponse x
Prelude.Generic)
newDeletePolicyVersionResponse ::
  DeletePolicyVersionResponse
newDeletePolicyVersionResponse :: DeletePolicyVersionResponse
newDeletePolicyVersionResponse =
  DeletePolicyVersionResponse
DeletePolicyVersionResponse'
instance Prelude.NFData DeletePolicyVersionResponse where
  rnf :: DeletePolicyVersionResponse -> ()
rnf DeletePolicyVersionResponse
_ = ()