{-# 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.Lightsail.GetOperation
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns information about a specific operation. Operations include
-- events such as when you create an instance, allocate a static IP, attach
-- a static IP, and so on.
module Amazonka.Lightsail.GetOperation
  ( -- * Creating a Request
    GetOperation (..),
    newGetOperation,

    -- * Request Lenses
    getOperation_operationId,

    -- * Destructuring the Response
    GetOperationResponse (..),
    newGetOperationResponse,

    -- * Response Lenses
    getOperationResponse_operation,
    getOperationResponse_httpStatus,
  )
where

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

-- | /See:/ 'newGetOperation' smart constructor.
data GetOperation = GetOperation'
  { -- | A GUID used to identify the operation.
    GetOperation -> Text
operationId :: Prelude.Text
  }
  deriving (GetOperation -> GetOperation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetOperation -> GetOperation -> Bool
$c/= :: GetOperation -> GetOperation -> Bool
== :: GetOperation -> GetOperation -> Bool
$c== :: GetOperation -> GetOperation -> Bool
Prelude.Eq, ReadPrec [GetOperation]
ReadPrec GetOperation
Int -> ReadS GetOperation
ReadS [GetOperation]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetOperation]
$creadListPrec :: ReadPrec [GetOperation]
readPrec :: ReadPrec GetOperation
$creadPrec :: ReadPrec GetOperation
readList :: ReadS [GetOperation]
$creadList :: ReadS [GetOperation]
readsPrec :: Int -> ReadS GetOperation
$creadsPrec :: Int -> ReadS GetOperation
Prelude.Read, Int -> GetOperation -> ShowS
[GetOperation] -> ShowS
GetOperation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetOperation] -> ShowS
$cshowList :: [GetOperation] -> ShowS
show :: GetOperation -> String
$cshow :: GetOperation -> String
showsPrec :: Int -> GetOperation -> ShowS
$cshowsPrec :: Int -> GetOperation -> ShowS
Prelude.Show, forall x. Rep GetOperation x -> GetOperation
forall x. GetOperation -> Rep GetOperation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetOperation x -> GetOperation
$cfrom :: forall x. GetOperation -> Rep GetOperation x
Prelude.Generic)

-- |
-- Create a value of 'GetOperation' 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:
--
-- 'operationId', 'getOperation_operationId' - A GUID used to identify the operation.
newGetOperation ::
  -- | 'operationId'
  Prelude.Text ->
  GetOperation
newGetOperation :: Text -> GetOperation
newGetOperation Text
pOperationId_ =
  GetOperation' {$sel:operationId:GetOperation' :: Text
operationId = Text
pOperationId_}

-- | A GUID used to identify the operation.
getOperation_operationId :: Lens.Lens' GetOperation Prelude.Text
getOperation_operationId :: Lens' GetOperation Text
getOperation_operationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetOperation' {Text
operationId :: Text
$sel:operationId:GetOperation' :: GetOperation -> Text
operationId} -> Text
operationId) (\s :: GetOperation
s@GetOperation' {} Text
a -> GetOperation
s {$sel:operationId:GetOperation' :: Text
operationId = Text
a} :: GetOperation)

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

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

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

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

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

-- | /See:/ 'newGetOperationResponse' smart constructor.
data GetOperationResponse = GetOperationResponse'
  { -- | An array of objects that describe the result of the action, such as the
    -- status of the request, the timestamp of the request, and the resources
    -- affected by the request.
    GetOperationResponse -> Maybe Operation
operation :: Prelude.Maybe Operation,
    -- | The response's http status code.
    GetOperationResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetOperationResponse -> GetOperationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetOperationResponse -> GetOperationResponse -> Bool
$c/= :: GetOperationResponse -> GetOperationResponse -> Bool
== :: GetOperationResponse -> GetOperationResponse -> Bool
$c== :: GetOperationResponse -> GetOperationResponse -> Bool
Prelude.Eq, ReadPrec [GetOperationResponse]
ReadPrec GetOperationResponse
Int -> ReadS GetOperationResponse
ReadS [GetOperationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetOperationResponse]
$creadListPrec :: ReadPrec [GetOperationResponse]
readPrec :: ReadPrec GetOperationResponse
$creadPrec :: ReadPrec GetOperationResponse
readList :: ReadS [GetOperationResponse]
$creadList :: ReadS [GetOperationResponse]
readsPrec :: Int -> ReadS GetOperationResponse
$creadsPrec :: Int -> ReadS GetOperationResponse
Prelude.Read, Int -> GetOperationResponse -> ShowS
[GetOperationResponse] -> ShowS
GetOperationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetOperationResponse] -> ShowS
$cshowList :: [GetOperationResponse] -> ShowS
show :: GetOperationResponse -> String
$cshow :: GetOperationResponse -> String
showsPrec :: Int -> GetOperationResponse -> ShowS
$cshowsPrec :: Int -> GetOperationResponse -> ShowS
Prelude.Show, forall x. Rep GetOperationResponse x -> GetOperationResponse
forall x. GetOperationResponse -> Rep GetOperationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetOperationResponse x -> GetOperationResponse
$cfrom :: forall x. GetOperationResponse -> Rep GetOperationResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetOperationResponse' 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:
--
-- 'operation', 'getOperationResponse_operation' - An array of objects that describe the result of the action, such as the
-- status of the request, the timestamp of the request, and the resources
-- affected by the request.
--
-- 'httpStatus', 'getOperationResponse_httpStatus' - The response's http status code.
newGetOperationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetOperationResponse
newGetOperationResponse :: Int -> GetOperationResponse
newGetOperationResponse Int
pHttpStatus_ =
  GetOperationResponse'
    { $sel:operation:GetOperationResponse' :: Maybe Operation
operation = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetOperationResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An array of objects that describe the result of the action, such as the
-- status of the request, the timestamp of the request, and the resources
-- affected by the request.
getOperationResponse_operation :: Lens.Lens' GetOperationResponse (Prelude.Maybe Operation)
getOperationResponse_operation :: Lens' GetOperationResponse (Maybe Operation)
getOperationResponse_operation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetOperationResponse' {Maybe Operation
operation :: Maybe Operation
$sel:operation:GetOperationResponse' :: GetOperationResponse -> Maybe Operation
operation} -> Maybe Operation
operation) (\s :: GetOperationResponse
s@GetOperationResponse' {} Maybe Operation
a -> GetOperationResponse
s {$sel:operation:GetOperationResponse' :: Maybe Operation
operation = Maybe Operation
a} :: GetOperationResponse)

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

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