{-# 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.Route53AutoNaming.GetInstance
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets information about a specified instance.
module Amazonka.Route53AutoNaming.GetInstance
  ( -- * Creating a Request
    GetInstance (..),
    newGetInstance,

    -- * Request Lenses
    getInstance_serviceId,
    getInstance_instanceId,

    -- * Destructuring the Response
    GetInstanceResponse (..),
    newGetInstanceResponse,

    -- * Response Lenses
    getInstanceResponse_instance,
    getInstanceResponse_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.Route53AutoNaming.Types

-- | /See:/ 'newGetInstance' smart constructor.
data GetInstance = GetInstance'
  { -- | The ID of the service that the instance is associated with.
    GetInstance -> Text
serviceId :: Prelude.Text,
    -- | The ID of the instance that you want to get information about.
    GetInstance -> Text
instanceId :: Prelude.Text
  }
  deriving (GetInstance -> GetInstance -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetInstance -> GetInstance -> Bool
$c/= :: GetInstance -> GetInstance -> Bool
== :: GetInstance -> GetInstance -> Bool
$c== :: GetInstance -> GetInstance -> Bool
Prelude.Eq, ReadPrec [GetInstance]
ReadPrec GetInstance
Int -> ReadS GetInstance
ReadS [GetInstance]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetInstance]
$creadListPrec :: ReadPrec [GetInstance]
readPrec :: ReadPrec GetInstance
$creadPrec :: ReadPrec GetInstance
readList :: ReadS [GetInstance]
$creadList :: ReadS [GetInstance]
readsPrec :: Int -> ReadS GetInstance
$creadsPrec :: Int -> ReadS GetInstance
Prelude.Read, Int -> GetInstance -> ShowS
[GetInstance] -> ShowS
GetInstance -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetInstance] -> ShowS
$cshowList :: [GetInstance] -> ShowS
show :: GetInstance -> String
$cshow :: GetInstance -> String
showsPrec :: Int -> GetInstance -> ShowS
$cshowsPrec :: Int -> GetInstance -> ShowS
Prelude.Show, forall x. Rep GetInstance x -> GetInstance
forall x. GetInstance -> Rep GetInstance x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetInstance x -> GetInstance
$cfrom :: forall x. GetInstance -> Rep GetInstance x
Prelude.Generic)

-- |
-- Create a value of 'GetInstance' 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:
--
-- 'serviceId', 'getInstance_serviceId' - The ID of the service that the instance is associated with.
--
-- 'instanceId', 'getInstance_instanceId' - The ID of the instance that you want to get information about.
newGetInstance ::
  -- | 'serviceId'
  Prelude.Text ->
  -- | 'instanceId'
  Prelude.Text ->
  GetInstance
newGetInstance :: Text -> Text -> GetInstance
newGetInstance Text
pServiceId_ Text
pInstanceId_ =
  GetInstance'
    { $sel:serviceId:GetInstance' :: Text
serviceId = Text
pServiceId_,
      $sel:instanceId:GetInstance' :: Text
instanceId = Text
pInstanceId_
    }

-- | The ID of the service that the instance is associated with.
getInstance_serviceId :: Lens.Lens' GetInstance Prelude.Text
getInstance_serviceId :: Lens' GetInstance Text
getInstance_serviceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetInstance' {Text
serviceId :: Text
$sel:serviceId:GetInstance' :: GetInstance -> Text
serviceId} -> Text
serviceId) (\s :: GetInstance
s@GetInstance' {} Text
a -> GetInstance
s {$sel:serviceId:GetInstance' :: Text
serviceId = Text
a} :: GetInstance)

-- | The ID of the instance that you want to get information about.
getInstance_instanceId :: Lens.Lens' GetInstance Prelude.Text
getInstance_instanceId :: Lens' GetInstance Text
getInstance_instanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetInstance' {Text
instanceId :: Text
$sel:instanceId:GetInstance' :: GetInstance -> Text
instanceId} -> Text
instanceId) (\s :: GetInstance
s@GetInstance' {} Text
a -> GetInstance
s {$sel:instanceId:GetInstance' :: Text
instanceId = Text
a} :: GetInstance)

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

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

