[commit: packages/directory] master: Migrate test: T8482 (d619c51)
git at git.haskell.org
git at git.haskell.org
Fri Dec 18 09:51:21 UTC 2015
Repository : ssh://git@git.haskell.org/directory
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/d619c51d72212103e3a8972280ca37ac141fc759/directory
>---------------------------------------------------------------
commit d619c51d72212103e3a8972280ca37ac141fc759
Author: Phil Ruffwind <rf at rufflewind.com>
Date: Fri May 29 20:40:10 2015 -0400
Migrate test: T8482
>---------------------------------------------------------------
d619c51d72212103e3a8972280ca37ac141fc759
tests/Main.hs | 2 ++
tests/T8482.hs | 23 ++++++++++++++---------
tests/T8482.stdout | 3 ---
tests/all.T | 2 --
4 files changed, 16 insertions(+), 14 deletions(-)
diff --git a/tests/Main.hs b/tests/Main.hs
index 0b9ee83..f831c8d 100644
--- a/tests/Main.hs
+++ b/tests/Main.hs
@@ -2,8 +2,10 @@ module Main (main) where
import qualified Util as T
import qualified CanonicalizePath
import qualified FileTime
+import qualified T8482
main :: IO ()
main = T.testMain $ \ _t -> do
T.isolatedRun _t "CanonicalizePath" CanonicalizePath.main
T.isolatedRun _t "FileTime" FileTime.main
+ T.isolatedRun _t "T8482" T8482.main
diff --git a/tests/T8482.hs b/tests/T8482.hs
index 3bea8af..33b2d25 100644
--- a/tests/T8482.hs
+++ b/tests/T8482.hs
@@ -1,16 +1,21 @@
+{-# LANGUAGE CPP #-}
+module T8482 where
+#include "util.inl"
+import GHC.IO.Exception (IOErrorType(InappropriateType))
import System.Directory
-import Control.Exception
+import System.IO.Error (ioeGetErrorType)
+tmp1 :: FilePath
tmp1 = "T8482.tmp1"
+
+testdir :: FilePath
testdir = "T8482.dir"
-main = do
+main :: TestEnv -> IO ()
+main _t = do
writeFile tmp1 "hello"
createDirectory testdir
- tryRenameFile testdir tmp1 >>= print -- InappropriateType
- tryRenameFile tmp1 testdir >>= print -- InappropriateType
- tryRenameFile tmp1 "." >>= print -- InappropriateType
- removeDirectory testdir
- removeFile tmp1
- where tryRenameFile :: FilePath -> FilePath -> IO (Either IOException ())
- tryRenameFile opath npath = try $ renameFile opath npath
+ T(expectIOErrorType) () (is InappropriateType) (renameFile testdir tmp1)
+ T(expectIOErrorType) () (is InappropriateType) (renameFile tmp1 testdir)
+ T(expectIOErrorType) () (is InappropriateType) (renameFile tmp1 ".")
+ where is t = (== t) . ioeGetErrorType
diff --git a/tests/T8482.stdout b/tests/T8482.stdout
deleted file mode 100644
index 277bc18..0000000
--- a/tests/T8482.stdout
+++ /dev/null
@@ -1,3 +0,0 @@
-Left T8482.dir: renameFile: inappropriate type (is a directory)
-Left T8482.dir: renameFile: inappropriate type (is a directory)
-Left .: renameFile: inappropriate type (is a directory)
diff --git a/tests/all.T b/tests/all.T
index 54e4dd9..65c8cc5 100644
--- a/tests/all.T
+++ b/tests/all.T
@@ -26,6 +26,4 @@ test('createDirectoryIfMissing001', normal, compile_and_run, [''])
# No sane way to tell whether the output is reasonable here...
test('getHomeDirectory001', ignore_output, compile_and_run, [''])
-test('T8482', normal, compile_and_run, [''])
-
test('removeDirectoryRecursive001', normal, compile_and_run, [''])
More information about the ghc-commits
mailing list