{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.Discovery.Types.AgentInfo
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.Discovery.Types.AgentInfo where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Discovery.Types.AgentNetworkInfo
import Amazonka.Discovery.Types.AgentStatus
import qualified Amazonka.Prelude as Prelude

-- | Information about agents or connectors associated with the user’s Amazon
-- Web Services account. Information includes agent or connector IDs, IP
-- addresses, media access control (MAC) addresses, agent or connector
-- health, hostname where the agent or connector resides, and agent version
-- for each agent.
--
-- /See:/ 'newAgentInfo' smart constructor.
data AgentInfo = AgentInfo'
  { -- | The agent or connector ID.
    AgentInfo -> Maybe Text
agentId :: Prelude.Maybe Prelude.Text,
    -- | Network details about the host where the agent or connector resides.
    AgentInfo -> Maybe [AgentNetworkInfo]
agentNetworkInfoList :: Prelude.Maybe [AgentNetworkInfo],
    -- | Type of agent.
    AgentInfo -> Maybe Text
agentType :: Prelude.Maybe Prelude.Text,
    -- | Status of the collection process for an agent or connector.
    AgentInfo -> Maybe Text
collectionStatus :: Prelude.Maybe Prelude.Text,
    -- | The ID of the connector.
    AgentInfo -> Maybe Text
connectorId :: Prelude.Maybe Prelude.Text,
    -- | The health of the agent or connector.
    AgentInfo -> Maybe AgentStatus
health :: Prelude.Maybe AgentStatus,
    -- | The name of the host where the agent or connector resides. The host can
    -- be a server or virtual machine.
    AgentInfo -> Maybe Text
hostName :: Prelude.Maybe Prelude.Text,
    -- | Time since agent or connector health was reported.
    AgentInfo -> Maybe Text
lastHealthPingTime :: Prelude.Maybe Prelude.Text,
    -- | Agent\'s first registration timestamp in UTC.
    AgentInfo -> Maybe Text
registeredTime :: Prelude.Maybe Prelude.Text,
    -- | The agent or connector version.
    AgentInfo -> Maybe Text
version :: Prelude.Maybe Prelude.Text
  }
  deriving (AgentInfo -> AgentInfo -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AgentInfo -> AgentInfo -> Bool
$c/= :: AgentInfo -> AgentInfo -> Bool
== :: AgentInfo -> AgentInfo -> Bool
$c== :: AgentInfo -> AgentInfo -> Bool
Prelude.Eq, ReadPrec [AgentInfo]
ReadPrec AgentInfo
Int -> ReadS AgentInfo
ReadS [AgentInfo]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AgentInfo]
$creadListPrec :: ReadPrec [AgentInfo]
readPrec :: ReadPrec AgentInfo
$creadPrec :: ReadPrec AgentInfo
readList :: ReadS [AgentInfo]
$creadList :: ReadS [AgentInfo]
readsPrec :: Int -> ReadS AgentInfo
$creadsPrec :: Int -> ReadS AgentInfo
Prelude.Read, Int -> AgentInfo -> ShowS
[AgentInfo] -> ShowS
AgentInfo -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AgentInfo] -> ShowS
$cshowList :: [AgentInfo] -> ShowS
show :: AgentInfo -> String
$cshow :: AgentInfo -> String
showsPrec :: Int -> AgentInfo -> ShowS
$cshowsPrec :: Int -> AgentInfo -> ShowS
Prelude.Show, forall x. Rep AgentInfo x -> AgentInfo
forall x. AgentInfo -> Rep AgentInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AgentInfo x -> AgentInfo
$cfrom :: forall x. AgentInfo -> Rep AgentInfo x
Prelude.Generic)

-- |
-- Create a value of 'AgentInfo' 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:
--
-- 'agentId', 'agentInfo_agentId' - The agent or connector ID.
--
-- 'agentNetworkInfoList', 'agentInfo_agentNetworkInfoList' - Network details about the host where the agent or connector resides.
--
-- 'agentType', 'agentInfo_agentType' - Type of agent.
--
-- 'collectionStatus', 'agentInfo_collectionStatus' - Status of the collection process for an agent or connector.
--
-- 'connectorId', 'agentInfo_connectorId' - The ID of the connector.
--
-- 'health', 'agentInfo_health' - The health of the agent or connector.
--
-- 'hostName', 'agentInfo_hostName' - The name of the host where the agent or connector resides. The host can
-- be a server or virtual machine.
--
-- 'lastHealthPingTime', 'agentInfo_lastHealthPingTime' - Time since agent or connector health was reported.
--
-- 'registeredTime', 'agentInfo_registeredTime' - Agent\'s first registration timestamp in UTC.
--
-- 'version', 'agentInfo_version' - The agent or connector version.
newAgentInfo ::
  AgentInfo
