[commit: packages/directory] Mistuke-bump-win32-version-bounds, bgamari-patch-1, master: Add renamePath (de6a440)

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


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

On branches: Mistuke-bump-win32-version-bounds,bgamari-patch-1,master
Link       : http://ghc.haskell.org/trac/ghc/changeset/de6a440288d85d4804aceecf8b73344d9a59555d/directory

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

commit de6a440288d85d4804aceecf8b73344d9a59555d
Author: Phil Ruffwind <rf at rufflewind.com>
Date:   Thu Jul 14 00:31:01 2016 -0400

    Add renamePath
    
    Fixes #58.


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

de6a440288d85d4804aceecf8b73344d9a59555d
 System/Directory.hs                       | 64 ++++++++++++++++++++++++++-----
 changelog.md                              |  3 ++
 directory.cabal                           |  1 +
 tests/Main.hs                             |  2 +
 tests/{RenameFile001.hs => RenamePath.hs} | 13 +++++--
 5 files changed, 70 insertions(+), 13 deletions(-)

diff --git a/System/Directory.hs b/System/Directory.hs
index f33ba7c..f20cc74 100644
--- a/System/Directory.hs
+++ b/System/Directory.hs
@@ -48,6 +48,7 @@ module System.Directory
     -- * Actions on files
     , removeFile
     , renameFile
+    , renamePath
     , copyFile
     , copyFileWithMetadata
 
@@ -674,11 +675,7 @@ renameDirectory opath npath =
    when (not is_dir) $ do
      ioError . (`ioeSetErrorString` "not a directory") $
        (mkIOError InappropriateType "renameDirectory" Nothing (Just opath))
