filepath-1.1.0.2: Library for manipulating FilePath's in a cross platform way.Source codeContentsIndex
System.FilePath.Posix
Portabilityportable
Stabilitystable
Maintainerlibraries@haskell.org
Contents
Separator predicates
Path methods (environment $PATH)
Extension methods
Drive methods
Operations on a FilePath, as a list of directories
Low level FilePath operators
File name manipulators
Description
A library for FilePath manipulations, using Posix style paths on all platforms. Importing System.FilePath is usually better.
Synopsis
FilePath
pathSeparator :: Char
pathSeparators :: [Char]
isPathSeparator :: Char -> Bool
searchPathSeparator :: Char
isSearchPathSeparator :: Char -> Bool
extSeparator :: Char
isExtSeparator :: Char -> Bool
splitSearchPath :: String -> [FilePath]
getSearchPath :: IO [FilePath]
splitExtension :: FilePath -> (String, String)
takeExtension :: FilePath -> String
replaceExtension :: FilePath -> String -> FilePath
dropExtension :: FilePath -> FilePath
addExtension :: FilePath -> String -> FilePath
hasExtension :: FilePath -> Bool
(<.>) :: FilePath -> String -> FilePath
splitExtensions :: FilePath -> (FilePath, String)
dropExtensions :: FilePath -> FilePath
takeExtensions :: FilePath -> String
splitDrive :: FilePath -> (FilePath, FilePath)
joinDrive :: FilePath -> FilePath -> FilePath
takeDrive :: FilePath -> FilePath
hasDrive :: FilePath -> Bool
dropDrive :: FilePath -> FilePath
isDrive :: FilePath -> Bool
splitFileName :: FilePath -> (String, String)
takeFileName :: FilePath -> FilePath
replaceFileName :: FilePath -> String -> FilePath
dropFileName :: FilePath -> FilePath
takeBaseName :: FilePath -> String
replaceBaseName :: FilePath -> String -> FilePath
takeDirectory :: FilePath -> FilePath
replaceDirectory :: FilePath -> String -> FilePath
combine :: FilePath -> FilePath -> FilePath
(</>) :: FilePath -> FilePath -> FilePath
splitPath :: FilePath -> [FilePath]
joinPath :: [FilePath] -> FilePath
splitDirectories :: FilePath -> [FilePath]
hasTrailingPathSeparator :: FilePath -> Bool
addTrailingPathSeparator :: FilePath -> FilePath
dropTrailingPathSeparator :: FilePath -> FilePath
normalise :: FilePath -> FilePath
equalFilePath :: FilePath -> FilePath -> Bool
makeRelative :: FilePath -> FilePath -> FilePath
isRelative :: FilePath -> Bool
isAbsolute :: FilePath -> Bool
isValid :: FilePath -> Bool
makeValid :: FilePath -> FilePath
Separator predicates
FilePath
pathSeparator :: CharSource

The character that separates directories. In the case where more than one character is possible, pathSeparator is the 'ideal' one.

 Windows: pathSeparator == '\\'
 Posix:   pathSeparator ==  '/'
 isPathSeparator pathSeparator
pathSeparators :: [Char]Source

The list of all possible separators.

 Windows: pathSeparators == ['\\', '/']
 Posix:   pathSeparators == ['/']
 pathSeparator `elem` pathSeparators
isPathSeparator :: Char -> BoolSource

Rather than using (== pathSeparator), use this. Test if something is a path separator.

 isPathSeparator a == (a `elem` pathSeparators)
searchPathSeparator :: CharSource

The character that is used to separate the entries in the $PATH environment variable.

 Windows: searchPathSeparator == ';'
 Posix:   searchPathSeparator == ':'
isSearchPathSeparator :: Char -> BoolSource

Is the character a file separator?

 isSearchPathSeparator a == (a == searchPathSeparator)
extSeparator :: CharSource

File extension character

 extSeparator == '.'
