{-# 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.StorageGateway.DisableGateway
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Disables a tape gateway when the gateway is no longer functioning. For
-- example, if your gateway VM is damaged, you can disable the gateway so
-- you can recover virtual tapes.
--
-- Use this operation for a tape gateway that is not reachable or not
-- functioning. This operation is only supported in the tape gateway type.
--
-- After a gateway is disabled, it cannot be enabled.
module Amazonka.StorageGateway.DisableGateway
  ( -- * Creating a Request
    DisableGateway (..),
    newDisableGateway,

    -- * Request Lenses
    disableGateway_gatewayARN,

    -- * Destructuring the Response
    DisableGatewayResponse (..),
    newDisableGatewayResponse,

    -- * Response Lenses
    disableGatewayResponse_gatewayARN,
    disableGatewayResponse_httpStatus,
  )
where

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
import Amazonka.StorageGateway.Types

-- | DisableGatewayInput
--
-- /See:/ 'newDisableGateway' smart constructor.
data DisableGateway = DisableGateway'
  { DisableGateway -> Text
gatewayARN :: Prelude.Text
  }
  deriving (DisableGateway -> DisableGateway -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisableGateway -> DisableGateway -> Bool
$c/= :: DisableGateway -> DisableGateway -> Bool
== :: DisableGateway -> DisableGateway -> Bool
$c== :: DisableGateway -> DisableGateway -> Bool
Prelude.Eq, ReadPrec [DisableGateway]
ReadPrec DisableGateway
Int -> ReadS DisableGateway
ReadS [DisableGateway]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DisableGateway]
$creadListPrec :: ReadPrec [DisableGateway]
readPrec :: ReadPrec DisableGateway
$creadPrec :: ReadPrec DisableGateway
readList :: ReadS [DisableGateway]
$creadList :: ReadS [DisableGateway]
readsPrec :: Int -> ReadS DisableGateway
$creadsPrec :: Int -> ReadS DisableGateway
Prelude.Read, Int -> DisableGateway -> ShowS
[DisableGateway] -> ShowS
DisableGateway -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisableGateway] -> ShowS
$cshowList :: [DisableGateway] -> ShowS
show :: DisableGateway -> String
$cshow :: DisableGateway -> String
showsPrec :: Int -> DisableGateway -> ShowS
$cshowsPrec :: Int -> DisableGateway -> ShowS
Prelude.Show, forall x. Rep DisableGateway x -> DisableGateway
forall x. DisableGateway -> Rep DisableGateway x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DisableGateway x -> DisableGateway
$cfrom :: forall x. DisableGateway -> Rep DisableGateway x
Prelude.Generic)

-- |
-- Create a value of 'DisableGateway' 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:
--
-- 'gatewayARN', 'disableGateway_gatewayARN' - Undocumented member.
newDisableGateway ::
  -- | 'gatewayARN'
  Prelude.Text ->
  DisableGateway
newDisableGateway :: Text -> DisableGateway
newDisableGateway Text
pGatewayARN_ =
  DisableGateway' {$sel:gatewayARN:DisableGateway' :: Text
gatewayARN = Text
pGatewayARN_}

-- | Undocumented member.
disableGateway_gatewayARN :: Lens.Lens' DisableGateway Prelude.Text
disableGateway_gatewayARN :: Lens' DisableGateway Text
disableGateway_gatewayARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisableGateway' {Text
gatewayARN :: Text
$sel:gatewayARN:DisableGateway' :: DisableGateway -> Text
gatewayARN} -> Text
gatewayARN) (\s :: DisableGateway
s@DisableGateway' {} Text
a -> DisableGateway
s {$sel:gatewayARN:DisableGateway' :: Text
gatewayARN = Text
a} :: DisableGateway)

instance Core.AWSRequest DisableGateway where
  type
    AWSResponse DisableGateway =
      DisableGatewayResponse
  request :: (Service -> Service) -> DisableGateway -> Request DisableGateway
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 DisableGateway
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DisableGateway)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text -> Int -> DisableGatewayResponse
DisableGatewayResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"GatewayARN")
            forall (f :: * -> *) a b. Applicative f => 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 DisableGateway where
  hashWithSalt :: Int -> DisableGateway -> Int
hashWithSalt Int
_salt DisableGateway' {Text
gatewayARN :: Text
$sel:gatewayARN:DisableGateway' :: DisableGateway -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
gatewayARN

instance Prelude.NFData DisableGateway where
  rnf :: DisableGateway -> ()
rnf DisableGateway' {Text
gatewayARN :: Text
$sel:gatewayARN:DisableGateway' :: DisableGateway -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
gatewayARN

