Skip to content
This repository was archived by the owner on Nov 24, 2025. It is now read-only.
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension


Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
2 changes: 0 additions & 2 deletions .github/workflows/applications.yml
Original file line number Diff line number Diff line change
Expand Up @@ -364,7 +364,6 @@ jobs:
cabal build -j2 --ghc-options=-j2 \
chainweb:bench:bench \
exe:b64 \
exe:calculate-release \
exe:compact \
exe:db-checksum \
exe:ea \
Expand Down Expand Up @@ -403,7 +402,6 @@ jobs:
mkdir -p artifacts/chainweb
cp $(cabal list-bin b64) artifacts/chainweb
cp $(cabal list-bin bench) artifacts/chainweb
cp $(cabal list-bin calculate-release) artifacts/chainweb
cp $(cabal list-bin chainweb-node) artifacts/chainweb
cp $(cabal list-bin chainweb-storage-tests) artifacts/chainweb
cp $(cabal list-bin chainweb-tests) artifacts/chainweb
Expand Down
1 change: 0 additions & 1 deletion .github/workflows/macos.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -120,7 +120,6 @@ jobs:
cabal build -j \
chainweb:bench:bench \
exe:b64 \
exe:calculate-release \
exe:compact \
exe:db-checksum \
exe:ea \
Expand Down
6 changes: 3 additions & 3 deletions chainweb.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -562,7 +562,7 @@ library chainweb-test-utils
, pact-time:numeric >=0.3.0.1
, pact-tng >=5.0
, pact-tng:pact-request-api >=5.0
, property-matchers
, property-matchers >= 0.7
, quickcheck-instances >= 0.3
, random >= 1.3
, resourcet >= 1.3
Expand Down Expand Up @@ -730,7 +730,7 @@ test-suite chainweb-tests
, pact-tng:pact-repl
, patience >= 0.3
, prettyprinter
, property-matchers
, property-matchers >= 0.7
, pretty-show
, quickcheck-instances >= 0.3
, random >= 1.3
Expand Down Expand Up @@ -899,7 +899,7 @@ benchmark bench
, pact
, pact-tng
, pact-tng:pact-request-api
, property-matchers
, property-matchers >= 0.7
, random >= 1.3
, safe-exceptions
, streaming
Expand Down
63 changes: 0 additions & 63 deletions cwtools/calculate-release/Main.hs

This file was deleted.

18 changes: 0 additions & 18 deletions cwtools/cwtools.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -92,24 +92,6 @@ executable b64
, optparse-applicative
, text

executable calculate-release
import: warning-flags, debugging-flags
default-language: Haskell2010
ghc-options:
-threaded
hs-source-dirs: calculate-release
main-is: Main.hs
build-depends:
-- internal
, chainweb

-- external
, base >= 4.12 && < 5
, lens
, lens-aeson
, time
, wreq

