{-# 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.DeleteType
-- 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 @Type@ object.
module Amazonka.AppSync.DeleteType
  ( -- * Creating a Request
    DeleteType (..),
    newDeleteType,

    -- * Request Lenses
    deleteType_apiId,
    deleteType_typeName,

    -- * Destructuring the Response
    DeleteTypeResponse (..),
    newDeleteTypeResponse,

    -- * Response Lenses
    deleteTypeResponse_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:/ 'newDeleteType' smart constructor.
data DeleteType = DeleteType'
  { -- | The API ID.
    DeleteType -> Text
apiId :: Prelude.Text,
    -- | The type name.
    DeleteType -> Text
typeName :: Prelude.Text
  }
  deriving (DeleteType -> DeleteType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteType -> DeleteType -> Bool
$c/= :: DeleteType -> DeleteType -> Bool
== :: DeleteType -> DeleteType -> Bool
$c== :: DeleteType -> DeleteType -> Bool
Prelude.Eq, ReadPrec [DeleteType]
ReadPrec DeleteType
Int -> ReadS DeleteType
ReadS [DeleteType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteType]
$creadListPrec :: ReadPrec [DeleteType]
readPrec :: ReadPrec DeleteType
$creadPrec :: ReadPrec DeleteType
readList :: ReadS [DeleteType]
$creadList :: ReadS [DeleteType]
readsPrec :: Int -> ReadS DeleteType
$creadsPrec :: Int -> ReadS DeleteType
Prelude.Read, Int -> DeleteType -> ShowS
[DeleteType] -> ShowS
DeleteType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteType] -> ShowS
$cshowList :: [DeleteType] -> ShowS
show :: DeleteType -> String
$cshow :: DeleteType -> String
showsPrec :: Int -> DeleteType -> ShowS
$cshowsPrec :: Int -> DeleteType -> ShowS
Prelude.Show, forall x. Rep DeleteType x -> DeleteType
forall x. DeleteType -> Rep DeleteType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteType x -> DeleteType
$cfrom :: forall x. DeleteType -> Rep DeleteType x
Prelude.Generic)

-- |
-- Create a value of 'DeleteType' 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', 'deleteType_apiId' - The API ID.
--
-- 'typeName', 'deleteType_typeName' - The type name.
newDeleteType ::
  -- | 'apiId'
  Prelude.Text ->
  -- | 'typeName'
  Prelude.Text ->
  DeleteType
newDeleteType :: Text -> Text -> DeleteType
newDeleteType Text
pApiId_ Text
pTypeName_ =
  DeleteType' {$sel:apiId:DeleteType' :: Text
apiId = Text
pApiId_, $sel:typeName:DeleteType' :: Text
typeName = Text
pTypeName_}

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

-- | The type name.
deleteType_typeName :: Lens.Lens' DeleteType Prelude.Text
deleteType_typeName :: Lens' DeleteType Text
deleteType_typeName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteType' {Text
typeName :: Text
$sel:typeName:DeleteType' :: DeleteType -> Text
typeName} -> Text
typeName) (\s :: DeleteType
s@DeleteType' {} Text
a -> DeleteType
s {$sel:typeName:DeleteType' :: Text
typeName = Text
a} :: DeleteType)

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

instance Prelude.NFData DeleteType where
  rnf :: DeleteType -> ()
rnf DeleteType' {Text
typeName :: Text
apiId :: Text
$sel:typeName:DeleteType' :: DeleteType -> Text
$sel:apiId:DeleteType' :: DeleteType -> 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
typeName

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

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

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

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

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

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