[commit: packages/directory] master: Update tests/FileTime.hs to also check for does-not-exist errors (41cd458)
git at git.haskell.org
git at git.haskell.org
Fri Dec 18 09:51:07 UTC 2015
Repository : ssh://git@git.haskell.org/directory
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/41cd458703d4ef88c3539c7ab46096afd8ef9deb/directory
>---------------------------------------------------------------
commit 41cd458703d4ef88c3539c7ab46096afd8ef9deb
Author: Phil Ruffwind <rf at rufflewind.com>
Date: Sat May 30 23:47:32 2015 -0400
Update tests/FileTime.hs to also check for does-not-exist errors
>---------------------------------------------------------------
41cd458703d4ef88c3539c7ab46096afd8ef9deb
tests/FileTime.hs | 8 ++++++++
tests/Util.hs | 2 +-
2 files changed, 9 insertions(+), 1 deletion(-)
diff --git a/tests/FileTime.hs b/tests/FileTime.hs
index c830864..580aa7d 100644
--- a/tests/FileTime.hs
+++ b/tests/FileTime.hs
@@ -2,6 +2,7 @@
module FileTime where
#include "util.inl"
import System.Directory
+import System.IO.Error (isDoesNotExistError)
import Data.Foldable (for_)
import qualified Data.Time.Clock as Time
@@ -10,6 +11,13 @@ main _t = do
now <- Time.getCurrentTime
let someTimeAgo = Time.addUTCTime (-3600) now
+ T(expectIOErrorType) () isDoesNotExistError $
+ getAccessTime "nonexistent-file"
+ T(expectIOErrorType) () isDoesNotExistError $
+ getModificationTime "nonexistent-file"
+ T(expectIOErrorType) () isDoesNotExistError $
+ setModificationTime "nonexistent-file" someTimeAgo
+
writeFile "foo" ""
for_ [ ("foo", someTimeAgo)
, (".", someTimeAgo)
diff --git a/tests/Util.hs b/tests/Util.hs
index 3a0584c..cf1f134 100644
--- a/tests/Util.hs
+++ b/tests/Util.hs
@@ -108,7 +108,7 @@ expectNearTime t file line context x y diff =
expectIOErrorType :: Show a =>
TestEnv -> String -> Integer -> a
- -> (IOError -> Bool) -> IO a -> IO ()
+ -> (IOError -> Bool) -> IO b -> IO ()
expectIOErrorType t file line context which action = do
result <- tryIOError action
checkEither t [showContext file line context] $ case result of
More information about the ghc-commits
mailing list