newAgentInfo :: AgentInfo
newAgentInfo =
  AgentInfo'
    { $sel:agentId:AgentInfo' :: Maybe Text
agentId = forall a. Maybe a
Prelude.Nothing,
      $sel:agentNetworkInfoList:AgentInfo' :: Maybe [AgentNetworkInfo]
agentNetworkInfoList = forall a. Maybe a
Prelude.Nothing,
      $sel:agentType:AgentInfo' :: Maybe Text
agentType = forall a. Maybe a
Prelude.Nothing,
      $sel:collectionStatus:AgentInfo' :: Maybe Text
collectionStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:connectorId:AgentInfo' :: Maybe Text
connectorId = forall a. Maybe a
Prelude.Nothing,
      $sel:health:AgentInfo' :: Maybe AgentStatus
health = forall a. Maybe a
Prelude.Nothing,
      $sel:hostName:AgentInfo' :: Maybe Text
hostName = forall a. Maybe a
Prelude.Nothing,
      $sel:lastHealthPingTime:AgentInfo' :: Maybe Text
lastHealthPingTime = forall a. Maybe a
Prelude.Nothing,
      $sel:registeredTime:AgentInfo' :: Maybe Text
registeredTime = forall a. Maybe a
Prelude.Nothing,
      $sel:version:AgentInfo' :: Maybe Text
version = forall a. Maybe a
Prelude.Nothing
    }

-- | The agent or connector ID.
agentInfo_agentId :: Lens.Lens' AgentInfo (Prelude.Maybe Prelude.Text)
agentInfo_agentId :: Lens' AgentInfo (Maybe Text)
agentInfo_agentId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AgentInfo' {Maybe Text
agentId :: Maybe Text
$sel:agentId:AgentInfo' :: AgentInfo -> Maybe Text
agentId} -> Maybe Text
agentId) (\s :: AgentInfo
s@AgentInfo' {} Maybe Text
a -> AgentInfo
s {$sel:agentId:AgentInfo' :: Maybe Text
agentId = Maybe Text
a} :: AgentInfo)

-- | Network details about the host where the agent or connector resides.
agentInfo_agentNetworkInfoList :: Lens.Lens' AgentInfo (Prelude.Maybe [AgentNetworkInfo])
agentInfo_agentNetworkInfoList :: Lens' AgentInfo (Maybe [AgentNetworkInfo])
agentInfo_agentNetworkInfoList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AgentInfo' {Maybe [AgentNetworkInfo]
agentNetworkInfoList :: Maybe [AgentNetworkInfo]
$sel:agentNetworkInfoList:AgentInfo' :: AgentInfo -> Maybe [AgentNetworkInfo]
agentNetworkInfoList} -> Maybe [AgentNetworkInfo]
agentNetworkInfoList) (\s :: AgentInfo
s@AgentInfo' {} Maybe [AgentNetworkInfo]
a -> AgentInfo
s {$sel:agentNetworkInfoList:AgentInfo' :: Maybe [AgentNetworkInfo]
agentNetworkInfoList = Maybe [AgentNetworkInfo]
a} :: AgentInfo) 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 s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | Type of agent.
agentInfo_agentType :: Lens.Lens' AgentInfo (Prelude.Maybe Prelude.Text)
agentInfo_agentType :: Lens' AgentInfo (Maybe Text)
agentInfo_agentType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AgentInfo' {Maybe Text
agentType :: Maybe Text
$sel:agentType:AgentInfo' :: AgentInfo -> Maybe Text
agentType} -> Maybe Text
agentType) (\s :: AgentInfo
s@AgentInfo' {} Maybe Text
a -> AgentInfo
s {$sel:agentType:AgentInfo' :: Maybe Text
agentType = Maybe Text
a} :: AgentInfo)

