{-# 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.GameLift.GetInstanceAccess
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Requests remote access to a fleet instance. Remote access is useful for
-- debugging, gathering benchmarking data, or observing activity in real
-- time.
--
-- To remotely access an instance, you need credentials that match the
-- operating system of the instance. For a Windows instance, GameLift
-- returns a user name and password as strings for use with a Windows
-- Remote Desktop client. For a Linux instance, GameLift returns a user
-- name and RSA private key, also as strings, for use with an SSH client.
-- The private key must be saved in the proper format to a @.pem@ file
-- before using. If you\'re making this request using the CLI, saving the
-- secret can be handled as part of the @GetInstanceAccess@ request, as
-- shown in one of the examples for this operation.
--
-- To request access to a specific instance, specify the IDs of both the
-- instance and the fleet it belongs to. You can retrieve a fleet\'s
-- instance IDs by calling
-- <https://docs.aws.amazon.com/gamelift/latest/apireference/API_DescribeInstances.html DescribeInstances>.
--
-- __Learn more__
--
-- <https://docs.aws.amazon.com/gamelift/latest/developerguide/fleets-remote-access.html Remotely Access Fleet Instances>
--
-- <https://docs.aws.amazon.com/gamelift/latest/developerguide/fleets-creating-debug.html Debug Fleet Issues>
--
-- __Related actions__
--
-- <https://docs.aws.amazon.com/gamelift/latest/developerguide/reference-awssdk.html#reference-awssdk-resources-fleets All APIs by task>
module Amazonka.GameLift.GetInstanceAccess
  ( -- * Creating a Request
    GetInstanceAccess (..),
    newGetInstanceAccess,

    -- * Request Lenses
    getInstanceAccess_fleetId,
    getInstanceAccess_instanceId,

    -- * Destructuring the Response
    GetInstanceAccessResponse (..),
    newGetInstanceAccessResponse,

    -- * Response Lenses
    getInstanceAccessResponse_instanceAccess,
    getInstanceAccessResponse_httpStatus,
  )
where

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

-- | /See:/ 'newGetInstanceAccess' smart constructor.
data GetInstanceAccess = GetInstanceAccess'
  { -- | A unique identifier for the fleet that contains the instance you want
    -- access to. You can use either the fleet ID or ARN value. The fleet can
    -- be in any of the following statuses: @ACTIVATING@, @ACTIVE@, or @ERROR@.
    -- Fleets with an @ERROR@ status may be accessible for a short time before
    -- they are deleted.
    GetInstanceAccess -> Text
fleetId :: Prelude.Text,
    -- | A unique identifier for the instance you want to get access to. You can
    -- access an instance in any status.
    GetInstanceAccess -> Text
instanceId :: Prelude.Text
  }
  deriving (GetInstanceAccess -> GetInstanceAccess -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetInstanceAccess -> GetInstanceAccess -> Bool
$c/= :: GetInstanceAccess -> GetInstanceAccess -> Bool
== :: GetInstanceAccess -> GetInstanceAccess -> Bool
$c== :: GetInstanceAccess -> GetInstanceAccess -> Bool
Prelude.Eq, ReadPrec [GetInstanceAccess]
ReadPrec GetInstanceAccess
Int -> ReadS GetInstanceAccess
ReadS [GetInstanceAccess]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetInstanceAccess]
$creadListPrec :: ReadPrec [GetInstanceAccess]
readPrec :: ReadPrec GetInstanceAccess
$creadPrec :: ReadPrec GetInstanceAccess
readList :: ReadS [GetInstanceAccess]
$creadList :: ReadS [GetInstanceAccess]
readsPrec :: Int -> ReadS GetInstanceAccess
$creadsPrec :: Int -> ReadS GetInstanceAccess
Prelude.Read, Int -> GetInstanceAccess -> ShowS
[GetInstanceAccess] -> ShowS
GetInstanceAccess -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetInstanceAccess] -> ShowS
$cshowList :: [GetInstanceAccess] -> ShowS
show :: GetInstanceAccess -> String
$cshow :: GetInstanceAccess -> String
showsPrec :: Int -> GetInstanceAccess -> ShowS
$cshowsPrec :: Int -> GetInstanceAccess -> ShowS
Prelude.Show, forall x. Rep GetInstanceAccess x -> GetInstanceAccess
forall x. GetInstanceAccess -> Rep GetInstanceAccess x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetInstanceAccess x -> GetInstanceAccess
$cfrom :: forall x. GetInstanceAccess -> Rep GetInstanceAccess x
Prelude.Generic)

-- |
-- Create a value of 'GetInstanceAccess' 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:
--
-- 'fleetId', 'getInstanceAccess_fleetId' - A unique identifier for the fleet that contains the instance you want
-- access to. You can use either the fleet ID or ARN value. The fleet can
-- be in any of the following statuses: @ACTIVATING@, @ACTIVE@, or @ERROR@.
-- Fleets with an @ERROR@ status may be accessible for a short time before
-- they are deleted.
--
-- 'instanceId', 'getInstanceAccess_instanceId' - A unique identifier for the instance you want to get access to. You can
-- access an instance in any status.
newGetInstanceAccess ::
  -- | 'fleetId'
  Prelude.Text ->
  -- | 'instanceId'
  Prelude.Text ->
  GetInstanceAccess
newGetInstanceAccess :: Text -> Text -> GetInstanceAccess
newGetInstanceAccess Text
pFleetId_ Text
pInstanceId_ =
  GetInstanceAccess'
    { $sel:fleetId:GetInstanceAccess' :: Text
fleetId = Text
pFleetId_,
      $sel:instanceId:GetInstanceAccess' :: Text
instanceId = Text
pInstanceId_
    }

