[commit: packages/directory] master: Migrate test: GetDirContents002 (3e63d4b)
git at git.haskell.org
git at git.haskell.org
Fri Dec 18 09:51:29 UTC 2015
Repository : ssh://git@git.haskell.org/directory
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/3e63d4bbed66c3f76b73cef5c2287e2772d21c33/directory
>---------------------------------------------------------------
commit 3e63d4bbed66c3f76b73cef5c2287e2772d21c33
Author: Phil Ruffwind <rf at rufflewind.com>
Date: Thu Jun 4 23:28:24 2015 -0400
Migrate test: GetDirContents002
>---------------------------------------------------------------
3e63d4bbed66c3f76b73cef5c2287e2772d21c33
tests/GetDirContents002.hs | 10 ++++++++++
tests/Main.hs | 2 ++
tests/all.T | 3 ---
tests/getDirContents002.hs | 3 ---
tests/getDirContents002.stderr | 1 -
tests/getDirContents002.stderr-mingw32 | 1 -
6 files changed, 12 insertions(+), 8 deletions(-)
diff --git a/tests/GetDirContents002.hs b/tests/GetDirContents002.hs
new file mode 100644
index 0000000..98a2353
--- /dev/null
+++ b/tests/GetDirContents002.hs
@@ -0,0 +1,10 @@
+{-# LANGUAGE CPP #-}
+module GetDirContents002 where
+#include "util.inl"
+import System.Directory
+import System.IO.Error (isDoesNotExistError)
+
+main :: TestEnv -> IO ()
+main _t = do
+ T(expectIOErrorType) () isDoesNotExistError $
+ getDirectoryContents "nonexistent"
diff --git a/tests/Main.hs b/tests/Main.hs
index 25d3cea..25ff4cc 100644
--- a/tests/Main.hs
+++ b/tests/Main.hs
@@ -6,6 +6,7 @@ import qualified Directory001
import qualified DoesDirectoryExist001
import qualified FileTime
import qualified GetDirContents001
+import qualified GetDirContents002
import qualified T8482
main :: IO ()
@@ -16,4 +17,5 @@ main = T.testMain $ \ _t -> do
T.isolatedRun _t "DoesDirectoryExist001" DoesDirectoryExist001.main
T.isolatedRun _t "FileTime" FileTime.main
T.isolatedRun _t "GetDirContents001" GetDirContents001.main
+ T.isolatedRun _t "GetDirContents002" GetDirContents002.main
T.isolatedRun _t "T8482" T8482.main
diff --git a/tests/all.T b/tests/all.T
index 7d39c1a..ed6abbb 100644
--- a/tests/all.T
+++ b/tests/all.T
@@ -1,6 +1,3 @@
-test('getDirContents002', [ normalise_exe, exit_code(1) ],
- compile_and_run, [''])
-
# Depends on binary from previous run, which gets removed by the driver way=ghci
test('getPermissions001', omit_ways(['ghci']), compile_and_run, ['-cpp'])
diff --git a/tests/getDirContents002.hs b/tests/getDirContents002.hs
deleted file mode 100644
index 1b45a3a..0000000
--- a/tests/getDirContents002.hs
+++ /dev/null
@@ -1,3 +0,0 @@
-import System.Directory
-
-main = getDirectoryContents "nonexistent"
diff --git a/tests/getDirContents002.stderr b/tests/getDirContents002.stderr
deleted file mode 100644
index 981c1bc..0000000
--- a/tests/getDirContents002.stderr
+++ /dev/null
@@ -1 +0,0 @@
-getDirContents002: nonexistent: getDirectoryContents: does not exist (No such file or directory)
diff --git a/tests/getDirContents002.stderr-mingw32 b/tests/getDirContents002.stderr-mingw32
deleted file mode 100644
index c90d9bc..0000000
--- a/tests/getDirContents002.stderr-mingw32
+++ /dev/null
@@ -1 +0,0 @@
-getDirContents002.exe: nonexistent: getDirectoryContents: does not exist (The system cannot find the path specified.)
More information about the ghc-commits
mailing list