{-# 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.Outposts.GetOutpost
-- 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 the specified Outpost.
module Amazonka.Outposts.GetOutpost
  ( -- * Creating a Request
    GetOutpost (..),
    newGetOutpost,

    -- * Request Lenses
    getOutpost_outpostId,

    -- * Destructuring the Response
    GetOutpostResponse (..),
    newGetOutpostResponse,

    -- * Response Lenses
    getOutpostResponse_outpost,
    getOutpostResponse_httpStatus,
  )
where

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

-- | /See:/ 'newGetOutpost' smart constructor.
data GetOutpost = GetOutpost'
  { -- | The ID or the Amazon Resource Name (ARN) of the Outpost.
    GetOutpost -> Text
outpostId :: Prelude.Text
  }
  deriving (GetOutpost -> GetOutpost -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetOutpost -> GetOutpost -> Bool
$c/= :: GetOutpost -> GetOutpost -> Bool
== :: GetOutpost -> GetOutpost -> Bool
$c== :: GetOutpost -> GetOutpost -> Bool
Prelude.Eq, ReadPrec [GetOutpost]
ReadPrec GetOutpost
Int -> ReadS GetOutpost
ReadS [GetOutpost]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetOutpost]
$creadListPrec :: ReadPrec [GetOutpost]
readPrec :: ReadPrec GetOutpost
$creadPrec :: ReadPrec GetOutpost
readList :: ReadS [GetOutpost]
$creadList :: ReadS [GetOutpost]
readsPrec :: Int -> ReadS GetOutpost
$creadsPrec :: Int -> ReadS GetOutpost
Prelude.Read, Int -> GetOutpost -> ShowS
[GetOutpost] -> ShowS
GetOutpost -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetOutpost] -> ShowS
$cshowList :: [GetOutpost] -> ShowS
show :: GetOutpost -> String
$cshow :: GetOutpost -> String
showsPrec :: Int -> GetOutpost -> ShowS
$cshowsPrec :: Int -> GetOutpost -> ShowS
Prelude.Show, forall x. Rep GetOutpost x -> GetOutpost
forall x. GetOutpost -> Rep GetOutpost x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetOutpost x -> GetOutpost
$cfrom :: forall x. GetOutpost -> Rep GetOutpost x
Prelude.Generic)

-- |
-- Create a value of 'GetOutpost' 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:
--
-- 'outpostId', 'getOutpost_outpostId' - The ID or the Amazon Resource Name (ARN) of the Outpost.
newGetOutpost ::
  -- | 'outpostId'
  Prelude.Text ->
  GetOutpost
newGetOutpost :: Text -> GetOutpost
newGetOutpost Text
pOutpostId_ =
  GetOutpost' {$sel:outpostId:GetOutpost' :: Text
outpostId = Text
pOutpostId_}

-- | The ID or the Amazon Resource Name (ARN) of the Outpost.
getOutpost_outpostId :: Lens.Lens' GetOutpost Prelude.Text
getOutpost_outpostId :: Lens' GetOutpost Text
getOutpost_outpostId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetOutpost' {Text
outpostId :: Text
$sel:outpostId:GetOutpost' :: GetOutpost -> Text
outpostId} -> Text
outpostId) (\s :: GetOutpost
s@GetOutpost' {} Text
a -> GetOutpost
s {$sel:outpostId:GetOutpost' :: Text
outpostId = Text
a} :: GetOutpost)

instance Core.AWSRequest GetOutpost where
  type AWSResponse GetOutpost = GetOutpostResponse
  request :: (Service -> Service) -> GetOutpost -> Request GetOutpost
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetOutpost
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetOutpost)))
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 Outpost -> Int -> GetOutpostResponse
GetOutpostResponse'
            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
"Outpost")
            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 GetOutpost where
  hashWithSalt :: Int -> GetOutpost -> Int
hashWithSalt Int
_salt GetOutpost' {Text
outpostId :: Text
$sel:outpostId:GetOutpost' :: GetOutpost -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
outpostId

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

instance Data.ToHeaders GetOutpost where
  toHeaders :: GetOutpost -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToPath GetOutpost where
  toPath :: GetOutpost -> ByteString
toPath GetOutpost' {Text
outpostId :: Text
$sel:outpostId:GetOutpost' :: GetOutpost -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"/outposts/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
outpostId]

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

-- | /See:/ 'newGetOutpostResponse' smart constructor.
data GetOutpostResponse = GetOutpostResponse'
  { GetOutpostResponse -> Maybe Outpost
outpost :: Prelude.Maybe Outpost,
    -- | The response's http status code.
    GetOutpostResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetOutpostResponse -> GetOutpostResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetOutpostResponse -> GetOutpostResponse -> Bool
$c/= :: GetOutpostResponse -> GetOutpostResponse -> Bool
== :: GetOutpostResponse -> GetOutpostResponse -> Bool
$c== :: GetOutpostResponse -> GetOutpostResponse -> Bool
Prelude.Eq, ReadPrec [GetOutpostResponse]
ReadPrec GetOutpostResponse
Int -> ReadS GetOutpostResponse
ReadS [GetOutpostResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetOutpostResponse]
$creadListPrec :: ReadPrec [GetOutpostResponse]
readPrec :: ReadPrec GetOutpostResponse
$creadPrec :: ReadPrec GetOutpostResponse
readList :: ReadS [GetOutpostResponse]
$creadList :: ReadS [GetOutpostResponse]
readsPrec :: Int -> ReadS GetOutpostResponse
$creadsPrec :: Int -> ReadS GetOutpostResponse
Prelude.Read, Int -> GetOutpostResponse -> ShowS
[GetOutpostResponse] -> ShowS
GetOutpostResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetOutpostResponse] -> ShowS
$cshowList :: [GetOutpostResponse] -> ShowS
show :: GetOutpostResponse -> String
$cshow :: GetOutpostResponse -> String
showsPrec :: Int -> GetOutpostResponse -> ShowS
$cshowsPrec :: Int -> GetOutpostResponse -> ShowS
Prelude.Show, forall x. Rep GetOutpostResponse x -> GetOutpostResponse
forall x. GetOutpostResponse -> Rep GetOutpostResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetOutpostResponse x -> GetOutpostResponse
$cfrom :: forall x. GetOutpostResponse -> Rep GetOutpostResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetOutpostResponse' 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:
--
-- 'outpost', 'getOutpostResponse_outpost' - Undocumented member.
--
-- 'httpStatus', 'getOutpostResponse_httpStatus' - The response's http status code.
newGetOutpostResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetOutpostResponse
newGetOutpostResponse :: Int -> GetOutpostResponse
newGetOutpostResponse Int
pHttpStatus_ =
  GetOutpostResponse'
    { $sel:outpost:GetOutpostResponse' :: Maybe Outpost
outpost = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetOutpostResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Undocumented member.
getOutpostResponse_outpost :: Lens.Lens' GetOutpostResponse (Prelude.Maybe Outpost)
getOutpostResponse_outpost :: Lens' GetOutpostResponse (Maybe Outpost)
getOutpostResponse_outpost = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetOutpostResponse' {Maybe Outpost
outpost :: Maybe Outpost
$sel:outpost:GetOutpostResponse' :: GetOutpostResponse -> Maybe Outpost
outpost} -> Maybe Outpost
outpost) (\s :: GetOutpostResponse
s@GetOutpostResponse' {} Maybe Outpost
a -> GetOutpostResponse
s {$sel:outpost:GetOutpostResponse' :: Maybe Outpost
outpost = Maybe Outpost
a} :: GetOutpostResponse)

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

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