{-# 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.GetLoadBalancer
-- 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 the specified Lightsail load balancer.
module Amazonka.Lightsail.GetLoadBalancer
  ( -- * Creating a Request
    GetLoadBalancer (..),
    newGetLoadBalancer,

    -- * Request Lenses
    getLoadBalancer_loadBalancerName,

    -- * Destructuring the Response
    GetLoadBalancerResponse (..),
    newGetLoadBalancerResponse,

    -- * Response Lenses
    getLoadBalancerResponse_loadBalancer,
    getLoadBalancerResponse_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:/ 'newGetLoadBalancer' smart constructor.
data GetLoadBalancer = GetLoadBalancer'
  { -- | The name of the load balancer.
    GetLoadBalancer -> Text
loadBalancerName :: Prelude.Text
  }
  deriving (GetLoadBalancer -> GetLoadBalancer -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetLoadBalancer -> GetLoadBalancer -> Bool
$c/= :: GetLoadBalancer -> GetLoadBalancer -> Bool
== :: GetLoadBalancer -> GetLoadBalancer -> Bool
$c== :: GetLoadBalancer -> GetLoadBalancer -> Bool
Prelude.Eq, ReadPrec [GetLoadBalancer]
ReadPrec GetLoadBalancer
Int -> ReadS GetLoadBalancer
ReadS [GetLoadBalancer]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetLoadBalancer]
$creadListPrec :: ReadPrec [GetLoadBalancer]
readPrec :: ReadPrec GetLoadBalancer
$creadPrec :: ReadPrec GetLoadBalancer
readList :: ReadS [GetLoadBalancer]
$creadList :: ReadS [GetLoadBalancer]
readsPrec :: Int -> ReadS GetLoadBalancer
$creadsPrec :: Int -> ReadS GetLoadBalancer
Prelude.Read, Int -> GetLoadBalancer -> ShowS
[GetLoadBalancer] -> ShowS
GetLoadBalancer -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetLoadBalancer] -> ShowS
$cshowList :: [GetLoadBalancer] -> ShowS
show :: GetLoadBalancer -> String
$cshow :: GetLoadBalancer -> String
showsPrec :: Int -> GetLoadBalancer -> ShowS
$cshowsPrec :: Int -> GetLoadBalancer -> ShowS
Prelude.Show, forall x. Rep GetLoadBalancer x -> GetLoadBalancer
forall x. GetLoadBalancer -> Rep GetLoadBalancer x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetLoadBalancer x -> GetLoadBalancer
$cfrom :: forall x. GetLoadBalancer -> Rep GetLoadBalancer x
Prelude.Generic)

-- |
-- Create a value of 'GetLoadBalancer' 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:
--
-- 'loadBalancerName', 'getLoadBalancer_loadBalancerName' - The name of the load balancer.
newGetLoadBalancer ::
  -- | 'loadBalancerName'
  Prelude.Text ->
  GetLoadBalancer
newGetLoadBalancer :: Text -> GetLoadBalancer
newGetLoadBalancer Text
pLoadBalancerName_ =
  GetLoadBalancer'
    { $sel:loadBalancerName:GetLoadBalancer' :: Text
loadBalancerName =
        Text
pLoadBalancerName_
    }

-- | The name of the load balancer.
getLoadBalancer_loadBalancerName :: Lens.Lens' GetLoadBalancer Prelude.Text
getLoadBalancer_loadBalancerName :: Lens' GetLoadBalancer Text
getLoadBalancer_loadBalancerName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetLoadBalancer' {Text
loadBalancerName :: Text
$sel:loadBalancerName:GetLoadBalancer' :: GetLoadBalancer -> Text
loadBalancerName} -> Text
loadBalancerName) (\s :: GetLoadBalancer
s@GetLoadBalancer' {} Text
a -> GetLoadBalancer
s {$sel:loadBalancerName:GetLoadBalancer' :: Text
loadBalancerName = Text
a} :: GetLoadBalancer)

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

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

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

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

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

-- | /See:/ 'newGetLoadBalancerResponse' smart constructor.
data GetLoadBalancerResponse = GetLoadBalancerResponse'
  { -- | An object containing information about your load balancer.
    GetLoadBalancerResponse -> Maybe LoadBalancer
loadBalancer :: Prelude.Maybe LoadBalancer,
    -- | The response's http status code.
    GetLoadBalancerResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetLoadBalancerResponse -> GetLoadBalancerResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetLoadBalancerResponse -> GetLoadBalancerResponse -> Bool
$c/= :: GetLoadBalancerResponse -> GetLoadBalancerResponse -> Bool
== :: GetLoadBalancerResponse -> GetLoadBalancerResponse -> Bool
$c== :: GetLoadBalancerResponse -> GetLoadBalancerResponse -> Bool
Prelude.Eq, ReadPrec [GetLoadBalancerResponse]
ReadPrec GetLoadBalancerResponse
Int -> ReadS GetLoadBalancerResponse
ReadS [GetLoadBalancerResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetLoadBalancerResponse]
$creadListPrec :: ReadPrec [GetLoadBalancerResponse]
readPrec :: ReadPrec GetLoadBalancerResponse
$creadPrec :: ReadPrec GetLoadBalancerResponse
readList :: ReadS [GetLoadBalancerResponse]
$creadList :: ReadS [GetLoadBalancerResponse]
readsPrec :: Int -> ReadS GetLoadBalancerResponse
$creadsPrec :: Int -> ReadS GetLoadBalancerResponse
Prelude.Read, Int -> GetLoadBalancerResponse -> ShowS
[GetLoadBalancerResponse] -> ShowS
GetLoadBalancerResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetLoadBalancerResponse] -> ShowS
$cshowList :: [GetLoadBalancerResponse] -> ShowS
show :: GetLoadBalancerResponse -> String
$cshow :: GetLoadBalancerResponse -> String
showsPrec :: Int -> GetLoadBalancerResponse -> ShowS
$cshowsPrec :: Int -> GetLoadBalancerResponse -> ShowS
Prelude.Show, forall x. Rep GetLoadBalancerResponse x -> GetLoadBalancerResponse
forall x. GetLoadBalancerResponse -> Rep GetLoadBalancerResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetLoadBalancerResponse x -> GetLoadBalancerResponse
$cfrom :: forall x. GetLoadBalancerResponse -> Rep GetLoadBalancerResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetLoadBalancerResponse' 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:
--
-- 'loadBalancer', 'getLoadBalancerResponse_loadBalancer' - An object containing information about your load balancer.
--
-- 'httpStatus', 'getLoadBalancerResponse_httpStatus' - The response's http status code.
newGetLoadBalancerResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetLoadBalancerResponse
newGetLoadBalancerResponse :: Int -> GetLoadBalancerResponse
newGetLoadBalancerResponse Int
pHttpStatus_ =
  GetLoadBalancerResponse'
    { $sel:loadBalancer:GetLoadBalancerResponse' :: Maybe LoadBalancer
loadBalancer =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetLoadBalancerResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An object containing information about your load balancer.
getLoadBalancerResponse_loadBalancer :: Lens.Lens' GetLoadBalancerResponse (Prelude.Maybe LoadBalancer)
getLoadBalancerResponse_loadBalancer :: Lens' GetLoadBalancerResponse (Maybe LoadBalancer)
getLoadBalancerResponse_loadBalancer = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetLoadBalancerResponse' {Maybe LoadBalancer
loadBalancer :: Maybe LoadBalancer
$sel:loadBalancer:GetLoadBalancerResponse' :: GetLoadBalancerResponse -> Maybe LoadBalancer
loadBalancer} -> Maybe LoadBalancer
loadBalancer) (\s :: GetLoadBalancerResponse
s@GetLoadBalancerResponse' {} Maybe LoadBalancer
a -> GetLoadBalancerResponse
s {$sel:loadBalancer:GetLoadBalancerResponse' :: Maybe LoadBalancer
loadBalancer = Maybe LoadBalancer
a} :: GetLoadBalancerResponse)

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

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