{-# 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.CodeStarConnections.GetHost
-- 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 the host ARN and details such as status, provider type,
-- endpoint, and, if applicable, the VPC configuration.
module Amazonka.CodeStarConnections.GetHost
  ( -- * Creating a Request
    GetHost (..),
    newGetHost,

    -- * Request Lenses
    getHost_hostArn,

    -- * Destructuring the Response
    GetHostResponse (..),
    newGetHostResponse,

    -- * Response Lenses
    getHostResponse_name,
    getHostResponse_providerEndpoint,
    getHostResponse_providerType,
    getHostResponse_status,
    getHostResponse_vpcConfiguration,
    getHostResponse_httpStatus,
  )
where

import Amazonka.CodeStarConnections.Types
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

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

-- |
-- Create a value of 'GetHost' 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:
--
-- 'hostArn', 'getHost_hostArn' - The Amazon Resource Name (ARN) of the requested host.
newGetHost ::
  -- | 'hostArn'
  Prelude.Text ->
  GetHost
newGetHost :: Text -> GetHost
newGetHost Text
pHostArn_ = GetHost' {$sel:hostArn:GetHost' :: Text
hostArn = Text
pHostArn_}

-- | The Amazon Resource Name (ARN) of the requested host.
getHost_hostArn :: Lens.Lens' GetHost Prelude.Text
getHost_hostArn :: Lens' GetHost Text
getHost_hostArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetHost' {Text
hostArn :: Text
$sel:hostArn:GetHost' :: GetHost -> Text
hostArn} -> Text
hostArn) (\s :: GetHost
s@GetHost' {} Text
a -> GetHost
s {$sel:hostArn:GetHost' :: Text
hostArn = Text
a} :: GetHost)

instance Core.AWSRequest GetHost where
  type AWSResponse GetHost = GetHostResponse
  request :: (Service -> Service) -> GetHost -> Request GetHost
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 GetHost
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetHost)))
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 Text
-> Maybe Text
-> Maybe ProviderType
-> Maybe Text
-> Maybe VpcConfiguration
-> Int
-> GetHostResponse
GetHostResponse'
            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
"Name")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ProviderEndpoint")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ProviderType")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Status")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"VpcConfiguration")
            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 GetHost where
  hashWithSalt :: Int -> GetHost -> Int
hashWithSalt Int
_salt GetHost' {Text
hostArn :: Text
$sel:hostArn:GetHost' :: GetHost -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
hostArn

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

instance Data.ToHeaders GetHost where
  toHeaders :: GetHost -> 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
"com.amazonaws.codestar.connections.CodeStar_connections_20191201.GetHost" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.0" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON GetHost where
  toJSON :: GetHost -> Value
toJSON GetHost' {Text
hostArn :: Text
$sel:hostArn:GetHost' :: GetHost -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"HostArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
hostArn)]
      )

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

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

-- | /See:/ 'newGetHostResponse' smart constructor.
data GetHostResponse = GetHostResponse'
  { -- | The name of the requested host.
    GetHostResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The endpoint of the infrastructure represented by the requested host.
    GetHostResponse -> Maybe Text
providerEndpoint :: Prelude.Maybe Prelude.Text,
    -- | The provider type of the requested host, such as GitHub Enterprise
    -- Server.
    GetHostResponse -> Maybe ProviderType
providerType :: Prelude.Maybe ProviderType,
    -- | The status of the requested host.
    GetHostResponse -> Maybe Text
status :: Prelude.Maybe Prelude.Text,
    -- | The VPC configuration of the requested host.
    GetHostResponse -> Maybe VpcConfiguration
vpcConfiguration :: Prelude.Maybe VpcConfiguration,
    -- | The response's http status code.
    GetHostResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetHostResponse -> GetHostResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetHostResponse -> GetHostResponse -> Bool
$c/= :: GetHostResponse -> GetHostResponse -> Bool
== :: GetHostResponse -> GetHostResponse -> Bool
$c== :: GetHostResponse -> GetHostResponse -> Bool
Prelude.Eq, ReadPrec [GetHostResponse]
ReadPrec GetHostResponse
Int -> ReadS GetHostResponse
ReadS [GetHostResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetHostResponse]
$creadListPrec :: ReadPrec [GetHostResponse]
readPrec :: ReadPrec GetHostResponse
$creadPrec :: ReadPrec GetHostResponse
readList :: ReadS [GetHostResponse]
$creadList :: ReadS [GetHostResponse]
readsPrec :: Int -> ReadS GetHostResponse
$creadsPrec :: Int -> ReadS GetHostResponse
Prelude.Read, Int -> GetHostResponse -> ShowS
[GetHostResponse] -> ShowS
GetHostResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetHostResponse] -> ShowS
$cshowList :: [GetHostResponse] -> ShowS
show :: GetHostResponse -> String
$cshow :: GetHostResponse -> String
showsPrec :: Int -> GetHostResponse -> ShowS
$cshowsPrec :: Int -> GetHostResponse -> ShowS
Prelude.Show, forall x. Rep GetHostResponse x -> GetHostResponse
forall x. GetHostResponse -> Rep GetHostResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetHostResponse x -> GetHostResponse
$cfrom :: forall x. GetHostResponse -> Rep GetHostResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetHostResponse' 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:
--
-- 'name', 'getHostResponse_name' - The name of the requested host.
--
-- 'providerEndpoint', 'getHostResponse_providerEndpoint' - The endpoint of the infrastructure represented by the requested host.
--
-- 'providerType', 'getHostResponse_providerType' - The provider type of the requested host, such as GitHub Enterprise
-- Server.
--
-- 'status', 'getHostResponse_status' - The status of the requested host.
--
-- 'vpcConfiguration', 'getHostResponse_vpcConfiguration' - The VPC configuration of the requested host.
--
-- 'httpStatus', 'getHostResponse_httpStatus' - The response's http status code.
newGetHostResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetHostResponse
newGetHostResponse :: Int -> GetHostResponse
newGetHostResponse Int
pHttpStatus_ =
  GetHostResponse'
    { $sel:name:GetHostResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:providerEndpoint:GetHostResponse' :: Maybe Text
providerEndpoint = forall a. Maybe a
Prelude.Nothing,
      $sel:providerType:GetHostResponse' :: Maybe ProviderType
providerType = forall a. Maybe a
Prelude.Nothing,
      $sel:status:GetHostResponse' :: Maybe Text
status = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcConfiguration:GetHostResponse' :: Maybe VpcConfiguration
vpcConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetHostResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The name of the requested host.
getHostResponse_name :: Lens.Lens' GetHostResponse (Prelude.Maybe Prelude.Text)
getHostResponse_name :: Lens' GetHostResponse (Maybe Text)
getHostResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetHostResponse' {Maybe Text
name :: Maybe Text
$sel:name:GetHostResponse' :: GetHostResponse -> Maybe Text
name} -> Maybe Text
name) (\s :: GetHostResponse
s@GetHostResponse' {} Maybe Text
a -> GetHostResponse
s {$sel:name:GetHostResponse' :: Maybe Text
name = Maybe Text
a} :: GetHostResponse)