instance Data.ToHeaders DisableGateway where
  toHeaders :: DisableGateway -> 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
"StorageGateway_20130630.DisableGateway" ::
                          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 DisableGateway where
  toJSON :: DisableGateway -> Value
toJSON DisableGateway' {Text
gatewayARN :: Text
$sel:gatewayARN:DisableGateway' :: DisableGateway -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"GatewayARN" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
gatewayARN)]
      )

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

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

-- | DisableGatewayOutput
--
-- /See:/ 'newDisableGatewayResponse' smart constructor.
data DisableGatewayResponse = DisableGatewayResponse'
  { -- | The unique Amazon Resource Name (ARN) of the disabled gateway.
    DisableGatewayResponse -> Maybe Text
gatewayARN :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DisableGatewayResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DisableGatewayResponse -> DisableGatewayResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisableGatewayResponse -> DisableGatewayResponse -> Bool
$c/= :: DisableGatewayResponse -> DisableGatewayResponse -> Bool
== :: DisableGatewayResponse -> DisableGatewayResponse -> Bool
$c== :: DisableGatewayResponse -> DisableGatewayResponse -> Bool
Prelude.Eq, ReadPrec [DisableGatewayResponse]
ReadPrec DisableGatewayResponse
Int -> ReadS DisableGatewayResponse
ReadS [DisableGatewayResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DisableGatewayResponse]
$creadListPrec :: ReadPrec [DisableGatewayResponse]
readPrec :: ReadPrec DisableGatewayResponse
$creadPrec :: ReadPrec DisableGatewayResponse
readList :: ReadS [DisableGatewayResponse]
$creadList :: ReadS [DisableGatewayResponse]
readsPrec :: Int -> ReadS DisableGatewayResponse
$creadsPrec :: Int -> ReadS DisableGatewayResponse
Prelude.Read, Int -> DisableGatewayResponse -> ShowS
[DisableGatewayResponse] -> ShowS
DisableGatewayResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisableGatewayResponse] -> ShowS
$cshowList :: [DisableGatewayResponse] -> ShowS
show :: DisableGatewayResponse -> String
$cshow :: DisableGatewayResponse -> String
showsPrec :: Int -> DisableGatewayResponse -> ShowS
$cshowsPrec :: Int -> DisableGatewayResponse -> ShowS
Prelude.Show, forall x. Rep DisableGatewayResponse x -> DisableGatewayResponse
forall x. DisableGatewayResponse -> Rep DisableGatewayResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DisableGatewayResponse x -> DisableGatewayResponse
$cfrom :: forall x. DisableGatewayResponse -> Rep DisableGatewayResponse x
Prelude.Generic)

-- |
-- Create a value of 'DisableGatewayResponse' 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:
--
-- 'gatewayARN', 'disableGatewayResponse_gatewayARN' - The unique Amazon Resource Name (ARN) of the disabled gateway.
--
-- 'httpStatus', 'disableGatewayResponse_httpStatus' - The response's http status code.
newDisableGatewayResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DisableGatewayResponse
newDisableGatewayResponse :: Int -> DisableGatewayResponse
newDisableGatewayResponse Int
pHttpStatus_ =
  DisableGatewayResponse'
    { $sel:gatewayARN:DisableGatewayResponse' :: Maybe Text
gatewayARN =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DisableGatewayResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The unique Amazon Resource Name (ARN) of the disabled gateway.
disableGatewayResponse_gatewayARN :: Lens.Lens' DisableGatewayResponse (Prelude.Maybe Prelude.Text)
disableGatewayResponse_gatewayARN :: Lens' DisableGatewayResponse (Maybe Text)
disableGatewayResponse_gatewayARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisableGatewayResponse' {Maybe Text
gatewayARN :: Maybe Text
$sel:gatewayARN:DisableGatewayResponse' :: DisableGatewayResponse -> Maybe Text
gatewayARN} -> Maybe Text
gatewayARN) (\s :: DisableGatewayResponse
s@DisableGatewayResponse' {} Maybe Text
a -> DisableGatewayResponse
s {$sel:gatewayARN:DisableGatewayResponse' :: Maybe Text
gatewayARN = Maybe Text
a} :: DisableGatewayResponse)

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

instance Prelude.NFData DisableGatewayResponse where
  rnf :: DisableGatewayResponse -> ()
rnf DisableGatewayResponse' {Int
Maybe Text
httpStatus :: Int
gatewayARN :: Maybe Text
$sel:httpStatus:DisableGatewayResponse' :: DisableGatewayResponse -> Int
$sel:gatewayARN:DisableGatewayResponse' :: DisableGatewayResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
gatewayARN
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus