[commit: packages/directory] master: Migrate test: DoesDirectoryExist001 (27e0ef9)

git at git.haskell.org git at git.haskell.org
Fri Dec 18 09:51:25 UTC 2015


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/27e0ef9e03796b59eaa5b224d948a10da0874441/directory

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

commit 27e0ef9e03796b59eaa5b224d948a10da0874441
Author: Phil Ruffwind <rf at rufflewind.com>
Date:   Thu Jun 4 21:41:53 2015 -0400

    Migrate test: DoesDirectoryExist001


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

27e0ef9e03796b59eaa5b224d948a10da0874441
 tests/DoesDirectoryExist001.hs     | 17 +++++++++++++++++
 tests/Main.hs                      |  2 ++
 tests/all.T                        |  1 -
 tests/doesDirectoryExist001.hs     | 11 -----------
 tests/doesDirectoryExist001.stdout |  1 -
 5 files changed, 19 insertions(+), 13 deletions(-)

diff --git a/tests/DoesDirectoryExist001.hs b/tests/DoesDirectoryExist001.hs
new file mode 100644
index 0000000..b5a1aa9
--- /dev/null
+++ b/tests/DoesDirectoryExist001.hs
@@ -0,0 +1,17 @@
+{-# LANGUAGE CPP #-}
+module DoesDirectoryExist001 where
+#include "util.inl"
+import System.Directory
+
+main :: TestEnv -> IO ()
+main _t = do
+
+  -- [regression test] "/" was not recognised as a directory prior to GHC 6.1
+  T(expect) () =<< doesDirectoryExist rootDir
+
+  where
+#ifdef mingw32_HOST_OS
+    rootDir = "C:\\"
+#else
+    rootDir = "/"
+#endif
diff --git a/tests/Main.hs b/tests/Main.hs
index ccd54a1..fed205e 100644
--- a/tests/Main.hs
+++ b/tests/Main.hs
@@ -2,6 +2,7 @@ module Main (main) where
 import qualified Util as T
 import qualified CanonicalizePath
 import qualified Directory001
+import qualified DoesDirectoryExist001
 import qualified FileTime
 import qualified T8482
 
@@ -9,5 +10,6 @@ main :: IO ()
 main = T.testMain $ \ _t -> do
   T.isolatedRun _t "CanonicalizePath" CanonicalizePath.main
   T.isolatedRun _t "Directory001" Directory001.main
+  T.isolatedRun _t "DoesDirectoryExist001" DoesDirectoryExist001.main
   T.isolatedRun _t "FileTime" FileTime.main
   T.isolatedRun _t "T8482" T8482.main
diff --git a/tests/all.T b/tests/all.T
index 6029348..8a30d22 100644
--- a/tests/all.T
+++ b/tests/all.T
@@ -1,5 +1,4 @@
 test('currentDirectory001',     normal, compile_and_run, [''])
-test('doesDirectoryExist001',   normal, compile_and_run, [''])
 
 # This test is a bit bogus.  Disable for GHCi.
 test('getDirContents001', omit_ways(['ghci']), compile_and_run, ['-fno-gen-manifest'])
diff --git a/tests/doesDirectoryExist001.hs b/tests/doesDirectoryExist001.hs
deleted file mode 100644
index 2548183..0000000
--- a/tests/doesDirectoryExist001.hs
+++ /dev/null
@@ -1,11 +0,0 @@
-{-# LANGUAGE CPP #-}
--- !!! "/" was not recognised as a directory in 6.0.x
-import System.Directory
-
-#ifdef mingw32_HOST_OS
-root = "C:\\"
-#else
-root = "/"
-#endif
-
-main = doesDirectoryExist root >>= print
diff --git a/tests/doesDirectoryExist001.stdout b/tests/doesDirectoryExist001.stdout
deleted file mode 100644
index 0ca9514..0000000
--- a/tests/doesDirectoryExist001.stdout
+++ /dev/null
@@ -1 +0,0 @@
-True



More information about the ghc-commits mailing list