{-# 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.DataSync.DescribeAgent
-- 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 metadata such as the name, the network interfaces, and the
-- status (that is, whether the agent is running or not) for an agent. To
-- specify which agent to describe, use the Amazon Resource Name (ARN) of
-- the agent in your request.
module Amazonka.DataSync.DescribeAgent
  ( -- * Creating a Request
    DescribeAgent (..),
    newDescribeAgent,

    -- * Request Lenses
    describeAgent_agentArn,

    -- * Destructuring the Response
    DescribeAgentResponse (..),
    newDescribeAgentResponse,

    -- * Response Lenses
    describeAgentResponse_agentArn,
    describeAgentResponse_creationTime,
    describeAgentResponse_endpointType,
    describeAgentResponse_lastConnectionTime,
    describeAgentResponse_name,
    describeAgentResponse_privateLinkConfig,
    describeAgentResponse_status,
    describeAgentResponse_httpStatus,
  )
where

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

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

-- |
-- Create a value of 'DescribeAgent' 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:
--
-- 'agentArn', 'describeAgent_agentArn' - The Amazon Resource Name (ARN) of the agent to describe.
newDescribeAgent ::
  -- | 'agentArn'
  Prelude.Text ->
  DescribeAgent
newDescribeAgent :: Text -> DescribeAgent
newDescribeAgent Text
pAgentArn_ =
  DescribeAgent' {$sel:agentArn:DescribeAgent' :: Text
agentArn = Text
pAgentArn_}

-- | The Amazon Resource Name (ARN) of the agent to describe.
describeAgent_agentArn :: Lens.Lens' DescribeAgent Prelude.Text
describeAgent_agentArn :: Lens' DescribeAgent Text
describeAgent_agentArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAgent' {Text
agentArn :: Text
$sel:agentArn:DescribeAgent' :: DescribeAgent -> Text
agentArn} -> Text
agentArn) (\s :: DescribeAgent
s@DescribeAgent' {} Text
a -> DescribeAgent
s {$sel:agentArn:DescribeAgent' :: Text
agentArn = Text
a} :: DescribeAgent)

instance Core.AWSRequest DescribeAgent where
  type
    AWSResponse DescribeAgent =
      DescribeAgentResponse
  request :: (Service -> Service) -> DescribeAgent -> Request DescribeAgent
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 DescribeAgent
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DescribeAgent)))
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 POSIX
-> Maybe EndpointType
-> Maybe POSIX
-> Maybe Text
-> Maybe PrivateLinkConfig
-> Maybe AgentStatus
-> Int
-> DescribeAgentResponse
DescribeAgentResponse'
            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
"AgentArn")
            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
"CreationTime")
            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
"EndpointType")
            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
"LastConnectionTime")
            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
"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
"PrivateLinkConfig")
            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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable DescribeAgent where
  hashWithSalt :: Int -> DescribeAgent -> Int
hashWithSalt Int
_salt DescribeAgent' {Text
agentArn :: Text
$sel:agentArn:DescribeAgent' :: DescribeAgent -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
agentArn

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

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

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

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

