{-# 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.ManagedBlockChain.Types.Node
-- 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.ManagedBlockChain.Types.Node where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.ManagedBlockChain.Types.NodeFrameworkAttributes
import Amazonka.ManagedBlockChain.Types.NodeLogPublishingConfiguration
import Amazonka.ManagedBlockChain.Types.NodeStatus
import Amazonka.ManagedBlockChain.Types.StateDBType
import qualified Amazonka.Prelude as Prelude

-- | Configuration properties of a node.
--
-- /See:/ 'newNode' smart constructor.
data Node = Node'
  { -- | The Amazon Resource Name (ARN) of the node. For more information about
    -- ARNs and their format, see
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
    -- in the /Amazon Web Services General Reference/.
    Node -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The Availability Zone in which the node exists. Required for Ethereum
    -- nodes.
    Node -> Maybe Text
availabilityZone :: Prelude.Maybe Prelude.Text,
    -- | The date and time that the node was created.
    Node -> Maybe ISO8601
creationDate :: Prelude.Maybe Data.ISO8601,
    -- | Attributes of the blockchain framework being used.
    Node -> Maybe NodeFrameworkAttributes
frameworkAttributes :: Prelude.Maybe NodeFrameworkAttributes,
    -- | The unique identifier of the node.
    Node -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | The instance type of the node.
    Node -> Maybe Text
instanceType :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the customer managed key in Key
    -- Management Service (KMS) that the node uses for encryption at rest. If
    -- the value of this parameter is @\"AWS Owned KMS Key\"@, the node uses an
    -- Amazon Web Services owned KMS key for encryption. The node inherits this
    -- parameter from the member that it belongs to.
    --
    -- For more information, see
    -- <https://docs.aws.amazon.com/managed-blockchain/latest/hyperledger-fabric-dev/managed-blockchain-encryption-at-rest.html Encryption at Rest>
    -- in the /Amazon Managed Blockchain Hyperledger Fabric Developer Guide/.
    --
    -- Applies only to Hyperledger Fabric.
    Node -> Maybe Text
kmsKeyArn :: Prelude.Maybe Prelude.Text,
    -- | Configuration properties for logging events associated with a peer node
    -- on a Hyperledger Fabric network on Managed Blockchain.
    Node -> Maybe NodeLogPublishingConfiguration
logPublishingConfiguration :: Prelude.Maybe NodeLogPublishingConfiguration,
    -- | The unique identifier of the member to which the node belongs.
    --
    -- Applies only to Hyperledger Fabric.
    Node -> Maybe Text
memberId :: Prelude.Maybe Prelude.Text,
    -- | The unique identifier of the network that the node is on.
    Node -> Maybe Text
networkId :: Prelude.Maybe Prelude.Text,
    -- | The state database that the node uses. Values are @LevelDB@ or
    -- @CouchDB@.
    --
    -- Applies only to Hyperledger Fabric.
    Node -> Maybe StateDBType
stateDB :: Prelude.Maybe StateDBType,
    -- | The status of the node.
    --
    -- -   @CREATING@ - The Amazon Web Services account is in the process of
    --     creating a node.
    --
    -- -   @AVAILABLE@ - The node has been created and can participate in the
    --     network.
    --
    -- -   @UNHEALTHY@ - The node is impaired and might not function as
    --     expected. Amazon Managed Blockchain automatically finds nodes in
    --     this state and tries to recover them. If a node is recoverable, it
    --     returns to @AVAILABLE@. Otherwise, it moves to @FAILED@ status.
    --
    -- -   @CREATE_FAILED@ - The Amazon Web Services account attempted to
    --     create a node and creation failed.
    --
    -- -   @UPDATING@ - The node is in the process of being updated.
    --
    -- -   @DELETING@ - The node is in the process of being deleted.
    --
    -- -   @DELETED@ - The node can no longer participate on the network.
    --
    -- -   @FAILED@ - The node is no longer functional, cannot be recovered,
    --     and must be deleted.
    --
    -- -   @INACCESSIBLE_ENCRYPTION_KEY@ - The node is impaired and might not
    --     function as expected because it cannot access the specified customer
    --     managed key in KMS for encryption at rest. Either the KMS key was
    --     disabled or deleted, or the grants on the key were revoked.
    --
    --     The effect of disabling or deleting a key or of revoking a grant
    --     isn\'t immediate. It might take some time for the node resource to
    --     discover that the key is inaccessible. When a resource is in this
    --     state, we recommend deleting and recreating the resource.
    Node -> Maybe NodeStatus
status :: Prelude.Maybe NodeStatus,
    -- | Tags assigned to the node. Each tag consists of a key and optional
    -- value.
    --
    -- For more information about tags, see
    -- <https://docs.aws.amazon.com/managed-blockchain/latest/ethereum-dev/tagging-resources.html Tagging Resources>
    -- in the /Amazon Managed Blockchain Ethereum Developer Guide/, or
    -- <https://docs.aws.amazon.com/managed-blockchain/latest/hyperledger-fabric-dev/tagging-resources.html Tagging Resources>
    -- in the /Amazon Managed Blockchain Hyperledger Fabric Developer Guide/.
    Node -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text)
  }
  deriving (Node -> Node -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Node -> Node -> Bool
$c/= :: Node -> Node -> Bool
== :: Node -> Node -> Bool
$c== :: Node -> Node -> Bool
Prelude.Eq, ReadPrec [Node]
ReadPrec Node
Int -> ReadS Node
ReadS [Node]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Node]
$creadListPrec :: ReadPrec [Node]
readPrec :: ReadPrec Node
$creadPrec :: ReadPrec Node
readList :: ReadS [Node]
$creadList :: ReadS [Node]
readsPrec :: Int -> ReadS Node
$creadsPrec :: Int -> ReadS Node
Prelude.Read, Int -> Node -> ShowS
[Node] -> ShowS
Node -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Node] -> ShowS
$cshowList :: [Node] -> ShowS
show :: Node -> String
$cshow :: Node -> String
showsPrec :: Int -> Node -> ShowS
$cshowsPrec :: Int -> Node -> ShowS
Prelude.Show, forall x. Rep Node x -> Node
forall x. Node -> Rep Node x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Node x -> Node
$cfrom :: forall x. Node -> Rep Node x
Prelude.Generic)

