[project @ 2004-11-13 14:37:18 by panne]
authorpanne <unknown>
Sat, 13 Nov 2004 14:37:18 +0000 (14:37 +0000)
committerpanne <unknown>
Sat, 13 Nov 2004 14:37:18 +0000 (14:37 +0000)
Get rid of those ugly WinDoze CR/LF

System/FilePath.hs

index 801b529..317c7f4 100644 (file)
@@ -1,80 +1,80 @@
------------------------------------------------------------------------------\r
--- |\r
--- Module      :  System.FilePath\r
--- Copyright   :  (c) The University of Glasgow 2004\r
--- License     :  BSD-style (see the file libraries/base/LICENSE)\r
--- \r
--- Maintainer  :  libraries@haskell.org\r
--- Stability   :  stable\r
--- Portability :  portable\r
---\r
--- System-independent pathname manipulations.\r
---\r
------------------------------------------------------------------------------\r
-\r
-module System.FilePath\r
-         ( -- * File path\r
-           FilePath\r
-         , splitFileName\r
-         , splitFileExt\r
-         , splitFilePath\r
-         , joinFileName\r
-         , joinFileExt\r
-         , joinPaths         \r
-         , changeFileExt\r
-         , isRootedPath\r
-         , isAbsolutePath\r
-\r
-         , pathParents\r
-         , commonParent\r
-\r
-         -- * Search path\r
-         , parseSearchPath\r
-         , mkSearchPath\r
-\r
-         -- * Separators\r
-         , isPathSeparator\r
-         , pathSeparator\r
-         , searchPathSeparator\r
-         ) where\r
-\r
+-----------------------------------------------------------------------------
+-- |
+-- Module      :  System.FilePath
+-- Copyright   :  (c) The University of Glasgow 2004
+-- License     :  BSD-style (see the file libraries/base/LICENSE)
+-- 
+-- Maintainer  :  libraries@haskell.org
+-- Stability   :  stable
+-- Portability :  portable
+--
+-- System-independent pathname manipulations.
+--
+-----------------------------------------------------------------------------
+
+module System.FilePath
+         ( -- * File path
+           FilePath
+         , splitFileName
+         , splitFileExt
+         , splitFilePath
+         , joinFileName
+         , joinFileExt
+         , joinPaths         
+         , changeFileExt
+         , isRootedPath
+         , isAbsolutePath
+
+         , pathParents
+         , commonParent
+
+         -- * Search path
+         , parseSearchPath
+         , mkSearchPath
+
+         -- * Separators
+         , isPathSeparator
+         , pathSeparator
+         , searchPathSeparator
+         ) where
+
 import Data.List(intersperse)
 
 --------------------------------------------------------------
 -- * FilePath
 --------------------------------------------------------------
 
--- | Split the path into directory and file name\r
---\r
--- Examples:\r
---\r
--- \[Posix\]\r
---\r
--- > splitFileName "/"            == ("/",    "")\r
--- > splitFileName "/foo/bar.ext" == ("/foo", "bar.ext")\r
--- > splitFileName "bar.ext"      == (".",    "bar.ext")\r
--- > splitFileName "/foo/."       == ("/foo", ".")\r
--- > splitFileName "/foo/.."      == ("/foo", "..")\r
---\r
--- \[Windows\]\r
---\r
--- > splitFileName "\\"               == ("\\",      "")\r
--- > splitFileName "c:\\foo\\bar.ext" == ("c:\\foo", "bar.ext")\r
--- > splitFileName "bar.ext"          == (".",       "bar.ext")\r
--- > splitFileName "c:\\foo\\."       == ("c:\\foo", ".")\r
--- > splitFileName "c:\\foo\\.."      == ("c:\\foo", "..")\r
---\r
--- The first case in the above examples returns an empty file name.\r
--- This is a special case because the \"\/\" (\"\\\\\" on Windows) \r
--- path doesn\'t refer to an object (file or directory) which resides \r
--- within a directory.\r
+-- | Split the path into directory and file name
+--
+-- Examples:
+--
+-- \[Posix\]
+--
+-- > splitFileName "/"            == ("/",    "")
+-- > splitFileName "/foo/bar.ext" == ("/foo", "bar.ext")
+-- > splitFileName "bar.ext"      == (".",    "bar.ext")
+-- > splitFileName "/foo/."       == ("/foo", ".")
+-- > splitFileName "/foo/.."      == ("/foo", "..")
+--
+-- \[Windows\]
+--
+-- > splitFileName "\\"               == ("\\",      "")
+-- > splitFileName "c:\\foo\\bar.ext" == ("c:\\foo", "bar.ext")
+-- > splitFileName "bar.ext"          == (".",       "bar.ext")
+-- > splitFileName "c:\\foo\\."       == ("c:\\foo", ".")
+-- > splitFileName "c:\\foo\\.."      == ("c:\\foo", "..")
+--
+-- The first case in the above examples returns an empty file name.
+-- This is a special case because the \"\/\" (\"\\\\\" on Windows) 
+-- path doesn\'t refer to an object (file or directory) which resides 
+-- within a directory.
 splitFileName :: FilePath -> (String, String)
 splitFileName p = (reverse (path2++drive), reverse fname)
   where