instance Data.ToHeaders GetInstance where
  toHeaders :: GetInstance -> 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
"Route53AutoNaming_v20170314.GetInstance" ::
                          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 GetInstance where
  toJSON :: GetInstance -> Value
toJSON GetInstance' {Text
instanceId :: Text
serviceId :: Text
$sel:instanceId:GetInstance' :: GetInstance -> Text
$sel:serviceId:GetInstance' :: GetInstance -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"ServiceId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
serviceId),
            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 GetInstance where
  toPath :: GetInstance -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newGetInstanceResponse' smart constructor.
data GetInstanceResponse = GetInstanceResponse'
  { -- | A complex type that contains information about a specified instance.
    GetInstanceResponse -> Maybe Instance
instance' :: Prelude.Maybe Instance,
    -- | The response's http status code.
    GetInstanceResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetInstanceResponse -> GetInstanceResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetInstanceResponse -> GetInstanceResponse -> Bool
$c/= :: GetInstanceResponse -> GetInstanceResponse -> Bool
== :: GetInstanceResponse -> GetInstanceResponse -> Bool
$c== :: GetInstanceResponse -> GetInstanceResponse -> Bool
Prelude.Eq, ReadPrec [GetInstanceResponse]
ReadPrec GetInstanceResponse
Int -> ReadS GetInstanceResponse
ReadS [GetInstanceResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetInstanceResponse]
$creadListPrec :: ReadPrec [GetInstanceResponse]
readPrec :: ReadPrec GetInstanceResponse
$creadPrec :: ReadPrec GetInstanceResponse
readList :: ReadS [GetInstanceResponse]
$creadList :: ReadS [GetInstanceResponse]
readsPrec :: Int -> ReadS GetInstanceResponse
$creadsPrec :: Int -> ReadS GetInstanceResponse
Prelude.Read, Int -> GetInstanceResponse -> ShowS
[GetInstanceResponse] -> ShowS
GetInstanceResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetInstanceResponse] -> ShowS
$cshowList :: [GetInstanceResponse] -> ShowS
show :: GetInstanceResponse -> String
$cshow :: GetInstanceResponse -> String
showsPrec :: Int -> GetInstanceResponse -> ShowS
$cshowsPrec :: Int -> GetInstanceResponse -> ShowS
Prelude.Show, forall x. Rep GetInstanceResponse x -> GetInstanceResponse
forall x. GetInstanceResponse -> Rep GetInstanceResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetInstanceResponse x -> GetInstanceResponse
$cfrom :: forall x. GetInstanceResponse -> Rep GetInstanceResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetInstanceResponse' 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:
--
-- 'instance'', 'getInstanceResponse_instance' - A complex type that contains information about a specified instance.
--
-- 'httpStatus', 'getInstanceResponse_httpStatus' - The response's http status code.
newGetInstanceResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetInstanceResponse
newGetInstanceResponse :: Int -> GetInstanceResponse
newGetInstanceResponse Int
pHttpStatus_ =
  GetInstanceResponse'
    { $sel:instance':GetInstanceResponse' :: Maybe Instance
instance' = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetInstanceResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A complex type that contains information about a specified instance.
getInstanceResponse_instance :: Lens.Lens' GetInstanceResponse (Prelude.Maybe Instance)
getInstanceResponse_instance :: Lens' GetInstanceResponse (Maybe Instance)
getInstanceResponse_instance = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetInstanceResponse' {Maybe Instance
instance' :: Maybe Instance
$sel:instance':GetInstanceResponse' :: GetInstanceResponse -> Maybe Instance
instance'} -> Maybe Instance
instance') (\s :: GetInstanceResponse
s@GetInstanceResponse' {} Maybe Instance
a -> GetInstanceResponse
s {$sel:instance':GetInstanceResponse' :: Maybe Instance
instance' = Maybe Instance
a} :: GetInstanceResponse)

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

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