Skip to content

Commit

Permalink
Add phases definition for the local-cluster
Browse files Browse the repository at this point in the history
  • Loading branch information
paolino committed Apr 30, 2024
1 parent aa7972e commit 39c7057
Show file tree
Hide file tree
Showing 2 changed files with 70 additions and 0 deletions.
Original file line number Diff line number Diff line change
@@ -0,0 +1,69 @@
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}

module Cardano.Wallet.Launch.Cluster.Monitoring.Phase
( Phase (..)
, RelayNode (..)
, History (..)
)
where

import Prelude

import Cardano.Launcher.Node
( CardanoNodeConn
, cardanoNodeConn
, nodeSocketFile
)
import Data.Aeson
( FromJSON
, ToJSON
)
import Data.Aeson.Types
( FromJSON (..)
, ToJSON (..)
)
import Data.Map
( Map
)
import Data.Time
( UTCTime
)
import GHC.Generics
( Generic
)

-- | A relay node as a reference to it's socket file or pipe
newtype RelayNode = RelayNode CardanoNodeConn
deriving stock (Eq, Show, Generic)

instance ToJSON RelayNode where
toJSON (RelayNode f) = toJSON $ nodeSocketFile f

instance FromJSON RelayNode where
parseJSON x = do
f <- parseJSON x
case cardanoNodeConn f of
Right conn -> pure $ RelayNode conn
Left e -> fail e

-- | The different phases the cluster can be in. We use the convention to report
-- the start of a phase.
data Phase
= RetrievingFunds
| Metadata
| Genesis
| Pool0
| Funding
| Pools
| Relay
| Cluster (Maybe RelayNode)
deriving stock (Eq, Show, Generic)
deriving anyclass (ToJSON, FromJSON)

-- | The history of the cluster phases
newtype History = History
{ history :: Map UTCTime Phase
}
deriving stock (Eq, Show)
1 change: 1 addition & 0 deletions lib/local-cluster/local-cluster.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -52,6 +52,7 @@ library
Cardano.Wallet.Launch.Cluster.KeyRegistration
Cardano.Wallet.Launch.Cluster.Logging
Cardano.Wallet.Launch.Cluster.MonetaryPolicyScript
Cardano.Wallet.Launch.Cluster.Monitoring.Phase
Cardano.Wallet.Launch.Cluster.Node.GenNodeConfig
Cardano.Wallet.Launch.Cluster.Node.GenTopology
Cardano.Wallet.Launch.Cluster.Node.NodeParams
Expand Down

0 comments on commit 39c7057

Please sign in to comment.