{-# 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.EC2.GetConsoleScreenshot
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieve a JPG-format screenshot of a running instance to help with
-- troubleshooting.
--
-- The returned content is Base64-encoded.
module Amazonka.EC2.GetConsoleScreenshot
  ( -- * Creating a Request
    GetConsoleScreenshot (..),
    newGetConsoleScreenshot,

    -- * Request Lenses
    getConsoleScreenshot_dryRun,
    getConsoleScreenshot_wakeUp,
    getConsoleScreenshot_instanceId,

    -- * Destructuring the Response
    GetConsoleScreenshotResponse (..),
    newGetConsoleScreenshotResponse,

    -- * Response Lenses
    getConsoleScreenshotResponse_imageData,
    getConsoleScreenshotResponse_instanceId,
    getConsoleScreenshotResponse_httpStatus,
  )
where

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

-- | /See:/ 'newGetConsoleScreenshot' smart constructor.
data GetConsoleScreenshot = GetConsoleScreenshot'
  { -- | Checks whether you have the required permissions for the action, without
    -- actually making the request, and provides an error response. If you have
    -- the required permissions, the error response is @DryRunOperation@.
    -- Otherwise, it is @UnauthorizedOperation@.
    GetConsoleScreenshot -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | When set to @true@, acts as keystroke input and wakes up an instance
    -- that\'s in standby or \"sleep\" mode.
    GetConsoleScreenshot -> Maybe Bool
wakeUp :: Prelude.Maybe Prelude.Bool,
    -- | The ID of the instance.
    GetConsoleScreenshot -> Text
instanceId :: Prelude.Text
  }
  deriving (GetConsoleScreenshot -> GetConsoleScreenshot -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetConsoleScreenshot -> GetConsoleScreenshot -> Bool
$c/= :: GetConsoleScreenshot -> GetConsoleScreenshot -> Bool
== :: GetConsoleScreenshot -> GetConsoleScreenshot -> Bool
$c== :: GetConsoleScreenshot -> GetConsoleScreenshot -> Bool
Prelude.Eq, ReadPrec [GetConsoleScreenshot]
ReadPrec GetConsoleScreenshot
Int -> ReadS GetConsoleScreenshot
ReadS [GetConsoleScreenshot]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetConsoleScreenshot]
$creadListPrec :: ReadPrec [GetConsoleScreenshot]
readPrec :: ReadPrec GetConsoleScreenshot
$creadPrec :: ReadPrec GetConsoleScreenshot
readList :: ReadS [GetConsoleScreenshot]
$creadList :: ReadS [GetConsoleScreenshot]
readsPrec :: Int -> ReadS GetConsoleScreenshot
$creadsPrec :: Int -> ReadS GetConsoleScreenshot
Prelude.Read, Int -> GetConsoleScreenshot -> ShowS
[GetConsoleScreenshot] -> ShowS
GetConsoleScreenshot -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetConsoleScreenshot] -> ShowS
$cshowList :: [GetConsoleScreenshot] -> ShowS
show :: GetConsoleScreenshot -> String
$cshow :: GetConsoleScreenshot -> String
showsPrec :: Int -> GetConsoleScreenshot -> ShowS
$cshowsPrec :: Int -> GetConsoleScreenshot -> ShowS
Prelude.Show, forall x. Rep GetConsoleScreenshot x -> GetConsoleScreenshot
forall x. GetConsoleScreenshot -> Rep GetConsoleScreenshot x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetConsoleScreenshot x -> GetConsoleScreenshot
$cfrom :: forall x. GetConsoleScreenshot -> Rep GetConsoleScreenshot x
Prelude.Generic)

-- |
-- Create a value of 'GetConsoleScreenshot' 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:
--
-- 'dryRun', 'getConsoleScreenshot_dryRun' - Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
--
-- 'wakeUp', 'getConsoleScreenshot_wakeUp' - When set to @true@, acts as keystroke input and wakes up an instance
-- that\'s in standby or \"sleep\" mode.
--
-- 'instanceId', 'getConsoleScreenshot_instanceId' - The ID of the instance.
newGetConsoleScreenshot ::
  -- | 'instanceId'
  Prelude.Text ->
  GetConsoleScreenshot
