{-# 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.ShutdownGateway
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Shuts down a gateway. To specify which gateway to shut down, use the
-- Amazon Resource Name (ARN) of the gateway in the body of your request.
--
-- The operation shuts down the gateway service component running in the
-- gateway\'s virtual machine (VM) and not the host VM.
--
-- If you want to shut down the VM, it is recommended that you first shut
-- down the gateway component in the VM to avoid unpredictable conditions.
--
-- After the gateway is shutdown, you cannot call any other API except
-- StartGateway, DescribeGatewayInformation, and ListGateways. For more
-- information, see ActivateGateway. Your applications cannot read from or
-- write to the gateway\'s storage volumes, and there are no snapshots
-- taken.
--
-- When you make a shutdown request, you will get a @200 OK@ success
-- response immediately. However, it might take some time for the gateway
-- to shut down. You can call the DescribeGatewayInformation API to check
-- the status. For more information, see ActivateGateway.
--
-- If do not intend to use the gateway again, you must delete the gateway
-- (using DeleteGateway) to no longer pay software charges associated with
-- the gateway.
module Amazonka.StorageGateway.ShutdownGateway
  ( -- * Creating a Request
    ShutdownGateway (..),
    newShutdownGateway,

    -- * Request Lenses
    shutdownGateway_gatewayARN,

    -- * Destructuring the Response
    ShutdownGatewayResponse (..),
    newShutdownGatewayResponse,

    -- * Response Lenses
    shutdownGatewayResponse_gatewayARN,
    shutdownGatewayResponse_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

-- | A JSON object containing the Amazon Resource Name (ARN) of the gateway
-- to shut down.
--
-- /See:/ 'newShutdownGateway' smart constructor.
data ShutdownGateway = ShutdownGateway'
  { ShutdownGateway -> Text
gatewayARN :: Prelude.Text
  }
  deriving (ShutdownGateway -> ShutdownGateway -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ShutdownGateway -> ShutdownGateway -> Bool
$c/= :: ShutdownGateway -> ShutdownGateway -> Bool
== :: ShutdownGateway -> ShutdownGateway -> Bool
$c== :: ShutdownGateway -> ShutdownGateway -> Bool
Prelude.Eq, ReadPrec [ShutdownGateway]
ReadPrec ShutdownGateway
Int -> ReadS ShutdownGateway
ReadS [ShutdownGateway]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ShutdownGateway]
$creadListPrec :: ReadPrec [ShutdownGateway]
readPrec :: ReadPrec ShutdownGateway
$creadPrec :: ReadPrec ShutdownGateway
readList :: ReadS [ShutdownGateway]
$creadList :: ReadS [ShutdownGateway]
readsPrec :: Int -> ReadS ShutdownGateway
$creadsPrec :: Int -> ReadS ShutdownGateway
Prelude.Read, Int -> ShutdownGateway -> ShowS
[ShutdownGateway] -> ShowS
ShutdownGateway -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ShutdownGateway] -> ShowS
$cshowList :: [ShutdownGateway] -> ShowS
show :: ShutdownGateway -> String
$cshow :: ShutdownGateway -> String
showsPrec :: Int -> ShutdownGateway -> ShowS
$cshowsPrec :: Int -> ShutdownGateway -> ShowS
Prelude.Show, forall x. Rep ShutdownGateway x -> ShutdownGateway
forall x. ShutdownGateway -> Rep ShutdownGateway x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ShutdownGateway x -> ShutdownGateway
$cfrom :: forall x. ShutdownGateway -> Rep ShutdownGateway x
Prelude.Generic)

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

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

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

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

instance Data.ToHeaders ShutdownGateway where
  toHeaders :: ShutdownGateway -> 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.ShutdownGateway" ::
                          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 ShutdownGateway where
  toJSON :: ShutdownGateway -> Value
toJSON ShutdownGateway' {Text
gatewayARN :: Text
$sel:gatewayARN:ShutdownGateway' :: ShutdownGateway -> 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 ShutdownGateway where
  toPath :: ShutdownGateway -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

-- |
-- Create a value of 'ShutdownGatewayResponse' 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', 'shutdownGatewayResponse_gatewayARN' - Undocumented member.
--
-- 'httpStatus', 'shutdownGatewayResponse_httpStatus' - The response's http status code.
newShutdownGatewayResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ShutdownGatewayResponse
newShutdownGatewayResponse :: Int -> ShutdownGatewayResponse
newShutdownGatewayResponse Int
pHttpStatus_ =
  ShutdownGatewayResponse'
    { $sel:gatewayARN:ShutdownGatewayResponse' :: Maybe Text
gatewayARN =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ShutdownGatewayResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

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

instance Prelude.NFData ShutdownGatewayResponse where
  rnf :: ShutdownGatewayResponse -> ()
rnf ShutdownGatewayResponse' {Int
Maybe Text
httpStatus :: Int
gatewayARN :: Maybe Text
$sel:httpStatus:ShutdownGatewayResponse' :: ShutdownGatewayResponse -> Int
$sel:gatewayARN:ShutdownGatewayResponse' :: ShutdownGatewayResponse -> 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