[commit: packages/directory] master: Migrate test: GetPermissions001 (057ebd8)

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


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

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

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

commit 057ebd8b6c536c4daf155bf072fc8bf37ece600e
Author: Phil Ruffwind <rf at rufflewind.com>
Date:   Fri Jun 5 01:21:17 2015 -0400

    Migrate test: GetPermissions001


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

057ebd8b6c536c4daf155bf072fc8bf37ece600e
 tests/GetPermissions001.hs                         | 47 ++++++++++++++++++++++
 tests/Main.hs                                      |  2 +
 tests/all.T                                        |  3 --
 tests/getPermissions001.hs                         | 20 ---------
 tests/getPermissions001.stdout                     |  3 --
 tests/getPermissions001.stdout-alpha-dec-osf3      |  3 --
 .../getPermissions001.stdout-i386-unknown-freebsd  |  3 --
 .../getPermissions001.stdout-i386-unknown-openbsd  |  3 --
 tests/getPermissions001.stdout-mingw               |  3 --
 ...getPermissions001.stdout-x86_64-unknown-openbsd |  3 --
 10 files changed, 49 insertions(+), 41 deletions(-)

diff --git a/tests/GetPermissions001.hs b/tests/GetPermissions001.hs
new file mode 100644
index 0000000..e330230
--- /dev/null
+++ b/tests/GetPermissions001.hs
@@ -0,0 +1,47 @@
+{-# LANGUAGE CPP #-}
+module GetPermissions001 where
+#include "util.inl"
+import System.Directory
+
+main :: TestEnv -> IO ()
+main _t = do
+
+  checkCurrentDir
+  checkExecutable
+  checkOrdinary
+  checkTrailingSlash
+
+  where
+
+    checkCurrentDir = do
+      -- since the current directory is created by the test runner,
+      -- it should be readable, writable, and searchable
+      p <- getPermissions "."
+      T(expect) () (readable p)
+      T(expect) () (writable p)
+      T(expect) () (not (executable p))
+      T(expect) () (searchable p)
+
+    checkExecutable = do
+      -- 'find' expected to exist on both Windows and POSIX,
+      -- though we have no idea if it's writable
+      Just f <- findExecutable "find"
+      p <- getPermissions f
+      T(expect) () (readable p)
+      T(expect) () (executable p)
+      T(expect) () (not (searchable p))
+
+    checkOrdinary = do
+      writeFile "foo" ""
+      p <- getPermissions "foo"
+      T(expect) () (readable p)
+      T(expect) () (writable p)
+      T(expect) () (not (executable p))
+      T(expect) () (not (searchable p))
+
+    -- [regression test] (issue #9)
+    -- Windows doesn't like trailing path separators
+    checkTrailingSlash = do
+      createDirectory "bar"
+      _ <- getPermissions "bar/"
+      return ()
diff --git a/tests/Main.hs b/tests/Main.hs
index 25ff4cc..af44336 100644
--- a/tests/Main.hs
+++ b/tests/Main.hs
@@ -7,6 +7,7 @@ import qualified DoesDirectoryExist001
 import qualified FileTime
 import qualified GetDirContents001
 import qualified GetDirContents002
+import qualified GetPermissions001
 import qualified T8482
 
 main :: IO ()
@@ -18,4 +19,5 @@ main = T.testMain $ \ _t -> do
   T.isolatedRun _t "FileTime" FileTime.main
   T.isolatedRun _t "GetDirContents001" GetDirContents001.main
   T.isolatedRun _t "GetDirContents002" GetDirContents002.main
+  T.isolatedRun _t "GetPermissions001" GetPermissions001.main
   T.isolatedRun _t "T8482" T8482.main
diff --git a/tests/all.T b/tests/all.T
index ed6abbb..bb8fa54 100644
--- a/tests/all.T
+++ b/tests/all.T
@@ -1,6 +1,3 @@
-# Depends on binary from previous run, which gets removed by the driver way=ghci
-test('getPermissions001', omit_ways(['ghci']), compile_and_run, ['-cpp'])
-
 test('copyFile001', extra_clean(['copyFile001dir/target']),
                     compile_and_run, [''])
 test('copyFile002', extra_clean(['copyFile002dir/target']),
diff --git a/tests/getPermissions001.hs b/tests/getPermissions001.hs
deleted file mode 100644
index 6582928..0000000
--- a/tests/getPermissions001.hs
+++ /dev/null
@@ -1,20 +0,0 @@
-{-# LANGUAGE CPP #-}
-import System.Directory
-
-main = do
-#ifdef mingw32_HOST_OS
-  let exe = ".exe"
-#else
-  let exe = ""
-#endif
-  p <- getPermissions "."
-  print p
-  p <- getPermissions "getPermissions001.hs"
-  print p
-  p <- getPermissions ("getPermissions001" ++ exe)
-  print p
-
-  -- issue #9: Windows doesn't like trailing path separators
-  _ <- getPermissions "../tests/"
-
-  return ()
diff --git a/tests/getPermissions001.stdout b/tests/getPermissions001.stdout
deleted file mode 100644
index 1e18354..0000000
--- a/tests/getPermissions001.stdout
+++ /dev/null
@@ -1,3 +0,0 @@
-Permissions {readable = True, writable = True, executable = False, searchable = True}
-Permissions {readable = True, writable = True, executable = False, searchable = False}
-Permissions {readable = True, writable = True, executable = True, searchable = False}
diff --git a/tests/getPermissions001.stdout-alpha-dec-osf3 b/tests/getPermissions001.stdout-alpha-dec-osf3
deleted file mode 100644
index 8b030e2..0000000
--- a/tests/getPermissions001.stdout-alpha-dec-osf3
+++ /dev/null
@@ -1,3 +0,0 @@
-Permissions {readable = True, writable = True, executable = False, searchable = True}
-Permissions {readable = True, writable = True, executable = False, searchable = False}
-Permissions {readable = True, writable = False, executable = True, searchable = False}
diff --git a/tests/getPermissions001.stdout-i386-unknown-freebsd b/tests/getPermissions001.stdout-i386-unknown-freebsd
deleted file mode 100644
index 8b030e2..0000000
--- a/tests/getPermissions001.stdout-i386-unknown-freebsd
+++ /dev/null
@@ -1,3 +0,0 @@
-Permissions {readable = True, writable = True, executable = False, searchable = True}
-Permissions {readable = True, writable = True, executable = False, searchable = False}
-Permissions {readable = True, writable = False, executable = True, searchable = False}
diff --git a/tests/getPermissions001.stdout-i386-unknown-openbsd b/tests/getPermissions001.stdout-i386-unknown-openbsd
deleted file mode 100644
index 8b030e2..0000000
--- a/tests/getPermissions001.stdout-i386-unknown-openbsd
+++ /dev/null
@@ -1,3 +0,0 @@
-Permissions {readable = True, writable = True, executable = False, searchable = True}
-Permissions {readable = True, writable = True, executable = False, searchable = False}
-Permissions {readable = True, writable = False, executable = True, searchable = False}
diff --git a/tests/getPermissions001.stdout-mingw b/tests/getPermissions001.stdout-mingw
deleted file mode 100644
index 4dcaba5..0000000
--- a/tests/getPermissions001.stdout-mingw
+++ /dev/null
@@ -1,3 +0,0 @@
-Permissions {readable = True, writable = True, executable = True, searchable = True}
-Permissions {readable = True, writable = True, executable = True, searchable = True}
-Permissions {readable = True, writable = True, executable = True, searchable = True}
diff --git a/tests/getPermissions001.stdout-x86_64-unknown-openbsd b/tests/getPermissions001.stdout-x86_64-unknown-openbsd
deleted file mode 100644
index 8b030e2..0000000
--- a/tests/getPermissions001.stdout-x86_64-unknown-openbsd
+++ /dev/null
@@ -1,3 +0,0 @@
-Permissions {readable = True, writable = True, executable = False, searchable = True}
-Permissions {readable = True, writable = True, executable = False, searchable = False}
-Permissions {readable = True, writable = False, executable = True, searchable = False}



More information about the ghc-commits mailing list