Fix whitespace
[haskell-directory.git] / System / Directory.hs
index 8b7dee3..e6b49c2 100644 (file)
@@ -39,6 +39,7 @@ module System.Directory
     , copyFile                  -- :: FilePath -> FilePath -> IO ()
     
     , canonicalizePath
+    , makeRelativeToCurrentDirectory
     , findExecutable
 
     -- * Existence tests
@@ -65,20 +66,24 @@ module System.Directory
     , getModificationTime       -- :: FilePath -> IO ClockTime
    ) where
 
-import System.Directory.Internals
 import System.Environment      ( getEnv )
+import System.FilePath
 import System.IO.Error
 import Control.Monad           ( when, unless )
 
 #ifdef __NHC__
 import Directory
-import NHC.FFI
 #endif /* __NHC__ */
 
 #ifdef __HUGS__
 import Hugs.Directory
 #endif /* __HUGS__ */
 
+import Foreign
+import Foreign.C
+
+{-# CFILES cbits/directory.c #-}
+
 #ifdef __GLASGOW_HASKELL__
 import Prelude
 
@@ -87,8 +92,6 @@ import System.Posix.Types
 import System.Posix.Internals
 import System.Time             ( ClockTime(..) )
 import System.IO
-import Foreign
-import Foreign.C
 
 import GHC.IOBase      ( IOException(..), IOErrorType(..), ioException )
 
@@ -267,11 +270,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
@@ -328,7 +332,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 ()
@@ -504,34 +508,64 @@ renameFile opath npath =
 
 {- |@'copyFile' old new@ copies the existing file from /old/ to /new/.
 If the /new/ file already exists, it is atomically replaced by the /old/ file.
-Neither path may refer to an existing directory.
+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 ()
 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
+        (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
 #endif
 
-#ifdef __GLASGOW_HASKELL__
 -- | Given path referring to a file or directory, returns a
 -- canonicalized path, with the intent that two paths referring
 -- to the same file\/directory will map to the same canonicalized
@@ -564,11 +598,12 @@ foreign import ccall unsafe "realpath"
                               -> CString
                               -> IO CString
 #endif
-#else /* !__GLASGOW_HASKELL__ */
--- dummy implementation
-canonicalizePath :: FilePath -> IO FilePath
-canonicalizePath fpath = return fpath
-#endif /* !__GLASGOW_HASKELL__ */
+
+-- | '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 
@@ -576,7 +611,7 @@ canonicalizePath fpath = return fpath
 -- such executable. For example (findExecutable \"ghc\")
 -- gives you the path to GHC.
 findExecutable :: String -> IO (Maybe FilePath)
-findExecutable binary = do
+findExecutable binary =
 #if defined(mingw32_HOST_OS)
   withCString binary $ \c_binary ->
   withCString ('.':exeExtension) $ \c_ext ->
@@ -588,7 +623,7 @@ findExecutable binary = do
               return (Just fpath)
       else return Nothing
 
-foreign import stdcall unsafe "SearchPath"
+foreign import stdcall unsafe "SearchPathA"
             c_SearchPath :: CString
                          -> CString
                          -> CString
@@ -597,17 +632,18 @@ foreign import stdcall unsafe "SearchPath"
                          -> Ptr CString
                          -> IO CInt
 #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
 
@@ -826,26 +862,24 @@ 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_long_path_size"
-  long_path_size :: Int
-
-foreign import ccall unsafe "__hscore_R_OK" r_OK :: CMode
-foreign import ccall unsafe "__hscore_W_OK" w_OK :: CMode
-foreign import ccall unsafe "__hscore_X_OK" x_OK :: CMode
+foreign import ccall unsafe "__hscore_R_OK" r_OK :: CInt
+foreign import ccall unsafe "__hscore_W_OK" w_OK :: CInt
+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_long_path_size"
+  long_path_size :: Int
+
+#else
+long_path_size :: Int
+long_path_size = 2048  --  // guess?
+
 #endif /* __GLASGOW_HASKELL__ */
 
 {- | Returns the current user's home directory.
@@ -871,7 +905,7 @@ cannot be found.
 -}
 getHomeDirectory :: IO FilePath
 getHomeDirectory =
-#if __GLASGOW_HASKELL__ && defined(mingw32_HOST_OS)
+#if defined(mingw32_HOST_OS)
   allocaBytes long_path_size $ \pPath -> do
      r <- c_SHGetFolderPath nullPtr csidl_PROFILE nullPtr 0 pPath
      if (r < 0)
@@ -913,7 +947,7 @@ cannot be found.
 -}
 getAppUserDataDirectory :: String -> IO FilePath
 getAppUserDataDirectory appName = do
-#if __GLASGOW_HASKELL__ && defined(mingw32_HOST_OS)
+#if defined(mingw32_HOST_OS)
   allocaBytes long_path_size $ \pPath -> do
      r <- c_SHGetFolderPath nullPtr csidl_APPDATA nullPtr 0 pPath
      when (r<0) (raiseUnsupported "System.Directory.getAppUserDataDirectory")
@@ -947,7 +981,7 @@ cannot be found.
 -}
 getUserDocumentsDirectory :: IO FilePath
 getUserDocumentsDirectory = do
-#if __GLASGOW_HASKELL__ && defined(mingw32_HOST_OS)
+#if defined(mingw32_HOST_OS)
   allocaBytes long_path_size $ \pPath -> do
      r <- c_SHGetFolderPath nullPtr csidl_PERSONAL nullPtr 0 pPath
      when (r<0) (raiseUnsupported "System.Directory.getUserDocumentsDirectory")
@@ -984,7 +1018,7 @@ The function doesn\'t verify whether the path exists.
 -}
 getTemporaryDirectory :: IO FilePath
 getTemporaryDirectory = do
-#if __GLASGOW_HASKELL__ && defined(mingw32_HOST_OS)
+#if defined(mingw32_HOST_OS)
   allocaBytes long_path_size $ \pPath -> do
      r <- c_GetTempPath (fromIntegral long_path_size) pPath
      peekCString pPath
@@ -992,7 +1026,7 @@ getTemporaryDirectory = do
   catch (getEnv "TMPDIR") (\ex -> return "/tmp")
 #endif
 
-#if __GLASGOW_HASKELL__ && defined(mingw32_HOST_OS)
+#if defined(mingw32_HOST_OS)
 foreign import ccall unsafe "__hscore_getFolderPath"
             c_SHGetFolderPath :: Ptr () 
                               -> CInt 
@@ -1011,3 +1045,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
+