@@ -20,9 +20,9 @@ import Pos.Chain.Update (ApplicationName (ApplicationName),
20
20
BlockVersion (BlockVersion ),
21
21
BlockVersionData (bvdMaxBlockSize , bvdUnlockStakeEpoch ),
22
22
BlockVersionModifier (bvmMaxBlockSize , bvmUnlockStakeEpoch ),
23
- SoftwareVersion (SoftwareVersion ), UpdateConfiguration ,
24
- ccApplicationVersion_L , ccLastKnownBlockVersion_L ,
25
- obftEraFlagValue )
23
+ SoftwareVersion (.. ), UpdateConfiguration ,
24
+ ccApplicationName_L , ccApplicationVersion_L ,
25
+ ccLastKnownBlockVersion_L , obftEraFlagValue )
26
26
import qualified Pos.Client.CLI as CLI
27
27
import Pos.Core.Slotting (EpochIndex )
28
28
import Pos.DB.Class (gsAdoptedBVData )
@@ -42,15 +42,18 @@ import Types (NodeType (..))
42
42
43
43
import Serokell.Data.Memory.Units (Byte )
44
44
45
- mutateConfiguration :: Configuration -> Configuration
46
- mutateConfiguration cfg = (cfg & ccUpdate_L . ccLastKnownBlockVersion_L .~ BlockVersion 0 1 0 ) & ccUpdate_L . ccApplicationVersion_L .~ 1
45
+ -- | Helper to make sure BV and SV are set in accordance with the arguments passed in
46
+ confSetBvAndSv :: BlockVersion -> SoftwareVersion -> Configuration -> Configuration
47
+ confSetBvAndSv bv sv cfg = ((cfg & ccUpdate_L . ccLastKnownBlockVersion_L .~ bv)
48
+ & ccUpdate_L . ccApplicationVersion_L .~ (svNumber sv))
49
+ & ccUpdate_L . ccApplicationName_L .~ (svAppName sv)
47
50
48
51
mutateConfigurationForObft :: Configuration -> Configuration
49
- mutateConfigurationForObft cfg = (cfg & ccUpdate_L . ccLastKnownBlockVersion_L .~ BlockVersion 1 0 0 ) & over ccGenesis_L (updateUnlockStakeEpoch obftEraFlagValue)
50
-
51
- updateUnlockStakeEpoch :: EpochIndex -> StaticConfig -> StaticConfig
52
- updateUnlockStakeEpoch ei (GCSrc _ _) = error " updateUnlockStakeEpoch: got GCSrc"
53
- updateUnlockStakeEpoch ei (GCSpec gs) = GCSpec (gs { gsBlockVersionData = ((gsBlockVersionData gs) { bvdUnlockStakeEpoch = ei })})
52
+ mutateConfigurationForObft = over ccGenesis_L (updateUnlockStakeEpoch obftEraFlagValue)
53
+ where
54
+ updateUnlockStakeEpoch :: EpochIndex -> StaticConfig -> StaticConfig
55
+ updateUnlockStakeEpoch _ (GCSrc _ _) = error " updateUnlockStakeEpoch: got GCSrc"
56
+ updateUnlockStakeEpoch ei (GCSpec gs) = GCSpec (gs { gsBlockVersionData = ((gsBlockVersionData gs) { bvdUnlockStakeEpoch = ei })})
54
57
55
58
data ExpectedResult = SuccessFullUpdate | FailedProposalUpdate deriving (Show , Eq )
56
59
@@ -60,81 +63,23 @@ data ExpectedResult = SuccessFullUpdate | FailedProposalUpdate deriving (Show, E
60
63
logMsg :: String -> PocMode ()
61
64
logMsg = liftIO . hPutStrLn stderr
62
65
63
- {-# ANN testHardForkMechanism ("HLint: ignore Reduce duplication" :: Text) #-}
64
- testHardForkMechanism :: Script ()
65
- testHardForkMechanism = do
66
- genesisConfig <- getGenesisConfig
67
- let
68
- proposal :: Dict HasConfigurations -> Diffusion PocMode -> PocMode ()
69
- proposal Dict diffusion = do
70
- let
71
- keyIndex :: Int
72
- keyIndex = 0
73
- blockVersion = BlockVersion 0 1 0
74
- softwareVersion = SoftwareVersion (ApplicationName " cardano-sl" ) 1
75
- blockVersionModifier :: BlockVersionModifier
76
- blockVersionModifier = def { bvmUnlockStakeEpoch = Just obftEraFlagValue }
77
- doUpdate diffusion genesisConfig keyIndex blockVersion softwareVersion blockVersionModifier
78
- expectedResult = SuccessFullUpdate
79
- onStartup $ \ Dict _diffusion -> do
80
- stateDir <- view acStatePath
81
- loadNKeys stateDir 4
82
- on (1 ,2 ) proposal
83
- on (2 ,6 ) $ \ Dict _diffusion -> do
84
- uc <- view (lensOf @ UpdateConfiguration )
85
- proposals <- GS. getConfirmedProposals uc Nothing
86
- case (proposals, expectedResult) of
87
- ([] , FailedProposalUpdate ) -> do
88
- logMsg " expected failed proposal, passing test"
89
- endScript ExitSuccess
90
- (_, FailedProposalUpdate ) -> do
91
- logMsg " expected failure, but proposal was accepted!"
92
- endScript $ ExitFailure 1
93
- ([] , _) -> do
94
- logMsg " expected proposal to pass, but it didnt"
95
- endScript $ ExitFailure 2
96
- ([_one], SuccessFullUpdate ) -> do
97
- stateDir <- view acStatePath
98
- opts <- view acScriptOptions
99
- let
100
- -- the config for the script-runner is mirrored to the nodes it starts
101
- cfg = opts ^. srCommonNodeArgs . CLI. commonArgs_L
102
- newConfiguration <- liftIO $ mutateConfigurationYaml (cfg ^. CLI. configurationOptions_L . cfoFilePath_L) (cfg ^. CLI. configurationOptions_L . cfoKey_L) mutateConfigurationForObft
103
- liftIO $ BS. writeFile (T. unpack $ stateDir <> " /configuration2.yaml" ) newConfiguration
104
- let
105
- cfg2 = cfg & CLI. configurationOptions_L . cfoFilePath_L .~ (T. unpack $ stateDir <> " /configuration2.yaml" )
106
- forAllNodes_ $ \ node -> do
107
- stopNodeByName (Core , node)
108
- startNode $ NodeInfo node Core stateDir (stateDir <> " /topology.yaml" ) cfg2
109
- (_toomany, SuccessFullUpdate ) -> do
110
- logMsg " expected 1 proposal to pass, but >1 have passed"
111
- endScript $ ExitFailure 3
112
- on (3 ,10 ) $ \ Dict _diffusion -> do
113
- bvd <- gsAdoptedBVData
114
- case (bvdUnlockStakeEpoch bvd == obftEraFlagValue) of
115
- True -> do
116
- liftIO $ hPutStrLn stderr " test passed"
117
- endScript ExitSuccess
118
- _ -> do
119
- liftIO $ hPutStrLn stderr " bvdUnlockStakeEpoch was not what was we expected"
120
- endScript $ ExitFailure 4
121
- forM_ (range (0 ,20 )) $ \ epoch -> do
122
- on(epoch, 0 ) $ printbvd epoch 0
123
- on(epoch, 1 ) $ printbvd epoch 1
124
-
125
- test4 :: Byte -> ExpectedResult -> Script ()
126
- test4 targetblocksize expectedResult = do
66
+ sharedUpdateTester :: (Configuration -> Configuration )
67
+ -> ExpectedResult
68
+ -> BlockVersion
69
+ -> SoftwareVersion
70
+ -> BlockVersionModifier
71
+ -> (BlockVersionData -> Bool )
72
+ -> String
73
+ -> Script ()
74
+ sharedUpdateTester mutateConf expectedResult blockVersion softwareVersion
75
+ blockVersionModifier checkBvd errMsg = do
127
76
genesisConfig <- getGenesisConfig
128
77
let
129
78
proposal :: Dict HasConfigurations -> Diffusion PocMode -> PocMode ()
130
79
proposal Dict diffusion = do
131
80
let
132
81
keyIndex :: Int
133
82
keyIndex = 0
134
- blockVersion = BlockVersion 0 1 0
135
- softwareVersion = SoftwareVersion (ApplicationName " cardano-sl" ) 1
136
- blockVersionModifier :: BlockVersionModifier
137
- blockVersionModifier = def { bvmMaxBlockSize = Just targetblocksize }
138
83
doUpdate diffusion genesisConfig keyIndex blockVersion softwareVersion blockVersionModifier
139
84
onStartup $ \ Dict _diffusion -> do
140
85
stateDir <- view acStatePath
@@ -145,43 +90,85 @@ test4 targetblocksize expectedResult = do
145
90
proposals <- GS. getConfirmedProposals uc Nothing
146
91
case (proposals, expectedResult) of
147
92
([] , FailedProposalUpdate ) -> do
148
- logMsg " expected failed proposal, passing test "
93
+ logMsg " test passed: proposal failed, as expected "
149
94
endScript ExitSuccess
150
95
(_, FailedProposalUpdate ) -> do
151
- logMsg " expected failure, but proposal was accepted! "
96
+ logMsg " test failed: proposal was accepted, but we expected failure "
152
97
endScript $ ExitFailure 1
153
98
([] , _) -> do
154
- logMsg " expected proposal to pass , but it didnt "
99
+ logMsg " test failed: proposal failed , but we expected success "
155
100
endScript $ ExitFailure 2
156
101
([_one], SuccessFullUpdate ) -> do
157
102
stateDir <- view acStatePath
158
103
opts <- view acScriptOptions
159
104
let
160
105
-- the config for the script-runner is mirrored to the nodes it starts
161
106
cfg = opts ^. srCommonNodeArgs . CLI. commonArgs_L
162
- newConfiguration <- liftIO $ mutateConfigurationYaml (cfg ^. CLI. configurationOptions_L . cfoFilePath_L) (cfg ^. CLI. configurationOptions_L . cfoKey_L) mutateConfiguration
107
+ fullConfMutator = mutateConf . confSetBvAndSv blockVersion softwareVersion
108
+ --
109
+ newConfiguration <- liftIO $ mutateConfigurationYaml (cfg ^. CLI. configurationOptions_L . cfoFilePath_L)
110
+ (cfg ^. CLI. configurationOptions_L . cfoKey_L)
111
+ fullConfMutator
163
112
liftIO $ BS. writeFile (T. unpack $ stateDir <> " /configuration2.yaml" ) newConfiguration
164
113
let
165
114
cfg2 = cfg & CLI. configurationOptions_L . cfoFilePath_L .~ (T. unpack $ stateDir <> " /configuration2.yaml" )
166
115
forAllNodes_ $ \ node -> do
167
116
stopNodeByName (Core , node)
168
117
startNode $ NodeInfo node Core stateDir (stateDir <> " /topology.yaml" ) cfg2
169
118
(_toomany, SuccessFullUpdate ) -> do
170
- logMsg " expected 1 proposal to pass, but >1 have passed"
119
+ logMsg " test failed: expected 1 proposal to pass, but >1 have passed"
171
120
endScript $ ExitFailure 3
172
121
on (3 ,10 ) $ \ Dict _diffusion -> do
173
122
bvd <- gsAdoptedBVData
174
- if bvdMaxBlockSize bvd == targetblocksize
123
+ if checkBvd bvd
175
124
then do
176
125
liftIO $ hPutStrLn stderr " test passed"
177
126
endScript ExitSuccess
178
127
else do
179
- liftIO $ hPutStrLn stderr " max block size not what was expected "
128
+ liftIO $ hPutStrLn stderr errMsg
180
129
endScript $ ExitFailure 4
181
130
forM_ (range (0 ,20 )) $ \ epoch -> do
182
131
on(epoch, 0 ) $ printbvd epoch 0
183
132
on(epoch, 1 ) $ printbvd epoch 1
184
133
134
+ testHardForkMechanism :: Script ()
135
+ testHardForkMechanism =
136
+ sharedUpdateTester mutateConf expectedResult blockVersion softwareVersion
137
+ blockVersionModifier checkBvd errMsg
138
+ where
139
+ mutateConf :: Configuration -> Configuration
140
+ mutateConf = mutateConfigurationForObft
141
+ expectedResult :: ExpectedResult
142
+ expectedResult = SuccessFullUpdate
143
+ blockVersion :: BlockVersion
144
+ blockVersion = BlockVersion 1 0 0
145
+ softwareVersion :: SoftwareVersion
146
+ softwareVersion = SoftwareVersion (ApplicationName " cardano-sl" ) 0
147
+ blockVersionModifier :: BlockVersionModifier
148
+ blockVersionModifier = def { bvmUnlockStakeEpoch = Just obftEraFlagValue }
149
+ checkBvd :: BlockVersionData -> Bool
150
+ checkBvd bvd = bvdUnlockStakeEpoch bvd == obftEraFlagValue
151
+ errMsg :: String
152
+ errMsg = " bvdUnlockStakeEpoch was not what was we expected"
153
+
154
+ test4 :: Byte -> ExpectedResult -> Script ()
155
+ test4 targetblocksize expectedResult =
156
+ sharedUpdateTester mutateConf expectedResult blockVersion softwareVersion
157
+ blockVersionModifier checkBvd errMsg
158
+ where
159
+ mutateConf :: Configuration -> Configuration
160
+ mutateConf = identity
161
+ blockVersion :: BlockVersion
162
+ blockVersion = BlockVersion 0 1 0
163
+ softwareVersion :: SoftwareVersion
164
+ softwareVersion = SoftwareVersion (ApplicationName " cardano-sl" ) 1
165
+ blockVersionModifier :: BlockVersionModifier
166
+ blockVersionModifier = def { bvmMaxBlockSize = Just targetblocksize }
167
+ checkBvd :: BlockVersionData -> Bool
168
+ checkBvd bvd = bvdMaxBlockSize bvd == targetblocksize
169
+ errMsg :: String
170
+ errMsg = " max block size not what was expected"
171
+
185
172
emptyScript :: Script ()
186
173
emptyScript = do
187
174
pure ()
0 commit comments