Fix a URL
[haskell-directory.git] / System / Directory.hs
index 1d63bde..42ed6af 100644 (file)
@@ -39,6 +39,7 @@ module System.Directory
     , copyFile                  -- :: FilePath -> FilePath -> IO ()
     
     , canonicalizePath
+    , makeRelativeToCurrentDirectory
     , findExecutable
 
     -- * Existence tests
@@ -65,13 +66,18 @@ module System.Directory
     , getModificationTime       -- :: FilePath -> IO ClockTime
    ) where
 
-import System.Directory.Internals
+import Prelude hiding ( catch )
+
 import System.Environment      ( getEnv )
-import System.IO.Error
+import System.FilePath
+import System.IO
+import System.IO.Error hiding ( catch, try )
 import Control.Monad           ( when, unless )
+import Control.Exception
 
 #ifdef __NHC__
 import Directory
+import System (system)
 #endif /* __NHC__ */
 
 #ifdef __HUGS__
@@ -84,13 +90,9 @@ import Foreign.C
 {-# CFILES cbits/directory.c #-}
 
 #ifdef __GLASGOW_HASKELL__
-import Prelude
-
-import Control.Exception       ( bracket )
 import System.Posix.Types
 import System.Posix.Internals
 import System.Time             ( ClockTime(..) )
-import System.IO
 
 import GHC.IOBase      ( IOException(..), IOErrorType(..), ioException )
 
@@ -99,7 +101,7 @@ A directory contains a series of entries, each of which is a named
 reference to a file system object (file, directory etc.).  Some
 entries may be hidden, inaccessible, or have some administrative
 function (e.g. `.' or `..' under POSIX
-<http://www.opengroup.org/onlinepubs/007904975/toc.htm>), but in 
+<http://www.opengroup.org/onlinepubs/009695399/>), but in 
 this standard all such entries are considered to form part of the
 directory contents. Entries in sub-directories are not, however,
 considered to form part of the directory contents.
@@ -153,6 +155,29 @@ The operation may fail with:
 getPermissions :: FilePath -> IO Permissions
 getPermissions name = do
   withCString name $ \s -> do
+#ifdef mingw32_HOST_OS
+  -- stat() does a better job of guessing the permissions on Windows
+  -- than access() does.  e.g. for execute permission, it looks at the
+  -- filename extension :-)
+  --
+  -- I tried for a while to do this properly, using the Windows security API,
+  -- and eventually gave up.  getPermissions is a flawed API anyway. -- SimonM
+  allocaBytes sizeof_stat $ \ p_stat -> do
+  throwErrnoIfMinus1_ "getPermissions" $ c_stat s p_stat
+  mode <- st_mode p_stat
+  let read   = mode .&. s_IRUSR
+  let write  = mode .&. s_IWUSR
+  let exec   = mode .&. s_IXUSR
+  let is_dir = mode .&. s_IFDIR
+  return (
+    Permissions {
+      readable   = read  /= 0,
+      writable   = write /= 0,
+      executable = is_dir == 0 && exec /= 0,
+      searchable = is_dir /= 0 && exec /= 0
+    }
+   )
+#else
   read  <- c_access s r_OK
   write <- c_access s w_OK
   exec  <- c_access s x_OK
@@ -166,6 +191,7 @@ getPermissions name = do
       searchable = is_dir && exec == 0
     }
    )