isExtSeparator :: Char -> BoolSource

Is the character an extension character?

 isExtSeparator a == (a == extSeparator)
Path methods (environment $PATH)
splitSearchPath :: String -> [FilePath]Source

Take a string, split it on the searchPathSeparator character.

Follows the recommendations in http://www.opengroup.org/onlinepubs/009695399/basedefs/xbd_chap08.html

 Posix:   splitSearchPath "File1:File2:File3"  == ["File1","File2","File3"]
 Posix:   splitSearchPath "File1::File2:File3" == ["File1",".","File2","File3"]
 Windows: splitSearchPath "File1;File2;File3"  == ["File1","File2","File3"]
 Windows: splitSearchPath "File1;;File2;File3" == ["File1","File2","File3"]
getSearchPath :: IO [FilePath]Source
Get a list of filepaths in the $PATH.
Extension methods
splitExtension :: FilePath -> (String, String)Source

Split on the extension. addExtension is the inverse.

 uncurry (++) (splitExtension x) == x
 uncurry addExtension (splitExtension x) == x
 splitExtension "file.txt" == ("file",".txt")
 splitExtension "file" == ("file","")
 splitExtension "file/file.txt" == ("file/file",".txt")
 splitExtension "file.txt/boris" == ("file.txt/boris","")
 splitExtension "file.txt/boris.ext" == ("file.txt/boris",".ext")
 splitExtension "file/path.txt.bob.fred" == ("file/path.txt.bob",".fred")
 splitExtension "file/path.txt/" == ("file/path.txt/","")
takeExtension :: FilePath -> StringSource

Get the extension of a file, returns "" for no extension, .ext otherwise.

 takeExtension x == snd (splitExtension x)
 Valid x => takeExtension (addExtension x "ext") == ".ext"
 Valid x => takeExtension (replaceExtension x "ext") == ".ext"
replaceExtension :: FilePath -> String -> FilePathSource

Set the extension of a file, overwriting one if already present.

 replaceExtension "file.txt" ".bob" == "file.bob"
 replaceExtension "file.txt" "bob" == "file.bob"
 replaceExtension "file" ".bob" == "file.bob"
 replaceExtension "file.txt" "" == "file"
 replaceExtension "file.fred.bob" "txt" == "file.fred.txt"
dropExtension :: FilePath -> FilePathSource

Remove last extension, and the "." preceding it.

 dropExtension x == fst (splitExtension x)
addExtension :: FilePath -> String -> FilePathSource

Add an extension, even if there is already one there. E.g. addExtension "foo.txt" "bat" -> "foo.txt.bat".

 addExtension "file.txt" "bib" == "file.txt.bib"
 addExtension "file." ".bib" == "file..bib"
 addExtension "file" ".bib" == "file.bib"
 addExtension "/" "x" == "/.x"
 Valid x => takeFileName (addExtension (addTrailingPathSeparator x) "ext") == ".ext"
 Windows: addExtension "\\\\share" ".txt" == "\\\\share\\.txt"
hasExtension :: FilePath -> BoolSource

Does the given filename have an extension?

 null (takeExtension x) == not (hasExtension x)
(<.>) :: FilePath -> String -> FilePathSource
Alias to addExtension, for people who like that sort of thing.
splitExtensions :: FilePath -> (FilePath, String)Source

Split on all extensions

 splitExtensions "file.tar.gz" == ("file",".tar.gz")
dropExtensions :: FilePath -> FilePathSource

Drop all extensions

 not $ hasExtension (dropExtensions x)
takeExtensions :: FilePath -> StringSource

Get all extensions

 takeExtensions "file.tar.gz" == ".tar.gz"
Drive methods
splitDrive :: FilePath -> (FilePath, FilePath)Source

