{-# 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.AppSync.DeleteFunction
-- 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 @Function@.
module Amazonka.AppSync.DeleteFunction
  ( -- * Creating a Request
    DeleteFunction (..),
    newDeleteFunction,

    -- * Request Lenses
    deleteFunction_apiId,
    deleteFunction_functionId,

    -- * Destructuring the Response
    DeleteFunctionResponse (..),
    newDeleteFunctionResponse,

    -- * Response Lenses
    deleteFunctionResponse_httpStatus,
  )
where

import Amazonka.AppSync.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:/ 'newDeleteFunction' smart constructor.
data DeleteFunction = DeleteFunction'
  { -- | The GraphQL API ID.
    DeleteFunction -> Text
apiId :: Prelude.Text,
    -- | The @Function@ ID.
    DeleteFunction -> Text
functionId :: Prelude.Text
  }
  deriving (DeleteFunction -> DeleteFunction -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteFunction -> DeleteFunction -> Bool
$c/= :: DeleteFunction -> DeleteFunction -> Bool
== :: DeleteFunction -> DeleteFunction -> Bool
$c== :: DeleteFunction -> DeleteFunction -> Bool
Prelude.Eq, ReadPrec [DeleteFunction]
ReadPrec DeleteFunction
Int -> ReadS DeleteFunction
ReadS [DeleteFunction]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteFunction]
$creadListPrec :: ReadPrec [DeleteFunction]
readPrec :: ReadPrec DeleteFunction
$creadPrec :: ReadPrec DeleteFunction
readList :: ReadS [DeleteFunction]
$creadList :: ReadS [DeleteFunction]
readsPrec :: Int -> ReadS DeleteFunction
$creadsPrec :: Int -> ReadS DeleteFunction
Prelude.Read, Int -> DeleteFunction -> ShowS
[DeleteFunction] -> ShowS
DeleteFunction -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteFunction] -> ShowS
$cshowList :: [DeleteFunction] -> ShowS
show :: DeleteFunction -> String
$cshow :: DeleteFunction -> String
showsPrec :: Int -> DeleteFunction -> ShowS
$cshowsPrec :: Int -> DeleteFunction -> ShowS
Prelude.Show, forall x. Rep DeleteFunction x -> DeleteFunction
forall x. DeleteFunction -> Rep DeleteFunction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteFunction x -> DeleteFunction
$cfrom :: forall x. DeleteFunction -> Rep DeleteFunction x
Prelude.Generic)

-- |
-- Create a value of 'DeleteFunction' 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:
--
-- 'apiId', 'deleteFunction_apiId' - The GraphQL API ID.
--
-- 'functionId', 'deleteFunction_functionId' - The @Function@ ID.
newDeleteFunction ::
  -- | 'apiId'
  Prelude.Text ->
  -- | 'functionId'
  Prelude.Text ->
  DeleteFunction
newDeleteFunction :: Text -> Text -> DeleteFunction
newDeleteFunction Text
pApiId_ Text
pFunctionId_ =
  DeleteFunction'
    { $sel:apiId:DeleteFunction' :: Text
apiId = Text
pApiId_,
      $sel:functionId:DeleteFunction' :: Text
functionId = Text
pFunctionId_
    }

-- | The GraphQL API ID.
deleteFunction_apiId :: Lens.Lens' DeleteFunction Prelude.Text
deleteFunction_apiId :: Lens' DeleteFunction Text
deleteFunction_apiId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteFunction' {Text
apiId :: Text
$sel:apiId:DeleteFunction' :: DeleteFunction -> Text
apiId} -> Text
apiId) (\s :: DeleteFunction
s@DeleteFunction' {} Text
a -> DeleteFunction
s {$sel:apiId:DeleteFunction' :: Text
apiId = Text
a} :: DeleteFunction)

-- | The @Function@ ID.
deleteFunction_functionId :: Lens.Lens' DeleteFunction Prelude.Text
deleteFunction_functionId :: Lens' DeleteFunction Text
deleteFunction_functionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteFunction' {Text
functionId :: Text
$sel:functionId:DeleteFunction' :: DeleteFunction -> Text
functionId} -> Text
functionId) (\s :: DeleteFunction
s@DeleteFunction' {} Text
a -> DeleteFunction
s {$sel:functionId:DeleteFunction' :: Text
functionId = Text
a} :: DeleteFunction)

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

instance Prelude.NFData DeleteFunction where
  rnf :: DeleteFunction -> ()
rnf DeleteFunction' {Text
functionId :: Text
apiId :: Text
$sel:functionId:DeleteFunction' :: DeleteFunction -> Text
$sel:apiId:DeleteFunction' :: DeleteFunction -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
apiId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
functionId

instance Data.ToHeaders DeleteFunction where
  toHeaders :: DeleteFunction -> 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.ToPath DeleteFunction where
  toPath :: DeleteFunction -> ByteString
toPath DeleteFunction' {Text
functionId :: Text
apiId :: Text
$sel:functionId:DeleteFunction' :: DeleteFunction -> Text
$sel:apiId:DeleteFunction' :: DeleteFunction -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/v1/apis/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
apiId,
        ByteString
"/functions/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
functionId
      ]

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

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

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

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

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