-- | DescribeAgentResponse
--
-- /See:/ 'newDescribeAgentResponse' smart constructor.
data DescribeAgentResponse = DescribeAgentResponse'
  { -- | The Amazon Resource Name (ARN) of the agent.
    DescribeAgentResponse -> Maybe Text
agentArn :: Prelude.Maybe Prelude.Text,
    -- | The time that the agent was activated (that is, created in your
    -- account).
    DescribeAgentResponse -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
    -- | The type of endpoint that your agent is connected to. If the endpoint is
    -- a VPC endpoint, the agent is not accessible over the public internet.
    DescribeAgentResponse -> Maybe EndpointType
endpointType :: Prelude.Maybe EndpointType,
    -- | The time that the agent last connected to DataSync.
    DescribeAgentResponse -> Maybe POSIX
lastConnectionTime :: Prelude.Maybe Data.POSIX,
    -- | The name of the agent.
    DescribeAgentResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The subnet and the security group that DataSync used to access a VPC
    -- endpoint.
    DescribeAgentResponse -> Maybe PrivateLinkConfig
privateLinkConfig :: Prelude.Maybe PrivateLinkConfig,
    -- | The status of the agent. If the status is ONLINE, then the agent is
    -- configured properly and is available to use. The Running status is the
    -- normal running status for an agent. If the status is OFFLINE, the
    -- agent\'s VM is turned off or the agent is in an unhealthy state. When
    -- the issue that caused the unhealthy state is resolved, the agent returns
    -- to ONLINE status.
    DescribeAgentResponse -> Maybe AgentStatus
status :: Prelude.Maybe AgentStatus,
    -- | The response's http status code.
    DescribeAgentResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeAgentResponse -> DescribeAgentResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeAgentResponse -> DescribeAgentResponse -> Bool
$c/= :: DescribeAgentResponse -> DescribeAgentResponse -> Bool
== :: DescribeAgentResponse -> DescribeAgentResponse -> Bool
$c== :: DescribeAgentResponse -> DescribeAgentResponse -> Bool
Prelude.Eq, ReadPrec [DescribeAgentResponse]
ReadPrec DescribeAgentResponse
Int -> ReadS DescribeAgentResponse
ReadS [DescribeAgentResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeAgentResponse]
$creadListPrec :: ReadPrec [DescribeAgentResponse]
readPrec :: ReadPrec DescribeAgentResponse
$creadPrec :: ReadPrec DescribeAgentResponse
readList :: ReadS [DescribeAgentResponse]
$creadList :: ReadS [DescribeAgentResponse]
readsPrec :: Int -> ReadS DescribeAgentResponse
$creadsPrec :: Int -> ReadS DescribeAgentResponse
Prelude.Read, Int -> DescribeAgentResponse -> ShowS
[DescribeAgentResponse] -> ShowS
DescribeAgentResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeAgentResponse] -> ShowS
$cshowList :: [DescribeAgentResponse] -> ShowS
show :: DescribeAgentResponse -> String
$cshow :: DescribeAgentResponse -> String
showsPrec :: Int -> DescribeAgentResponse -> ShowS
$cshowsPrec :: Int -> DescribeAgentResponse -> ShowS
Prelude.Show, forall x. Rep DescribeAgentResponse x -> DescribeAgentResponse
forall x. DescribeAgentResponse -> Rep DescribeAgentResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeAgentResponse x -> DescribeAgentResponse
$cfrom :: forall x. DescribeAgentResponse -> Rep DescribeAgentResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeAgentResponse' 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:
--
-- 'agentArn', 'describeAgentResponse_agentArn' - The Amazon Resource Name (ARN) of the agent.
--
-- 'creationTime', 'describeAgentResponse_creationTime' - The time that the agent was activated (that is, created in your
-- account).
--
-- 'endpointType', 'describeAgentResponse_endpointType' - The type of endpoint that your agent is connected to. If the endpoint is
-- a VPC endpoint, the agent is not accessible over the public internet.
--
-- 'lastConnectionTime', 'describeAgentResponse_lastConnectionTime' - The time that the agent last connected to DataSync.
--
-- 'name', 'describeAgentResponse_name' - The name of the agent.
--
-- 'privateLinkConfig', 'describeAgentResponse_privateLinkConfig' - The subnet and the security group that DataSync used to access a VPC
-- endpoint.
--
-- 'status', 'describeAgentResponse_status' - The status of the agent. If the status is ONLINE, then the agent is
-- configured properly and is available to use. The Running status is the
-- normal running status for an agent. If the status is OFFLINE, the
-- agent\'s VM is turned off or the agent is in an unhealthy state. When
-- the issue that caused the unhealthy state is resolved, the agent returns
-- to ONLINE status.
--
-- 'httpStatus', 'describeAgentResponse_httpStatus' - The response's http status code.
newDescribeAgentResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeAgentResponse
newDescribeAgentResponse :: Int -> DescribeAgentResponse
newDescribeAgentResponse Int
pHttpStatus_ =
  DescribeAgentResponse'
    { $sel:agentArn:DescribeAgentResponse' :: Maybe Text
agentArn = forall a. Maybe a
Prelude.Nothing,
      $sel:creationTime:DescribeAgentResponse' :: Maybe POSIX
creationTime = forall a. Maybe a
Prelude.Nothing,
      $sel:endpointType:DescribeAgentResponse' :: Maybe EndpointType
endpointType = forall a. Maybe a
Prelude.Nothing,
      $sel:lastConnectionTime:DescribeAgentResponse' :: Maybe POSIX
lastConnectionTime = forall a. Maybe a
Prelude.Nothing,
      $sel:name:DescribeAgentResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:privateLinkConfig:DescribeAgentResponse' :: Maybe PrivateLinkConfig
privateLinkConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:status:DescribeAgentResponse' :: Maybe AgentStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeAgentResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Resource Name (ARN) of the agent.
describeAgentResponse_agentArn :: Lens.Lens' DescribeAgentResponse (Prelude.Maybe Prelude.Text)
describeAgentResponse_agentArn :: Lens' DescribeAgentResponse (Maybe Text)
describeAgentResponse_agentArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAgentResponse' {Maybe Text
agentArn :: Maybe Text
$sel:agentArn:DescribeAgentResponse' :: DescribeAgentResponse -> Maybe Text
agentArn} -> Maybe Text
agentArn) (\s :: DescribeAgentResponse
s@DescribeAgentResponse' {} Maybe Text
a -> DescribeAgentResponse
s {$sel:agentArn:DescribeAgentResponse' :: Maybe Text
agentArn = Maybe Text
a} :: DescribeAgentResponse)