Split a path into a drive and a path. On Unix, / is a Drive.

 uncurry (++) (splitDrive x) == x
 Windows: splitDrive "file" == ("","file")
 Windows: splitDrive "c:/file" == ("c:/","file")
 Windows: splitDrive "c:\\file" == ("c:\\","file")
 Windows: splitDrive "\\\\shared\\test" == ("\\\\shared\\","test")
 Windows: splitDrive "\\\\shared" == ("\\\\shared","")
 Windows: splitDrive "\\\\?\\UNC\\shared\\file" == ("\\\\?\\UNC\\shared\\","file")
 Windows: splitDrive "\\\\?\\UNCshared\\file" == ("\\\\?\\","UNCshared\\file")
 Windows: splitDrive "\\\\?\\d:\\file" == ("\\\\?\\d:\\","file")
 Windows: splitDrive "/d" == ("","/d")
 Posix:   splitDrive "/test" == ("/","test")
 Posix:   splitDrive "//test" == ("//","test")
 Posix:   splitDrive "test/file" == ("","test/file")
 Posix:   splitDrive "file" == ("","file")
joinDrive :: FilePath -> FilePath -> FilePathSource

Join a drive and the rest of the path.

          uncurry joinDrive (splitDrive x) == x
 Windows: joinDrive "C:" "foo" == "C:foo"
 Windows: joinDrive "C:\\" "bar" == "C:\\bar"
 Windows: joinDrive "\\\\share" "foo" == "\\\\share\\foo"
 Windows: joinDrive "/:" "foo" == "/:\\foo"
takeDrive :: FilePath -> FilePathSource

Get the drive from a filepath.

 takeDrive x == fst (splitDrive x)
hasDrive :: FilePath -> BoolSource

Does a path have a drive.

 not (hasDrive x) == null (takeDrive x)
dropDrive :: FilePath -> FilePathSource

Delete the drive, if it exists.

 dropDrive x == snd (splitDrive x)
isDrive :: FilePath -> BoolSource
Is an element a drive
Operations on a FilePath, as a list of directories
splitFileName :: FilePath -> (String, String)Source

Split a filename into directory and file. combine is the inverse.

 uncurry (++) (splitFileName x) == x
 Valid x => uncurry combine (splitFileName x) == x
 splitFileName "file/bob.txt" == ("file/", "bob.txt")
 splitFileName "file/" == ("file/", "")
 splitFileName "bob" == ("", "bob")
 Posix:   splitFileName "/" == ("/","")
 Windows: splitFileName "c:" == ("c:","")
takeFileName :: FilePath -> FilePathSource

Get the file name.

 takeFileName "test/" == ""
 takeFileName x `isSuffixOf` x
 takeFileName x == snd (splitFileName x)
 Valid x => takeFileName (replaceFileName x "fred") == "fred"
 Valid x => takeFileName (x </> "fred") == "fred"
 Valid x => isRelative (takeFileName x)
replaceFileName :: FilePath -> String -> FilePathSource

Set the filename.

 Valid x => replaceFileName x (takeFileName x) == x
dropFileName :: FilePath -> FilePathSource

Drop the filename.

 dropFileName x == fst (splitFileName x)
takeBaseName :: FilePath -> StringSource

Get the base name, without an extension or path.

 takeBaseName "file/test.txt" == "test"
 takeBaseName "dave.ext" == "dave"
 takeBaseName "" == ""
 takeBaseName "test" == "test"
 takeBaseName (addTrailingPathSeparator x) == ""
 takeBaseName "file/file.tar.gz" == "file.tar"
replaceBaseName :: FilePath -> String -> FilePathSource

Set the base name.

 replaceBaseName "file/test.txt" "bob" == "file/bob.txt"
 replaceBaseName "fred" "bill" == "bill"
 replaceBaseName "/dave/fred/bob.gz.tar" "new" == "/dave/fred/new.tar"
 replaceBaseName x (takeBaseName x) == x
takeDirectory :: FilePath -> FilePathSource

