[commit: packages/directory] master: Migrate test: Directory001 (7d5c1eb)

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


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/7d5c1eb6de40513a78c509f92307a232fd2c1d5c/directory

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

commit 7d5c1eb6de40513a78c509f92307a232fd2c1d5c
Author: Phil Ruffwind <rf at rufflewind.com>
Date:   Thu Jun 4 21:14:31 2015 -0400

    Migrate test: Directory001


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

7d5c1eb6de40513a78c509f92307a232fd2c1d5c
 tests/Directory001.hs     | 19 +++++++++++++++++++
 tests/Main.hs             |  2 ++
 tests/all.T               |  1 -
 tests/directory001.hs     | 16 ----------------
 tests/directory001.stdout |  1 -
 5 files changed, 21 insertions(+), 18 deletions(-)

diff --git a/tests/Directory001.hs b/tests/Directory001.hs
new file mode 100644
index 0000000..60a2dac
--- /dev/null
+++ b/tests/Directory001.hs
@@ -0,0 +1,19 @@
+{-# LANGUAGE CPP #-}
+module Directory001 where
+#include "util.inl"
+import System.Directory
+
+main :: TestEnv -> IO ()
+main _t = do
+
+  createDirectory "foo"
+  writeFile "foo/bar" str
+  renameFile "foo/bar" "foo/baz"
+  renameDirectory "foo" "bar"
+  str' <- readFile "bar/baz"
+  T(expectEq) () str' str
+  removeFile "bar/baz"
+  removeDirectory "bar"
+
+  where
+    str = "Okay\n"
diff --git a/tests/Main.hs b/tests/Main.hs
index f831c8d..ccd54a1 100644
--- a/tests/Main.hs
+++ b/tests/Main.hs
@@ -1,11 +1,13 @@
 module Main (main) where
 import qualified Util as T
 import qualified CanonicalizePath
+import qualified Directory001
 import qualified FileTime
 import qualified T8482
 
 main :: IO ()
 main = T.testMain $ \ _t -> do
   T.isolatedRun _t "CanonicalizePath" CanonicalizePath.main
+  T.isolatedRun _t "Directory001" Directory001.main
   T.isolatedRun _t "FileTime" FileTime.main
   T.isolatedRun _t "T8482" T8482.main
diff --git a/tests/all.T b/tests/all.T
index 65c8cc5..6029348 100644
--- a/tests/all.T
+++ b/tests/all.T
@@ -1,5 +1,4 @@
 test('currentDirectory001',     normal, compile_and_run, [''])
-test('directory001',            normal, compile_and_run, [''])
 test('doesDirectoryExist001',   normal, compile_and_run, [''])
 
 # This test is a bit bogus.  Disable for GHCi.
diff --git a/tests/directory001.hs b/tests/directory001.hs
deleted file mode 100644
index 5abfbdc..0000000
--- a/tests/directory001.hs
+++ /dev/null
@@ -1,16 +0,0 @@
-import System.IO
-import System.Directory
-
-main = do
-    createDirectory "foo"
-    h <- openFile "foo/bar" WriteMode
-    hPutStr h "Okay\n"
-    hClose h
-    renameFile "foo/bar" "foo/baz"
-    renameDirectory "foo" "bar"
-    h <- openFile "bar/baz" ReadMode
-    stuff <- hGetContents h
-    putStr stuff
---    hClose h  -- an error !
-    removeFile "bar/baz"
-    removeDirectory "bar"
diff --git a/tests/directory001.stdout b/tests/directory001.stdout
deleted file mode 100644
index 1ddd42b..0000000
--- a/tests/directory001.stdout
+++ /dev/null
@@ -1 +0,0 @@
-Okay



More information about the ghc-commits mailing list