{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}
module Network.AWS.CloudFront.DeletePublicKey
(
deletePublicKey
, DeletePublicKey
, dpkIfMatch
, dpkId
, deletePublicKeyResponse
, DeletePublicKeyResponse
) where
import Network.AWS.CloudFront.Types
import Network.AWS.CloudFront.Types.Product
import Network.AWS.Lens
import Network.AWS.Prelude
import Network.AWS.Request
import Network.AWS.Response
data DeletePublicKey = DeletePublicKey'
{ _dpkIfMatch :: !(Maybe Text)
, _dpkId :: !Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
deletePublicKey
:: Text
-> DeletePublicKey
deletePublicKey pId_ = DeletePublicKey' {_dpkIfMatch = Nothing, _dpkId = pId_}
dpkIfMatch :: Lens' DeletePublicKey (Maybe Text)
dpkIfMatch = lens _dpkIfMatch (\ s a -> s{_dpkIfMatch = a})
dpkId :: Lens' DeletePublicKey Text
dpkId = lens _dpkId (\ s a -> s{_dpkId = a})
instance AWSRequest DeletePublicKey where
type Rs DeletePublicKey = DeletePublicKeyResponse
request = delete cloudFront
response = receiveNull DeletePublicKeyResponse'
instance Hashable DeletePublicKey where
instance NFData DeletePublicKey where
instance ToHeaders DeletePublicKey where
toHeaders DeletePublicKey'{..}
= mconcat ["If-Match" =# _dpkIfMatch]
instance ToPath DeletePublicKey where
toPath DeletePublicKey'{..}
= mconcat ["/2017-10-30/public-key/", toBS _dpkId]
instance ToQuery DeletePublicKey where
toQuery = const mempty
data DeletePublicKeyResponse =
DeletePublicKeyResponse'
deriving (Eq, Read, Show, Data, Typeable, Generic)
deletePublicKeyResponse
:: DeletePublicKeyResponse
deletePublicKeyResponse = DeletePublicKeyResponse'
instance NFData DeletePublicKeyResponse where