[commit: packages/directory] master: Simplify tests using getDirectoryContentsA (0e7e7a3)

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


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

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

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

commit 0e7e7a3da429aefab831e6f0c9e98d3948a50879
Author: Guillaume Bouchard <guillaum.bouchard at gmail.com>
Date:   Sat Sep 26 09:55:56 2015 +0200

    Simplify tests using getDirectoryContentsA


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

0e7e7a3da429aefab831e6f0c9e98d3948a50879
 tests/CopyFile001.hs          | 6 ++----
 tests/CopyFile002.hs          | 6 ++----
 tests/GetDirContents001.hs    | 5 +----
 tests/TestUtils.hs            | 4 ++--
 tests/WithCurrentDirectory.hs | 5 ++---
 5 files changed, 9 insertions(+), 17 deletions(-)

diff --git a/tests/CopyFile001.hs b/tests/CopyFile001.hs
index c354e8d..6ecb706 100644
--- a/tests/CopyFile001.hs
+++ b/tests/CopyFile001.hs
@@ -3,19 +3,17 @@ 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
+  T(expectEq) () [from] . sort =<< getDirectoryContentsA dir
   copyFile (dir </> from) (dir </> to)
-  T(expectEq) () (specials <> [from, to]) . sort =<< getDirectoryContents dir
+  T(expectEq) () [from, to] . sort =<< getDirectoryContentsA dir
   T(expectEq) () contents =<< readFile (dir </> to)
   where
-    specials = [".", ".."]
     contents = "This is the data\n"
     from     = "source"
     to       = "target"
diff --git a/tests/CopyFile002.hs b/tests/CopyFile002.hs
index 0319637..ea2cd36 100644
--- a/tests/CopyFile002.hs
+++ b/tests/CopyFile002.hs
@@ -3,19 +3,17 @@ module CopyFile002 where
 #include "util.inl"
 import System.Directory
 import Data.List (sort)
-import Data.Monoid ((<>))
 
 main :: TestEnv -> IO ()
 main _t = do
   -- 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 "."
+  T(expectEq) () [from] . sort =<< getDirectoryContentsA "."
   copyFile from to
-  T(expectEq) () (specials <> [from, to]) . sort =<< getDirectoryContents "."
+  T(expectEq) () [from, to] . sort =<< getDirectoryContentsA "."
   T(expectEq) () contents =<< readFile to
   where
-    specials = [".", ".."]
     contents = "This is the data\n"
     from     = "source"
     to       = "target"
diff --git a/tests/GetDirContents001.hs b/tests/GetDirContents001.hs
index f460bb4..b529337 100644
--- a/tests/GetDirContents001.hs
+++ b/tests/GetDirContents001.hs
@@ -10,13 +10,10 @@ import System.FilePath  ((</>))
 main :: TestEnv -> IO ()
 main _t = do
   createDirectory dir
-  T(expectEq) () specials . sort =<< getDirectoryContents dir
   T(expectEq) () [] . sort =<< getDirectoryContentsA dir
   names <- for [1 .. 100 :: Int] $ \ i -> do
     let name = 'f' : show i
     writeFile (dir </> name) ""
     return name
-  T(expectEq) () (sort (specials <> names)) . sort =<< getDirectoryContents dir
-  T(expectEq) () (sort (names)) . sort =<< getDirectoryContentsA dir
+  T(expectEq) () (sort names) . sort =<< getDirectoryContentsA dir
   where dir      = "dir"
-        specials = [".", ".."]
diff --git a/tests/TestUtils.hs b/tests/TestUtils.hs
index 795fa09..11a8ea8 100644
--- a/tests/TestUtils.hs
+++ b/tests/TestUtils.hs
@@ -41,10 +41,10 @@ copyPathRecursive source dest =
     dirExists <- doesDirectoryExist source
     if dirExists
       then do
-        contents <- getDirectoryContents source
+        contents <- getDirectoryContentsA source
         createDirectory dest
         mapM_ (uncurry copyPathRecursive)
-          [(source </> x, dest </> x) | x <- contents, x /= "." && x /= ".."]
+          [(source </> x, dest </> x) | x <- contents]
       else copyFile source dest
 
 modifyPermissions :: FilePath -> (Permissions -> Permissions) -> IO ()
diff --git a/tests/WithCurrentDirectory.hs b/tests/WithCurrentDirectory.hs
index 520c363..808d4cf 100644
--- a/tests/WithCurrentDirectory.hs
+++ b/tests/WithCurrentDirectory.hs
@@ -10,17 +10,16 @@ main :: TestEnv -> IO ()
 main _t = do
   createDirectory dir
   -- Make sure we're starting empty
-  T(expectEq) () specials . sort =<< getDirectoryContents dir
+  T(expectEq) () [] . sort =<< getDirectoryContentsA dir
   cwd <- getCurrentDirectory
   withCurrentDirectory dir (writeFile testfile contents)
   -- Are we still in original directory?
   T(expectEq) () cwd =<< getCurrentDirectory
   -- Did the test file get created?
-  T(expectEq) () (specials <> [testfile]) . sort =<< getDirectoryContents dir
+  T(expectEq) () [testfile] . sort =<< getDirectoryContentsA dir
   -- Does the file contain what we expected to write?
   T(expectEq) () contents =<< readFile (dir </> testfile)
   where
     testfile = "testfile"
     contents = "some data\n"
     dir = "dir"
-    specials = [".", ".."]



More information about the ghc-commits mailing list