[project @ 2004-12-18 00:45:27 by ross]
[haskell-directory.git] / System / FilePath.hs
1 -----------------------------------------------------------------------------
2 -- |
3 -- Module      :  System.FilePath
4 -- Copyright   :  (c) The University of Glasgow 2004
5 -- License     :  BSD-style (see the file libraries/base/LICENSE)
6 -- 
7 -- Maintainer  :  libraries@haskell.org
8 -- Stability   :  stable
9 -- Portability :  portable
10 --
11 -- System-independent pathname manipulations.
12 --
13 -----------------------------------------------------------------------------
14
15 module System.FilePath
16          ( -- * File path
17            FilePath
18          , splitFileName
19          , splitFileExt
20          , splitFilePath
21          , joinFileName
22          , joinFileExt
23          , joinPaths         
24          , changeFileExt
25          , isRootedPath
26          , isAbsolutePath
27
28          , pathParents
29          , commonParent
30
31          -- * Search path
32          , parseSearchPath
33          , mkSearchPath
34
35          -- * Separators
36          , isPathSeparator
37          , pathSeparator
38          , searchPathSeparator
39
40          -- * Filename extensions
41          , exeExtension
42          , objExtension
43          , dllExtension
44          ) where
45
46 import Prelude -- necessary to get dependencies right
47
48 import Data.List(intersperse)
49
50 --------------------------------------------------------------
51 -- * FilePath
52 --------------------------------------------------------------
53
54 -- | Split the path into directory and file name
55 --
56 -- Examples:
57 --
58 -- \[Posix\]
59 --
60 -- > splitFileName "/"            == ("/",    "")
61 -- > splitFileName "/foo/bar.ext" == ("/foo", "bar.ext")
62 -- > splitFileName "bar.ext"      == (".",    "bar.ext")
63 -- > splitFileName "/foo/."       == ("/foo", ".")
64 -- > splitFileName "/foo/.."      == ("/foo", "..")
65 --
66 -- \[Windows\]
67 --
68 -- > splitFileName "\\"               == ("\\",      "")
69 -- > splitFileName "c:\\foo\\bar.ext" == ("c:\\foo", "bar.ext")
70 -- > splitFileName "bar.ext"          == (".",       "bar.ext")
71 -- > splitFileName "c:\\foo\\."       == ("c:\\foo", ".")
72 -- > splitFileName "c:\\foo\\.."      == ("c:\\foo", "..")
73 --
74 -- The first case in the above examples returns an empty file name.
75 -- This is a special case because the \"\/\" (\"\\\\\" on Windows) 
76 -- path doesn\'t refer to an object (file or directory) which resides 
77 -- within a directory.
78 splitFileName :: FilePath -> (String, String)
79 splitFileName p = (reverse (path2++drive), reverse fname)
80   where
81 #ifdef mingw32_TARGET_OS
82     (path,drive) = break (== ':') (reverse p)
83 #else
84     (path,drive) = (reverse p,"")
85 #endif
86     (fname,path1) = break isPathSeparator path
87     path2 = case path1 of
88       []                           -> "."
89       [_]                          -> path1   -- don't remove the trailing slash if 
90                                               -- there is only one character
91       (c:path) | isPathSeparator c -> path
92       _                            -> path1
93
94 -- | Split the path into file name and extension. If the file doesn\'t have extension,
95 -- the function will return empty string. The extension doesn\'t include a leading period.
96 --
97 -- Examples:
98 --
99 -- > splitFileExt "foo.ext" == ("foo", "ext")
100 -- > splitFileExt "foo"     == ("foo", "")
101 -- > splitFileExt "."       == (".",   "")
102 -- > splitFileExt ".."      == ("..",  "")
103 splitFileExt :: FilePath -> (String, String)
104 splitFileExt p =
105   case pre of
106         []      -> (p, [])
107         (_:pre) -> (reverse (pre++path), reverse suf)
108   where
109     (fname,path) = break isPathSeparator (reverse p)
110     (suf,pre) | fname == "." || fname == ".." = (fname,"")
111               | otherwise                     = break (== '.') fname
112
113 -- | Split the path into directory, file name and extension. 
114 -- The function is an optimized version of the following equation:
115 --
116 -- > splitFilePath path = (dir,name,ext)
117 -- >   where
118 -- >     (dir,basename) = splitFileName path
119 -- >     (name,ext)     = splitFileExt  basename
120 splitFilePath :: FilePath -> (String, String, String)
121 splitFilePath p =
122   case pre of
123     []      -> (reverse real_dir, reverse suf, [])
124     (_:pre) -> (reverse real_dir, reverse pre, reverse suf)
125   where
126 #ifdef mingw32_TARGET_OS
127     (path,drive) = break (== ':') (reverse p)
128 #else
129     (path,drive) = (reverse p,"")
130 #endif
131     (file,dir)   = break isPathSeparator path
132     (suf,pre)    = case file of
133                      ".." -> ("..", "")
134                      _    -> break (== '.') file
135     
136     real_dir = case dir of
137       []      -> '.':drive
138       [_]     -> pathSeparator:drive
139       (_:dir) -> dir++drive
140
141 -- | The 'joinFileName' function is the opposite of 'splitFileName'. 
142 -- It joins directory and file names to form complete file path.
143 --
144 -- The general rule is:
145 --
146 -- > dir `joinFileName` basename == path
147 -- >   where
148 -- >     (dir,basename) = splitFileName path
149 --
150 -- There might be an exeptions to the rule but in any case the
151 -- reconstructed path will refer to the same object (file or directory).
152 -- An example exception is that on Windows some slashes might be converted
153 -- to backslashes.
154 joinFileName :: String -> String -> FilePath
155 joinFileName ""  fname = fname
156 joinFileName "." fname = fname
157 joinFileName dir ""    = dir
158 joinFileName dir fname
159   | isPathSeparator (last dir) = dir++fname
160   | otherwise                  = dir++pathSeparator:fname
161
162 -- | The 'joinFileExt' function is the opposite of 'splitFileExt'.
163 -- It joins file name and extension to form complete file path.
164 --
165 -- The general rule is:
166 --
167 -- > filename `joinFileExt` ext == path
168 -- >   where
169 -- >     (filename,ext) = splitFileExt path
170 joinFileExt :: String -> String -> FilePath
171 joinFileExt path ""  = path
172 joinFileExt path ext = path ++ '.':ext
173
174 -- | Given a directory path \"dir\" and a file\/directory path \"rel\",
175 -- returns a merged path \"full\" with the property that
176 -- (cd dir; do_something_with rel) is equivalent to
177 -- (do_something_with full). If the \"rel\" path is an absolute path
178 -- then the returned path is equal to \"rel\"
179 joinPaths :: FilePath -> FilePath -> FilePath
180 joinPaths path1 path2
181   | isRootedPath path2 = path2
182   | otherwise          = 
183 #ifdef mingw32_TARGET_OS
184         case path2 of
185           d:':':path2' | take 2 path1 == [d,':'] -> path1 `joinFileName` path2'
186                        | otherwise               -> path2
187           _                                      -> path1 `joinFileName` path2
188 #else
189         path1 `joinFileName` path2
190 #endif
191   
192 -- | Changes the extension of a file path.
193 changeFileExt :: FilePath           -- ^ The path information to modify.
194           -> String                 -- ^ The new extension (without a leading period).
195                                     -- Specify an empty string to remove an existing 
196                                     -- extension from path.
197           -> FilePath               -- ^ A string containing the modified path information.
198 changeFileExt path ext = joinFileExt name ext
199   where
200     (name,_) = splitFileExt path
201
202 -- | On Unix and Macintosh the 'isRootedPath' function is a synonym to 'isAbsolutePath'.
203 -- The difference is important only on Windows. The rooted path must start from the root
204 -- directory but may not include the drive letter while the absolute path always includes
205 -- the drive letter and the full file path.
206 isRootedPath :: FilePath -> Bool
207 isRootedPath (c:_) | isPathSeparator c = True
208 #ifdef mingw32_TARGET_OS
209 isRootedPath (_:':':c:_) | isPathSeparator c = True  -- path with drive letter
210 #endif
211 isRootedPath _ = False
212
213 -- | Returns True if this path\'s meaning is independent of any OS
214 -- "working directory", False if it isn\'t.
215 isAbsolutePath :: FilePath -> Bool
216 #ifdef mingw32_TARGET_OS
217 isAbsolutePath (_:':':c:_) | isPathSeparator c = True
218 #else
219 isAbsolutePath (c:_)       | isPathSeparator c = True
220 #endif
221 isAbsolutePath _ = False
222
223 -- | Gets this path and all its parents.
224 -- The function is useful in case if you want to create 
225 -- some file but you aren\'t sure whether all directories 
226 -- in the path exists or if you want to search upward for some file.
227 -- 
228 -- Some examples:
229 --
230 -- \[Posix\]
231 --
232 -- >  pathParents "/"          == ["/"]
233 -- >  pathParents "/dir1"      == ["/", "/dir1"]
234 -- >  pathParents "/dir1/dir2" == ["/", "/dir1", "/dir1/dir2"]
235 -- >  pathParents "dir1"       == [".", "dir1"]
236 -- >  pathParents "dir1/dir2"  == [".", "dir1", "dir1/dir2"]
237 --
238 -- In the above examples \"\/\" isn\'t included in the list 
239 -- because you can\'t create root directory.
240 --
241 -- \[Windows\]
242 --
243 -- >  pathParents "c:"             == ["c:."]
244 -- >  pathParents "c:\\"           == ["c:\\"]
245 -- >  pathParents "c:\\dir1"       == ["c:\\", "c:\\dir1"]
246 -- >  pathParents "c:\\dir1\\dir2" == ["c:\\", "c:\\dir1", "c:\\dir1\\dir2"]
247 -- >  pathParents "c:dir1"         == ["c:.","c:dir1"]
248 -- >  pathParents "dir1\\dir2"     == [".", "dir1", "dir1\\dir2"]
249 --
250 -- Note that if the file is relative then the the current directory (\".\") 
251 -- will be explicitly listed.
252 pathParents :: FilePath -> [FilePath]
253 pathParents p =
254     root'' : map ((++) root') (dropEmptyPath $ inits path')
255     where
256 #ifdef mingw32_TARGET_OS
257        (root,path) = case break (== ':') p of
258           (path,    "") -> ("",path)
259           (root,_:path) -> (root++":",path)
260 #else
261        (root,path) = ("",p)
262 #endif
263        (root',root'',path') = case path of
264          (c:path) | isPathSeparator c -> (root++[pathSeparator],root++[pathSeparator],path)
265          _                            -> (root                 ,root++"."            ,path)
266
267        dropEmptyPath ("":paths) = paths
268        dropEmptyPath paths      = paths
269
270        inits :: String -> [String]
271        inits [] =  [""]
272        inits cs = 
273          case pre of
274            "."  -> inits suf
275            ".." -> map (joinFileName pre) (dropEmptyPath $ inits suf)
276            _    -> "" : map (joinFileName pre) (inits suf)
277          where
278            (pre,suf) = case break isPathSeparator cs of
279               (pre,"")    -> (pre, "")
280               (pre,_:suf) -> (pre,suf)
281
282 -- | Given a list of file paths, returns the longest common parent.
283 commonParent :: [FilePath] -> Maybe FilePath
284 commonParent []           = Nothing
285 commonParent paths@(p:ps) = 
286   case common Nothing "" p ps of
287 #ifdef mingw32_TARGET_OS
288     Nothing | all (not . isAbsolutePath) paths -> 
289       case foldr getDrive [] paths of
290         []  -> Just "."
291         [d] -> Just [d,':']
292         _   -> Nothing
293 #else
294     Nothing | all (not . isAbsolutePath) paths -> Just "."
295 #endif
296     mb_path   -> mb_path
297   where
298 #ifdef mingw32_TARGET_OS
299     getDrive (d:':':_) ds 
300       | not (d `elem` ds) = d:ds
301     getDrive _         ds = ds
302 #endif
303
304     common i acc []     ps = checkSep   i acc         ps
305     common i acc (c:cs) ps
306       | isPathSeparator c  = removeSep  i acc   cs [] ps
307       | otherwise          = removeChar i acc c cs [] ps
308
309     checkSep i acc []      = Just (reverse acc)
310     checkSep i acc ([]:ps) = Just (reverse acc)
311     checkSep i acc ((c1:p):ps)
312       | isPathSeparator c1 = checkSep i acc ps
313     checkSep i acc ps      = i
314
315     removeSep i acc cs pacc []          = 
316       common (Just (reverse (pathSeparator:acc))) (pathSeparator:acc) cs pacc
317     removeSep i acc cs pacc ([]    :ps) = Just (reverse acc)
318     removeSep i acc cs pacc ((c1:p):ps)
319       | isPathSeparator c1              = removeSep i acc cs (p:pacc) ps
320     removeSep i acc cs pacc ps          = i
321
322     removeChar i acc c cs pacc []          = common i (c:acc) cs pacc
323     removeChar i acc c cs pacc ([]    :ps) = i
324     removeChar i acc c cs pacc ((c1:p):ps)
325       | c == c1                            = removeChar i acc c cs (p:pacc) ps
326     removeChar i acc c cs pacc ps          = i
327
328 --------------------------------------------------------------
329 -- * Search path
330 --------------------------------------------------------------
331
332 -- | The function splits the given string to substrings
333 -- using the 'searchPathSeparator'.
334 parseSearchPath :: String -> [FilePath]
335 parseSearchPath path = split searchPathSeparator path
336   where
337     split :: Char -> String -> [String]
338     split c s =
339       case rest of
340         []      -> [chunk] 
341         _:rest' -> chunk : split c rest'
342       where
343         (chunk, rest) = break (==c) s
344
345 -- | The function concatenates the given paths to form a
346 -- single string where the paths are separated with 'searchPathSeparator'.
347 mkSearchPath :: [FilePath] -> String
348 mkSearchPath paths = concat (intersperse [searchPathSeparator] paths)
349
350
351 --------------------------------------------------------------
352 -- * Separators
353 --------------------------------------------------------------
354
355 -- | Checks whether the character is a valid path separator for the host platform.
356 -- The valid character is a 'pathSeparator' but since the Windows operating system 
357 -- also accepts a backslash (\"\\\") the function also checks for \"\/\" on this platform.
358 isPathSeparator :: Char -> Bool
359 isPathSeparator ch =
360 #ifdef mingw32_TARGET_OS
361   ch == '/' || ch == '\\'
362 #else
363   ch == '/'
364 #endif
365
366 -- | Provides a platform-specific character used to separate directory levels in a 
367 -- path string that reflects a hierarchical file system organization.
368 -- The separator is a slash (\"\/\") on Unix and Macintosh, and a backslash (\"\\\") on the 
369 -- Windows operating system.
370 pathSeparator :: Char
371 #ifdef mingw32_TARGET_OS
372 pathSeparator = '\\'
373 #else
374 pathSeparator = '/'
375 #endif
376
377 -- | A platform-specific character used to separate search path strings in 
378 -- environment variables. The separator is a colon (\":\") on Unix and Macintosh, 
379 -- and a semicolon (\";\") on the Windows operating system.
380 searchPathSeparator :: Char
381 #ifdef mingw32_TARGET_OS
382 searchPathSeparator = ';'
383 #else
384 searchPathSeparator = ':'
385 #endif
386
387 -- ToDo: This should be determined via autoconf (AC_EXEEXT)
388 -- | Extension for executable files
389 -- (typically @""@ on Unix and @".exe"@ on Windows or OS/2)
390 exeExtension :: String
391
392 -- ToDo: This should be determined via autoconf (AC_OBJEXT)
393 -- | Extension for object files
394 -- (typically @".o"@ on Unix and @".obj"@ on Windows)
395 objExtension :: String
396
397 -- | Extension for dynamically linked (or shared) libraries
398 -- (typically @".so"@ on Unix and @".dll"@ on Windows)
399 dllExtension :: String
400
401 #ifdef mingw32_TARGET_OS
402 exeExtension = ".exe"
403 objExtension = ".obj"
404 dllExtension = ".dll"
405 #else
406 exeExtension = ""
407 objExtension = ".o"
408 dllExtension = ".so"
409 #endif