[commit: packages/directory] master: Migrate test: GetDirContents001 (87272bb)
git at git.haskell.org
git at git.haskell.org
Fri Dec 18 09:51:31 UTC 2015
Repository : ssh://git@git.haskell.org/directory
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/87272bb290dde7c5d1aa96c89f5c678dfe9a4461/directory
>---------------------------------------------------------------
commit 87272bb290dde7c5d1aa96c89f5c678dfe9a4461
Author: Phil Ruffwind <rf at rufflewind.com>
Date: Thu Jun 4 23:23:46 2015 -0400
Migrate test: GetDirContents001
>---------------------------------------------------------------
87272bb290dde7c5d1aa96c89f5c678dfe9a4461
tests/GetDirContents001.hs | 20 ++++++++++++++++++++
tests/Main.hs | 2 ++
tests/all.T | 3 ---
tests/getDirContents001.hs | 18 ------------------
tests/getDirContents001.stdout | 2 --
5 files changed, 22 insertions(+), 23 deletions(-)
diff --git a/tests/GetDirContents001.hs b/tests/GetDirContents001.hs
new file mode 100644
index 0000000..aa7d495
--- /dev/null
+++ b/tests/GetDirContents001.hs
@@ -0,0 +1,20 @@
+{-# LANGUAGE CPP #-}
+module GetDirContents001 where
+#include "util.inl"
+import System.Directory
+import Data.List (sort)
+import Data.Monoid ((<>))
+import Data.Traversable (for)
+import System.FilePath ((</>))
+
+main :: TestEnv -> IO ()
+main _t = do
+ createDirectory dir
+ T(expectEq) () specials . sort =<< getDirectoryContents 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
+ where dir = "dir"
+ specials = [".", ".."]
diff --git a/tests/Main.hs b/tests/Main.hs
index b9efcce..25d3cea 100644
--- a/tests/Main.hs
+++ b/tests/Main.hs
@@ -5,6 +5,7 @@ import qualified CurrentDirectory001
import qualified Directory001
import qualified DoesDirectoryExist001
import qualified FileTime
+import qualified GetDirContents001
import qualified T8482
main :: IO ()
@@ -14,4 +15,5 @@ main = T.testMain $ \ _t -> do
T.isolatedRun _t "Directory001" Directory001.main
T.isolatedRun _t "DoesDirectoryExist001" DoesDirectoryExist001.main
T.isolatedRun _t "FileTime" FileTime.main
+ T.isolatedRun _t "GetDirContents001" GetDirContents001.main
T.isolatedRun _t "T8482" T8482.main
diff --git a/tests/all.T b/tests/all.T
index 9b7c14f..7d39c1a 100644
--- a/tests/all.T
+++ b/tests/all.T
@@ -1,6 +1,3 @@
-# This test is a bit bogus. Disable for GHCi.
-test('getDirContents001', omit_ways(['ghci']), compile_and_run, ['-fno-gen-manifest'])
-
test('getDirContents002', [ normalise_exe, exit_code(1) ],
compile_and_run, [''])
diff --git a/tests/getDirContents001.hs b/tests/getDirContents001.hs
deleted file mode 100644
index d09b645..0000000
--- a/tests/getDirContents001.hs
+++ /dev/null
@@ -1,18 +0,0 @@
-import System.Directory
-import Control.Exception
-import System.FilePath
-import Data.List
-
-dir = "getDirContents001.dir"
-
-main = do
- try cleanup :: IO (Either IOException ())
- bracket (createDirectory dir) (const cleanup) $ \_ -> do
- getDirectoryContents dir >>= print . sort
- mapM_ (\s -> writeFile (dir </> ('f':show s)) (show s)) [1..100]
- getDirectoryContents dir >>= print . sort
-
-cleanup = do
- files <- getDirectoryContents dir
- mapM_ (removeFile . (dir </>)) (filter (not . ("." `isPrefixOf`)) files)
- removeDirectory dir
diff --git a/tests/getDirContents001.stdout b/tests/getDirContents001.stdout
deleted file mode 100644
index fd68c28..0000000
--- a/tests/getDirContents001.stdout
+++ /dev/null
@@ -1,2 +0,0 @@
-[".",".."]
-[".","..","f1","f10","f100","f11","f12","f13","f14","f15","f16","f17","f18","f19","f2","f20","f21","f22","f23","f24","f25","f26","f27","f28","f29","f3","f30","f31","f32","f33","f34","f35","f36","f37","f38","f39","f4","f40","f41","f42","f43","f44","f45","f46","f47","f48","f49","f5","f50","f51","f52","f53","f54","f55","f56","f57","f58","f59","f6","f60","f61","f62","f63","f64","f65","f66","f67","f68","f69","f7","f70","f71","f72","f73","f74","f75","f76","f77","f78","f79","f8","f80","f81","f82","f83","f84","f85","f86","f87","f88","f89","f9","f90","f91","f92","f93","f94","f95","f96","f97","f98","f99"]
More information about the ghc-commits
mailing list