+#endif
 
 {- |The 'setPermissions' operation sets the
 permissions for the file or directory.
@@ -269,11 +295,12 @@ createDirectoryIfMissing :: Bool     -- ^ Create its parents too?
                         -> IO ()
 createDirectoryIfMissing parents file = do
   b <- doesDirectoryExist file
-  case (b,parents, file) of 
+  case (b,parents, file) of
     (_,     _, "") -> return ()
     (True,  _,  _) -> return ()
-    (_,  True,  _) -> mapM_ (createDirectoryIfMissing False) (tail (pathParents file))
+    (_,  True,  _) -> mapM_ (createDirectoryIfMissing False) $ mkParents file
     (_, False,  _) -> createDirectory file
+ where mkParents = scanl1 (</>) . splitDirectories . normalise
 
 #if __GLASGOW_HASKELL__
 {- | @'removeDirectory' dir@ removes an existing directory /dir/.  The
@@ -330,7 +357,7 @@ removeDirectory path = do
 removeDirectoryRecursive :: FilePath -> IO ()
 removeDirectoryRecursive startLoc = do
   cont <- getDirectoryContents startLoc
-  sequence_ [rm (startLoc `joinFileName` x) | x <- cont, x /= "." && x /= ".."]
+  sequence_ [rm (startLoc </> x) | x <- cont, x /= "." && x /= ".."]
   removeDirectory startLoc
   where
     rm :: FilePath -> IO ()
@@ -338,7 +365,7 @@ removeDirectoryRecursive startLoc = do
               case temp of
                 Left e  -> do isDir <- doesDirectoryExist f
                               -- If f is not a directory, re-throw the error
-                              unless isDir $ ioError e
+                              unless isDir $ throw e
                               removeDirectoryRecursive f
                 Right _ -> return ()
 
@@ -510,57 +537,34 @@ Neither path may refer to an existing directory.  The permissions of /old/ are
 copied to /new/, if possible.
 -}
 
-{- NOTES:
-
-It's tempting to try to remove the target file before opening it for
-writing.  This could be useful: for example if the target file is an
-executable that is in use, writing will fail, but unlinking first
-would succeed.
-
-However, it certainly isn't always what you want.
-
- * if the target file is hardlinked, removing it would break
-   the hard link, but just opening would preserve it.
-
- * opening and truncating will preserve permissions and
-   ACLs on the target.
-
- * If the destination file is read-only in a writable directory,
-   we might want copyFile to fail.  Removing the target first
-   would succeed, however.
-
- * If the destination file is special (eg. /dev/null), removing
-   it is probably not the right thing.  Copying to /dev/null
-   should leave /dev/null intact, not replace it with a plain
-   file.
-
- * There's a small race condition between removing the target and
-   opening it for writing during which time someone might
-   create it again.
--}
 copyFile :: FilePath -> FilePath -> IO ()
+#ifdef __NHC__
 copyFile fromFPath toFPath =
-#if (!(defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ > 600))
-       do readFile fromFPath >>= writeFile toFPath
-          try (copyPermissions fromFPath toFPath)
-          return ()
+    do readFile fromFPath >>= writeFile toFPath
+       try (copyPermissions fromFPath toFPath)
+       return ()
 #else
-       (bracket (openBinaryFile fromFPath ReadMode) hClose $ \hFrom ->
-        bracket (openBinaryFile toFPath WriteMode) hClose $ \hTo ->
-        allocaBytes bufferSize $ \buffer -> do
-               copyContents hFrom hTo buffer
-               try (copyPermissions fromFPath toFPath)
-               return ()) `catch` (ioError . changeFunName)
-       where
-               bufferSize = 1024
-               
-               changeFunName (IOError h iot fun str mb_fp) = IOError h iot "copyFile" str mb_fp
-               
-               copyContents hFrom hTo buffer = do
-                       count <- hGetBuf hFrom buffer bufferSize
-                       when (count > 0) $ do
-                               hPutBuf hTo buffer count
-                               copyContents hFrom hTo buffer
+copyFile fromFPath toFPath =
+    copy `catch` (\e -> case e of
+                        IOException e ->
+                            throw $ IOException $ ioeSetLocation e "copyFile"
+                        _ -> throw e)
+    where copy = bracket (openBinaryFile fromFPath ReadMode) hClose $ \hFrom ->
+                 bracketOnError openTmp cleanTmp $ \(tmpFPath, hTmp) ->
+                 do allocaBytes bufferSize $ copyContents hFrom hTmp
+                    hClose hTmp
+                    try (copyPermissions fromFPath tmpFPath)
+                    renameFile tmpFPath toFPath
+          openTmp = openBinaryTempFile (takeDirectory toFPath) ".copyFile.tmp"
+          cleanTmp (tmpFPath, hTmp) = do try $ hClose hTmp
+                                         try $ removeFile tmpFPath
+          bufferSize = 1024
+
+          copyContents hFrom hTo buffer = do
+                  count <- hGetBuf hFrom buffer bufferSize
+                  when (count > 0) $ do
+                          hPutBuf hTo buffer count
+                          copyContents hFrom hTo buffer
 #endif
 
 -- | Given path referring to a file or directory, returns a
@@ -596,6 +600,12 @@ foreign import ccall unsafe "realpath"
                               -> IO CString
 #endif
 
+-- | 'makeRelative' the current directory.
+makeRelativeToCurrentDirectory :: FilePath -> IO FilePath
+makeRelativeToCurrentDirectory x = do
+    cur <- getCurrentDirectory
+    return $ makeRelative cur x
+
 -- | Given an executable file name, searches for such file
 -- in the directories listed in system PATH. The returned value 
 -- is the path to the found executable or Nothing if there isn't
@@ -625,16 +635,16 @@ foreign import stdcall unsafe "SearchPathA"
 #else
  do
   path <- getEnv "PATH"
-  search (parseSearchPath path)
+  search (splitSearchPath path)
   where
-    fileName = binary `joinFileExt` exeExtension
+    fileName = binary <.> exeExtension
 
     search :: [FilePath] -> IO (Maybe FilePath)
     search [] = return Nothing
     search (d:ds) = do
-       let path = d `joinFileName` fileName
-       b <- doesFileExist path
-       if b then return (Just path)
+        let path = d </> fileName
+        b <- doesFileExist path
+        if b then return (Just path)
              else search ds
 #endif
 
@@ -853,14 +863,8 @@ isDirectory stat = do
   return (s_isdir mode)
 
 fileNameEndClean :: String -> String
-fileNameEndClean name = 
-  if i > 0 && (ec == '\\' || ec == '/') then 
-     fileNameEndClean (take i name)
-   else
-     name
-  where
-      i  = (length name) - 1
-      ec = name !! i
+fileNameEndClean name = if isDrive name then addTrailingPathSeparator name
+                                        else dropTrailingPathSeparator name
 
 foreign import ccall unsafe "__hscore_R_OK" r_OK :: CInt
 foreign import ccall unsafe "__hscore_W_OK" w_OK :: CInt
@@ -869,13 +873,14 @@ foreign import ccall unsafe "__hscore_X_OK" x_OK :: CInt
 foreign import ccall unsafe "__hscore_S_IRUSR" s_IRUSR :: CMode
 foreign import ccall unsafe "__hscore_S_IWUSR" s_IWUSR :: CMode
 foreign import ccall unsafe "__hscore_S_IXUSR" s_IXUSR :: CMode
+foreign import ccall unsafe "__hscore_S_IFDIR" s_IFDIR :: CMode
 
 foreign import ccall unsafe "__hscore_long_path_size"
   long_path_size :: Int
 
 #else
 long_path_size :: Int
-long_path_size = 2048  /* guess? */
+long_path_size = 2048  --  // guess?
 
 #endif /* __GLASGOW_HASKELL__ */
 
@@ -1042,3 +1047,14 @@ raiseUnsupported loc =
    ioException (IOError Nothing UnsupportedOperation loc "unsupported operation" Nothing)
 
 #endif
+
+-- ToDo: This should be determined via autoconf (AC_EXEEXT)
+-- | Extension for executable files
+-- (typically @\"\"@ on Unix and @\"exe\"@ on Windows or OS\/2)
+exeExtension :: String
+#ifdef mingw32_HOST_OS
+exeExtension = "exe"
+#else
+exeExtension = ""
+#endif
+