-- | Status of the collection process for an agent or connector.
agentInfo_collectionStatus :: Lens.Lens' AgentInfo (Prelude.Maybe Prelude.Text)
agentInfo_collectionStatus :: Lens' AgentInfo (Maybe Text)
agentInfo_collectionStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AgentInfo' {Maybe Text
collectionStatus :: Maybe Text
$sel:collectionStatus:AgentInfo' :: AgentInfo -> Maybe Text
collectionStatus} -> Maybe Text
collectionStatus) (\s :: AgentInfo
s@AgentInfo' {} Maybe Text
a -> AgentInfo
s {$sel:collectionStatus:AgentInfo' :: Maybe Text
collectionStatus = Maybe Text
a} :: AgentInfo)

-- | The ID of the connector.
agentInfo_connectorId :: Lens.Lens' AgentInfo (Prelude.Maybe Prelude.Text)
agentInfo_connectorId :: Lens' AgentInfo (Maybe Text)
agentInfo_connectorId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AgentInfo' {Maybe Text
connectorId :: Maybe Text
$sel:connectorId:AgentInfo' :: AgentInfo -> Maybe Text
connectorId} -> Maybe Text
connectorId) (\s :: AgentInfo
s@AgentInfo' {} Maybe Text
a -> AgentInfo
s {$sel:connectorId:AgentInfo' :: Maybe Text
connectorId = Maybe Text
a} :: AgentInfo)

-- | The health of the agent or connector.
agentInfo_health :: Lens.Lens' AgentInfo (Prelude.Maybe AgentStatus)
agentInfo_health :: Lens' AgentInfo (Maybe AgentStatus)
agentInfo_health = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AgentInfo' {Maybe AgentStatus
health :: Maybe AgentStatus
$sel:health:AgentInfo' :: AgentInfo -> Maybe AgentStatus
health} -> Maybe AgentStatus
health) (\s :: AgentInfo
s@AgentInfo' {} Maybe AgentStatus
a -> AgentInfo
s {$sel:health:AgentInfo' :: Maybe AgentStatus
health = Maybe AgentStatus
a} :: AgentInfo)

-- | The name of the host where the agent or connector resides. The host can
-- be a server or virtual machine.
agentInfo_hostName :: Lens.Lens' AgentInfo (Prelude.Maybe Prelude.Text)
agentInfo_hostName :: Lens' AgentInfo (Maybe Text)
agentInfo_hostName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AgentInfo' {Maybe Text
hostName :: Maybe Text
$sel:hostName:AgentInfo' :: AgentInfo -> Maybe Text
hostName} -> Maybe Text
hostName) (\s :: AgentInfo
s@AgentInfo' {} Maybe Text
a -> AgentInfo
s {$sel:hostName:AgentInfo' :: Maybe Text
hostName = Maybe Text
a} :: AgentInfo)

-- | Time since agent or connector health was reported.
agentInfo_lastHealthPingTime :: Lens.Lens' AgentInfo (Prelude.Maybe Prelude.Text)
agentInfo_lastHealthPingTime :: Lens' AgentInfo (Maybe Text)
agentInfo_lastHealthPingTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AgentInfo' {Maybe Text
lastHealthPingTime :: Maybe Text
$sel:lastHealthPingTime:AgentInfo' :: AgentInfo -> Maybe Text
lastHealthPingTime} -> Maybe Text
lastHealthPingTime) (\s :: AgentInfo
s@AgentInfo' {} Maybe Text
a -> AgentInfo
s {$sel:lastHealthPingTime:AgentInfo' :: Maybe Text
lastHealthPingTime = Maybe Text
a} :: AgentInfo)

-- | Agent\'s first registration timestamp in UTC.
agentInfo_registeredTime :: Lens.Lens' AgentInfo (Prelude.Maybe Prelude.Text)
agentInfo_registeredTime :: Lens' AgentInfo (Maybe Text)
agentInfo_registeredTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AgentInfo' {Maybe Text
registeredTime :: Maybe Text
$sel:registeredTime:AgentInfo' :: AgentInfo -> Maybe Text
registeredTime} -> Maybe Text
registeredTime) (\s :: AgentInfo
s@AgentInfo' {} Maybe Text
a -> AgentInfo
s {$sel:registeredTime:AgentInfo' :: Maybe Text
registeredTime = Maybe Text
a} :: AgentInfo)

