[commit: packages/directory] master: Migrate test: CopyFile002 (99841de)
git at git.haskell.org
git at git.haskell.org
Fri Dec 18 09:51:27 UTC 2015
Repository : ssh://git@git.haskell.org/directory
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/99841de10573f3762c7175c717205f1c56c57c4c/directory
>---------------------------------------------------------------
commit 99841de10573f3762c7175c717205f1c56c57c4c
Author: Phil Ruffwind <rf at rufflewind.com>
Date: Fri Jun 5 01:37:50 2015 -0400
Migrate test: CopyFile002
>---------------------------------------------------------------
99841de10573f3762c7175c717205f1c56c57c4c
tests/{CopyFile001.hs => CopyFile002.hs} | 17 ++++++++---------
tests/Main.hs | 2 ++
tests/all.T | 3 ---
tests/copyFile002.hs | 31 -------------------------------
tests/copyFile002.stdout | 5 -----
tests/copyFile002dir/source | 1 -
6 files changed, 10 insertions(+), 49 deletions(-)
diff --git a/tests/CopyFile001.hs b/tests/CopyFile002.hs
similarity index 61%
copy from tests/CopyFile001.hs
copy to tests/CopyFile002.hs
index c354e8d..0319637 100644
--- a/tests/CopyFile001.hs
+++ b/tests/CopyFile002.hs
@@ -1,22 +1,21 @@
{-# LANGUAGE CPP #-}
-module CopyFile001 where
+module CopyFile002 where
#include "util.inl"
import System.Directory
import Data.List (sort)
import Data.Monoid ((<>))
-import System.FilePath ((</>))
main :: TestEnv -> IO ()
main _t = do
- createDirectory dir
- writeFile (dir </> from) contents
- T(expectEq) () (specials <> [from]) . sort =<< getDirectoryContents dir
- copyFile (dir </> from) (dir </> to)
- T(expectEq) () (specials <> [from, to]) . sort =<< getDirectoryContents dir
- T(expectEq) () contents =<< readFile (dir </> to)
+ -- Similar to CopyFile001 but moves a file in the current directory
+ -- (Bug #1652 on GHC Trac)
+ writeFile from contents
+ T(expectEq) () (specials <> [from]) . sort =<< getDirectoryContents "."
+ copyFile from to
+ T(expectEq) () (specials <> [from, to]) . sort =<< getDirectoryContents "."
+ T(expectEq) () contents =<< readFile to
where
specials = [".", ".."]
contents = "This is the data\n"
from = "source"
to = "target"
- dir = "dir"
diff --git a/tests/Main.hs b/tests/Main.hs
index 0d6cfe6..c72d022 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 CopyFile001
+import qualified CopyFile002
import qualified CurrentDirectory001
import qualified Directory001
import qualified DoesDirectoryExist001
@@ -15,6 +16,7 @@ main :: IO ()
main = T.testMain $ \ _t -> do
T.isolatedRun _t "CanonicalizePath" CanonicalizePath.main
T.isolatedRun _t "CopyFile001" CopyFile001.main
+ T.isolatedRun _t "CopyFile002" CopyFile002.main
T.isolatedRun _t "CurrentDirectory001" CurrentDirectory001.main
T.isolatedRun _t "Directory001" Directory001.main
T.isolatedRun _t "DoesDirectoryExist001" DoesDirectoryExist001.main
diff --git a/tests/all.T b/tests/all.T
index 750a06f..90e87d1 100644
--- a/tests/all.T
+++ b/tests/all.T
@@ -1,6 +1,3 @@
-test('copyFile002', extra_clean(['copyFile002dir/target']),
- compile_and_run, [''])
-
test('renameFile001', extra_clean(['renameFile001.tmp1','renameFile001.tmp2']),
compile_and_run, [''])
diff --git a/tests/copyFile002.hs b/tests/copyFile002.hs
deleted file mode 100644
index 66c79cd..0000000
--- a/tests/copyFile002.hs
+++ /dev/null
@@ -1,31 +0,0 @@
-
-module Main (main) where
-
-import Control.Exception
-import Data.List
-import System.Directory
-import System.IO
-
--- like copyFile001, but moves a file in the current directory
--- See bug #1652
-main :: IO ()
-main = do d <- getCurrentDirectory
- flip finally (setCurrentDirectory d) $ do
- setCurrentDirectory "copyFile002dir"
- tryIO $ removeFile to
- cs_before <- getDirectoryContents "."
- putStrLn "Before:"
- print $ sort cs_before
- copyFile from to
- cs_before <- getDirectoryContents "."
- putStrLn "After:"
- print $ sort cs_before
- readFile to >>= print
-
-tryIO :: IO a -> IO (Either IOException a)
-tryIO = try
-
-from, to :: FilePath
-from = "source"
-to = "target"
-
diff --git a/tests/copyFile002.stdout b/tests/copyFile002.stdout
deleted file mode 100644
index 6b17d94..0000000
--- a/tests/copyFile002.stdout
+++ /dev/null
@@ -1,5 +0,0 @@
-Before:
-[".","..","source"]
-After:
-[".","..","source","target"]
-"This is the data"
diff --git a/tests/copyFile002dir/source b/tests/copyFile002dir/source
deleted file mode 100644
index 1b44515..0000000
--- a/tests/copyFile002dir/source
+++ /dev/null
@@ -1 +0,0 @@
-This is the data
\ No newline at end of file
More information about the ghc-commits
mailing list