-- |
-- Create a value of 'Node' 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:
--
-- 'arn', 'node_arn' - The Amazon Resource Name (ARN) of the node. For more information about
-- ARNs and their format, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
-- in the /Amazon Web Services General Reference/.
--
-- 'availabilityZone', 'node_availabilityZone' - The Availability Zone in which the node exists. Required for Ethereum
-- nodes.
--
-- 'creationDate', 'node_creationDate' - The date and time that the node was created.
--
-- 'frameworkAttributes', 'node_frameworkAttributes' - Attributes of the blockchain framework being used.
--
-- 'id', 'node_id' - The unique identifier of the node.
--
-- 'instanceType', 'node_instanceType' - The instance type of the node.
--
-- 'kmsKeyArn', 'node_kmsKeyArn' - The Amazon Resource Name (ARN) of the customer managed key in Key
-- Management Service (KMS) that the node uses for encryption at rest. If
-- the value of this parameter is @\"AWS Owned KMS Key\"@, the node uses an
-- Amazon Web Services owned KMS key for encryption. The node inherits this
-- parameter from the member that it belongs to.
--
-- For more information, see
-- <https://docs.aws.amazon.com/managed-blockchain/latest/hyperledger-fabric-dev/managed-blockchain-encryption-at-rest.html Encryption at Rest>
-- in the /Amazon Managed Blockchain Hyperledger Fabric Developer Guide/.
--
-- Applies only to Hyperledger Fabric.
--
-- 'logPublishingConfiguration', 'node_logPublishingConfiguration' - Configuration properties for logging events associated with a peer node
-- on a Hyperledger Fabric network on Managed Blockchain.
--
-- 'memberId', 'node_memberId' - The unique identifier of the member to which the node belongs.
--
-- Applies only to Hyperledger Fabric.
--
-- 'networkId', 'node_networkId' - The unique identifier of the network that the node is on.
--
-- 'stateDB', 'node_stateDB' - The state database that the node uses. Values are @LevelDB@ or
-- @CouchDB@.
--
-- Applies only to Hyperledger Fabric.
--
-- 'status', 'node_status' - The status of the node.
--
-- -   @CREATING@ - The Amazon Web Services account is in the process of
--     creating a node.
--
-- -   @AVAILABLE@ - The node has been created and can participate in the
--     network.
--
-- -   @UNHEALTHY@ - The node is impaired and might not function as
--     expected. Amazon Managed Blockchain automatically finds nodes in
--     this state and tries to recover them. If a node is recoverable, it
--     returns to @AVAILABLE@. Otherwise, it moves to @FAILED@ status.
--
-- -   @CREATE_FAILED@ - The Amazon Web Services account attempted to
--     create a node and creation failed.
--
-- -   @UPDATING@ - The node is in the process of being updated.
--
-- -   @DELETING@ - The node is in the process of being deleted.
--
-- -   @DELETED@ - The node can no longer participate on the network.
--
-- -   @FAILED@ - The node is no longer functional, cannot be recovered,
--     and must be deleted.
--
-- -   @INACCESSIBLE_ENCRYPTION_KEY@ - The node is impaired and might not
--     function as expected because it cannot access the specified customer
--     managed key in KMS for encryption at rest. Either the KMS key was
--     disabled or deleted, or the grants on the key were revoked.
--
--     The effect of disabling or deleting a key or of revoking a grant
--     isn\'t immediate. It might take some time for the node resource to
--     discover that the key is inaccessible. When a resource is in this
--     state, we recommend deleting and recreating the resource.
--
-- 'tags', 'node_tags' - Tags assigned to the node. Each tag consists of a key and optional
-- value.
--
-- For more information about tags, see
-- <https://docs.aws.amazon.com/managed-blockchain/latest/ethereum-dev/tagging-resources.html Tagging Resources>
-- in the /Amazon Managed Blockchain Ethereum Developer Guide/, or
-- <https://docs.aws.amazon.com/managed-blockchain/latest/hyperledger-fabric-dev/tagging-resources.html Tagging Resources>
-- in the /Amazon Managed Blockchain Hyperledger Fabric Developer Guide/.
newNode ::
  Node
