[commit: packages/directory] improve-tests-for-real: Hook testsuite to cabal test (5bd7e05)

git at git.haskell.org git at git.haskell.org
Thu Mar 19 11:37:46 UTC 2015


Repository : ssh://git@git.haskell.org/directory

On branch  : improve-tests-for-real
Link       : http://ghc.haskell.org/trac/ghc/changeset/5bd7e0511066404503fa9dd19429815166f9c8ce/directory

>---------------------------------------------------------------

commit 5bd7e0511066404503fa9dd19429815166f9c8ce
Author: Phil Ruffwind <rf at rufflewind.com>
Date:   Mon Mar 2 05:09:03 2015 -0500

    Hook testsuite to cabal test


>---------------------------------------------------------------

5bd7e0511066404503fa9dd19429815166f9c8ce
 directory.cabal   |  6 +++---
 test/main.hs      | 20 --------------------
 testsuite/Main.hs |  9 +++++++++
 testsuite/run     |  7 -------
 4 files changed, 12 insertions(+), 30 deletions(-)

diff --git a/directory.cabal b/directory.cabal
index c648e0d..bb6f9b3 100644
--- a/directory.cabal
+++ b/directory.cabal
@@ -65,9 +65,9 @@ Library
 
 test-suite test
   default-language: Haskell2010
-  hs-source-dirs: test
-  main-is: main.hs
+  hs-source-dirs: testsuite
+  main-is: Main.hs
   type: exitcode-stdio-1.0
   build-depends: base
                , directory
-               , containers
+               , process
diff --git a/test/main.hs b/test/main.hs
deleted file mode 100644
index 7a9fcb3..0000000
--- a/test/main.hs
+++ /dev/null
@@ -1,20 +0,0 @@
-{-# LANGUAGE NoImplicitPrelude #-}
--- Simplistic test suite for now. Worthwhile to add a dependency on a
--- test framework at some point.
-module Main (main) where
-
-import qualified Data.Set         as Set
-import           Prelude          (IO, error, fmap, return, show, (==))
-import           System.Directory (getDirectoryContents)
-
-main :: IO ()
-main = do
-    let expected = Set.fromList
-            [ "."
-            , ".."
-            , "main.hs"
-            ]
-    actual <- fmap Set.fromList (getDirectoryContents "test")
-    if expected == actual
-        then return ()
-        else error (show (expected, actual))
diff --git a/testsuite/Main.hs b/testsuite/Main.hs
new file mode 100644
index 0000000..052add8
--- /dev/null
+++ b/testsuite/Main.hs
@@ -0,0 +1,9 @@
+module Main (main) where
+import System.Directory ()
+import System.Environment (getArgs)
+import System.Process (callProcess)
+
+main :: IO ()
+main =
+  -- execute in the Cabal sandbox environment
+  callProcess "cabal" . (["exec", "--", "sh", "testsuite/run"] ++) =<< getArgs
diff --git a/testsuite/run b/testsuite/run
index 6725d39..329011d 100755
--- a/testsuite/run
+++ b/testsuite/run
@@ -24,12 +24,5 @@ sed >dist/testsuite/Makefile \
     "s|^TOP=.*$|TOP=../dist/testsuite/ghc/testsuite|" \
     tests/Makefile
 
-# there's no way to pass arguments when `sh` is in `-s` mode, so we have to
-# write the shell commands to an actual file
-cat >dist/testsuite/run.sh <<"EOF"
 cd tests
 make -f ../dist/testsuite/Makefile WAY=normal EXTRA_HC_OPTS="$HSFLAGS" "$@"
-EOF
-
-cabal build
-exec cabal exec sh -- -e dist/testsuite/run.sh "$@"



More information about the ghc-commits mailing list