-#ifdef mingw32_TARGET_OS\r
-    (path,drive) = break (== ':') (reverse p)\r
-#else\r
-    (path,drive) = (reverse p,"")\r
+#ifdef mingw32_TARGET_OS
+    (path,drive) = break (== ':') (reverse p)
+#else
+    (path,drive) = (reverse p,"")
 #endif
     (fname,path1) = break isPathSeparator path
     path2 = case path1 of
@@ -84,14 +84,14 @@ splitFileName p = (reverse (path2++drive), reverse fname)
       (c:path) | isPathSeparator c -> path
       _                            -> path1
 
--- | Split the path into file name and extension. If the file doesn\'t have extension,\r
--- the function will return empty string. The extension doesn\'t include a leading period.\r
---\r
--- Examples:\r
---\r
--- > splitFileExt "foo.ext" == ("foo", "ext")\r
--- > splitFileExt "foo"     == ("foo", "")\r
--- > splitFileExt "."       == (".",   "")\r
+-- | Split the path into file name and extension. If the file doesn\'t have extension,
+-- the function will return empty string. The extension doesn\'t include a leading period.
+--
+-- Examples:
+--
+-- > splitFileExt "foo.ext" == ("foo", "ext")
+-- > splitFileExt "foo"     == ("foo", "")
+-- > splitFileExt "."       == (".",   "")
 -- > splitFileExt ".."      == ("..",  "")
 splitFileExt :: FilePath -> (String, String)
 splitFileExt p =
@@ -103,35 +103,35 @@ splitFileExt p =
     (suf,pre) | fname == "." || fname == ".." = (fname,"")
               | otherwise                     = break (== '.') fname
 
--- | Split the path into directory, file name and extension. \r
--- The function is an optimized version of the following equation:\r
---\r
--- > splitFilePath path = (dir,name,ext)\r
--- >   where\r
--- >     (dir,basename) = splitFileName path\r
--- >     (name,ext)     = splitFileExt  basename\r
-splitFilePath :: FilePath -> (String, String, String)\r
-splitFilePath p =\r
-  case pre of\r
-    []      -> (reverse real_dir, reverse suf, [])\r
-    (_:pre) -> (reverse real_dir, reverse pre, reverse suf)\r
-  where\r
-#ifdef mingw32_TARGET_OS\r
-    (path,drive) = break (== ':') (reverse p)\r
-#else\r
-    (path,drive) = (reverse p,"")\r
-#endif\r
-    (file,dir)   = break isPathSeparator path\r
-    (suf,pre)    = case file of\r
-                     ".." -> ("..", "")\r
-                     _    -> break (== '.') file\r
-    \r
-    real_dir = case dir of\r
-      []      -> '.':drive\r
-      [_]     -> pathSeparator:drive\r
-      (_:dir) -> dir++drive\r
+-- | Split the path into directory, file name and extension. 
+-- The function is an optimized version of the following equation:
+--
+-- > splitFilePath path = (dir,name,ext)
+-- >   where
+-- >     (dir,basename) = splitFileName path
+-- >     (name,ext)     = splitFileExt  basename
+splitFilePath :: FilePath -> (String, String, String)
+splitFilePath p =
+  case pre of
+    []      -> (reverse real_dir, reverse suf, [])
+    (_:pre) -> (reverse real_dir, reverse pre, reverse suf)
+  where
+#ifdef mingw32_TARGET_OS
+    (path,drive) = break (== ':') (reverse p)
+#else
+    (path,drive) = (reverse p,"")
+#endif
+    (file,dir)   = break isPathSeparator path
+    (suf,pre)    = case file of
+                     ".." -> ("..", "")
+                     _    -> break (== '.') file
+    
+    real_dir = case dir of
+      []      -> '.':drive
+      [_]     -> pathSeparator:drive
+      (_:dir) -> dir++drive
 