newNode :: Node
newNode =
  Node'
    { $sel:arn:Node' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:availabilityZone:Node' :: Maybe Text
availabilityZone = forall a. Maybe a
Prelude.Nothing,
      $sel:creationDate:Node' :: Maybe ISO8601
creationDate = forall a. Maybe a
Prelude.Nothing,
      $sel:frameworkAttributes:Node' :: Maybe NodeFrameworkAttributes
frameworkAttributes = forall a. Maybe a
Prelude.Nothing,
      $sel:id:Node' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:instanceType:Node' :: Maybe Text
instanceType = forall a. Maybe a
Prelude.Nothing,
      $sel:kmsKeyArn:Node' :: Maybe Text
kmsKeyArn = forall a. Maybe a
Prelude.Nothing,
      $sel:logPublishingConfiguration:Node' :: Maybe NodeLogPublishingConfiguration
logPublishingConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:memberId:Node' :: Maybe Text
memberId = forall a. Maybe a
Prelude.Nothing,
      $sel:networkId:Node' :: Maybe Text
networkId = forall a. Maybe a
Prelude.Nothing,
      $sel:stateDB:Node' :: Maybe StateDBType
stateDB = forall a. Maybe a
Prelude.Nothing,
      $sel:status:Node' :: Maybe NodeStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:Node' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing
    }

