summaryrefslogtreecommitdiff
path: root/test/Spec.hs
diff options
context:
space:
mode:
authorJosh Rahm <joshuarahm@gmail.com>2024-10-09 01:47:43 -0600
committerJosh Rahm <joshuarahm@gmail.com>2024-10-09 01:47:43 -0600
commit9832f887e1772e1c0f546371584be323ae440fb8 (patch)
treeb17ab95110ca45c673594db21ee2f73042163d1c /test/Spec.hs
parentbc404348ec9012eb08e08e29e8caf80dda73247f (diff)
downloadfiddle-9832f887e1772e1c0f546371584be323ae440fb8.tar.gz
fiddle-9832f887e1772e1c0f546371584be323ae440fb8.tar.bz2
fiddle-9832f887e1772e1c0f546371584be323ae440fb8.zip
Add system to spec for running integration shell scirpts.
The spec will recursively go through the test directories and look for `test.sh` files. If it finds one, it will run it. If the script returns 0, then the test passes, otherwise the test fails.
Diffstat (limited to 'test/Spec.hs')
-rw-r--r--test/Spec.hs56
1 files changed, 52 insertions, 4 deletions
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