Get the directory name, move up one level.

           takeDirectory x `isPrefixOf` x
           takeDirectory "foo" == ""
           takeDirectory "/foo/bar/baz" == "/foo/bar"
           takeDirectory "/foo/bar/baz/" == "/foo/bar/baz"
           takeDirectory "foo/bar/baz" == "foo/bar"
 Windows:  takeDirectory "foo\\bar" == "foo"
 Windows:  takeDirectory "foo\\bar\\\\" == "foo\\bar"
 Windows:  takeDirectory "C:\\" == "C:\\"
replaceDirectory :: FilePath -> String -> FilePathSource

Set the directory, keeping the filename the same.

 replaceDirectory x (takeDirectory x) `equalFilePath` x
combine :: FilePath -> FilePath -> FilePathSource

Combine two paths, if the second path isAbsolute, then it returns the second.

 Valid x => combine (takeDirectory x) (takeFileName x) `equalFilePath` x
 Posix:   combine "/" "test" == "/test"
 Posix:   combine "home" "bob" == "home/bob"
 Windows: combine "home" "bob" == "home\\bob"
 Windows: combine "home" "/bob" == "/bob"
(</>) :: FilePath -> FilePath -> FilePathSource
A nice alias for combine.
splitPath :: FilePath -> [FilePath]Source

Split a path by the directory separator.

 concat (splitPath x) == x
 splitPath "test//item/" == ["test//","item/"]
 splitPath "test/item/file" == ["test/","item/","file"]
 splitPath "" == []
 Windows: splitPath "c:\\test\\path" == ["c:\\","test\\","path"]
 Posix:   splitPath "/file/test" == ["/","file/","test"]
joinPath :: [FilePath] -> FilePathSource

Join path elements back together.

 Valid x => joinPath (splitPath x) == x
 joinPath [] == ""
 Posix: joinPath ["test","file","path"] == "test/file/path"
splitDirectories :: FilePath -> [FilePath]Source

Just as splitPath, but don't add the trailing slashes to each element.

 splitDirectories "test/file" == ["test","file"]
 splitDirectories "/test/file" == ["/","test","file"]
 Valid x => joinPath (splitDirectories x) `equalFilePath` x
 splitDirectories "" == []
Low level FilePath operators
hasTrailingPathSeparator :: FilePath -> BoolSource

Is an item either a directory or the last character a path separator?

 hasTrailingPathSeparator "test" == False
 hasTrailingPathSeparator "test/" == True
addTrailingPathSeparator :: FilePath -> FilePathSource

Add a trailing file path separator if one is not already present.

 hasTrailingPathSeparator (addTrailingPathSeparator x)
 hasTrailingPathSeparator x ==> addTrailingPathSeparator x == x
 Posix:    addTrailingPathSeparator "test/rest" == "test/rest/"
dropTrailingPathSeparator :: FilePath -> FilePathSource

Remove any trailing path separators

 dropTrailingPathSeparator "file/test/" == "file/test"
 not (hasTrailingPathSeparator (dropTrailingPathSeparator x)) || isDrive x
 Posix:    dropTrailingPathSeparator "/" == "/"
 Windows:  dropTrailingPathSeparator "\\" == "\\"
File name manipulators
normalise :: FilePath -> FilePathSource

Normalise a file

  • // outside of the drive can be made blank
  • / -> pathSeparator
  • ./ -> ""
 Posix:   normalise "/file/\\test////" == "/file/\\test/"
 Posix:   normalise "/file/./test" == "/file/test"
 Posix:   normalise "/test/file/../bob/fred/" == "/test/file/../bob/fred/"
 Posix:   normalise "../bob/fred/" == "../bob/fred/"
 Posix:   normalise "./bob/fred/" == "bob/fred/"
 Windows: normalise "c:\\file/bob\\" == "C:\\file\\bob\\"
 Windows: normalise "c:\\" == "C:\\"
 Windows: normalise "\\\\server\\test" == "\\\\server\\test"
 Windows: normalise "c:/file" == "C:\\file"
          normalise "." == "."
 Posix:   normalise "./" == "./"