-- | The Amazon Resource Name (ARN) of the node. For more information about
-- ARNs and their format, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
-- in the /Amazon Web Services General Reference/.
node_arn :: Lens.Lens' Node (Prelude.Maybe Prelude.Text)
node_arn :: Lens' Node (Maybe Text)
node_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Node' {Maybe Text
arn :: Maybe Text
$sel:arn:Node' :: Node -> Maybe Text
arn} -> Maybe Text
arn) (\s :: Node
s@Node' {} Maybe Text
a -> Node
s {$sel:arn:Node' :: Maybe Text
arn = Maybe Text
a} :: Node)

-- | The Availability Zone in which the node exists. Required for Ethereum
-- nodes.
node_availabilityZone :: Lens.Lens' Node (Prelude.Maybe Prelude.Text)
node_availabilityZone :: Lens' Node (Maybe Text)
node_availabilityZone = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Node' {Maybe Text
availabilityZone :: Maybe Text
$sel:availabilityZone:Node' :: Node -> Maybe Text
availabilityZone} -> Maybe Text
availabilityZone) (\s :: Node
s@Node' {} Maybe Text
a -> Node
s {$sel:availabilityZone:Node' :: Maybe Text
availabilityZone = Maybe Text
a} :: Node)

-- | The date and time that the node was created.
node_creationDate :: Lens.Lens' Node (Prelude.Maybe Prelude.UTCTime)
node_creationDate :: Lens' Node (Maybe UTCTime)
node_creationDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Node' {Maybe ISO8601
creationDate :: Maybe ISO8601
$sel:creationDate:Node' :: Node -> Maybe ISO8601
creationDate} -> Maybe ISO8601
creationDate) (\s :: Node
s@Node' {} Maybe ISO8601
a -> Node
s {$sel:creationDate:Node' :: Maybe ISO8601
creationDate = Maybe ISO8601
a} :: Node) 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

-- | Attributes of the blockchain framework being used.
node_frameworkAttributes :: Lens.Lens' Node (Prelude.Maybe NodeFrameworkAttributes)
node_frameworkAttributes :: Lens' Node (Maybe NodeFrameworkAttributes)
node_frameworkAttributes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Node' {Maybe NodeFrameworkAttributes
frameworkAttributes :: Maybe NodeFrameworkAttributes
$sel:frameworkAttributes:Node' :: Node -> Maybe NodeFrameworkAttributes
frameworkAttributes} -> Maybe NodeFrameworkAttributes
frameworkAttributes) (\s :: Node
s@Node' {} Maybe NodeFrameworkAttributes
a -> Node
s {$sel:frameworkAttributes:Node' :: Maybe NodeFrameworkAttributes
frameworkAttributes = Maybe NodeFrameworkAttributes
a} :: Node)

-- | The unique identifier of the node.
node_id :: Lens.Lens' Node (Prelude.Maybe Prelude.Text)
node_id :: Lens' Node (Maybe Text)
node_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Node' {Maybe Text
id :: Maybe Text
$sel:id:Node' :: Node -> Maybe Text
id} -> Maybe Text
id) (\s :: Node
s@Node' {} Maybe Text
a -> Node
s {$sel:id:Node' :: Maybe Text
id = Maybe Text
a} :: Node)

-- | The instance type of the node.
node_instanceType :: Lens.Lens' Node (Prelude.Maybe Prelude.Text)
node_instanceType :: Lens' Node (Maybe Text)
node_instanceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Node' {Maybe Text
instanceType :: Maybe Text
$sel:instanceType:Node' :: Node -> Maybe Text
instanceType} -> Maybe Text
instanceType) (\s :: Node
s@Node' {} Maybe Text
a -> Node
s {$sel:instanceType:Node' :: Maybe Text
instanceType = Maybe Text
a} :: Node)

