[commit: packages/directory] master: Migrate test: CurrentDirectory001 (1b4b75b)

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


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/1b4b75b68676acd505793849895c59ba608002c9/directory

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

commit 1b4b75b68676acd505793849895c59ba608002c9
Author: Phil Ruffwind <rf at rufflewind.com>
Date:   Thu Jun 4 23:11:46 2015 -0400

    Migrate test: CurrentDirectory001


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

1b4b75b68676acd505793849895c59ba608002c9
 tests/CurrentDirectory001.hs     | 14 ++++++++++++++
 tests/Main.hs                    |  2 ++
 tests/all.T                      |  2 --
 tests/currentDirectory001.hs     | 27 ---------------------------
 tests/currentDirectory001.stdout |  1 -
 5 files changed, 16 insertions(+), 30 deletions(-)

diff --git a/tests/CurrentDirectory001.hs b/tests/CurrentDirectory001.hs
new file mode 100644
index 0000000..b72c0dc
--- /dev/null
+++ b/tests/CurrentDirectory001.hs
@@ -0,0 +1,14 @@
+{-# LANGUAGE CPP #-}
+module CurrentDirectory001 where
+#include "util.inl"
+import System.Directory
+import Data.List (sort)
+
+main :: TestEnv -> IO ()
+main _t = do
+  prevDir <- getCurrentDirectory
+  createDirectory "dir"
+  setCurrentDirectory "dir"
+  T(expectEq) () [".", ".."] . sort =<< getDirectoryContents "."
+  setCurrentDirectory prevDir
+  removeDirectory "dir"
diff --git a/tests/Main.hs b/tests/Main.hs
index fed205e..b9efcce 100644
--- a/tests/Main.hs
+++ b/tests/Main.hs
@@ -1,6 +1,7 @@
 module Main (main) where
 import qualified Util as T
 import qualified CanonicalizePath
+import qualified CurrentDirectory001
 import qualified Directory001
 import qualified DoesDirectoryExist001
 import qualified FileTime
@@ -9,6 +10,7 @@ import qualified T8482
 main :: IO ()
 main = T.testMain $ \ _t -> do
   T.isolatedRun _t "CanonicalizePath" CanonicalizePath.main
+  T.isolatedRun _t "CurrentDirectory001" CurrentDirectory001.main
   T.isolatedRun _t "Directory001" Directory001.main
   T.isolatedRun _t "DoesDirectoryExist001" DoesDirectoryExist001.main
   T.isolatedRun _t "FileTime" FileTime.main
diff --git a/tests/all.T b/tests/all.T
index 8a30d22..9b7c14f 100644
--- a/tests/all.T
+++ b/tests/all.T
@@ -1,5 +1,3 @@
-test('currentDirectory001',     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/currentDirectory001.hs b/tests/currentDirectory001.hs
deleted file mode 100644
index 0b57a44..0000000
--- a/tests/currentDirectory001.hs
+++ /dev/null
@@ -1,27 +0,0 @@
-
-import System.Directory (getCurrentDirectory, setCurrentDirectory,
-                         createDirectory, removeDirectory,
-                         getDirectoryContents)
-
-main :: IO ()
-main = do
-    oldpwd <- getCurrentDirectory
-    createDirectory dir
-    setCurrentDirectory dir
-    ~[n1, n2] <- getDirectoryContents "."
-    if dot n1 && dot n2 
-     then do
-        setCurrentDirectory oldpwd
-        removeDirectory dir
-        putStr "Okay\n"
-      else
-        ioError (userError "Oops")
-
-dot :: String -> Bool
-dot "." = True
-dot ".." = True
-dot _ = False
-
-dir :: FilePath
-dir = "currentDirectory001-dir"
-
diff --git a/tests/currentDirectory001.stdout b/tests/currentDirectory001.stdout
deleted file mode 100644
index 1ddd42b..0000000
--- a/tests/currentDirectory001.stdout
+++ /dev/null
@@ -1 +0,0 @@
-Okay



More information about the ghc-commits mailing list