-- | The time that the agent was activated (that is, created in your
-- account).
describeAgentResponse_creationTime :: Lens.Lens' DescribeAgentResponse (Prelude.Maybe Prelude.UTCTime)
describeAgentResponse_creationTime :: Lens' DescribeAgentResponse (Maybe UTCTime)
describeAgentResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAgentResponse' {Maybe POSIX
creationTime :: Maybe POSIX
$sel:creationTime:DescribeAgentResponse' :: DescribeAgentResponse -> Maybe POSIX
creationTime} -> Maybe POSIX
creationTime) (\s :: DescribeAgentResponse
s@DescribeAgentResponse' {} Maybe POSIX
a -> DescribeAgentResponse
s {$sel:creationTime:DescribeAgentResponse' :: Maybe POSIX
creationTime = Maybe POSIX
a} :: DescribeAgentResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The type of endpoint that your agent is connected to. If the endpoint is
-- a VPC endpoint, the agent is not accessible over the public internet.
describeAgentResponse_endpointType :: Lens.Lens' DescribeAgentResponse (Prelude.Maybe EndpointType)
describeAgentResponse_endpointType :: Lens' DescribeAgentResponse (Maybe EndpointType)
describeAgentResponse_endpointType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAgentResponse' {Maybe EndpointType
endpointType :: Maybe EndpointType
$sel:endpointType:DescribeAgentResponse' :: DescribeAgentResponse -> Maybe EndpointType
endpointType} -> Maybe EndpointType
endpointType) (\s :: DescribeAgentResponse
s@DescribeAgentResponse' {} Maybe EndpointType
a -> DescribeAgentResponse
s {$sel:endpointType:DescribeAgentResponse' :: Maybe EndpointType
endpointType = Maybe EndpointType
a} :: DescribeAgentResponse)

