Skip to content
Open
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
3 changes: 3 additions & 0 deletions chainweb.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -148,6 +148,8 @@ library
, Chainweb.BlockHeader.Genesis.QuirkedGasPact5InstantTimedCPM1to9Payload
, Chainweb.BlockHeader.Genesis.Testnet040Payload
, Chainweb.BlockHeader.Genesis.Testnet041to19Payload
, Chainweb.BlockHeader.Genesis.Testnet060Payload
, Chainweb.BlockHeader.Genesis.Testnet061to19Payload
, Chainweb.BlockHeader.Genesis.Mainnet0Payload
, Chainweb.BlockHeader.Genesis.Mainnet1Payload
, Chainweb.BlockHeader.Genesis.Mainnet2Payload
Expand Down Expand Up @@ -273,6 +275,7 @@ library
, Chainweb.Version.RecapDevelopment
, Chainweb.Version.Registry
, Chainweb.Version.Testnet04
, Chainweb.Version.Testnet06
, Chainweb.Version.Utils
, Chainweb.WebBlockHeaderDB
, Chainweb.WebPactExecutionService
Expand Down
2 changes: 2 additions & 0 deletions cwtools/ea/Ea.hs
Original file line number Diff line number Diff line change
Expand Up @@ -84,6 +84,7 @@ main = do
, pact53Transitionnet
, quirkedPact5Instantnet
, testnet04
, testnet06
, mainnet
, genTxModules
, genCoinV3Payloads
Expand All @@ -108,6 +109,7 @@ main = do
pact53Transitionnet = mkPayloads [pact53TransitionCPM0, pact53TransitionCPMN]
quirkedPact5Instantnet = mkPayloads [quirkedPact5InstantCPM0, quirkedPact5InstantCPMN]
testnet04 = mkPayloads [testnet040, testnet04N]
testnet06 = mkPayloads [testnet060, testnet06N]
mainnet = mkPayloads
[ mainnet0
, mainnet1
Expand Down
27 changes: 27 additions & 0 deletions cwtools/ea/Ea/Genesis.hs
Original file line number Diff line number Diff line change
Expand Up @@ -36,6 +36,10 @@ module Ea.Genesis
, testnet040
, testnet04N

-- * Testnet06 Genesis txs
, testnet060
, testnet06N

-- * Mainnet Genesis txs
, mainnet0
, mainnet1
Expand Down Expand Up @@ -77,6 +81,7 @@ import Chainweb.Version.Development
import Chainweb.Version.RecapDevelopment
import Chainweb.Version.Mainnet
import Chainweb.Version.Testnet04
import Chainweb.Version.Testnet06

-- ---------------------------------------------------------------------- --
-- Genesis Tx Data
Expand Down Expand Up @@ -372,6 +377,28 @@ testnetAllocations = "pact/genesis/testnet04/allocations.yaml"
testnetKeysets :: FilePath
testnetKeysets = "pact/genesis/testnet04/keysets.yaml"


-- ---------------------------------------------------------------------- --
-- Testnet 06

testnet060 :: Genesis
testnet060 = Genesis
{ _version = Testnet06
, _tag = "Testnet06"
, _txChainIds = onlyChainId 0
, _coinbase = Just "pact/genesis/testnet06/grants0.yaml"
, _keysets = Just "pact/genesis/testnet06/keysets.yaml"
, _allocations = Just "pact/genesis/testnet06/allocations.yaml"
, _namespaces = Just testNs
, _coinContract = [fungibleAssetV1, coinContractV1, gasPayer]
}

testnet06N :: Genesis
testnet06N = testnet060
& txChainIds .~ mkChainIdRange 1 19
& coinbase ?~ "pact/genesis/testnet06/grantsN.yaml"


-- ---------------------------------------------------------------------- --
-- Mainnet

Expand Down
6 changes: 6 additions & 0 deletions pact/genesis/testnet06/allocations.yaml
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
code: |-
(coin.create-allocation-account "allocation00" (time "1900-10-15T18:00:00Z") "allocation00" 1000000.0)
(coin.create-allocation-account "allocation01" (time "2026-01-31T18:00:00Z") "allocation01" 1000000.0)
(coin.create-allocation-account "allocation02" (time "2026-06-31T18:00:00Z") "allocation02" 1000000.0)
nonce: testnet-allocations-0
keyPairs: []
21 changes: 21 additions & 0 deletions pact/genesis/testnet06/grants0.yaml
Original file line number Diff line number Diff line change
@@ -0,0 +1,21 @@
# Internal testnet accounts
code: |-
(coin.coinbase "sender0" (read-keyset "sender0") 1.0)
(coin.coinbase "pascal" (read-keyset "pascal") 100000.0)
(coin.coinbase "edmund" (read-keyset "edmund") 100000.0)
(coin.coinbase "jose" (read-keyset "jose") 100000.0)
(coin.coinbase "jumbo" (read-keyset "jumbo") 100000.0)
(coin.coinbase "philipp" (read-keyset "edmund") 100000.0)
(coin.coinbase "louis" (read-keyset "louis") 100000.0)


data:
sender0: ["c03e76c81a56f831a1ea91b93545d6b49daffc53c7416e065fcffb025faee47e"]
pascal: ["85e745b37605de2e4be123c8e9e65404227912c429e45f87b348b5c19ffb1f38"]
edmund: ["bb42ed45d8f2676b0b75cc11abe834f8287841322271ba574011e4fdf23631b7"]
jose: ["f5a17c5fd9f9d2623ba5e6283de1445f694c0d5a6f7df7b6a44a4f887b3e9eae"]
jumbo: ["eeb0fca9d4d8a72178e4d150152858484a63c27d3991caf48cc9003479156f00"]
philipp: ["3c7cd44578bb90b793e62a10f05a99ce9a2e0f067fbb4ff094d19e13a279ef9b"]
louis: ["c389e2fab9fabdc2958d3d9916ea7899f35b906d192b69f211a79bb4c2379bcf"]
nonce: testnet06-grants-0
keyPairs: []
8 changes: 8 additions & 0 deletions pact/genesis/testnet06/grantsN.yaml
Original file line number Diff line number Diff line change
@@ -0,0 +1,8 @@
# Internal testnet accounts
code: |-
(coin.coinbase "sender0" (read-keyset "sender0") 1.0)

data:
sender0: ["c03e76c81a56f831a1ea91b93545d6b49daffc53c7416e065fcffb025faee47e"]
nonce: testnet06-grants-N
keyPairs: []
12 changes: 12 additions & 0 deletions pact/genesis/testnet06/keysets.yaml
Original file line number Diff line number Diff line change
@@ -0,0 +1,12 @@
code: |-
(define-keyset "allocation00" (read-keyset "allocation00"))
(define-keyset "allocation01" (read-keyset "allocation01"))
(define-keyset "allocation02" (read-keyset "allocation02"))

data:
allocation00: ["f8a1c425cb65899ae0bf0dd4c6a982554f2ce8914c5084446f4999c3c0019990"]
allocation01: ["e55612401fb67190d3c0a905749264806a3b66c9b9d048b84b96e120e4a387dc"]
allocation02: ["d2502cdab08ef8649090e924d0fd69ce89c2c314fb52bf54405769aa5b425eeb"]

nonce: testnet06-keysets-N
keyPairs: []
37 changes: 37 additions & 0 deletions src/Chainweb/BlockHeader/Genesis/Testnet060Payload.hs

Large diffs are not rendered by default.

37 changes: 37 additions & 0 deletions src/Chainweb/BlockHeader/Genesis/Testnet061to19Payload.hs

Large diffs are not rendered by default.

12 changes: 7 additions & 5 deletions src/Chainweb/Version/Registry.hs
Original file line number Diff line number Diff line change
Expand Up @@ -49,14 +49,15 @@ import Chainweb.Version.Development
import Chainweb.Version.RecapDevelopment
import Chainweb.Version.Mainnet
import Chainweb.Version.Testnet04
import Chainweb.Version.Testnet06
import Chainweb.Utils.Rule
-- temporarily left off because it doesn't validate

{-# NOINLINE versionMap #-}
versionMap :: IORef (HashMap ChainwebVersionCode ChainwebVersion)
versionMap = unsafePerformIO $ do
traverse_ validateVersion knownVersions
newIORef $ HM.fromList [(_versionCode v, v) | v <- [mainnet, testnet04]]
newIORef $ HM.fromList [(_versionCode v, v) | v <- [mainnet, testnet04, testnet06]]

-- | Register a version into our registry by code, ensuring it contains no
-- errors and there are no others registered with that code.
Expand All @@ -74,8 +75,8 @@ registerVersion v = do
-- | Unregister a version from the registry. This is ONLY for testing versions.
unregisterVersion :: HasCallStack => ChainwebVersion -> IO ()
unregisterVersion v = do
if elem (_versionCode v) (_versionCode <$> [mainnet, testnet04])
then error "You cannot unregister mainnet or testnet04 versions"
if elem (_versionCode v) (_versionCode <$> [mainnet, testnet06])
then error "You cannot unregister mainnet or testnet06 versions"
else atomicModifyIORef' versionMap $ \m -> (HM.delete (_versionCode v) m, ())

validateVersion :: HasCallStack => ChainwebVersion -> IO ()
Expand Down Expand Up @@ -146,6 +147,7 @@ lookupVersionByName :: HasCallStack => ChainwebVersionName -> ChainwebVersion
lookupVersionByName name
| name == _versionName mainnet = mainnet
| name == _versionName testnet04 = testnet04
| name == _versionName testnet06 = testnet06
| otherwise = lookupVersion & versionName .~ name
where
lookupVersion = unsafeDupablePerformIO $ do
Expand All @@ -163,12 +165,12 @@ fabricateVersionWithName name =

-- | Versions known to us by name.
knownVersions :: [ChainwebVersion]
knownVersions = [mainnet, testnet04, recapDevnet, devnet]
knownVersions = [mainnet, testnet04, testnet06, recapDevnet, devnet]

-- | Look up a known version by name, usually with `m` instantiated to some
-- configuration parser monad.
findKnownVersion :: MonadFail m => ChainwebVersionName -> m ChainwebVersion
findKnownVersion vn =
case find (\v -> _versionName v == vn) knownVersions of
Nothing -> fail $ T.unpack (getChainwebVersionName vn) <> " is not a known version: try development, mainnet01, or testnet04"
Nothing -> fail $ T.unpack (getChainwebVersionName vn) <> " is not a known version: try development, mainnet01, or testnet04/06 "
Just v -> return v
2 changes: 2 additions & 0 deletions src/Chainweb/Version/Testnet04.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,8 @@
{-# language QuasiQuotes #-}
{-# language ViewPatterns #-}

-- Note: Testnet04 is deprecated

module Chainweb.Version.Testnet04(testnet04, pattern Testnet04) where

import Control.Lens
Expand Down
127 changes: 127 additions & 0 deletions src/Chainweb/Version/Testnet06.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,127 @@
{-# language LambdaCase #-}
{-# language NumericUnderscores #-}
{-# language OverloadedStrings #-}
{-# language PatternSynonyms #-}
{-# language QuasiQuotes #-}
{-# language ViewPatterns #-}

module Chainweb.Version.Testnet06(testnet06, pattern Testnet06) where

import qualified Data.HashMap.Strict as HM
import qualified Data.Set as Set

import Chainweb.BlockCreationTime
import Chainweb.BlockHeight
import Chainweb.ChainId
import Chainweb.Difficulty
import Chainweb.Graph
import Chainweb.Time
import Chainweb.Utils
import Chainweb.Utils.Rule
import Chainweb.Version
import P2P.BootstrapNodes

import Pact.Types.Verifier

import qualified Chainweb.Pact.Transactions.OtherTransactions as CoinV2
import qualified Chainweb.Pact.Transactions.CoinV3Transactions as CoinV3
import qualified Chainweb.Pact.Transactions.CoinV4Transactions as CoinV4
import qualified Chainweb.Pact.Transactions.CoinV5Transactions as CoinV5
import qualified Chainweb.Pact.Transactions.CoinV6Transactions as CoinV6

import qualified Chainweb.BlockHeader.Genesis.Testnet060Payload as TST0
import qualified Chainweb.BlockHeader.Genesis.Testnet061to19Payload as TSTN

pattern Testnet06 :: ChainwebVersion
pattern Testnet06 <- ((== testnet06) -> True) where
Testnet06 = testnet06

testnet06 :: ChainwebVersion
testnet06 = ChainwebVersion
{ _versionCode = ChainwebVersionCode 0x00000008
, _versionName = ChainwebVersionName "testnet06"

, _versionForks = tabulateHashMap $ \case
SlowEpoch -> AllChains $ ForkAtBlockHeight $ BlockHeight 0
Vuln797Fix -> AllChains $ ForkAtBlockHeight $ BlockHeight 0
PactBackCompat_v16 -> AllChains $ ForkAtBlockHeight $ BlockHeight 0
OldTargetGuard -> AllChains $ ForkAtBlockHeight $ BlockHeight 0
SkipFeatureFlagValidation -> AllChains $ ForkAtBlockHeight $ BlockHeight 0
SkipTxTimingValidation -> AllChains $ ForkAtBlockHeight $ BlockHeight 2
ModuleNameFix -> AllChains $ ForkAtBlockHeight $ BlockHeight 2
ModuleNameFix2 -> AllChains $ ForkAtBlockHeight $ BlockHeight 2
CoinV2 -> onChains $ [(unsafeChainId 0, ForkAtBlockHeight $ BlockHeight 3)] <> [(unsafeChainId i, ForkAtBlockHeight $ BlockHeight 4) | i <- [1..19]]
OldDAGuard -> AllChains $ ForkAtBlockHeight $ BlockHeight 13
PactEvents -> AllChains $ ForkAtBlockHeight $ BlockHeight 40
SPVBridge -> AllChains $ ForkAtBlockHeight $ BlockHeight 50
Pact4Coin3 -> AllChains $ ForkAtBlockHeight $ BlockHeight 80
Pact42 -> AllChains $ ForkAtBlockHeight $ BlockHeight 90
EnforceKeysetFormats -> AllChains $ ForkAtBlockHeight $ BlockHeight 100
CheckTxHash -> AllChains $ ForkAtBlockHeight $ BlockHeight 110
Chainweb213Pact -> AllChains $ ForkAtBlockHeight $ BlockHeight 95
Chainweb214Pact -> AllChains $ ForkAtBlockHeight $ BlockHeight 115
Chainweb215Pact -> AllChains $ ForkAtBlockHeight $ BlockHeight 165
Pact44NewTrans -> AllChains $ ForkAtBlockHeight $ BlockHeight 185
Chainweb216Pact -> AllChains $ ForkAtBlockHeight $ BlockHeight 215
Chainweb217Pact -> AllChains $ ForkAtBlockHeight $ BlockHeight 470
Chainweb218Pact -> AllChains $ ForkAtBlockHeight $ BlockHeight 500
Chainweb219Pact -> AllChains $ ForkAtBlockHeight $ BlockHeight 550
Chainweb220Pact -> AllChains $ ForkAtBlockHeight $ BlockHeight 560
Chainweb221Pact -> AllChains $ ForkAtBlockHeight $ BlockHeight 580
Chainweb222Pact -> AllChains $ ForkAtBlockHeight $ BlockHeight 590
Chainweb223Pact -> AllChains $ ForkAtBlockHeight $ BlockHeight 600
Chainweb224Pact -> AllChains $ ForkAtBlockHeight $ BlockHeight 610
Chainweb225Pact -> AllChains $ ForkAtBlockHeight $ BlockHeight 620
Pact5Fork -> AllChains $ ForkAtBlockHeight $ BlockHeight 640
Chainweb228Pact -> AllChains $ ForkAtBlockHeight $ BlockHeight 650
Chainweb230Pact -> AllChains $ ForkAtBlockHeight $ BlockHeight 680
Chainweb231Pact -> AllChains $ ForkAtBlockHeight $ BlockHeight 690
Chainweb31 -> AllChains $ ForkAtBlockHeight $ BlockHeight 700
MigratePlatformShare -> AllChains $ ForkNever

, _versionUpgrades = foldr (chainZip HM.union) (AllChains mempty)
[ indexByForkHeights testnet06
[ (CoinV2, AllChains (Pact4Upgrade CoinV2.transactions False))
, (Pact4Coin3, AllChains (Pact4Upgrade CoinV3.transactions True))
, (Chainweb214Pact, AllChains (Pact4Upgrade CoinV4.transactions True))
, (Chainweb215Pact, AllChains (Pact4Upgrade CoinV5.transactions True))
, (Chainweb223Pact, AllChains (Pact4Upgrade CoinV6.transactions False))
]
]

, _versionGraphs = Bottom (minBound, twentyChainGraph)
, _versionBlockDelay = BlockDelay 30_000_000
, _versionWindow = WindowWidth 120
, _versionHeaderBaseSizeBytes = 318 - 110
, _versionBootstraps = domainAddr2PeerInfo testnet06BootstrapHosts
, _versionGenesis = VersionGenesis
-- TODO Setup properly here
{ _genesisBlockTarget = onChains $ concat
[ [(unsafeChainId i, HashTarget $ maxBound `div` 100_000) | i <- [0..19]]
]
-- TODO Setup Genesis time properly
, _genesisTime = AllChains $ BlockCreationTime [timeMicrosQQ| 2019-07-17T18:28:37.613832 |]
, _genesisBlockPayload = onChains $ concat
[ [(unsafeChainId 0, TST0.payloadBlock)]
, [(unsafeChainId i, TSTN.payloadBlock) | i <- [1..19]]
]
}

, _versionMaxBlockGasLimit = Bottom (minBound, Just 180_000)
, _versionSpvProofRootValidWindow = Bottom (minBound, Nothing)
, _versionCheats = VersionCheats
{ _disablePow = False
, _fakeFirstEpochStart = False
, _disablePact = False
}
, _versionDefaults = VersionDefaults
{ _disablePeerValidation = False
, _disableMempoolSync = False
}
, _versionVerifierPluginNames = AllChains $
(600, Set.fromList $ map VerifierName ["hyperlane_v3_message"]) `Above`
Bottom (minBound, mempty)
, _versionQuirks = noQuirks
, _versionForkNumber = 0
, _versionForkVoteCastingLength = 120 * 119 -- 5 days
}
17 changes: 17 additions & 0 deletions src/P2P/BootstrapNodes.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,8 @@
module P2P.BootstrapNodes
( mainnetBootstrapHosts
, testnet04BootstrapHosts
, testnet06BootstrapHosts
,
) where

-- internal modules
Expand Down Expand Up @@ -57,3 +59,18 @@ testnet04BootstrapHosts = []
-- , "ap1.testnet.chainweb.com:443"
-- , "ap2.testnet.chainweb.com:443"
-- ]

-- -------------------------------------------------------------------------- --
-- | Testnet06 bootstrap nodes.
--
-- Nodes in this list need a public DNS name and a corresponding TLS
-- certificate. Operators of the nodes are expected to guarantee long term
-- availability of the nodes.
--
-- Please make a pull request, if you like to see your node being included here.
--
testnet06BootstrapHosts :: [HostAddress]
testnet06BootstrapHosts = map unsafeHostAddressFromText
[ "testnet06-1.chainweb-community.org:443"
, "testnet06-2.chainweb-community.org:443"
]
Loading