newGetConsoleScreenshot :: Text -> GetConsoleScreenshot
newGetConsoleScreenshot Text
pInstanceId_ =
  GetConsoleScreenshot'
    { $sel:dryRun:GetConsoleScreenshot' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:wakeUp:GetConsoleScreenshot' :: Maybe Bool
wakeUp = forall a. Maybe a
Prelude.Nothing,
      $sel:instanceId:GetConsoleScreenshot' :: Text
instanceId = Text
pInstanceId_
    }

-- | Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
getConsoleScreenshot_dryRun :: Lens.Lens' GetConsoleScreenshot (Prelude.Maybe Prelude.Bool)
getConsoleScreenshot_dryRun :: Lens' GetConsoleScreenshot (Maybe Bool)
getConsoleScreenshot_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetConsoleScreenshot' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:GetConsoleScreenshot' :: GetConsoleScreenshot -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: GetConsoleScreenshot
s@GetConsoleScreenshot' {} Maybe Bool
a -> GetConsoleScreenshot
s {$sel:dryRun:GetConsoleScreenshot' :: Maybe Bool
dryRun = Maybe Bool
a} :: GetConsoleScreenshot)

-- | When set to @true@, acts as keystroke input and wakes up an instance
-- that\'s in standby or \"sleep\" mode.
getConsoleScreenshot_wakeUp :: Lens.Lens' GetConsoleScreenshot (Prelude.Maybe Prelude.Bool)
getConsoleScreenshot_wakeUp :: Lens' GetConsoleScreenshot (Maybe Bool)
getConsoleScreenshot_wakeUp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetConsoleScreenshot' {Maybe Bool
wakeUp :: Maybe Bool
$sel:wakeUp:GetConsoleScreenshot' :: GetConsoleScreenshot -> Maybe Bool
wakeUp} -> Maybe Bool
wakeUp) (\s :: GetConsoleScreenshot
s@GetConsoleScreenshot' {} Maybe Bool
a -> GetConsoleScreenshot
s {$sel:wakeUp:GetConsoleScreenshot' :: Maybe Bool
wakeUp = Maybe Bool
a} :: GetConsoleScreenshot)

-- | The ID of the instance.
getConsoleScreenshot_instanceId :: Lens.Lens' GetConsoleScreenshot Prelude.Text
getConsoleScreenshot_instanceId :: Lens' GetConsoleScreenshot Text
getConsoleScreenshot_instanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetConsoleScreenshot' {Text
instanceId :: Text
$sel:instanceId:GetConsoleScreenshot' :: GetConsoleScreenshot -> Text
instanceId} -> Text
instanceId) (\s :: GetConsoleScreenshot
s@GetConsoleScreenshot' {} Text
a -> GetConsoleScreenshot
s {$sel:instanceId:GetConsoleScreenshot' :: Text
instanceId = Text
a} :: GetConsoleScreenshot)

instance Core.AWSRequest GetConsoleScreenshot where
  type
    AWSResponse GetConsoleScreenshot =
      GetConsoleScreenshotResponse
  request :: (Service -> Service)
-> GetConsoleScreenshot -> Request GetConsoleScreenshot
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetConsoleScreenshot
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetConsoleScreenshot)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXML
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe Text -> Maybe Text -> Int -> GetConsoleScreenshotResponse
GetConsoleScreenshotResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"imageData")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"instanceId")
            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 GetConsoleScreenshot where
  hashWithSalt :: Int -> GetConsoleScreenshot -> Int
hashWithSalt Int
_salt GetConsoleScreenshot' {Maybe Bool
Text
instanceId :: Text
wakeUp :: Maybe Bool
dryRun :: Maybe Bool
$sel:instanceId:GetConsoleScreenshot' :: GetConsoleScreenshot -> Text
$sel:wakeUp:GetConsoleScreenshot' :: GetConsoleScreenshot -> Maybe Bool
$sel:dryRun:GetConsoleScreenshot' :: GetConsoleScreenshot -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
dryRun
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
wakeUp
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
instanceId

instance Prelude.NFData GetConsoleScreenshot where
  rnf :: GetConsoleScreenshot -> ()