-- | The Amazon Resource Name (ARN) of the customer managed key in Key
-- Management Service (KMS) that the node uses for encryption at rest. If
-- the value of this parameter is @\"AWS Owned KMS Key\"@, the node uses an
-- Amazon Web Services owned KMS key for encryption. The node inherits this
-- parameter from the member that it belongs to.
--
-- For more information, see
-- <https://docs.aws.amazon.com/managed-blockchain/latest/hyperledger-fabric-dev/managed-blockchain-encryption-at-rest.html Encryption at Rest>
-- in the /Amazon Managed Blockchain Hyperledger Fabric Developer Guide/.
--
-- Applies only to Hyperledger Fabric.
node_kmsKeyArn :: Lens.Lens' Node (Prelude.Maybe Prelude.Text)
node_kmsKeyArn :: Lens' Node (Maybe Text)
node_kmsKeyArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Node' {Maybe Text
kmsKeyArn :: Maybe Text
$sel:kmsKeyArn:Node' :: Node -> Maybe Text
kmsKeyArn} -> Maybe Text
kmsKeyArn) (\s :: Node
s@Node' {} Maybe Text
a -> Node
s {$sel:kmsKeyArn:Node' :: Maybe Text
kmsKeyArn = Maybe Text
a} :: Node)

-- | Configuration properties for logging events associated with a peer node
-- on a Hyperledger Fabric network on Managed Blockchain.
node_logPublishingConfiguration :: Lens.Lens' Node (Prelude.Maybe NodeLogPublishingConfiguration)
node_logPublishingConfiguration :: Lens' Node (Maybe NodeLogPublishingConfiguration)
node_logPublishingConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Node' {Maybe NodeLogPublishingConfiguration
logPublishingConfiguration :: Maybe NodeLogPublishingConfiguration
$sel:logPublishingConfiguration:Node' :: Node -> Maybe NodeLogPublishingConfiguration
logPublishingConfiguration} -> Maybe NodeLogPublishingConfiguration
logPublishingConfiguration) (\s :: Node
s@Node' {} Maybe NodeLogPublishingConfiguration
a -> Node
s {$sel:logPublishingConfiguration:Node' :: Maybe NodeLogPublishingConfiguration
logPublishingConfiguration = Maybe NodeLogPublishingConfiguration
a} :: Node)

-- | The unique identifier of the member to which the node belongs.
--
-- Applies only to Hyperledger Fabric.
node_memberId :: Lens.Lens' Node (Prelude.Maybe Prelude.Text)
node_memberId :: Lens' Node (Maybe Text)
node_memberId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Node' {Maybe Text
memberId :: Maybe Text
$sel:memberId:Node' :: Node -> Maybe Text
memberId} -> Maybe Text
memberId) (\s :: Node
s@Node' {} Maybe Text
a -> Node
s {$sel:memberId:Node' :: Maybe Text
memberId = Maybe Text
a} :: Node)

-- | The unique identifier of the network that the node is on.
node_networkId :: Lens.Lens' Node (Prelude.Maybe Prelude.Text)
node_networkId :: Lens' Node (Maybe Text)
node_networkId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Node' {Maybe Text
networkId :: Maybe Text
$sel:networkId:Node' :: Node -> Maybe Text
networkId} -> Maybe Text
networkId) (\s :: Node
s@Node' {} Maybe Text
a -> Node
s {$sel:networkId:Node' :: Maybe Text
networkId = Maybe Text
a} :: Node)

-- | The state database that the node uses. Values are @LevelDB@ or
-- @CouchDB@.
--
-- Applies only to Hyperledger Fabric.
node_stateDB :: Lens.Lens' Node (Prelude.Maybe StateDBType)
node_stateDB :: Lens' Node (Maybe StateDBType)
node_stateDB = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Node' {Maybe StateDBType
stateDB :: Maybe StateDBType
$sel:stateDB:Node' :: Node -> Maybe StateDBType
stateDB} -> Maybe StateDBType
stateDB) (\s :: Node
s@Node' {} Maybe StateDBType
a -> Node
s {$sel:stateDB:Node' :: Maybe StateDBType
stateDB = Maybe StateDBType
a} :: Node)

