diff options
-rw-r--r-- | package.yaml | 1 | ||||
-rw-r--r-- | test/Spec.hs | 56 | ||||
-rw-r--r-- | test/integrations/anonymous_parsed/input.fdl | 11 | ||||
-rwxr-xr-x | test/integrations/anonymous_parsed/test.sh | 17 |
4 files changed, 81 insertions, 4 deletions
diff --git a/package.yaml b/package.yaml index 52a04d7..fcdfa58 100644 --- a/package.yaml +++ b/package.yaml @@ -31,6 +31,7 @@ tests: - base >= 4.0.0 - text - containers + - process ghc-options: - -Wall diff --git a/test/Spec.hs b/test/Spec.hs index 834ade8..68cf994 100644 --- a/test/Spec.hs +++ b/test/Spec.hs @@ -1,7 +1,55 @@ +{-# LANGUAGE OverloadedStrings #-} + +import Control.Monad (filterM, forM, forM_) +import qualified Data.Text as Text +import System.Directory (doesDirectoryExist, getCurrentDirectory, listDirectory) +import System.Exit (ExitCode (..)) +import System.FilePath (takeFileName, (</>)) +import System.Process (readProcessWithExitCode) import Test.Hspec +-- | Recursively walk a directory to find all 'test.sh' files. +findTestScripts :: FilePath -> IO [FilePath] +findTestScripts dir = do + -- Get the list of all entries in the directory + entries <- listDirectory dir + -- Make the entries absolute paths + let entries' = map (dir </>) entries + -- Separate directories and files + dirs <- filterM doesDirectoryExist entries' + let files = filter ((== "test.sh") . takeFileName) entries' + -- Recursively find 'test.sh' files in subdirectories + nestedFiles <- concat <$> mapM findTestScripts dirs + -- Return the found 'test.sh' files + return $ files ++ nestedFiles + +-- | Run a 'test.sh' file and check its exit code. +runTestScript :: FilePath -> IO Bool +runTestScript scriptPath = do + -- Run the script and capture the exit code + (exitCode, _, _) <- readProcessWithExitCode "bash" [scriptPath] "" + -- Return True if exit code is 0, else False + return (exitCode == ExitSuccess) + +-- | HSpec test integration for running all 'test.sh' scripts in a given directory. +hspecTestScripts :: FilePath -> Spec +hspecTestScripts dir = do + -- Find all 'test.sh' scripts + runIO (findTestScripts dir) >>= \testScripts -> do + -- For each script, create an HSpec test case + forM_ testScripts $ \scriptPath -> + it (testName scriptPath) $ do + passed <- runTestScript scriptPath + passed `shouldBe` True + where + splitOn on str = map Text.unpack $ Text.splitOn (Text.pack on) (Text.pack str) + testName str = case reverse (splitOn "/" str) of + (_ : x : _) -> x + _ -> str + main :: IO () -main = hspec $ do - describe "add" $ do - it "adds two positive numbers" $ do - 2 + 3 `shouldBe` 5 +main = do + -- Get the current directory + currentDir <- getCurrentDirectory + -- Run HSpec with the generated test suite + hspec $ parallel $ describe "Integration Tests" $ hspecTestScripts currentDir diff --git a/test/integrations/anonymous_parsed/input.fdl b/test/integrations/anonymous_parsed/input.fdl new file mode 100644 index 0000000..316c631 --- /dev/null +++ b/test/integrations/anonymous_parsed/input.fdl @@ -0,0 +1,11 @@ +package fiddle.test { + type test_type : struct { + reg test_reg(32) : struct { + test_bits : enum (1) { + on = 0b1, + off = 0b0, + }; + reserved(31); + }; + }; +}; diff --git a/test/integrations/anonymous_parsed/test.sh b/test/integrations/anonymous_parsed/test.sh new file mode 100755 index 0000000..9bcb6a6 --- /dev/null +++ b/test/integrations/anonymous_parsed/test.sh @@ -0,0 +1,17 @@ +#!/bin/bash +source "$(git rev-parse --show-toplevel)/test/integrations/common.sh" + +output=$( + stack run -- --dump-parsed input.fdl | + jq '.. + | objects + | select(._con == "RegisterBitsAnonymousType") + | .anonBitsType + .anonEnumBody[0] + .enumConsts[0] + .directedSubtree + .enumConstIdent') + +assert_eq "$output" '"on"' + +finish |