-- | A unique identifier for the fleet that contains the instance you want
-- access to. You can use either the fleet ID or ARN value. The fleet can
-- be in any of the following statuses: @ACTIVATING@, @ACTIVE@, or @ERROR@.
-- Fleets with an @ERROR@ status may be accessible for a short time before
-- they are deleted.
getInstanceAccess_fleetId :: Lens.Lens' GetInstanceAccess Prelude.Text
getInstanceAccess_fleetId :: Lens' GetInstanceAccess Text
getInstanceAccess_fleetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetInstanceAccess' {Text
fleetId :: Text
$sel:fleetId:GetInstanceAccess' :: GetInstanceAccess -> Text
fleetId} -> Text
fleetId) (\s :: GetInstanceAccess
s@GetInstanceAccess' {} Text
a -> GetInstanceAccess
s {$sel:fleetId:GetInstanceAccess' :: Text
fleetId = Text
a} :: GetInstanceAccess)

-- | A unique identifier for the instance you want to get access to. You can
-- access an instance in any status.
getInstanceAccess_instanceId :: Lens.Lens' GetInstanceAccess Prelude.Text
getInstanceAccess_instanceId :: Lens' GetInstanceAccess Text
getInstanceAccess_instanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetInstanceAccess' {Text
instanceId :: Text
$sel:instanceId:GetInstanceAccess' :: GetInstanceAccess -> Text
instanceId} -> Text
instanceId) (\s :: GetInstanceAccess
s@GetInstanceAccess' {} Text
a -> GetInstanceAccess
s {$sel:instanceId:GetInstanceAccess' :: Text
instanceId = Text
a} :: GetInstanceAccess)

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

instance Prelude.NFData GetInstanceAccess where
  rnf :: GetInstanceAccess -> ()
rnf GetInstanceAccess' {Text
instanceId :: Text
fleetId :: Text
$sel:instanceId:GetInstanceAccess' :: GetInstanceAccess -> Text
$sel:fleetId:GetInstanceAccess' :: GetInstanceAccess -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
fleetId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
instanceId

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

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

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

-- | /See:/ 'newGetInstanceAccessResponse' smart constructor.
data GetInstanceAccessResponse = GetInstanceAccessResponse'
  { -- | The connection information for a fleet instance, including IP address
    -- and access credentials.
    GetInstanceAccessResponse -> Maybe InstanceAccess
instanceAccess :: Prelude.Maybe InstanceAccess,
    -- | The response's http status code.
    GetInstanceAccessResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetInstanceAccessResponse -> GetInstanceAccessResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetInstanceAccessResponse -> GetInstanceAccessResponse -> Bool
$c/= :: GetInstanceAccessResponse -> GetInstanceAccessResponse -> Bool
== :: GetInstanceAccessResponse -> GetInstanceAccessResponse -> Bool
$c== :: GetInstanceAccessResponse -> GetInstanceAccessResponse -> Bool
Prelude.Eq, Int -> GetInstanceAccessResponse -> ShowS
[GetInstanceAccessResponse] -> ShowS
GetInstanceAccessResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetInstanceAccessResponse] -> ShowS
$cshowList :: [GetInstanceAccessResponse] -> ShowS
show :: GetInstanceAccessResponse -> String
$cshow :: GetInstanceAccessResponse -> String
showsPrec :: Int -> GetInstanceAccessResponse -> ShowS
$cshowsPrec :: Int -> GetInstanceAccessResponse -> ShowS
Prelude.Show, forall x.
Rep GetInstanceAccessResponse x -> GetInstanceAccessResponse
forall x.
GetInstanceAccessResponse -> Rep GetInstanceAccessResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetInstanceAccessResponse x -> GetInstanceAccessResponse
$cfrom :: forall x.
GetInstanceAccessResponse -> Rep GetInstanceAccessResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetInstanceAccessResponse' 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:
--
-- 'instanceAccess', 'getInstanceAccessResponse_instanceAccess' - The connection information for a fleet instance, including IP address
-- and access credentials.
--
-- 'httpStatus', 'getInstanceAccessResponse_httpStatus' - The response's http status code.
newGetInstanceAccessResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetInstanceAccessResponse
newGetInstanceAccessResponse :: Int -> GetInstanceAccessResponse
newGetInstanceAccessResponse Int
pHttpStatus_ =
  GetInstanceAccessResponse'
    { $sel:instanceAccess:GetInstanceAccessResponse' :: Maybe InstanceAccess
instanceAccess =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetInstanceAccessResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The connection information for a fleet instance, including IP address
-- and access credentials.
getInstanceAccessResponse_instanceAccess :: Lens.Lens' GetInstanceAccessResponse (Prelude.Maybe InstanceAccess)
getInstanceAccessResponse_instanceAccess :: Lens' GetInstanceAccessResponse (Maybe InstanceAccess)
getInstanceAccessResponse_instanceAccess = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetInstanceAccessResponse' {Maybe InstanceAccess
instanceAccess :: Maybe InstanceAccess
$sel:instanceAccess:GetInstanceAccessResponse' :: GetInstanceAccessResponse -> Maybe InstanceAccess
instanceAccess} -> Maybe InstanceAccess
instanceAccess) (\s :: GetInstanceAccessResponse
s@GetInstanceAccessResponse' {} Maybe InstanceAccess
a -> GetInstanceAccessResponse
s {$sel:instanceAccess:GetInstanceAccessResponse' :: Maybe InstanceAccess
instanceAccess = Maybe InstanceAccess
a} :: GetInstanceAccessResponse)

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

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