[commit: packages/directory] master: Add tests for setPermissions (b03d55f)

git at git.haskell.org git at git.haskell.org
Mon Apr 17 21:35:55 UTC 2017


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

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

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

commit b03d55f8815a1ae2bc406d5da99c825f63a91a52
Author: Phil Ruffwind <rf at rufflewind.com>
Date:   Tue Mar 7 00:51:51 2017 -0500

    Add tests for setPermissions


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

b03d55f8815a1ae2bc406d5da99c825f63a91a52
 tests/GetPermissions001.hs | 15 +++++++++++++++
 1 file changed, 15 insertions(+)

diff --git a/tests/GetPermissions001.hs b/tests/GetPermissions001.hs
index 045d35d..c94288f 100644
--- a/tests/GetPermissions001.hs
+++ b/tests/GetPermissions001.hs
@@ -1,6 +1,7 @@
 {-# LANGUAGE CPP #-}
 module GetPermissions001 where
 #include "util.inl"
+import TestUtils
 
 main :: TestEnv -> IO ()
 main _t = do
@@ -10,6 +11,20 @@ main _t = do
   checkOrdinary
   checkTrailingSlash
 
+  -- 'writable' is the only permission that can be changed on Windows
+  writeFile "foo.txt" ""
+  foo <- makeAbsolute "foo.txt"
+  modifyPermissions "foo.txt" (\ p -> p { writable = False })
+  T(expect) () =<< not . writable <$> getPermissions "foo.txt"
+  modifyPermissions "foo.txt" (\ p -> p { writable = True })
+  T(expect) () =<< writable <$> getPermissions "foo.txt"
+  modifyPermissions "foo.txt" (\ p -> p { writable = False })
+  T(expect) () =<< not . writable <$> getPermissions "foo.txt"
+  modifyPermissions foo (\ p -> p { writable = True })
+  T(expect) () =<< writable <$> getPermissions foo
+  modifyPermissions foo (\ p -> p { writable = False })
+  T(expect) () =<< not . writable <$> getPermissions foo
+
   where
 
     checkCurrentDir = do



More information about the ghc-commits mailing list