[commit: packages/directory] master: Migrate test: CopyFile001 (d0d0e45)

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


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

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

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

commit d0d0e4558e623a141183c8b1e9dc21d839746d3d
Author: Phil Ruffwind <rf at rufflewind.com>
Date:   Fri Jun 5 01:29:34 2015 -0400

    Migrate test: CopyFile001


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

d0d0e4558e623a141183c8b1e9dc21d839746d3d
 tests/CopyFile001.hs        | 22 ++++++++++++++++++++++
 tests/Main.hs               |  2 ++
 tests/all.T                 |  2 --
 tests/copyFile001.hs        | 26 --------------------------
 tests/copyFile001.stdout    |  5 -----
 tests/copyFile001dir/source |  1 -
 6 files changed, 24 insertions(+), 34 deletions(-)

diff --git a/tests/CopyFile001.hs b/tests/CopyFile001.hs
new file mode 100644
index 0000000..c354e8d
--- /dev/null
+++ b/tests/CopyFile001.hs
@@ -0,0 +1,22 @@
+{-# LANGUAGE CPP #-}
+module CopyFile001 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)
+  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 af44336..0d6cfe6 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 CopyFile001
 import qualified CurrentDirectory001
 import qualified Directory001
 import qualified DoesDirectoryExist001
@@ -13,6 +14,7 @@ import qualified T8482
 main :: IO ()
 main = T.testMain $ \ _t -> do
   T.isolatedRun _t "CanonicalizePath" CanonicalizePath.main
+  T.isolatedRun _t "CopyFile001" CopyFile001.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 bb8fa54..750a06f 100644
--- a/tests/all.T
+++ b/tests/all.T
@@ -1,5 +1,3 @@
-test('copyFile001', extra_clean(['copyFile001dir/target']),
-                    compile_and_run, [''])
 test('copyFile002', extra_clean(['copyFile002dir/target']),
                     compile_and_run, [''])
 
diff --git a/tests/copyFile001.hs b/tests/copyFile001.hs
deleted file mode 100644
index 0a59af2..0000000
--- a/tests/copyFile001.hs
+++ /dev/null
@@ -1,26 +0,0 @@
-
-module Main (main) where
-
-import Control.Exception
-import Data.List
-import System.Directory
-import System.IO
-
-main :: IO ()
-main = do tryIO $ removeFile to
-          cs_before <- getDirectoryContents "copyFile001dir"
-          putStrLn "Before:"
-          print $ sort cs_before
-          copyFile from to
-          cs_before <- getDirectoryContents "copyFile001dir"
-          putStrLn "After:"
-          print $ sort cs_before
-          readFile to >>= print
-
-tryIO :: IO a -> IO (Either IOException a)
-tryIO = try
-
-from, to :: FilePath
-from = "copyFile001dir/source"
-to   = "copyFile001dir/target"
-
diff --git a/tests/copyFile001.stdout b/tests/copyFile001.stdout
deleted file mode 100644
index 6b17d94..0000000
--- a/tests/copyFile001.stdout
+++ /dev/null
@@ -1,5 +0,0 @@
-Before:
-[".","..","source"]
-After:
-[".","..","source","target"]
-"This is the data"
diff --git a/tests/copyFile001dir/source b/tests/copyFile001dir/source
deleted file mode 100644
index 1b44515..0000000
--- a/tests/copyFile001dir/source
+++ /dev/null
@@ -1 +0,0 @@
-This is the data
\ No newline at end of file



More information about the ghc-commits mailing list