-- | The status of the node.
--
-- -   @CREATING@ - The Amazon Web Services account is in the process of
--     creating a node.
--
-- -   @AVAILABLE@ - The node has been created and can participate in the
--     network.
--
-- -   @UNHEALTHY@ - The node is impaired and might not function as
--     expected. Amazon Managed Blockchain automatically finds nodes in
--     this state and tries to recover them. If a node is recoverable, it
--     returns to @AVAILABLE@. Otherwise, it moves to @FAILED@ status.
--
-- -   @CREATE_FAILED@ - The Amazon Web Services account attempted to
--     create a node and creation failed.
--
-- -   @UPDATING@ - The node is in the process of being updated.
--
-- -   @DELETING@ - The node is in the process of being deleted.
--
-- -   @DELETED@ - The node can no longer participate on the network.
--
-- -   @FAILED@ - The node is no longer functional, cannot be recovered,
--     and must be deleted.
--
-- -   @INACCESSIBLE_ENCRYPTION_KEY@ - The node is impaired and might not
--     function as expected because it cannot access the specified customer
--     managed key in KMS for encryption at rest. Either the KMS key was
--     disabled or deleted, or the grants on the key were revoked.
--
--     The effect of disabling or deleting a key or of revoking a grant
--     isn\'t immediate. It might take some time for the node resource to
--     discover that the key is inaccessible. When a resource is in this
--     state, we recommend deleting and recreating the resource.
node_status :: Lens.Lens' Node (Prelude.Maybe NodeStatus)
node_status :: Lens' Node (Maybe NodeStatus)
node_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Node' {Maybe NodeStatus
status :: Maybe NodeStatus
$sel:status:Node' :: Node -> Maybe NodeStatus
status} -> Maybe NodeStatus
status) (\s :: Node
s@Node' {} Maybe NodeStatus
a -> Node
s {$sel:status:Node' :: Maybe NodeStatus
status = Maybe NodeStatus
a} :: Node)

-- | Tags assigned to the node. Each tag consists of a key and optional
-- value.
--
-- For more information about tags, see
-- <https://docs.aws.amazon.com/managed-blockchain/latest/ethereum-dev/tagging-resources.html Tagging Resources>
-- in the /Amazon Managed Blockchain Ethereum Developer Guide/, or
-- <https://docs.aws.amazon.com/managed-blockchain/latest/hyperledger-fabric-dev/tagging-resources.html Tagging Resources>
-- in the /Amazon Managed Blockchain Hyperledger Fabric Developer Guide/.
node_tags :: Lens.Lens' Node (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
node_tags :: Lens' Node (Maybe (HashMap Text Text))
node_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Node' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:Node' :: Node -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: Node
s@Node' {} Maybe (HashMap Text Text)
a -> Node
s {$sel:tags:Node' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: Node) 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

instance Data.FromJSON Node where
  parseJSON :: Value -> Parser Node
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"Node"
      ( \Object
x ->
          Maybe Text
-> Maybe Text
-> Maybe ISO8601
-> Maybe NodeFrameworkAttributes
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe NodeLogPublishingConfiguration
-> Maybe Text
-> Maybe Text
-> Maybe StateDBType
-> Maybe NodeStatus
-> Maybe (HashMap Text Text)
-> Node
Node'
            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
"Arn")
            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
"AvailabilityZone")
            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
"CreationDate")
            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
"FrameworkAttributes")
            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
"Id")
            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
"InstanceType")
            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
"KmsKeyArn")
            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
"LogPublishingConfiguration")
            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
"MemberId")
            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
"NetworkId")
            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
"StateDB")
            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
"Status")
            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
"Tags" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
      )

instance Prelude.Hashable Node where
  hashWithSalt :: Int -> Node -> Int