-- | The endpoint of the infrastructure represented by the requested host.
getHostResponse_providerEndpoint :: Lens.Lens' GetHostResponse (Prelude.Maybe Prelude.Text)
getHostResponse_providerEndpoint :: Lens' GetHostResponse (Maybe Text)
getHostResponse_providerEndpoint = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetHostResponse' {Maybe Text
providerEndpoint :: Maybe Text
$sel:providerEndpoint:GetHostResponse' :: GetHostResponse -> Maybe Text
providerEndpoint} -> Maybe Text
providerEndpoint) (\s :: GetHostResponse
s@GetHostResponse' {} Maybe Text
a -> GetHostResponse
s {$sel:providerEndpoint:GetHostResponse' :: Maybe Text
providerEndpoint = Maybe Text
a} :: GetHostResponse)

-- | The provider type of the requested host, such as GitHub Enterprise
-- Server.
getHostResponse_providerType :: Lens.Lens' GetHostResponse (Prelude.Maybe ProviderType)
getHostResponse_providerType :: Lens' GetHostResponse (Maybe ProviderType)
getHostResponse_providerType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetHostResponse' {Maybe ProviderType
providerType :: Maybe ProviderType
$sel:providerType:GetHostResponse' :: GetHostResponse -> Maybe ProviderType
providerType} -> Maybe ProviderType
providerType) (\s :: GetHostResponse
s@GetHostResponse' {} Maybe ProviderType
a -> GetHostResponse
s {$sel:providerType:GetHostResponse' :: Maybe ProviderType
providerType = Maybe ProviderType
a} :: GetHostResponse)

-- | The status of the requested host.
getHostResponse_status :: Lens.Lens' GetHostResponse (Prelude.Maybe Prelude.Text)
getHostResponse_status :: Lens' GetHostResponse (Maybe Text)
getHostResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetHostResponse' {Maybe Text
status :: Maybe Text
$sel:status:GetHostResponse' :: GetHostResponse -> Maybe Text
status} -> Maybe Text
status) (\s :: GetHostResponse
s@GetHostResponse' {} Maybe Text
a -> GetHostResponse
s {$sel:status:GetHostResponse' :: Maybe Text
status = Maybe Text
a} :: GetHostResponse)

-- | The VPC configuration of the requested host.
getHostResponse_vpcConfiguration :: Lens.Lens' GetHostResponse (Prelude.Maybe VpcConfiguration)
getHostResponse_vpcConfiguration :: Lens' GetHostResponse (Maybe VpcConfiguration)
getHostResponse_vpcConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetHostResponse' {Maybe VpcConfiguration
vpcConfiguration :: Maybe VpcConfiguration
$sel:vpcConfiguration:GetHostResponse' :: GetHostResponse -> Maybe VpcConfiguration
vpcConfiguration} -> Maybe VpcConfiguration
vpcConfiguration) (\s :: GetHostResponse
s@GetHostResponse' {} Maybe VpcConfiguration
a -> GetHostResponse
s {$sel:vpcConfiguration:GetHostResponse' :: Maybe VpcConfiguration
vpcConfiguration = Maybe VpcConfiguration
a} :: GetHostResponse)

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

instance Prelude.NFData GetHostResponse where
  rnf :: GetHostResponse -> ()
rnf GetHostResponse' {Int
Maybe Text
Maybe ProviderType
Maybe VpcConfiguration
httpStatus :: Int
vpcConfiguration :: Maybe VpcConfiguration
status :: Maybe Text
providerType :: Maybe ProviderType
providerEndpoint :: Maybe Text
name :: Maybe Text
$sel:httpStatus:GetHostResponse' :: GetHostResponse -> Int
$sel:vpcConfiguration:GetHostResponse' :: GetHostResponse -> Maybe VpcConfiguration
$sel:status:GetHostResponse' :: GetHostResponse -> Maybe Text
$sel:providerType:GetHostResponse' :: GetHostResponse -> Maybe ProviderType
$sel:providerEndpoint:GetHostResponse' :: GetHostResponse -> Maybe Text
$sel:name:GetHostResponse' :: GetHostResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
providerEndpoint
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ProviderType
providerType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe VpcConfiguration
vpcConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus