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