Skip to content

Commit

Permalink
Remove cartouches and make ClusterLog more neat
Browse files Browse the repository at this point in the history
It now explains NO_POOLS=1 to you, and tells you if it is set or not.

Also disables two "expected warnings".
  • Loading branch information
Anviking committed Sep 21, 2020
1 parent cfe4bab commit fa26841
Showing 1 changed file with 28 additions and 40 deletions.
68 changes: 28 additions & 40 deletions lib/shelley/src/Cardano/Wallet/Shelley/Launch.hs
Expand Up @@ -4,6 +4,7 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE NumericUnderscores #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
Expand Down Expand Up @@ -1552,37 +1553,6 @@ timeout t (title, action) = do
Left _ -> fail ("Waited too long for: " <> title)
Right a -> pure a

-- | A little notice shown in the logs when setting up the cluster.
forkCartouche :: Text
forkCartouche = T.unlines
[ ""
, "########################################################################"
, "# #"
, "# Transition from byron to shelley has been triggered. #"
, "# #"
, "# This may take roughly 60s. Please be patient... #"
, "# #"
, "########################################################################"
]

-- | A little notice shown in the logs when setting up the cluster.
clusterCartouche :: Text
clusterCartouche = T.unlines
[ ""
, "########################################################################"
, "# #"
, "# ⚠ NOTICE ⚠ #"
, "# #"
, "# Cluster is booting. Stake pools are being registered on chain. #"
, "# #"
, "# This may take roughly 60s, after which pools will become active #"
, "# and will start producing blocks. Please be even more patient... #"
, "# #"
, "# ⚠ NOTICE ⚠ #"
, "# #"
, "########################################################################"
]

-- | Hash a ByteString using blake2b_256 and encode it in base16
blake2b256S :: ByteString -> String
blake2b256S =
Expand Down Expand Up @@ -1626,8 +1596,9 @@ withSystemTempDir tr name action = do
-------------------------------------------------------------------------------}

data ClusterLog
= MsgClusterCartouche
| MsgForkCartouche
= MsgRegisteringStakePools Int -- ^ How many pools
| MsgWaitingForFork
| MsgStartingCluster FilePath
| MsgLauncher String LauncherLog
| MsgStartedStaticServer String FilePath
| MsgTempNoCleanup FilePath
Expand All @@ -1644,8 +1615,20 @@ data ClusterLog

instance ToText ClusterLog where
toText = \case
MsgClusterCartouche -> clusterCartouche
MsgForkCartouche -> forkCartouche
MsgStartingCluster dir ->
"Configuring cluster in " <> T.pack dir
MsgWaitingForFork ->
"Transitioning from Byron to Shelley... Please wait 20s..."
MsgRegisteringStakePools 0 -> mconcat
[ "Not registering any stake pools due to "
, "NO_POOLS=1. Some tests may fail."
]
MsgRegisteringStakePools n -> mconcat
[ T.pack (show n)
, " stake pools are being registered on chain... "
, "Please wait 60s until active... "
, "Can be skipped using NO_POOLS=1."
]
MsgLauncher name msg ->
T.pack name <> " " <> toText msg
MsgStartedStaticServer baseUrl fp ->
Expand Down Expand Up @@ -1681,19 +1664,24 @@ instance ToText ClusterLog where
instance HasPrivacyAnnotation ClusterLog
instance HasSeverityAnnotation ClusterLog where
getSeverityAnnotation = \case
MsgClusterCartouche -> Warning
MsgForkCartouche -> Warning
MsgLauncher _ msg -> getSeverityAnnotation msg
MsgStartingCluster _ -> Notice
MsgRegisteringStakePools _ -> Notice
MsgWaitingForFork -> Notice
MsgLauncher _ _ -> Info
MsgStartedStaticServer _ _ -> Info
MsgTempNoCleanup _ -> Notice
MsgBracket _ _ -> Debug
MsgCLIStatus _ ExitSuccess _ _-> Debug
MsgCLIStatus _ (ExitFailure _) _ _-> Error
MsgCLIRetry _ -> Info
MsgCLIRetryResult{} -> Warning
MsgCLIRetryResult{} -> Info
-- NOTE: ^ Some failures are expected, so for cleaner logs we use Info,
-- instead of Warning.
MsgSocketIsReady _ -> Info
MsgStakeDistribution _ ExitSuccess _ _-> Info
MsgStakeDistribution _ (ExitFailure _) _ _-> Warning
MsgStakeDistribution _ (ExitFailure _) _ _-> Info
-- NOTE: ^ Some failures are expected, so for cleaner logs we use Info,
-- instead of Warning.
MsgDebug _ -> Debug
MsgGenOperatorKeyPair _ -> Debug
MsgCLI _ -> Debug
Expand Down

0 comments on commit fa26841

Please sign in to comment.