-- Compact pact state and RocksDB.
executable compact
import: warning-flags, debugging-flags
Expand Down
1 change: 0 additions & 1 deletion default.nix
Original file line number Diff line number Diff line change
Expand Up @@ -117,7 +117,6 @@ let haskellSrc = with nix-filter.lib; filter {
name = "cwtools";
exes = [
"b64"
"calculate-release"
"compact"
"db-checksum"
"ea"
Expand Down
132 changes: 29 additions & 103 deletions node/src/ChainwebNode.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE NumericUnderscores #-}
Expand Down Expand Up @@ -45,40 +46,6 @@ module Main
, main
) where

import Configuration.Utils hiding (Error)
import Configuration.Utils.Validation (validateFilePath)

import Control.Concurrent
import Control.Concurrent.Async
import Control.DeepSeq
import Control.Exception
import Control.Lens hiding ((.=))
import Control.Monad
import Control.Monad.Managed

import Data.Text (Text)
import qualified Data.Text as T
import Data.Time
import Data.Typeable

import GHC.Generics hiding (from)
import GHC.Stack
import GHC.Stats

import qualified Network.HTTP.Client as HTTP
import qualified Network.HTTP.Client.TLS as HTTPS

import qualified Streaming.Prelude as S

import System.Directory
import System.FilePath
import System.IO
import qualified System.Logger as L
import System.LogLevel
import System.Mem

-- internal modules

import Chainweb.BlockHeader
import Chainweb.Chainweb
import Chainweb.Chainweb.Configuration
Expand All @@ -94,35 +61,50 @@ import Chainweb.Mempool.Consensus (ReintroducedTxsLog)
import Chainweb.Mempool.InMemTypes (MempoolStats(..))
import Chainweb.Miner.Coordinator (MiningStats)
import Chainweb.Pact.Backend.DbCache (DbCacheStats)
import Chainweb.Pact.Service.PactQueue (PactQueueStats)
import Chainweb.Pact.RestAPI.Server (PactCmdLog(..))
import Chainweb.Pact.Service.PactQueue (PactQueueStats)
import Chainweb.Pact.Types
import Chainweb.Payload
import Chainweb.Payload.PayloadStore
import Chainweb.Storage.Table.RocksDB
import Chainweb.Time
import Data.Time.Format.ISO8601
import Chainweb.Utils
import Chainweb.Utils.RequestLog
import Chainweb.Version
import Chainweb.Version.Mainnet
import Chainweb.Version.Testnet04 (testnet04)
import Chainweb.Version.Registry

import Chainweb.Storage.Table.RocksDB

import Configuration.Utils hiding (Error)
import Configuration.Utils.Validation (validateFilePath)
import Control.Concurrent
import Control.Concurrent.Async
import Control.DeepSeq
import Control.Exception
import Control.Lens hiding ((.=))
import Control.Monad
import Control.Monad.Managed
import Data.LogMessage

import Data.Text (Text)
import Data.Typeable
import GHC.Generics hiding (from)
import GHC.Stack
import GHC.Stats
import Network.HTTP.Client qualified as HTTP
import Network.HTTP.Client.TLS qualified as HTTPS
import P2P.Node

import PkgInfo

import Streaming.Prelude qualified as S
import System.Directory
import System.FilePath
import System.IO
import System.LogLevel
import System.Logger qualified as L
import System.Mem
import Utils.CheckRLimits
import Utils.InstallSignalHandlers
import Utils.Logging
import Utils.Logging.Config
import Utils.Logging.Trace

import Utils.CheckRLimits
import Utils.InstallSignalHandlers

-- -------------------------------------------------------------------------- --
-- Configuration

Expand Down Expand Up @@ -479,60 +461,6 @@ mkTelemetryLogger
mkTelemetryLogger mgr = configureHandler
$ withJsonHandleBackend @a (sshow $ typeRep $ Proxy @a) mgr pkgInfoScopes

-- -------------------------------------------------------------------------- --
-- Service Date

newtype ServiceDate = ServiceDate Text

instance Show ServiceDate where
show (ServiceDate t) = "Service interval end: " <> T.unpack t

instance Exception ServiceDate where
fromException = asyncExceptionFromException
toException = asyncExceptionToException

withServiceDate
:: ChainwebVersion
-> (LogLevel -> Text -> IO ())
-> Maybe UTCTime
-> IO a
-> IO a
withServiceDate v lf msd inner = case msd of
Nothing -> do
inner
Just sd -> do
if _versionCode v == _versionCode mainnet || _versionCode v == _versionCode testnet04
then do
race (timer sd) inner >>= \case
Left () -> error "Service date thread terminated unexpectedly"
Right a -> return a
else do
inner
where
timer t = runForever lf "ServiceDate" $ do
now <- getCurrentTime
when (now >= t) $ do
lf Error shutdownMessage
throw $ ServiceDate shutdownMessage

let w = diffUTCTime t now
let micros = round $ w * 1_000_000
lf Warn warning
threadDelay $ min (10 * 60 * 1_000_000) micros

where
warning :: Text
warning = T.concat
[ "This version of chainweb node will stop working at " <> sshow t <> "."
, " Please upgrade to a new version before that date."
]

shutdownMessage :: Text
shutdownMessage = T.concat
[ "Shutting down. This version of chainweb was only valid until " <> sshow t <> "."
, " Please upgrade to a new version."
]

-- -------------------------------------------------------------------------- --
-- Encode Package Info into Log mesage scopes

Expand Down Expand Up @@ -575,9 +503,7 @@ main = do
, Handler $ \(e :: SomeException) ->
logFunctionJson logger Error (ProcessDied $ show e) >> throwIO e
] $ do
kt <- mapM iso8601ParseM (_versionServiceDate v)
withServiceDate (_configChainwebVersion (_nodeConfigChainweb conf)) (logFunctionText logger) kt $ void $
race (node conf logger) (gcRunner (logFunctionText logger))
void $ race (node conf logger) (gcRunner (logFunctionText logger))
where
gcRunner lf = runForever lf "GarbageCollect" $ do
performMajorGC
Expand Down
3 changes: 0 additions & 3 deletions src/Chainweb/RestAPI/NodeInfo.hs
Original file line number Diff line number Diff line change
Expand Up @@ -70,8 +70,6 @@ data NodeInfo = NodeInfo
-- ^ Genesis heights of each chain.
, nodeHistoricalChains :: NE.NonEmpty (BlockHeight, [(ChainId, [ChainId])])
-- ^ All graph upgrades
, nodeServiceDate :: Maybe Text
-- ^ The upcoming service date for the node.
, nodeBlockDelay :: BlockDelay
-- ^ The PoW block delay of the node (microseconds)
}
Expand All @@ -96,7 +94,6 @@ nodeInfoHandler v (SomeCutDb (CutDbT db :: CutDbT cas v)) = do
, nodeLatestBehaviorHeight = latestBehaviorAt v
, nodeGenesisHeights = map (\c -> (chainIdToText c, genesisHeight v c)) $ HS.toList (chainIds v)
, nodeHistoricalChains = ruleElems $ fmap (HM.toList . HM.map HS.toList . toAdjacencySets) $ _versionGraphs v
, nodeServiceDate = T.pack <$> _versionServiceDate v
, nodeBlockDelay = _versionBlockDelay v
}