rnf GetConsoleScreenshot' {Maybe Bool
Text
instanceId :: Text
wakeUp :: Maybe Bool
dryRun :: Maybe Bool
$sel:instanceId:GetConsoleScreenshot' :: GetConsoleScreenshot -> Text
$sel:wakeUp:GetConsoleScreenshot' :: GetConsoleScreenshot -> Maybe Bool
$sel:dryRun:GetConsoleScreenshot' :: GetConsoleScreenshot -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
dryRun
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
wakeUp
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
instanceId

instance Data.ToHeaders GetConsoleScreenshot where
  toHeaders :: GetConsoleScreenshot -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery GetConsoleScreenshot where
  toQuery :: GetConsoleScreenshot -> QueryString
toQuery GetConsoleScreenshot' {Maybe Bool
Text
instanceId :: Text
wakeUp :: Maybe Bool
dryRun :: Maybe Bool
$sel:instanceId:GetConsoleScreenshot' :: GetConsoleScreenshot -> Text
$sel:wakeUp:GetConsoleScreenshot' :: GetConsoleScreenshot -> Maybe Bool
$sel:dryRun:GetConsoleScreenshot' :: GetConsoleScreenshot -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"GetConsoleScreenshot" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2016-11-15" :: Prelude.ByteString),
        ByteString
"DryRun" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
dryRun,
        ByteString
"WakeUp" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
wakeUp,
        ByteString
"InstanceId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
instanceId
      ]

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

-- |
-- Create a value of 'GetConsoleScreenshotResponse' 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:
--
-- 'imageData', 'getConsoleScreenshotResponse_imageData' - The data that comprises the image.
--
-- 'instanceId', 'getConsoleScreenshotResponse_instanceId' - The ID of the instance.
--
-- 'httpStatus', 'getConsoleScreenshotResponse_httpStatus' - The response's http status code.
newGetConsoleScreenshotResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetConsoleScreenshotResponse
newGetConsoleScreenshotResponse :: Int -> GetConsoleScreenshotResponse
newGetConsoleScreenshotResponse Int
pHttpStatus_ =
  GetConsoleScreenshotResponse'
    { $sel:imageData:GetConsoleScreenshotResponse' :: Maybe Text
imageData =
        forall a. Maybe a
Prelude.Nothing,
      $sel:instanceId:GetConsoleScreenshotResponse' :: Maybe Text
instanceId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetConsoleScreenshotResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The data that comprises the image.
getConsoleScreenshotResponse_imageData :: Lens.Lens' GetConsoleScreenshotResponse (Prelude.Maybe Prelude.Text)
getConsoleScreenshotResponse_imageData :: Lens' GetConsoleScreenshotResponse (Maybe Text)
getConsoleScreenshotResponse_imageData = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetConsoleScreenshotResponse' {Maybe Text
imageData :: Maybe Text
$sel:imageData:GetConsoleScreenshotResponse' :: GetConsoleScreenshotResponse -> Maybe Text
imageData} -> Maybe Text
imageData) (\s :: GetConsoleScreenshotResponse
s@GetConsoleScreenshotResponse' {} Maybe Text
a -> GetConsoleScreenshotResponse
s {$sel:imageData:GetConsoleScreenshotResponse' :: Maybe Text
imageData = Maybe Text
a} :: GetConsoleScreenshotResponse)

-- | The ID of the instance.
getConsoleScreenshotResponse_instanceId :: Lens.Lens' GetConsoleScreenshotResponse (Prelude.Maybe Prelude.Text)
getConsoleScreenshotResponse_instanceId :: Lens' GetConsoleScreenshotResponse (Maybe Text)
getConsoleScreenshotResponse_instanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetConsoleScreenshotResponse' {Maybe Text
instanceId :: Maybe Text
$sel:instanceId:GetConsoleScreenshotResponse' :: GetConsoleScreenshotResponse -> Maybe Text
instanceId} -> Maybe Text
instanceId) (\s :: GetConsoleScreenshotResponse
s@GetConsoleScreenshotResponse' {} Maybe Text
a -> GetConsoleScreenshotResponse
s {$sel:instanceId:GetConsoleScreenshotResponse' :: Maybe Text
instanceId = Maybe Text
a} :: GetConsoleScreenshotResponse)

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

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