{-# LANGUAGE OverloadedStrings #-} import Test.Hspec import Test.QuickCheck import qualified Data.ByteString as BS import Baserock.Schema.V9 import Control.Exception (throwIO, evaluate, bracket_) import Control.Monad.Except import Data.Yaml import Turtle v9_mock_chunk_instructions_brie_cc = ChunkInstructions { _chunkInstructionsName = "brie-cc", _buildSystem = "autotools", _preConfigureCommands = ["make configure"], _configureCommands = [], _postConfigureCommands = [], _preBuildCommands = [], _buildCommands = ["make all"], _postBuildCommands = [], _preInstallCommands = [], _installCommands = [], _postInstallCommands = [] } v9_mock_chunk_instructions_linux_api_headers = ChunkInstructions { _chunkInstructionsName = "linux-api-headers", _buildSystem = "autotools", _preConfigureCommands = ["make configure"], _configureCommands = [], _postConfigureCommands = [], _preBuildCommands = [], _buildCommands = ["make all"], _postBuildCommands = [], _preInstallCommands = [], _installCommands = [], _postInstallCommands = [] } v9_mock_stratum_grilled_essential = Stratum { _stratumName = "grilled-essential", _stratumDescription = Nothing, _stratumBDs = [ ], _chunks = [ Chunk { _chunkName = "brie-cc", _buildMode = "staging", _chunkBuildSystem = "manual", _repo = "gitlab:brie-cc", _chunkMorph = Just "quux/strata/grilled-essential/brie-cc.morph", _ref = "foo", _sha = Just "0c3506aa4f33da7fc2fba0fd6b614bf8e861e3ba", _chunkBDs = [] }, Chunk { _chunkName = "linux-api-headers", _buildMode = "staging", _chunkBuildSystem = "manual", _repo = "gitlab:kernel/linux-stable", _chunkMorph = Just "quux/strata/grilled-essential/linux-api-headers.morph", _ref = "bar", _sha = Just "9db87049dd8b357bf9be97f6394b5251e8606fe2", _chunkBDs = [ "brie-cc" ] } ]} v9_mock_chunk_instructions_ccake = ChunkInstructions { _chunkInstructionsName = "ccake", _buildSystem = "autotools", _preConfigureCommands = ["make configure"], _configureCommands = [], _postConfigureCommands = [], _preBuildCommands = [], _buildCommands = ["make all"], _postBuildCommands = [], _preInstallCommands = [], _installCommands = [], _postInstallCommands = [] } v9_mock_chunk_instructions_sesame_sed = ChunkInstructions { _chunkInstructionsName = "sesame-sed", _buildSystem = "autotools", _preConfigureCommands = ["make configure"], _configureCommands = [], _postConfigureCommands = [], _preBuildCommands = [], _buildCommands = ["make all"], _postBuildCommands = [], _preInstallCommands = [], _installCommands = [], _postInstallCommands = [] } v9_mock_stratum_core = Stratum { _stratumName = "core", _stratumDescription = Nothing, _stratumBDs = [ StratumBD { _stratumBDMorph = "quux/strata/grilled-essential.morph" }], _chunks = [ Chunk { _chunkName = "ccake", _buildMode = "staging", _chunkBuildSystem = "manual", _repo = "gitlab:upstream/ccake", _chunkMorph = Just "quux/strata/core/ccake.morph", _ref = "master", _sha = Just "0c3506aa4f33da7fc2fba0fd6b614bf8e861e3ba", _chunkBDs = [] }, Chunk { _chunkName = "sesame-sed", _buildMode = "staging", _chunkBuildSystem = "manual", _repo = "gitlab:upstream/sesame-sed", _chunkMorph = Just "quux/strata/core/sesame-sed.morph", _ref = "master", _sha = Just "0c3506aa4f33da7fc2fba0fd6b614bf8e861e3ba", _chunkBDs = [ "ccake" ] } ]} v9_mock_system_quux = System { _systemName = "quux-system-x86_32", _systemDescription = Nothing, _arch = "x86_32", _strata = [ StratumInclude { _stratumIncludeName = "grilled-essential", _stratumIncludeMorph = "quux/strata/grilled-essential.morph" }, StratumInclude { _stratumIncludeName = "core", _stratumIncludeMorph = "quux/strata/core.morph" } ], _configurationExtensions = ["extensions/smooth-and-creamy"]} v9_mock_stratum_grilled_essential_ast = (v9_mock_stratum_grilled_essential, [("quux/strata/grilled-essential/brie-cc.morph", v9_mock_chunk_instructions_brie_cc), ("quux/strata/grilled-essential/linux-api-headers.morph", v9_mock_chunk_instructions_linux_api_headers)]) v9_mock_stratum_core_ast = (v9_mock_stratum_core, [("quux/strata/core/ccake.morph", v9_mock_chunk_instructions_ccake), ("quux/strata/core/sesame-sed.morph", v9_mock_chunk_instructions_sesame_sed)]) v9_mock_system_quux_ast = (v9_mock_system_quux, [("quux/strata/grilled-essential.morph", v9_mock_stratum_grilled_essential_ast), ("quux/strata/core.morph", v9_mock_stratum_core_ast)]) in_mock_definitions_v9 = bracket_ (cd "test/mock-definitions-v9") (cd "../../") testDecodeAgainst x y = either (error . show) id <$> decodeFileEither x `shouldReturn` (Just y) main :: IO () main = hspec $ around_ in_mock_definitions_v9 $ do describe "Baserock.Schema.V9" $ do describe "ChunkInstructions" $ do it "decodes correctly" $ do "quux/strata/grilled-essential/brie-cc.morph" `testDecodeAgainst` v9_mock_chunk_instructions_brie_cc "quux/strata/grilled-essential/linux-api-headers.morph" `testDecodeAgainst` v9_mock_chunk_instructions_linux_api_headers "quux/strata/core/ccake.morph" `testDecodeAgainst` v9_mock_chunk_instructions_ccake "quux/strata/core/sesame-sed.morph" `testDecodeAgainst` v9_mock_chunk_instructions_sesame_sed it "encodes correctly" $ do BS.readFile "quux/strata/grilled-essential/brie-cc.morph" `shouldReturn` toPrettyYaml v9_mock_chunk_instructions_brie_cc BS.readFile "quux/strata/grilled-essential/linux-api-headers.morph" `shouldReturn` toPrettyYaml v9_mock_chunk_instructions_linux_api_headers BS.readFile "quux/strata/core/ccake.morph" `shouldReturn` toPrettyYaml v9_mock_chunk_instructions_ccake BS.readFile "quux/strata/core/sesame-sed.morph" `shouldReturn` toPrettyYaml v9_mock_chunk_instructions_sesame_sed describe "Stratum" $ do it "decodes correctly" $ do "quux/strata/grilled-essential.morph" `testDecodeAgainst` v9_mock_stratum_grilled_essential "quux/strata/core.morph" `testDecodeAgainst` v9_mock_stratum_core it "encodes correctly" $ do BS.readFile "quux/strata/grilled-essential.morph" `shouldReturn` toPrettyYaml v9_mock_stratum_grilled_essential BS.readFile "quux/strata/core.morph" `shouldReturn` toPrettyYaml v9_mock_stratum_core describe "System" $ do it "decodes correctly" $ do "quux/systems/quux-system-x86_32.morph" `testDecodeAgainst` v9_mock_system_quux it "encodes correctly" $ do BS.readFile "quux/systems/quux-system-x86_32.morph" `shouldReturn` toPrettyYaml v9_mock_system_quux describe "StratumAST" $ do it "decodes correctly" $ do either (error . show) id <$> decodeStratumAST "quux/strata/grilled-essential.morph" `shouldReturn` v9_mock_stratum_grilled_essential_ast either (error . show) id <$> decodeStratumAST "quux/strata/core.morph" `shouldReturn` v9_mock_stratum_core_ast describe "SystemAST" $ do it "decodes correctly" $ do either (error . show) id <$> decodeSystemAST "quux/systems/quux-system-x86_32.morph" `shouldReturn` v9_mock_system_quux_ast