Expand Down
3 changes: 0 additions & 3 deletions src/Chainweb/Version.hs
Original file line number Diff line number Diff line change
Expand Up @@ -74,7 +74,6 @@ module Chainweb.Version
, versionGenesis
, versionVerifierPluginNames
, versionQuirks
, versionServiceDate
, genesisBlockPayload
, genesisBlockPayloadHash
, genesisBlockTarget
Expand Down Expand Up @@ -513,8 +512,6 @@ data ChainwebVersion
-- ^ Verifier plugins that can be run to verify transaction contents.
, _versionQuirks :: VersionQuirks
-- ^ Modifications to behavior at particular blockheights
, _versionServiceDate :: Maybe String
-- ^ The node service date for this version.
}
deriving stock (Generic)
deriving anyclass NFData
Expand Down
1 change: 0 additions & 1 deletion src/Chainweb/Version/Development.hs
Original file line number Diff line number Diff line change
Expand Up @@ -64,5 +64,4 @@ devnet = ChainwebVersion
, _versionVerifierPluginNames = AllChains $ Bottom
(minBound, Set.fromList $ map VerifierName ["hyperlane_v3_message", "allow", "signed_list"])
, _versionQuirks = noQuirks
, _versionServiceDate = Nothing
}
1 change: 0 additions & 1 deletion src/Chainweb/Version/Mainnet.hs
Original file line number Diff line number Diff line change
Expand Up @@ -231,5 +231,4 @@ mainnet = ChainwebVersion
, (unsafeChainId 9, HM.fromList [((BlockHeight 4594049, TxBlockIdx 0), Gas 69_092)])
]
}
, _versionServiceDate = Just "2026-01-07T00:00:00Z"
}
1 change: 0 additions & 1 deletion src/Chainweb/Version/RecapDevelopment.hs
Original file line number Diff line number Diff line change
Expand Up @@ -128,5 +128,4 @@ recapDevnet = ChainwebVersion
(600, Set.fromList $ map VerifierName ["hyperlane_v3_message", "allow", "signed_list"]) `Above`
Bottom (minBound, mempty)
, _versionQuirks = noQuirks
, _versionServiceDate = Nothing
}
1 change: 0 additions & 1 deletion src/Chainweb/Version/Testnet04.hs
Original file line number Diff line number Diff line change
Expand Up @@ -199,5 +199,4 @@ testnet04 = ChainwebVersion
, (unsafeChainId 2, HM.fromList [((BlockHeight 4108311, TxBlockIdx 0), Gas 65_130)])
]
}
, _versionServiceDate = Just "2026-01-07T00:00:00Z"
}
1 change: 0 additions & 1 deletion test/lib/Chainweb/Test/Orphans/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -299,7 +299,6 @@ instance Arbitrary NodeInfo where
, nodeLatestBehaviorHeight = latestBehaviorAt v
, nodeGenesisHeights = map (\c -> (chainIdToText c, genesisHeight v c)) $ HS.toList $ chainIds v
, nodeHistoricalChains = ruleElems $ fmap (HM.toList . HM.map HS.toList . toAdjacencySets) $ _versionGraphs v
, nodeServiceDate = T.pack <$> _versionServiceDate v
, nodeBlockDelay = _versionBlockDelay v
}

Expand Down
Loading
Loading