-#ifdef mingw32_HOST_OS
-   Win32.moveFileEx opath npath Win32.mOVEFILE_REPLACE_EXISTING
-#else
-   Posix.rename opath npath
-#endif
+   renamePath opath npath
 
 {- |@'renameFile' old new@ changes the name of an existing file system
 object from /old/ to /new/.  If the /new/ object already
@@ -728,11 +725,7 @@ renameFile :: FilePath -> FilePath -> IO ()
 renameFile opath npath = (`ioeSetLocation` "renameFile") `modifyIOError` do
    -- XXX the tests are not performed atomically with the rename
    checkNotDir opath
-#ifdef mingw32_HOST_OS
-   Win32.moveFileEx opath npath Win32.mOVEFILE_REPLACE_EXISTING
-#else
-   Posix.rename opath npath
-#endif
+   renamePath opath npath
      -- The underlying rename implementation can throw odd exceptions when the
      -- destination is a directory.  For example, Windows typically throws a
      -- permission error, while POSIX systems may throw a resource busy error
@@ -752,6 +745,57 @@ renameFile opath npath = (`ioeSetLocation` "renameFile") `modifyIOError` do
          errIsDir path = ioError . (`ioeSetErrorString` "is a directory") $
                          mkIOError InappropriateType "" Nothing (Just path)
 
+-- | Rename a file or directory.  If the destination path already exists, it
+-- is replaced atomically.  The destination path must not point to an existing
+-- directory.  A conformant implementation need not support renaming files in
+-- all situations (e.g. renaming across different physical devices), but the
+-- constraints must be documented.
+--
+-- The operation may fail with:
+--
+-- * 'HardwareFault'
+-- A physical I\/O error has occurred.
+-- @[EIO]@
+--
+-- * 'InvalidArgument'
+-- Either operand is not a valid file name.
+-- @[ENAMETOOLONG, ELOOP]@
+--
+-- * 'isDoesNotExistError' \/ 'NoSuchThing'
+-- The original file does not exist, or there is no path to the target.
+-- @[ENOENT, ENOTDIR]@
+--
+-- * 'isPermissionError' \/ 'PermissionDenied'
+-- The process has insufficient privileges to perform the operation.
+-- @[EROFS, EACCES, EPERM]@
+--
+-- * 'ResourceExhausted'
+-- Insufficient resources are available to perform the operation.
+-- @[EDQUOT, ENOSPC, ENOMEM, EMLINK]@
+--
+-- * 'UnsatisfiedConstraints'
+-- Implementation-dependent constraints are not satisfied.
+-- @[EBUSY]@
+--
+-- * 'UnsupportedOperation'
+-- The implementation does not support renaming in this situation.
+-- @[EXDEV]@
+--
+-- * 'InappropriateType'
+-- Either the destination path refers to an existing directory, or one of the
+-- parent segments in the destination path is not a directory.
+-- @[ENOTDIR, EISDIR, EINVAL, EEXIST, ENOTEMPTY]@
+--
+renamePath :: FilePath                  -- ^ Old path
+           -> FilePath                  -- ^ New path
+           -> IO ()
+renamePath opath npath = (`ioeSetLocation` "renamePath") `modifyIOError` do
+#ifdef mingw32_HOST_OS
+   Win32.moveFileEx opath npath Win32.mOVEFILE_REPLACE_EXISTING
+#else
+   Posix.rename opath npath
+#endif
+
 -- | Copy a file with its permissions.  If the destination file already exists,
 -- it is replaced atomically.  Neither path may refer to an existing
 -- directory.  No exceptions are thrown if the permissions could not be
diff --git a/changelog.md b/changelog.md
index cfd6fc4..a053b88 100644
--- a/changelog.md
+++ b/changelog.md
@@ -10,6 +10,9 @@ Changelog for the [`directory`][1] package
   * Add `doesPathExist` and `getFileSize`
     ([#57](https://github.com/haskell/directory/issues/57))
 
+  * Add `renamePath`
+    ([#58](https://github.com/haskell/directory/issues/58))
+
 ## 1.2.6.3 (May 2016)
 
   * Add missing import of `(<*>)` on Windows for `base` earlier than 4.8.0.0
diff --git a/directory.cabal b/directory.cabal
index b7bdf17..419b7f8 100644
--- a/directory.cabal
+++ b/directory.cabal
@@ -99,6 +99,7 @@ test-suite test
         RemoveDirectoryRecursive001
         RenameDirectory
         RenameFile001
+        RenamePath
         Safe
         T8482
         WithCurrentDirectory
diff --git a/tests/Main.hs b/tests/Main.hs
index 2b9227f..be178ca 100644
--- a/tests/Main.hs
+++ b/tests/Main.hs
@@ -21,6 +21,7 @@ import qualified IsSymbolicLink
 import qualified RemoveDirectoryRecursive001
 import qualified RenameDirectory
 import qualified RenameFile001
+import qualified RenamePath
 import qualified Safe
 import qualified T8482
 import qualified WithCurrentDirectory
@@ -48,6 +49,7 @@ main = T.testMain $ \ _t -> do
   T.isolatedRun _t "RemoveDirectoryRecursive001" RemoveDirectoryRecursive001.main
   T.isolatedRun _t "RenameDirectory" RenameDirectory.main
   T.isolatedRun _t "RenameFile001" RenameFile001.main
+  T.isolatedRun _t "RenamePath" RenamePath.main
   T.isolatedRun _t "Safe" Safe.main
   T.isolatedRun _t "T8482" T8482.main
   T.isolatedRun _t "WithCurrentDirectory" WithCurrentDirectory.main
diff --git a/tests/RenameFile001.hs b/tests/RenamePath.hs
similarity index 62%
copy from tests/RenameFile001.hs
copy to tests/RenamePath.hs
index f20bfb7..fe3fd35 100644
--- a/tests/RenameFile001.hs
+++ b/tests/RenamePath.hs
@@ -1,16 +1,23 @@
 {-# LANGUAGE CPP #-}
-module RenameFile001 where
+module RenamePath where
 #include "util.inl"
 import System.Directory
 
 main :: TestEnv -> IO ()
 main _t = do
+
+  createDirectory "a"
+  T(expectEq) () ["a"] =<< listDirectory "."
+  renamePath "a" "b"
+  T(expectEq) () ["b"] =<< listDirectory "."
+
   writeFile tmp1 contents1
-  renameFile tmp1 tmp2
+  renamePath tmp1 tmp2
   T(expectEq) () contents1 =<< readFile tmp2
   writeFile tmp1 contents2
-  renameFile tmp2 tmp1
+  renamePath tmp2 tmp1
   T(expectEq) () contents1 =<< readFile tmp1
+
   where
     tmp1 = "tmp1"
     tmp2 = "tmp2"



More information about the ghc-commits mailing list