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