--- | The 'joinFileName' function is the opposite of 'splitFileName'. \r
+-- | The 'joinFileName' function is the opposite of 'splitFileName'. 
 -- It joins directory and file names to form complete file path.
 --
 -- The general rule is:
@@ -145,14 +145,14 @@ splitFilePath p =
 -- An example exception is that on Windows some slashes might be converted
 -- to backslashes.
 joinFileName :: String -> String -> FilePath
-joinFileName ""  fname = fname\r
+joinFileName ""  fname = fname
 joinFileName "." fname = fname
 joinFileName dir ""    = dir
 joinFileName dir fname
   | isPathSeparator (last dir) = dir++fname
   | otherwise                  = dir++pathSeparator:fname
 
--- | The 'joinFileExt' function is the opposite of 'splitFileExt'.\r
+-- | The 'joinFileExt' function is the opposite of 'splitFileExt'.
 -- It joins file name and extension to form complete file path.
 --
 -- The general rule is:
@@ -163,47 +163,47 @@ joinFileName dir fname
 joinFileExt :: String -> String -> FilePath
 joinFileExt path ""  = path
 joinFileExt path ext = path ++ '.':ext
-\r
--- | Given a directory path \"dir\" and a file\/directory path \"rel\",\r
--- returns a merged path \"full\" with the property that\r
--- (cd dir; do_something_with rel) is equivalent to\r
--- (do_something_with full). If the \"rel\" path is an absolute path\r
--- then the returned path is equal to \"rel\"\r
-joinPaths :: FilePath -> FilePath -> FilePath\r
-joinPaths path1 path2\r
-  | isRootedPath path2 = path2\r
-  | otherwise          = \r
-#ifdef mingw32_TARGET_OS\r
-        case path2 of\r
-          d:':':path2' | take 2 path1 == [d,':'] -> path1 `joinFileName` path2'\r
-                       | otherwise               -> path2\r
-          _                                      -> path1 `joinFileName` path2\r
-#else\r
-        path1 `joinFileName` path2\r
-#endif\r
-  \r
--- | Changes the extension of a file path.\r
-changeFileExt :: FilePath           -- ^ The path information to modify.\r
-          -> String                 -- ^ The new extension (without a leading period).\r
-                                    -- Specify an empty string to remove an existing \r
-                                    -- extension from path.\r
-          -> FilePath               -- ^ A string containing the modified path information.\r
+
+-- | Given a directory path \"dir\" and a file\/directory path \"rel\",
+-- returns a merged path \"full\" with the property that
+-- (cd dir; do_something_with rel) is equivalent to
+-- (do_something_with full). If the \"rel\" path is an absolute path
+-- then the returned path is equal to \"rel\"
+joinPaths :: FilePath -> FilePath -> FilePath
+joinPaths path1 path2
+  | isRootedPath path2 = path2
+  | otherwise          = 
+#ifdef mingw32_TARGET_OS
+        case path2 of
+          d:':':path2' | take 2 path1 == [d,':'] -> path1 `joinFileName` path2'
+                       | otherwise               -> path2
+          _                                      -> path1 `joinFileName` path2
+#else
+        path1 `joinFileName` path2
+#endif
+  
+-- | Changes the extension of a file path.
+changeFileExt :: FilePath           -- ^ The path information to modify.
+          -> String                 -- ^ The new extension (without a leading period).
+                                    -- Specify an empty string to remove an existing 
+                                    -- extension from path.
+          -> FilePath               -- ^ A string containing the modified path information.
 changeFileExt path ext = joinFileExt name ext
   where
     (name,_) = splitFileExt path
-\r
+
 -- | On Unix and Macintosh the 'isRootedPath' function is a synonym to 'isAbsolutePath'.
--- The difference is important only on Windows. The rooted path must start from the root\r
--- directory but may not include the drive letter while the absolute path always includes\r
--- the drive letter and the full file path.\r
+-- The difference is important only on Windows. The rooted path must start from the root
+-- directory but may not include the drive letter while the absolute path always includes
+-- the drive letter and the full file path.
 isRootedPath :: FilePath -> Bool
 isRootedPath (c:_) | isPathSeparator c = True
 #ifdef mingw32_TARGET_OS
 isRootedPath (_:':':c:_) | isPathSeparator c = True  -- path with drive letter
 #endif
-isRootedPath _ = False\r
+isRootedPath _ = False
 
--- | Returns True if this path\'s meaning is independent of any OS\r
+-- | Returns True if this path\'s meaning is independent of any OS
 -- "working directory", False if it isn\'t.
 isAbsolutePath :: FilePath -> Bool
 #ifdef mingw32_TARGET_OS
@@ -211,68 +211,68 @@ isAbsolutePath (_:':':c:_) | isPathSeparator c = True
 #else
 isAbsolutePath (c:_)       | isPathSeparator c = True
 #endif
-isAbsolutePath _ = False\r
-\r
--- | Gets this path and all its parents.\r
--- The function is useful in case if you want to create \r
--- some file but you aren\'t sure whether all directories \r
--- in the path exists or if you want to search upward for some file.\r
--- \r
--- Some examples:\r
---\r
--- \[Posix\]\r
---\r
--- >  pathParents "/"          == ["/"]\r
--- >  pathParents "/dir1"      == ["/", "/dir1"]\r
--- >  pathParents "/dir1/dir2" == ["/", "/dir1", "/dir1/dir2"]\r
--- >  pathParents "dir1"       == [".", "dir1"]\r
--- >  pathParents "dir1/dir2"  == [".", "dir1", "dir1/dir2"]\r
---\r
--- In the above examples \"\/\" isn\'t included in the list \r
--- because you can\'t create root directory.\r
---\r
--- \[Windows\]\r
---\r
--- >  pathParents "c:"             == ["c:."]\r
--- >  pathParents "c:\\"           == ["c:\\"]\r
--- >  pathParents "c:\\dir1"       == ["c:\\", "c:\\dir1"]\r
--- >  pathParents "c:\\dir1\\dir2" == ["c:\\", "c:\\dir1", "c:\\dir1\\dir2"]\r
--- >  pathParents "c:dir1"         == ["c:.","c:dir1"]\r
--- >  pathParents "dir1\\dir2"     == [".", "dir1", "dir1\\dir2"]\r
---\r
--- Note that if the file is relative then the the current directory (\".\") \r
--- will be explicitly listed.\r
-pathParents :: FilePath -> [FilePath]\r
-pathParents p =\r
-    root'' : map ((++) root') (dropEmptyPath $ inits path')\r
-    where\r
-#ifdef mingw32_TARGET_OS\r
-       (root,path) = case break (== ':') p of\r
-          (path,    "") -> ("",path)\r
-          (root,_:path) -> (root++":",path)\r
-#else\r
-       (root,path) = ("",p)\r
-#endif\r
-       (root',root'',path') = case path of\r
-         (c:path) | isPathSeparator c -> (root++[pathSeparator],root++[pathSeparator],path)\r
-         _                            -> (root                 ,root++"."            ,path)\r
-\r
-       dropEmptyPath ("":paths) = paths\r
-       dropEmptyPath paths      = paths\r
-\r
-       inits :: String -> [String]\r
-       inits [] =  [""]\r
-       inits cs = \r
-         case pre of\r
-           "."  -> inits suf\r
-           ".." -> map (joinFileName pre) (dropEmptyPath $ inits suf)\r
-           _    -> "" : map (joinFileName pre) (inits suf)\r
-         where\r
-           (pre,suf) = case break isPathSeparator cs of\r
-              (pre,"")    -> (pre, "")\r
-              (pre,_:suf) -> (pre,suf)\r
-\r
--- | Given a list of file paths, returns the longest common parent.\r
+isAbsolutePath _ = False
+
+-- | Gets this path and all its parents.
+-- The function is useful in case if you want to create 
+-- some file but you aren\'t sure whether all directories 
+-- in the path exists or if you want to search upward for some file.
+-- 
+-- Some examples:
+--
+-- \[Posix\]
+--
+-- >  pathParents "/"          == ["/"]
+-- >  pathParents "/dir1"      == ["/", "/dir1"]
+-- >  pathParents "/dir1/dir2" == ["/", "/dir1", "/dir1/dir2"]
+-- >  pathParents "dir1"       == [".", "dir1"]
+-- >  pathParents "dir1/dir2"  == [".", "dir1", "dir1/dir2"]
+--
+-- In the above examples \"\/\" isn\'t included in the list 
+-- because you can\'t create root directory.
+--
+-- \[Windows\]
+--
+-- >  pathParents "c:"             == ["c:."]
+-- >  pathParents "c:\\"           == ["c:\\"]
+-- >  pathParents "c:\\dir1"       == ["c:\\", "c:\\dir1"]
+-- >  pathParents "c:\\dir1\\dir2" == ["c:\\", "c:\\dir1", "c:\\dir1\\dir2"]
+-- >  pathParents "c:dir1"         == ["c:.","c:dir1"]
+-- >  pathParents "dir1\\dir2"     == [".", "dir1", "dir1\\dir2"]
+--
+-- Note that if the file is relative then the the current directory (\".\") 
+-- will be explicitly listed.
+pathParents :: FilePath -> [FilePath]
+pathParents p =
+    root'' : map ((++) root') (dropEmptyPath $ inits path')
+    where
+#ifdef mingw32_TARGET_OS
+       (root,path) = case break (== ':') p of
+          (path,    "") -> ("",path)
+          (root,_:path) -> (root++":",path)
+#else
+       (root,path) = ("",p)
+#endif
+       (root',root'',path') = case path of
+         (c:path) | isPathSeparator c -> (root++[pathSeparator],root++[pathSeparator],path)
+         _                            -> (root                 ,root++"."            ,path)
+
+       dropEmptyPath ("":paths) = paths
+       dropEmptyPath paths      = paths
+
+       inits :: String -> [String]
+       inits [] =  [""]
+       inits cs = 
+         case pre of
+           "."  -> inits suf
+           ".." -> map (joinFileName pre) (dropEmptyPath $ inits suf)
+           _    -> "" : map (joinFileName pre) (inits suf)
+         where
+           (pre,suf) = case break isPathSeparator cs of
+              (pre,"")    -> (pre, "")
+              (pre,_:suf) -> (pre,suf)
+
+-- | Given a list of file paths, returns the longest common parent.
 commonParent :: [FilePath] -> Maybe FilePath
 commonParent []           = Nothing
 commonParent paths@(p:ps) = 
@@ -293,29 +293,29 @@ commonParent paths@(p:ps) =
     getDrive _         ds = ds
 
     common i acc []     ps = checkSep   i acc         ps
-    common i acc (c:cs) ps\r
-      | isPathSeparator c  = removeSep  i acc   cs [] ps\r
-      | otherwise          = removeChar i acc c cs [] ps\r
-\r
-    checkSep i acc []      = Just (reverse acc)\r
-    checkSep i acc ([]:ps) = Just (reverse acc)\r
-    checkSep i acc ((c1:p):ps)\r
-      | isPathSeparator c1 = checkSep i acc ps\r
-    checkSep i acc ps      = i\r
-\r
-    removeSep i acc cs pacc []          = \r
-      common (Just (reverse (pathSeparator:acc))) (pathSeparator:acc) cs pacc\r
-    removeSep i acc cs pacc ([]    :ps) = Just (reverse acc)\r
-    removeSep i acc cs pacc ((c1:p):ps)\r
-      | isPathSeparator c1              = removeSep i acc cs (p:pacc) ps\r
-    removeSep i acc cs pacc ps          = i\r
-\r
-    removeChar i acc c cs pacc []          = common i (c:acc) cs pacc\r
-    removeChar i acc c cs pacc ([]    :ps) = i\r
-    removeChar i acc c cs pacc ((c1:p):ps)\r
-      | c == c1                            = removeChar i acc c cs (p:pacc) ps\r
-    removeChar i acc c cs pacc ps          = i\r
-\r
+    common i acc (c:cs) ps
+      | isPathSeparator c  = removeSep  i acc   cs [] ps
+      | otherwise          = removeChar i acc c cs [] ps
+
+    checkSep i acc []      = Just (reverse acc)
+    checkSep i acc ([]:ps) = Just (reverse acc)
+    checkSep i acc ((c1:p):ps)
+      | isPathSeparator c1 = checkSep i acc ps
+    checkSep i acc ps      = i
+
+    removeSep i acc cs pacc []          = 
+      common (Just (reverse (pathSeparator:acc))) (pathSeparator:acc) cs pacc
+    removeSep i acc cs pacc ([]    :ps) = Just (reverse acc)
+    removeSep i acc cs pacc ((c1:p):ps)
+      | isPathSeparator c1              = removeSep i acc cs (p:pacc) ps
+    removeSep i acc cs pacc ps          = i
+
+    removeChar i acc c cs pacc []          = common i (c:acc) cs pacc
+    removeChar i acc c cs pacc ([]    :ps) = i
+    removeChar i acc c cs pacc ((c1:p):ps)
+      | c == c1                            = removeChar i acc c cs (p:pacc) ps
+    removeChar i acc c cs pacc ps          = i
+
 --------------------------------------------------------------
 -- * Search path
 --------------------------------------------------------------
@@ -324,27 +324,27 @@ commonParent paths@(p:ps) =
 -- using the 'searchPathSeparator'.
 parseSearchPath :: String -> [FilePath]
 parseSearchPath path = split searchPathSeparator path
-  where\r
-    split :: Char -> String -> [String]\r
-    split c s =\r
-      case rest of\r
-        []      -> [chunk] \r
-        _:rest' -> chunk : split c rest'\r
-      where\r
-        (chunk, rest) = break (==c) s\r
-\r
--- | The function concatenates the given paths to form a\r
--- single string where the paths are separated with 'searchPathSeparator'.\r
+  where
+    split :: Char -> String -> [String]
+    split c s =
+      case rest of
+        []      -> [chunk] 
+        _:rest' -> chunk : split c rest'
+      where
+        (chunk, rest) = break (==c) s
+
+-- | The function concatenates the given paths to form a
+-- single string where the paths are separated with 'searchPathSeparator'.
 mkSearchPath :: [FilePath] -> String
 mkSearchPath paths = concat (intersperse [searchPathSeparator] paths)
-\r
+
 
 --------------------------------------------------------------
 -- * Separators
 --------------------------------------------------------------
 
--- | Checks whether the character is a valid path separator for the host platform.\r
--- The valid character is a 'pathSeparator' but since the Windows operating system \r
+-- | Checks whether the character is a valid path separator for the host platform.
+-- The valid character is a 'pathSeparator' but since the Windows operating system 
 -- also accepts a backslash (\"\\\") the function also checks for \"\/\" on this platform.
 isPathSeparator :: Char -> Bool
 isPathSeparator ch =
@@ -354,9 +354,9 @@ isPathSeparator ch =
   ch == '/'
 #endif
 
--- | Provides a platform-specific character used to separate directory levels in a \r
--- path string that reflects a hierarchical file system organization.\r
--- The separator is a slash (\"\/\") on Unix and Macintosh, and a backslash (\"\\\") on the \r
+-- | Provides a platform-specific character used to separate directory levels in a 
+-- path string that reflects a hierarchical file system organization.
+-- The separator is a slash (\"\/\") on Unix and Macintosh, and a backslash (\"\\\") on the 
 -- Windows operating system.
 pathSeparator :: Char
 #ifdef mingw32_TARGET_OS
@@ -365,9 +365,9 @@ pathSeparator = '\\'
 pathSeparator = '/'
 #endif
 
--- | A platform-specific character used to separate search path strings in \r
--- environment variables. The separator is a colon (\":\") on Unix and Macintosh, \r
--- and a semicolon (\";\") on the Windows operating system.\r
+-- | A platform-specific character used to separate search path strings in 
+-- environment variables. The separator is a colon (\":\") on Unix and Macintosh, 
+-- and a semicolon (\";\") on the Windows operating system.
 searchPathSeparator :: Char
 #ifdef mingw32_TARGET_OS
 searchPathSeparator = ';'