{-# 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.StartGateway
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Starts a gateway that you previously shut down (see ShutdownGateway).
-- After the gateway starts, you can then make other API calls, your
-- applications can read from or write to the gateway\'s storage volumes
-- and you will be able to take snapshot backups.
--
-- When you make a request, you will get a 200 OK success response
-- immediately. However, it might take some time for the gateway to be
-- ready. You should call DescribeGatewayInformation and check the status
-- before making any additional API calls. For more information, see
-- ActivateGateway.
--
-- To specify which gateway to start, use the Amazon Resource Name (ARN) of
-- the gateway in your request.
module Amazonka.StorageGateway.StartGateway
  ( -- * Creating a Request
    StartGateway (..),
    newStartGateway,

    -- * Request Lenses
    startGateway_gatewayARN,

    -- * Destructuring the Response
    StartGatewayResponse (..),
    newStartGatewayResponse,

    -- * Response Lenses
    startGatewayResponse_gatewayARN,
    startGatewayResponse_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 start.
--
-- /See:/ 'newStartGateway' smart constructor.
data StartGateway = StartGateway'
  { StartGateway -> Text
gatewayARN :: Prelude.Text
  }
  deriving (StartGateway -> StartGateway -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartGateway -> StartGateway -> Bool
$c/= :: StartGateway -> StartGateway -> Bool
== :: StartGateway -> StartGateway -> Bool
$c== :: StartGateway -> StartGateway -> Bool
Prelude.Eq, ReadPrec [StartGateway]
ReadPrec StartGateway
Int -> ReadS StartGateway
ReadS [StartGateway]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartGateway]
$creadListPrec :: ReadPrec [StartGateway]
readPrec :: ReadPrec StartGateway
$creadPrec :: ReadPrec StartGateway
readList :: ReadS [StartGateway]
$creadList :: ReadS [StartGateway]
readsPrec :: Int -> ReadS StartGateway
$creadsPrec :: Int -> ReadS StartGateway
Prelude.Read, Int -> StartGateway -> ShowS
[StartGateway] -> ShowS
StartGateway -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartGateway] -> ShowS
$cshowList :: [StartGateway] -> ShowS
show :: StartGateway -> String
$cshow :: StartGateway -> String
showsPrec :: Int -> StartGateway -> ShowS
$cshowsPrec :: Int -> StartGateway -> ShowS
Prelude.Show, forall x. Rep StartGateway x -> StartGateway
forall x. StartGateway -> Rep StartGateway x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartGateway x -> StartGateway
$cfrom :: forall x. StartGateway -> Rep StartGateway x
Prelude.Generic)

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

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

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

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

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

instance Data.ToQuery StartGateway where
  toQuery :: StartGateway -> 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 restarted.
--
-- /See:/ 'newStartGatewayResponse' smart constructor.
data StartGatewayResponse = StartGatewayResponse'
  { StartGatewayResponse -> Maybe Text
gatewayARN :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    StartGatewayResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (StartGatewayResponse -> StartGatewayResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartGatewayResponse -> StartGatewayResponse -> Bool
$c/= :: StartGatewayResponse -> StartGatewayResponse -> Bool
== :: StartGatewayResponse -> StartGatewayResponse -> Bool
$c== :: StartGatewayResponse -> StartGatewayResponse -> Bool
Prelude.Eq, ReadPrec [StartGatewayResponse]
ReadPrec StartGatewayResponse
Int -> ReadS StartGatewayResponse
ReadS [StartGatewayResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartGatewayResponse]
$creadListPrec :: ReadPrec [StartGatewayResponse]
readPrec :: ReadPrec StartGatewayResponse
$creadPrec :: ReadPrec StartGatewayResponse
readList :: ReadS [StartGatewayResponse]
$creadList :: ReadS [StartGatewayResponse]
readsPrec :: Int -> ReadS StartGatewayResponse
$creadsPrec :: Int -> ReadS StartGatewayResponse
Prelude.Read, Int -> StartGatewayResponse -> ShowS
[StartGatewayResponse] -> ShowS
StartGatewayResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartGatewayResponse] -> ShowS
$cshowList :: [StartGatewayResponse] -> ShowS
show :: StartGatewayResponse -> String
$cshow :: StartGatewayResponse -> String
showsPrec :: Int -> StartGatewayResponse -> ShowS
$cshowsPrec :: Int -> StartGatewayResponse -> ShowS
Prelude.Show, forall x. Rep StartGatewayResponse x -> StartGatewayResponse
forall x. StartGatewayResponse -> Rep StartGatewayResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartGatewayResponse x -> StartGatewayResponse
$cfrom :: forall x. StartGatewayResponse -> Rep StartGatewayResponse x
Prelude.Generic)

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

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

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

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