-- | The time that the agent last connected to DataSync.
describeAgentResponse_lastConnectionTime :: Lens.Lens' DescribeAgentResponse (Prelude.Maybe Prelude.UTCTime)
describeAgentResponse_lastConnectionTime :: Lens' DescribeAgentResponse (Maybe UTCTime)
describeAgentResponse_lastConnectionTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAgentResponse' {Maybe POSIX
lastConnectionTime :: Maybe POSIX
$sel:lastConnectionTime:DescribeAgentResponse' :: DescribeAgentResponse -> Maybe POSIX
lastConnectionTime} -> Maybe POSIX
lastConnectionTime) (\s :: DescribeAgentResponse
s@DescribeAgentResponse' {} Maybe POSIX
a -> DescribeAgentResponse
s {$sel:lastConnectionTime:DescribeAgentResponse' :: Maybe POSIX
lastConnectionTime = Maybe POSIX
a} :: DescribeAgentResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

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

-- | The subnet and the security group that DataSync used to access a VPC
-- endpoint.
describeAgentResponse_privateLinkConfig :: Lens.Lens' DescribeAgentResponse (Prelude.Maybe PrivateLinkConfig)
describeAgentResponse_privateLinkConfig :: Lens' DescribeAgentResponse (Maybe PrivateLinkConfig)
describeAgentResponse_privateLinkConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAgentResponse' {Maybe PrivateLinkConfig
privateLinkConfig :: Maybe PrivateLinkConfig
$sel:privateLinkConfig:DescribeAgentResponse' :: DescribeAgentResponse -> Maybe PrivateLinkConfig
privateLinkConfig} -> Maybe PrivateLinkConfig
privateLinkConfig) (\s :: DescribeAgentResponse
s@DescribeAgentResponse' {} Maybe PrivateLinkConfig
a -> DescribeAgentResponse
s {$sel:privateLinkConfig:DescribeAgentResponse' :: Maybe PrivateLinkConfig
privateLinkConfig = Maybe PrivateLinkConfig
a} :: DescribeAgentResponse)

-- | The status of the agent. If the status is ONLINE, then the agent is
-- configured properly and is available to use. The Running status is the
-- normal running status for an agent. If the status is OFFLINE, the
-- agent\'s VM is turned off or the agent is in an unhealthy state. When
-- the issue that caused the unhealthy state is resolved, the agent returns
-- to ONLINE status.
describeAgentResponse_status :: Lens.Lens' DescribeAgentResponse (Prelude.Maybe AgentStatus)
describeAgentResponse_status :: Lens' DescribeAgentResponse (Maybe AgentStatus)
describeAgentResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAgentResponse' {Maybe AgentStatus
status :: Maybe AgentStatus
$sel:status:DescribeAgentResponse' :: DescribeAgentResponse -> Maybe AgentStatus
status} -> Maybe AgentStatus
status) (\s :: DescribeAgentResponse
s@DescribeAgentResponse' {} Maybe AgentStatus
a -> DescribeAgentResponse
s {$sel:status:DescribeAgentResponse' :: Maybe AgentStatus
status = Maybe AgentStatus
a} :: DescribeAgentResponse)

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

instance Prelude.NFData DescribeAgentResponse where
  rnf :: DescribeAgentResponse -> ()
rnf DescribeAgentResponse' {Int
Maybe Text
Maybe POSIX
Maybe AgentStatus
Maybe EndpointType
Maybe PrivateLinkConfig
httpStatus :: Int
status :: Maybe AgentStatus
privateLinkConfig :: Maybe PrivateLinkConfig
name :: Maybe Text
lastConnectionTime :: Maybe POSIX
endpointType :: Maybe EndpointType
creationTime :: Maybe POSIX
agentArn :: Maybe Text
$sel:httpStatus:DescribeAgentResponse' :: DescribeAgentResponse -> Int
$sel:status:DescribeAgentResponse' :: DescribeAgentResponse -> Maybe AgentStatus
$sel:privateLinkConfig:DescribeAgentResponse' :: DescribeAgentResponse -> Maybe PrivateLinkConfig
$sel:name:DescribeAgentResponse' :: DescribeAgentResponse -> Maybe Text
$sel:lastConnectionTime:DescribeAgentResponse' :: DescribeAgentResponse -> Maybe POSIX
$sel:endpointType:DescribeAgentResponse' :: DescribeAgentResponse -> Maybe EndpointType
$sel:creationTime:DescribeAgentResponse' :: DescribeAgentResponse -> Maybe POSIX
$sel:agentArn:DescribeAgentResponse' :: DescribeAgentResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
agentArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EndpointType
endpointType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastConnectionTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 PrivateLinkConfig
privateLinkConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AgentStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus