Skip to content

Commit

Permalink
Use getProjectBase to fix tests
Browse files Browse the repository at this point in the history
  • Loading branch information
newhoggy committed May 29, 2023
1 parent 48abe26 commit f5fb3a8
Showing 1 changed file with 38 additions and 32 deletions.
@@ -1,6 +1,9 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}

module Test.Golden.Testnet.Config where
module Test.Golden.Testnet.Config
( goldenDefaultConfigYaml
) where

import Prelude

Expand All @@ -9,6 +12,7 @@ import Data.Aeson.Encode.Pretty (encodePretty)
import qualified Data.ByteString.Lazy as LB
import qualified Data.Text as Text
import qualified Data.Text.Encoding as Text
import System.FilePath ((</>))

import Cardano.Api

Expand All @@ -17,38 +21,40 @@ import Testnet.Options
import Hedgehog
import Hedgehog.Extras.Test.Base (propertyOnce)
import Hedgehog.Extras.Test.Golden (diffVsGoldenFile)

import qualified Hedgehog.Extras.Test.Process as H

goldenDefaultConfigYaml :: Property
goldenDefaultConfigYaml = propertyOnce $ do
let allEras = map createConfigStringAndPath [minBound..maxBound]
base <- H.getProjectBase
let allEras = map (createConfigStringAndPath base) [minBound..maxBound]
mapM_ (uncurry diffVsGoldenFile) allEras
where
createConfigStringAndPath :: AnyCardanoEra -> (String, FilePath)
createConfigStringAndPath era =
let configStr = createConfigYamlString era
configPath = createGoldenFilePath era
in (configStr, configPath)

createGoldenFilePath :: AnyCardanoEra -> FilePath
createGoldenFilePath (AnyCardanoEra ByronEra) =
"test/cardano-testnet-test/files/golden/byron_node_default_config.json"
createGoldenFilePath (AnyCardanoEra ShelleyEra) =
"test/cardano-testnet-test/files/golden/shelley_node_default_config.json"
createGoldenFilePath (AnyCardanoEra AllegraEra) =
"test/cardano-testnet-test/files/golden/allegra_node_default_config.json"
createGoldenFilePath (AnyCardanoEra MaryEra) =
"test/cardano-testnet-test/files/golden/mary_node_default_config.json"
createGoldenFilePath (AnyCardanoEra AlonzoEra) =
"test/cardano-testnet-test/files/golden/alonzo_node_default_config.json"
createGoldenFilePath (AnyCardanoEra BabbageEra) =
"test/cardano-testnet-test/files/golden/babbage_node_default_config.json"
createGoldenFilePath (AnyCardanoEra ConwayEra) =
"test/cardano-testnet-test/files/golden/conway_node_default_config.json"

createConfigYamlString :: AnyCardanoEra -> String
createConfigYamlString era =
let configBs = LB.toStrict . encodePretty
. Object . defaultYamlHardforkViaConfig $ era
configStr = Text.unpack $ Text.decodeUtf8 configBs
in configStr

createConfigStringAndPath :: FilePath -> AnyCardanoEra -> (String, FilePath)
createConfigStringAndPath base era =
let configStr = createConfigYamlString era
configPath = base </> createGoldenFilePath era
in (configStr, configPath)

createGoldenFilePath :: AnyCardanoEra -> FilePath
createGoldenFilePath = \case
AnyCardanoEra ByronEra ->
"cardano-testnet/test/cardano-testnet-test/files/golden/byron_node_default_config.json"
AnyCardanoEra ShelleyEra ->
"cardano-testnet/test/cardano-testnet-test/files/golden/shelley_node_default_config.json"
AnyCardanoEra AllegraEra ->
"cardano-testnet/test/cardano-testnet-test/files/golden/allegra_node_default_config.json"
AnyCardanoEra MaryEra ->
"cardano-testnet/test/cardano-testnet-test/files/golden/mary_node_default_config.json"
AnyCardanoEra AlonzoEra ->
"cardano-testnet/test/cardano-testnet-test/files/golden/alonzo_node_default_config.json"
AnyCardanoEra BabbageEra ->
"cardano-testnet/test/cardano-testnet-test/files/golden/babbage_node_default_config.json"
AnyCardanoEra ConwayEra ->
"cardano-testnet/test/cardano-testnet-test/files/golden/conway_node_default_config.json"

createConfigYamlString :: AnyCardanoEra -> String
createConfigYamlString era =
let configBs = LB.toStrict . encodePretty
. Object . defaultYamlHardforkViaConfig $ era
configStr = Text.unpack $ Text.decodeUtf8 configBs
in configStr

0 comments on commit f5fb3a8

Please sign in to comment.