hashWithSalt Int
_salt Node' {Maybe Text
Maybe (HashMap Text Text)
Maybe ISO8601
Maybe NodeFrameworkAttributes
Maybe NodeLogPublishingConfiguration
Maybe NodeStatus
Maybe StateDBType
tags :: Maybe (HashMap Text Text)
status :: Maybe NodeStatus
stateDB :: Maybe StateDBType
networkId :: Maybe Text
memberId :: Maybe Text
logPublishingConfiguration :: Maybe NodeLogPublishingConfiguration
kmsKeyArn :: Maybe Text
instanceType :: Maybe Text
id :: Maybe Text
frameworkAttributes :: Maybe NodeFrameworkAttributes
creationDate :: Maybe ISO8601
availabilityZone :: Maybe Text
arn :: Maybe Text
$sel:tags:Node' :: Node -> Maybe (HashMap Text Text)
$sel:status:Node' :: Node -> Maybe NodeStatus
$sel:stateDB:Node' :: Node -> Maybe StateDBType
$sel:networkId:Node' :: Node -> Maybe Text
$sel:memberId:Node' :: Node -> Maybe Text
$sel:logPublishingConfiguration:Node' :: Node -> Maybe NodeLogPublishingConfiguration
$sel:kmsKeyArn:Node' :: Node -> Maybe Text
$sel:instanceType:Node' :: Node -> Maybe Text
$sel:id:Node' :: Node -> Maybe Text
$sel:frameworkAttributes:Node' :: Node -> Maybe NodeFrameworkAttributes
$sel:creationDate:Node' :: Node -> Maybe ISO8601
$sel:availabilityZone:Node' :: Node -> Maybe Text
$sel:arn:Node' :: Node -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
arn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
availabilityZone
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
creationDate
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe NodeFrameworkAttributes
frameworkAttributes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
id
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
instanceType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
kmsKeyArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe NodeLogPublishingConfiguration
logPublishingConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
memberId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
networkId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe StateDBType
stateDB
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe NodeStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags

instance Prelude.NFData Node where
  rnf :: Node -> ()
rnf Node' {Maybe Text
Maybe (HashMap Text Text)
Maybe ISO8601
Maybe NodeFrameworkAttributes
Maybe NodeLogPublishingConfiguration
Maybe NodeStatus
Maybe StateDBType
tags :: Maybe (HashMap Text Text)
status :: Maybe NodeStatus
stateDB :: Maybe StateDBType
networkId :: Maybe Text
memberId :: Maybe Text
logPublishingConfiguration :: Maybe NodeLogPublishingConfiguration
kmsKeyArn :: Maybe Text
instanceType :: Maybe Text
id :: Maybe Text
frameworkAttributes :: Maybe NodeFrameworkAttributes
creationDate :: Maybe ISO8601
availabilityZone :: Maybe Text
arn :: Maybe Text
$sel:tags:Node' :: Node -> Maybe (HashMap Text Text)
$sel:status:Node' :: Node -> Maybe NodeStatus
$sel:stateDB:Node' :: Node -> Maybe StateDBType
$sel:networkId:Node' :: Node -> Maybe Text
$sel:memberId:Node' :: Node -> Maybe Text
$sel:logPublishingConfiguration:Node' :: Node -> Maybe NodeLogPublishingConfiguration
$sel:kmsKeyArn:Node' :: Node -> Maybe Text
$sel:instanceType:Node' :: Node -> Maybe Text
$sel:id:Node' :: Node -> Maybe Text
$sel:frameworkAttributes:Node' :: Node -> Maybe NodeFrameworkAttributes
$sel:creationDate:Node' :: Node -> Maybe ISO8601
$sel:availabilityZone:Node' :: Node -> Maybe Text
$sel:arn:Node' :: Node -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
availabilityZone
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
creationDate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe NodeFrameworkAttributes
frameworkAttributes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
id
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
instanceType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
kmsKeyArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe NodeLogPublishingConfiguration
logPublishingConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
memberId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
networkId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe StateDBType
stateDB
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe NodeStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags