{-# 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 "../../") main :: IO () main = hspec $ around_ in_mock_definitions_v9 $ do describe "Baserock.Schema.V9" $ do describe "ChunkInstructions" $ do it "decodes correctly" $ do decodeFile "quux/strata/grilled-essential/brie-cc.morph" `shouldReturn` (Just v9_mock_chunk_instructions_brie_cc :: Maybe ChunkInstructions) decodeFile "quux/strata/grilled-essential/linux-api-headers.morph" `shouldReturn` (Just v9_mock_chunk_instructions_linux_api_headers :: Maybe ChunkInstructions) decodeFile "quux/strata/core/ccake.morph" `shouldReturn` (Just v9_mock_chunk_instructions_ccake :: Maybe ChunkInstructions) decodeFile "quux/strata/core/sesame-sed.morph" `shouldReturn` (Just v9_mock_chunk_instructions_sesame_sed :: Maybe ChunkInstructions) 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 decodeFile "quux/strata/grilled-essential.morph" `shouldReturn` (Just v9_mock_stratum_grilled_essential :: Maybe Stratum) decodeFile "quux/strata/core.morph" `shouldReturn` (Just v9_mock_stratum_core :: Maybe Stratum) 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 decodeFile "quux/systems/quux-system-x86_32.morph" `shouldReturn` (Just v9_mock_system_quux :: Maybe System) 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