4
4
{-# LANGUAGE OverloadedStrings #-}
5
5
{-# LANGUAGE ScopedTypeVariables #-}
6
6
7
- {- HLINT ignore "Use head" -}
8
-
9
7
module Cardano.Testnet.Test.Cli.Queries
10
8
( hprop_cli_queries
11
9
) where
@@ -19,10 +17,15 @@ import Prelude
19
17
20
18
import Control.Monad (forM_ )
21
19
import qualified Data.Aeson as Aeson
20
+ import Data.Bifunctor (bimap )
21
+ import Data.String
22
+ import Data.Text (Text )
23
+ import qualified Data.Text as T
22
24
import qualified Data.Vector as Vector
23
25
import GHC.Stack (HasCallStack )
24
26
import System.FilePath ((</>) )
25
27
28
+ import Testnet.Components.Configuration (eraToString )
26
29
import Testnet.Components.Query
27
30
import Testnet.Components.TestWatchdog
28
31
import qualified Testnet.Process.Cli as H
@@ -50,6 +53,7 @@ hprop_cli_queries = H.integrationWorkspace "cli-queries" $ \tempAbsBasePath' ->
50
53
let sbe = ShelleyBasedEraConway
51
54
era = toCardanoEra sbe
52
55
cEra = AnyCardanoEra era
56
+ eraName = eraToString era
53
57
fastTestnetOptions = cardanoDefaultTestnetOptions
54
58
{ cardanoEpochLength = 100
55
59
, cardanoSlotLength = 0.1
@@ -78,53 +82,102 @@ hprop_cli_queries = H.integrationWorkspace "cli-queries" $ \tempAbsBasePath' ->
78
82
H. note_ $ " Socketpath: " <> socketPath
79
83
H. note_ $ " Foldblocks config file: " <> configurationFile
80
84
81
- -- TODO: we could wait less: waiting 1 block should suffice.
82
85
checkDRepsNumber epochStateView sbe 3
83
86
84
- -- protocol-parameters to stdout
85
- protocolParametersOut <- H. execCli' execConfig
86
- [ " conway" , " query" , " protocol-parameters" ]
87
- H. diffVsGoldenFile
88
- protocolParametersOut
89
- " test/cardano-testnet-test/files/golden/queries/protocolParametersOut.txt"
90
- -- protocol-parameters to a file
91
- let protocolParametersOutFile = work </> " protocol-parameters-out.json"
92
- H. noteM_ $ H. execCli' execConfig [ " conway" , " query" , " protocol-parameters"
93
- , " --out-file" , protocolParametersOutFile]
94
- H. diffFileVsGoldenFile
95
- protocolParametersOutFile
96
- " test/cardano-testnet-test/files/golden/queries/protocolParametersFileOut.json"
97
-
98
- -- tip to stdout
99
- _ :: QueryTipLocalStateOutput <- H. noteShowM $ H. execCliStdoutToJson execConfig [ " conway" , " query" , " tip" ]
100
- -- tip to a file
101
- let tipOutFile = work </> " tip-out.json"
102
- H. noteM_ $ H. execCli' execConfig [ " conway" , " query" , " tip"
103
- , " --out-file" , tipOutFile]
104
- _ :: QueryTipLocalStateOutput <- H. leftFailM . H. readJsonFile $ tipOutFile
105
-
106
- -- stake-pools to stdout
107
- stakePoolsOut <- H. execCli' execConfig [ " conway" , " query" , " stake-pools" ]
108
- length (lines stakePoolsOut) H. === 3 -- Because, by default, 3 stake pools are created
109
- -- Light test of the query's answer, the ids should exist:
110
- forM_ (lines stakePoolsOut) $ \ stakePoolId -> do
111
- H. execCli' execConfig [ " conway" , " query" , " pool-state"
112
- , " --stake-pool-id" , stakePoolId ]
113
- -- stake-pools to a file
114
- let stakePoolsOutFile = work </> " stake-pools-out.json"
115
- H. noteM_ $ H. execCli' execConfig [ " conway" , " query" , " stake-pools"
116
- , " --out-file" , stakePoolsOutFile]
117
-
118
- -- query drep-state to stdout
119
- -- TODO: deserialize to a Haskell value when
120
- -- https://github.com/IntersectMBO/cardano-cli/issues/606 is tackled
121
- dreps :: Aeson. Value <- H. noteShowM $ H. execCliStdoutToJson execConfig [ " conway" , " query" , " drep-state" , " --all-dreps" ]
122
- assertArrayOfSize dreps 3
123
- -- query drep-state to a file
124
- let drepStateOutFile = work </> " drep-state-out.json"
125
- H. noteM_ $ H. execCli' execConfig [ " conway" , " query" , " drep-state" , " --all-dreps"
126
- , " --out-file" , drepStateOutFile]
127
- _ :: Aeson. Value <- H. leftFailM . H. readJsonFile $ drepStateOutFile
87
+
88
+ -- protocol-parameters
89
+ do
90
+ -- to stdout
91
+ protocolParametersOut <- H. execCli' execConfig [ eraName, " query" , " protocol-parameters" ]
92
+ H. diffVsGoldenFile
93
+ protocolParametersOut
94
+ " test/cardano-testnet-test/files/golden/queries/protocolParametersOut.txt"
95
+ -- protocol-parameters to a file
96
+ let protocolParametersOutFile = work </> " protocol-parameters-out.json"
97
+ H. noteM_ $ H. execCli' execConfig [ eraName, " query" , " protocol-parameters"
98
+ , " --out-file" , protocolParametersOutFile]
99
+ H. diffFileVsGoldenFile
100
+ protocolParametersOutFile
101
+ " test/cardano-testnet-test/files/golden/queries/protocolParametersFileOut.json"
102
+
103
+ -- tip
104
+ do
105
+ -- to stdout
106
+ _ :: QueryTipLocalStateOutput <- H. noteShowM $ H. execCliStdoutToJson execConfig [ eraName, " query" , " tip" ]
107
+ -- to a file
108
+ let tipOutFile = work </> " tip-out.json"
109
+ H. noteM_ $ H. execCli' execConfig [ eraName, " query" , " tip"
110
+ , " --out-file" , tipOutFile]
111
+ _ :: QueryTipLocalStateOutput <- H. readJsonFileOk tipOutFile
112
+ pure ()
113
+
114
+ -- stake-pools
115
+ do
116
+ -- to stdout
117
+ stakePoolsOut <- H. execCli' execConfig [ eraName, " query" , " stake-pools" ]
118
+ H. assertWith stakePoolsOut $ \ pools ->
119
+ length (lines pools) == 3 -- Because, by default, 3 stake pools are created
120
+ -- Light test of the query's answer, the ids should exist:
121
+ forM_ (lines stakePoolsOut) $ \ stakePoolId -> do
122
+ H. execCli' execConfig [ eraName, " query" , " pool-state"
123
+ , " --stake-pool-id" , stakePoolId ]
124
+ -- to a file
125
+ let stakePoolsOutFile = work </> " stake-pools-out.json"
126
+ H. noteM_ $ H. execCli' execConfig [ eraName, " query" , " stake-pools" , " --out-file" , stakePoolsOutFile]
127
+
128
+ -- stake-distribution
129
+ do
130
+ -- to stdout
131
+ stakeDistrOut <- H. execCli' execConfig [ eraName, " query" , " stake-distribution" ]
132
+ -- stake addresses with stake
133
+ let stakeAddresses :: [(Text , Text )] =
134
+ map
135
+ ( bimap T. strip T. strip
136
+ . T. breakOn " " -- separate address and stake
137
+ . T. strip
138
+ . fromString )
139
+ . drop 2 -- drop header
140
+ . lines
141
+ $ stakeDistrOut
142
+ H. assertWith stakeAddresses $ \ sa ->
143
+ -- Because, by default, 3 stake pools are created
144
+ length sa == 3
145
+ -- Light test of the query's answer, the ids should exist:
146
+ forM_ stakeAddresses $ \ (stakePoolId, _) -> do
147
+ H. execCli' execConfig [ eraName, " query" , " pool-state"
148
+ , " --stake-pool-id" , T. unpack stakePoolId ]
149
+ -- to a file
150
+ let stakePoolsOutFile = work </> " stake-distribution-out.json"
151
+ H. noteM_ $ H. execCli' execConfig [ eraName, " query" , " stake-distribution"
152
+ , " --out-file" , stakePoolsOutFile]
153
+
154
+ -- gov-state
155
+ do
156
+ -- to stdout
157
+ H. execCli' execConfig [ eraName, " query" , " gov-state" ]
158
+ >>=
159
+ (`H.diffVsGoldenFile`
160
+ " test/cardano-testnet-test/files/golden/queries/govStateOut.json" )
161
+ -- to a file
162
+ let govStateOutFile = work </> " gov-state-out.json"
163
+ H. noteM_ $ H. execCli' execConfig [ eraName, " query" , " gov-state" , " --out-file" , govStateOutFile]
164
+ H. diffFileVsGoldenFile
165
+ govStateOutFile
166
+ " test/cardano-testnet-test/files/golden/queries/govStateOut.json"
167
+
168
+ -- drep-state
169
+ do
170
+ -- to stdout
171
+ -- TODO: deserialize to a Haskell value when
172
+ -- https://github.com/IntersectMBO/cardano-cli/issues/606 is tackled
173
+ dreps :: Aeson. Value <- H. noteShowM $ H. execCliStdoutToJson execConfig [ eraName, " query" , " drep-state" , " --all-dreps" ]
174
+ assertArrayOfSize dreps 3
175
+ -- to a file
176
+ let drepStateOutFile = work </> " drep-state-out.json"
177
+ H. noteM_ $ H. execCli' execConfig [ eraName, " query" , " drep-state" , " --all-dreps"
178
+ , " --out-file" , drepStateOutFile]
179
+ _ :: Aeson. Value <- H. readJsonFileOk drepStateOutFile
180
+ pure ()
128
181
129
182
H. success
130
183
0 commit comments