FIX BUILD (with GHC 6.2.x): System.Directory.Internals is no more
[ghc-hetmet.git] / compat / Compat / Directory.hs
1 {-# OPTIONS -cpp #-}
2 -----------------------------------------------------------------------------
3 -- |
4 -- Module      :  Compat.Directory
5 -- Copyright   :  (c) The University of Glasgow 2001-2004
6 -- License     :  BSD-style (see the file libraries/base/LICENSE)
7 -- 
8 -- Maintainer  :  libraries@haskell.org
9 -- Stability   :  provisional
10 -- Portability :  portable
11 --
12 -- Functions from System.Directory that aren't present in older versions
13 -- of that library.
14 --
15 -----------------------------------------------------------------------------
16
17 module Compat.Directory (
18         getAppUserDataDirectory,
19         copyFile,
20         findExecutable,
21         createDirectoryIfMissing
22   ) where
23
24 #include "../../includes/ghcconfig.h"
25
26 import System.Environment (getEnv)
27 import System.FilePath
28 #if __GLASGOW_HASKELL__ > 600
29 import Control.Exception        ( bracket )
30 import Control.Monad            ( when )
31 import Foreign.Marshal.Alloc    ( allocaBytes )
32 import System.IO (IOMode(..), openBinaryFile, hGetBuf, hPutBuf, hClose)
33 import System.IO.Error          ( try )
34 import GHC.IOBase ( IOException(..), IOErrorType(..) )
35 #else
36 import System.IO                ( try )
37 #endif
38 #if __GLASGOW_HASKELL__ && defined(mingw32_HOST_OS)
39 import Foreign.Ptr
40 import Foreign.C
41 #endif
42 import System.Directory(doesFileExist, doesDirectoryExist, getPermissions, setPermissions, createDirectory)
43
44 getAppUserDataDirectory :: String -> IO FilePath
45 getAppUserDataDirectory appName = do
46 #if __GLASGOW_HASKELL__ && defined(mingw32_HOST_OS)
47   allocaBytes long_path_size $ \pPath -> do
48      r <- c_SHGetFolderPath nullPtr csidl_APPDATA nullPtr 0 pPath
49      when (r<0) (raiseUnsupported "Compat.Directory.getAppUserDataDirectory")
50      s <- peekCString pPath
51      return (s++'\\':appName)
52 #else
53   path <- getEnv "HOME"
54   return (path++'/':'.':appName)
55 #endif
56
57 #if __GLASGOW_HASKELL__ && defined(mingw32_HOST_OS)
58 foreign import ccall unsafe "directory.h __hscore_getFolderPath"
59             c_SHGetFolderPath :: Ptr () 
60                               -> CInt 
61                               -> Ptr () 
62                               -> CInt 
63                               -> CString 
64                               -> IO CInt
65
66 -- __compat_long_path_size defined in cbits/directory.c
67 foreign import ccall unsafe "directory.h __compat_long_path_size"
68   long_path_size :: Int
69
70 foreign import ccall unsafe "directory.h __hscore_CSIDL_APPDATA"  csidl_APPDATA  :: CInt
71
72 raiseUnsupported loc = 
73    ioError (IOError Nothing UnsupportedOperation loc "unsupported operation" Nothing)
74 #endif
75
76
77 copyFile :: FilePath -> FilePath -> IO ()
78 copyFile fromFPath toFPath =
79 #if (!(defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ > 600))
80         do readFile fromFPath >>= writeFile toFPath
81            try (getPermissions fromFPath >>= setPermissions toFPath)
82            return ()
83 #else
84         (bracket (openBinaryFile fromFPath ReadMode) hClose $ \hFrom ->
85          bracket (openBinaryFile toFPath WriteMode) hClose $ \hTo ->
86          allocaBytes bufferSize $ \buffer -> do
87                 copyContents hFrom hTo buffer
88                 try (getPermissions fromFPath >>= setPermissions toFPath)
89                 return ()) `catch` (ioError . changeFunName)
90         where
91                 bufferSize = 1024
92                 
93                 changeFunName (IOError h iot fun str mb_fp) = IOError h iot "copyFile" str mb_fp
94                 
95                 copyContents hFrom hTo buffer = do
96                         count <- hGetBuf hFrom buffer bufferSize
97                         when (count > 0) $ do
98                                 hPutBuf hTo buffer count
99                                 copyContents hFrom hTo buffer
100 #endif
101
102 -- | Given an executable file name, searches for such file
103 -- in the directories listed in system PATH. The returned value 
104 -- is the path to the found executable or Nothing if there isn't
105 -- such executable. For example (findExecutable \"ghc\")
106 -- gives you the path to GHC.
107 findExecutable :: String -> IO (Maybe FilePath)
108 findExecutable binary =
109 #if defined(mingw32_HOST_OS)
110   withCString binary $ \c_binary ->
111   withCString ('.':exeExtension) $ \c_ext ->
112   allocaBytes long_path_size $ \pOutPath ->
113   alloca $ \ppFilePart -> do
114     res <- c_SearchPath nullPtr c_binary c_ext (fromIntegral long_path_size) pOutPath ppFilePart
115     if res > 0 && res < fromIntegral long_path_size
116       then do fpath <- peekCString pOutPath
117               return (Just fpath)
118       else return Nothing
119
120 foreign import stdcall unsafe "SearchPathA"
121             c_SearchPath :: CString
122                          -> CString
123                          -> CString
124                          -> CInt
125                          -> CString
126                          -> Ptr CString
127                          -> IO CInt
128 #else
129  do
130   path <- getEnv "PATH"
131   search (splitSearchPath path)
132   where
133     fileName = binary <.> exeExtension
134
135     search :: [FilePath] -> IO (Maybe FilePath)
136     search [] = return Nothing
137     search (d:ds) = do
138         let path = d </> fileName
139         b <- doesFileExist path
140         if b then return (Just path)
141              else search ds
142 #endif
143
144 -- ToDo: This should be determined via autoconf (AC_EXEEXT)
145 -- | Extension for executable files
146 -- (typically @\"\"@ on Unix and @\"exe\"@ on Windows or OS\/2)
147 exeExtension :: String
148 #ifdef mingw32_HOST_OS
149 exeExtension = "exe"
150 #else
151 exeExtension = ""
152 #endif
153
154 -- | @'createDirectoryIfMissing' parents dir@ creates a new directory 
155 -- @dir@ if it doesn\'t exist. If the first argument is 'True'
156 -- the function will also create all parent directories if they are missing.
157 createDirectoryIfMissing :: Bool     -- ^ Create its parents too?
158                          -> FilePath -- ^ The path to the directory you want to make
159                          -> IO ()
160 createDirectoryIfMissing parents file = do
161   b <- doesDirectoryExist file
162   case (b,parents, file) of
163     (_,     _, "") -> return ()
164     (True,  _,  _) -> return ()
165     (_,  True,  _) -> mapM_ (createDirectoryIfMissing False) $ mkParents file
166     (_, False,  _) -> createDirectory file
167  where mkParents = scanl1 (</>) . splitDirectories . normalise