-- | The agent or connector version.
agentInfo_version :: Lens.Lens' AgentInfo (Prelude.Maybe Prelude.Text)
agentInfo_version :: Lens' AgentInfo (Maybe Text)
agentInfo_version = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AgentInfo' {Maybe Text
version :: Maybe Text
$sel:version:AgentInfo' :: AgentInfo -> Maybe Text
version} -> Maybe Text
version) (\s :: AgentInfo
s@AgentInfo' {} Maybe Text
a -> AgentInfo
s {$sel:version:AgentInfo' :: Maybe Text
version = Maybe Text
a} :: AgentInfo)

instance Data.FromJSON AgentInfo where
  parseJSON :: Value -> Parser AgentInfo
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"AgentInfo"
      ( \Object
x ->
          Maybe Text
-> Maybe [AgentNetworkInfo]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe AgentStatus
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> AgentInfo
AgentInfo'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"agentId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"agentNetworkInfoList"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"agentType")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"collectionStatus")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"connectorId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"health")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"hostName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"lastHealthPingTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"registeredTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"version")
      )

instance Prelude.Hashable AgentInfo where
  hashWithSalt :: Int -> AgentInfo -> Int
hashWithSalt Int
_salt AgentInfo' {Maybe [AgentNetworkInfo]
Maybe Text
Maybe AgentStatus
version :: Maybe Text
registeredTime :: Maybe Text
lastHealthPingTime :: Maybe Text
hostName :: Maybe Text
health :: Maybe AgentStatus
connectorId :: Maybe Text
collectionStatus :: Maybe Text
agentType :: Maybe Text
agentNetworkInfoList :: Maybe [AgentNetworkInfo]
agentId :: Maybe Text
$sel:version:AgentInfo' :: AgentInfo -> Maybe Text
$sel:registeredTime:AgentInfo' :: AgentInfo -> Maybe Text
$sel:lastHealthPingTime:AgentInfo' :: AgentInfo -> Maybe Text
$sel:hostName:AgentInfo' :: AgentInfo -> Maybe Text
$sel:health:AgentInfo' :: AgentInfo -> Maybe AgentStatus
$sel:connectorId:AgentInfo' :: AgentInfo -> Maybe Text
$sel:collectionStatus:AgentInfo' :: AgentInfo -> Maybe Text
$sel:agentType:AgentInfo' :: AgentInfo -> Maybe Text
$sel:agentNetworkInfoList:AgentInfo' :: AgentInfo -> Maybe [AgentNetworkInfo]
$sel:agentId:AgentInfo' :: AgentInfo -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
agentId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [AgentNetworkInfo]
agentNetworkInfoList
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
agentType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
collectionStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
connectorId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AgentStatus
health
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
hostName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
lastHealthPingTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
registeredTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
version

instance Prelude.NFData AgentInfo where
  rnf :: AgentInfo -> ()
rnf AgentInfo' {Maybe [AgentNetworkInfo]
Maybe Text
Maybe AgentStatus
version :: Maybe Text
registeredTime :: Maybe Text
lastHealthPingTime :: Maybe Text
hostName :: Maybe Text
health :: Maybe AgentStatus
connectorId :: Maybe Text
collectionStatus :: Maybe Text
agentType :: Maybe Text
agentNetworkInfoList :: Maybe [AgentNetworkInfo]
agentId :: Maybe Text
$sel:version:AgentInfo' :: AgentInfo -> Maybe Text
$sel:registeredTime:AgentInfo' :: AgentInfo -> Maybe Text
$sel:lastHealthPingTime:AgentInfo' :: AgentInfo -> Maybe Text
$sel:hostName:AgentInfo' :: AgentInfo -> Maybe Text
$sel:health:AgentInfo' :: AgentInfo -> Maybe AgentStatus
$sel:connectorId:AgentInfo' :: AgentInfo -> Maybe Text
$sel:collectionStatus:AgentInfo' :: AgentInfo -> Maybe Text
$sel:agentType:AgentInfo' :: AgentInfo -> Maybe Text
$sel:agentNetworkInfoList:AgentInfo' :: AgentInfo -> Maybe [AgentNetworkInfo]
$sel:agentId:AgentInfo' :: AgentInfo -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
agentId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [AgentNetworkInfo]
agentNetworkInfoList
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
agentType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
collectionStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
connectorId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AgentStatus
health
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
hostName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
lastHealthPingTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
registeredTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
version