{-# 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.IoTSecureTunneling.CloseTunnel
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Closes a tunnel identified by the unique tunnel id. When a @CloseTunnel@
-- request is received, we close the WebSocket connections between the
-- client and proxy server so no data can be transmitted.
--
-- Requires permission to access the
-- <https://docs.aws.amazon.com/service-authorization/latest/reference/list_awsiot.html#awsiot-actions-as-permissions CloseTunnel>
-- action.
module Amazonka.IoTSecureTunneling.CloseTunnel
  ( -- * Creating a Request
    CloseTunnel (..),
    newCloseTunnel,

    -- * Request Lenses
    closeTunnel_delete,
    closeTunnel_tunnelId,

    -- * Destructuring the Response
    CloseTunnelResponse (..),
    newCloseTunnelResponse,

    -- * Response Lenses
    closeTunnelResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.IoTSecureTunneling.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newCloseTunnel' smart constructor.
data CloseTunnel = CloseTunnel'
  { -- | When set to true, IoT Secure Tunneling deletes the tunnel data
    -- immediately.
    CloseTunnel -> Maybe Bool
delete' :: Prelude.Maybe Prelude.Bool,
    -- | The ID of the tunnel to close.
    CloseTunnel -> Text
tunnelId :: Prelude.Text
  }
  deriving (CloseTunnel -> CloseTunnel -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CloseTunnel -> CloseTunnel -> Bool
$c/= :: CloseTunnel -> CloseTunnel -> Bool
== :: CloseTunnel -> CloseTunnel -> Bool
$c== :: CloseTunnel -> CloseTunnel -> Bool
Prelude.Eq, ReadPrec [CloseTunnel]
ReadPrec CloseTunnel
Int -> ReadS CloseTunnel
ReadS [CloseTunnel]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CloseTunnel]
$creadListPrec :: ReadPrec [CloseTunnel]
readPrec :: ReadPrec CloseTunnel
$creadPrec :: ReadPrec CloseTunnel
readList :: ReadS [CloseTunnel]
$creadList :: ReadS [CloseTunnel]
readsPrec :: Int -> ReadS CloseTunnel
$creadsPrec :: Int -> ReadS CloseTunnel
Prelude.Read, Int -> CloseTunnel -> ShowS
[CloseTunnel] -> ShowS
CloseTunnel -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CloseTunnel] -> ShowS
$cshowList :: [CloseTunnel] -> ShowS
show :: CloseTunnel -> String
$cshow :: CloseTunnel -> String
showsPrec :: Int -> CloseTunnel -> ShowS
$cshowsPrec :: Int -> CloseTunnel -> ShowS
Prelude.Show, forall x. Rep CloseTunnel x -> CloseTunnel
forall x. CloseTunnel -> Rep CloseTunnel x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CloseTunnel x -> CloseTunnel
$cfrom :: forall x. CloseTunnel -> Rep CloseTunnel x
Prelude.Generic)

-- |
-- Create a value of 'CloseTunnel' 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:
--
-- 'delete'', 'closeTunnel_delete' - When set to true, IoT Secure Tunneling deletes the tunnel data
-- immediately.
--
-- 'tunnelId', 'closeTunnel_tunnelId' - The ID of the tunnel to close.
newCloseTunnel ::
  -- | 'tunnelId'
  Prelude.Text ->
  CloseTunnel
newCloseTunnel :: Text -> CloseTunnel
newCloseTunnel Text
pTunnelId_ =
  CloseTunnel'
    { $sel:delete':CloseTunnel' :: Maybe Bool
delete' = forall a. Maybe a
Prelude.Nothing,
      $sel:tunnelId:CloseTunnel' :: Text
tunnelId = Text
pTunnelId_
    }

-- | When set to true, IoT Secure Tunneling deletes the tunnel data
-- immediately.
closeTunnel_delete :: Lens.Lens' CloseTunnel (Prelude.Maybe Prelude.Bool)
closeTunnel_delete :: Lens' CloseTunnel (Maybe Bool)
closeTunnel_delete = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CloseTunnel' {Maybe Bool
delete' :: Maybe Bool
$sel:delete':CloseTunnel' :: CloseTunnel -> Maybe Bool
delete'} -> Maybe Bool
delete') (\s :: CloseTunnel
s@CloseTunnel' {} Maybe Bool
a -> CloseTunnel
s {$sel:delete':CloseTunnel' :: Maybe Bool
delete' = Maybe Bool
a} :: CloseTunnel)

-- | The ID of the tunnel to close.
closeTunnel_tunnelId :: Lens.Lens' CloseTunnel Prelude.Text
closeTunnel_tunnelId :: Lens' CloseTunnel Text
closeTunnel_tunnelId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CloseTunnel' {Text
tunnelId :: Text
$sel:tunnelId:CloseTunnel' :: CloseTunnel -> Text
tunnelId} -> Text
tunnelId) (\s :: CloseTunnel
s@CloseTunnel' {} Text
a -> CloseTunnel
s {$sel:tunnelId:CloseTunnel' :: Text
tunnelId = Text
a} :: CloseTunnel)

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

instance Prelude.NFData CloseTunnel where
  rnf :: CloseTunnel -> ()
rnf CloseTunnel' {Maybe Bool
Text
tunnelId :: Text
delete' :: Maybe Bool
$sel:tunnelId:CloseTunnel' :: CloseTunnel -> Text
$sel:delete':CloseTunnel' :: CloseTunnel -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
delete'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
tunnelId

instance Data.ToHeaders CloseTunnel where
  toHeaders :: CloseTunnel -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"IoTSecuredTunneling.CloseTunnel" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON CloseTunnel where
  toJSON :: CloseTunnel -> Value
toJSON CloseTunnel' {Maybe Bool
Text
tunnelId :: Text
delete' :: Maybe Bool
$sel:tunnelId:CloseTunnel' :: CloseTunnel -> Text
$sel:delete':CloseTunnel' :: CloseTunnel -> Maybe Bool
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"delete" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Bool
delete',
            forall a. a -> Maybe a
Prelude.Just (Key
"tunnelId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
tunnelId)
          ]
      )

instance Data.ToPath CloseTunnel where
  toPath :: CloseTunnel -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

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

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

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