equalFilePath :: FilePath -> FilePath -> BoolSource

Equality of two FilePaths. If you call System.Directory.canonicalizePath first this has a much better chance of working. Note that this doesn't follow symlinks or DOSNAM~1s.

          x == y ==> equalFilePath x y
          normalise x == normalise y ==> equalFilePath x y
 Posix:   equalFilePath "foo" "foo/"
 Posix:   not (equalFilePath "foo" "/foo")
 Posix:   not (equalFilePath "foo" "FOO")
 Windows: equalFilePath "foo" "FOO"
makeRelative :: FilePath -> FilePath -> FilePathSource

Contract a filename, based on a relative path.

There is no corresponding makeAbsolute function, instead use System.Directory.canonicalizePath which has the same effect.

          Valid y => equalFilePath x y || (isRelative x && makeRelative y x == x) || equalFilePath (y </> makeRelative y x) x
          makeRelative x x == "."
          null y || equalFilePath (makeRelative x (x </> y)) y || null (takeFileName x)
 Windows: makeRelative "C:\\Home" "c:\\home\\bob" == "bob"
 Windows: makeRelative "C:\\Home" "c:/home/bob" == "bob"
 Windows: makeRelative "C:\\Home" "D:\\Home\\Bob" == "D:\\Home\\Bob"
 Windows: makeRelative "C:\\Home" "C:Home\\Bob" == "C:Home\\Bob"
 Windows: makeRelative "/Home" "/home/bob" == "bob"
 Posix:   makeRelative "/Home" "/home/bob" == "/home/bob"
 Posix:   makeRelative "/home/" "/home/bob/foo/bar" == "bob/foo/bar"
 Posix:   makeRelative "/fred" "bob" == "bob"
 Posix:   makeRelative "/file/test" "/file/test/fred" == "fred"
 Posix:   makeRelative "/file/test" "/file/test/fred/" == "fred/"
 Posix:   makeRelative "some/path" "some/path/a/b/c" == "a/b/c"
isRelative :: FilePath -> BoolSource

Is a path relative, or is it fixed to the root?

 Windows: isRelative "path\\test" == True
 Windows: isRelative "c:\\test" == False
 Windows: isRelative "c:test" == True
 Windows: isRelative "c:" == True
 Windows: isRelative "\\\\foo" == False
 Windows: isRelative "/foo" == True
 Posix:   isRelative "test/path" == True
 Posix:   isRelative "/test" == False
isAbsolute :: FilePath -> BoolSource
not . isRelative
 isAbsolute x == not (isRelative x)
isValid :: FilePath -> BoolSource

Is a FilePath valid, i.e. could you create a file like it?

          isValid "" == False
 Posix:   isValid "/random_ path:*" == True
 Posix:   isValid x == not (null x)
 Windows: isValid "c:\\test" == True
 Windows: isValid "c:\\test:of_test" == False
 Windows: isValid "test*" == False
 Windows: isValid "c:\\test\\nul" == False
 Windows: isValid "c:\\test\\prn.txt" == False
 Windows: isValid "c:\\nul\\file" == False
 Windows: isValid "\\\\" == False
makeValid :: FilePath -> FilePathSource

Take a FilePath and make it valid; does not change already valid FilePaths.

 isValid (makeValid x)
 isValid x ==> makeValid x == x
 makeValid "" == "_"
 Windows: makeValid "c:\\test:of_test" == "c:\\test_of_test"
 Windows: makeValid "test*" == "test_"
 Windows: makeValid "c:\\test\\nul" == "c:\\test\\nul_"
 Windows: makeValid "c:\\test\\prn.txt" == "c:\\test\\prn_.txt"
 Windows: makeValid "c:\\test/prn.txt" == "c:\\test/prn_.txt"
 Windows: makeValid "c:\\nul\\file" == "c:\\nul_\\file"
Produced by Haddock version 2.4.2