summaryrefslogtreecommitdiff
path: root/test/Spec.hs
blob: 68cf99451cb3622e7f2a24406faf79f5aa4f9960 (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
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 = do
  -- Get the current directory
  currentDir <- getCurrentDirectory
  -- Run HSpec with the generated test suite
  hspec $ parallel $ describe "Integration Tests" $ hspecTestScripts currentDir