easy-file-0.2.3: Cross-platform File handling
Safe HaskellSafe-Inferred
LanguageHaskell2010

System.EasyFile

Description

This is a module of cross-platform file handling for Unix/Mac/Windows.

The standard module System.Directory and System.FilePath have following shortcomings:

  • getModificationTime exists in System.Directory. But getAccessTime, getChangeTime, getCreationTime do not exist.
  • getModificationTime returns obsoleted type, ClockTime. It should return modern type, UTCTime, I believe.
  • Some file functions are missing. A function to tell the link counter, for instance.
  • Path separator is not unified. Even though Windows accepts '/' as a file separator, getCurrentDirectory in System.Directory returns '\' as a file separator. So, we need to specify regular expression like this: "[/\\]foo[/\\]bar[/\\]baz".
  • getHomeDirectory returns HOMEDRIVE/HOMEPATH instead of the HOME environment variable on Windows.

This module aims to resolve these problems and provides:

Synopsis

Actions on directories

createDirectory :: FilePath -> IO () #

createDirectory dir creates a new directory dir which is initially empty, or as near to empty as the operating system allows.

The operation may fail with:

  • isPermissionError The process has insufficient privileges to perform the operation. [EROFS, EACCES]
  • isAlreadyExistsError The operand refers to a directory that already exists. [EEXIST]
  • HardwareFault A physical I/O error has occurred. [EIO]
  • InvalidArgument The operand is not a valid directory name. [ENAMETOOLONG, ELOOP]
  • isDoesNotExistError There is no path to the directory. [ENOENT, ENOTDIR]
  • isFullError Insufficient resources (virtual memory, process file descriptors, physical disk space, etc.) are available to perform the operation. [EDQUOT, ENOSPC, ENOMEM, EMLINK]
  • InappropriateType The path refers to an existing non-directory object. [EEXIST]

createDirectoryIfMissing #

Arguments

:: Bool

Create its parents too?

-> FilePath

The path to the directory you want to make

-> IO () 

createDirectoryIfMissing parents dir creates a new directory dir if it doesn't exist. If the first argument is True the function will also create all parent directories if they are missing.

removeDirectory :: FilePath -> IO () #

removeDirectory dir removes an existing directory dir. The implementation may specify additional constraints which must be satisfied before a directory can be removed (e.g. the directory has to be empty, or may not be in use by other processes). It is not legal for an implementation to partially remove a directory unless the entire directory is removed. A conformant implementation need not support directory removal in all situations (e.g. removal of the root directory).

The operation may fail with:

  • HardwareFault A physical I/O error has occurred. [EIO]
  • InvalidArgument The operand is not a valid directory name. [ENAMETOOLONG, ELOOP]
  • isDoesNotExistError The directory does not exist. [ENOENT, ENOTDIR]
  • isPermissionError The process has insufficient privileges to perform the operation. [EROFS, EACCES, EPERM]
  • UnsatisfiedConstraints Implementation-dependent constraints are not satisfied. [EBUSY, ENOTEMPTY, EEXIST]
  • UnsupportedOperation The implementation does not support removal in this situation. [EINVAL]
  • InappropriateType The operand refers to an existing non-directory object. [ENOTDIR]

removeDirectoryRecursive :: FilePath -> IO () #

removeDirectoryRecursive dir removes an existing directory dir together with its contents and subdirectories. Within this directory, symbolic links are removed without affecting their targets.

On Windows, the operation fails if dir is a directory symbolic link.

This operation is reported to be flaky on Windows so retry logic may be advisable. See: https://github.com/haskell/directory/pull/108

renameDirectory :: FilePath -> FilePath -> IO () #

renameDirectory old new changes the name of an existing directory from old to new. If the new directory already exists, it is atomically replaced by the old directory. If the new directory is neither the old directory nor an alias of the old directory, it is removed as if by removeDirectory. A conformant implementation need not support renaming directories in all situations (e.g. renaming to an existing directory, or across different physical devices), but the constraints must be documented.

On Win32 platforms, renameDirectory fails if the new directory already exists.

The operation may fail with:

  • HardwareFault A physical I/O error has occurred. [EIO]
  • InvalidArgument Either operand is not a valid directory name. [ENAMETOOLONG, ELOOP]
  • isDoesNotExistError The original directory does not exist, or there is no path to the target. [ENOENT, ENOTDIR]
  • isPermissionError The process has insufficient privileges to perform the operation. [EROFS, EACCES, EPERM]
  • isFullError Insufficient resources are available to perform the operation. [EDQUOT, ENOSPC, ENOMEM, EMLINK]
  • UnsatisfiedConstraints Implementation-dependent constraints are not satisfied. [EBUSY, ENOTEMPTY, EEXIST]
  • UnsupportedOperation The implementation does not support renaming in this situation. [EINVAL, EXDEV]
  • InappropriateType Either path refers to an existing non-directory object. [ENOTDIR, EISDIR]

getDirectoryContents :: FilePath -> IO [FilePath] #

Similar to listDirectory, but always includes the special entries (. and ..). (This applies to Windows as well.)

The operation may fail with the same exceptions as listDirectory.

getCurrentDirectory :: IO FilePath Source #

If the operating system has a notion of current directories, getCurrentDirectory returns an absolute path to the current directory of the calling process.

The operation may fail with:

  • HardwareFault A physical I/O error has occurred. [EIO]
  • isDoesNotExistError / NoSuchThing There is no path referring to the current directory. [EPERM, ENOENT, ESTALE...]
  • isPermissionError / PermissionDenied The process has insufficient privileges to perform the operation. [EACCES]
  • ResourceExhausted Insufficient resources are available to perform the operation.
  • UnsupportedOperation The operating system has no notion of current directory.

setCurrentDirectory :: FilePath -> IO () #

Change the working directory to the given path.

In a multithreaded program, the current working directory is a global state shared among all threads of the process. Therefore, when performing filesystem operations from multiple threads, it is highly recommended to use absolute rather than relative paths (see: makeAbsolute).

The operation may fail with:

  • HardwareFault A physical I/O error has occurred. [EIO]
  • InvalidArgument The operand is not a valid directory name. [ENAMETOOLONG, ELOOP]
  • isDoesNotExistError The directory does not exist. [ENOENT, ENOTDIR]
  • isPermissionError The process has insufficient privileges to perform the operation. [EACCES]
  • UnsupportedOperation The operating system has no notion of current working directory, or the working directory cannot be dynamically changed.
  • InappropriateType The path refers to an existing non-directory object. [ENOTDIR]

Pre-defined directories

getHomeDirectory :: IO FilePath Source #

Returns the current user's home directory.

The directory returned is expected to be writable by the current user, but note that it isn't generally considered good practice to store application-specific data here; use getAppUserDataDirectory instead.

On Unix, getHomeDirectory returns the value of the HOME environment variable. On Windows, the system is queried for a suitable path; a typical path might be C:Documents And Settingsuser.

The operation may fail with:

  • UnsupportedOperation The operating system has no notion of home directory.
  • isDoesNotExistError The home directory for the current user does not exist, or cannot be found.

getHomeDirectory2 :: IO (Maybe FilePath) Source #

Returns the current user's home directory from the HOME environment variable.

getAppUserDataDirectory :: String -> IO FilePath Source #

Returns the pathname of a directory in which application-specific data for the current user can be stored. The result of getAppUserDataDirectory for a given application is specific to the current user.

The argument should be the name of the application, which will be used to construct the pathname (so avoid using unusual characters that might result in an invalid pathname).

Note: the directory may not actually exist, and may need to be created first. It is expected that the parent directory exists and is writable.

On Unix, this function returns $HOME/.appName. On Windows, a typical path might be

C:/Documents And Settings/user/Application Data/appName

The operation may fail with:

  • UnsupportedOperation The operating system has no notion of application-specific data directory.
  • isDoesNotExistError The home directory for the current user does not exist, or cannot be found.

getUserDocumentsDirectory :: IO FilePath Source #

Returns the current user's document directory.

The directory returned is expected to be writable by the current user, but note that it isn't generally considered good practice to store application-specific data here; use getAppUserDataDirectory instead.

On Unix, getUserDocumentsDirectory returns the value of the HOME environment variable. On Windows, the system is queried for a suitable path; a typical path might be C:/Documents and Settings/user/My Documents.

The operation may fail with:

  • UnsupportedOperation The operating system has no notion of document directory.
  • isDoesNotExistError The document directory for the current user does not exist, or cannot be found.

getTemporaryDirectory :: IO FilePath Source #

Returns the current directory for temporary files.

On Unix, getTemporaryDirectory returns the value of the TMPDIR environment variable or "/tmp" if the variable isn't defined. On Windows, the function checks for the existence of environment variables in the following order and uses the first path found:

  • TMP environment variable.
  • TEMP environment variable.
  • USERPROFILE environment variable.
  • The Windows directory

The operation may fail with:

  • UnsupportedOperation The operating system has no notion of temporary directory.

The function doesn't verify whether the path exists.

Actions on files

removeFile :: FilePath -> IO () #

removeFile file removes the directory entry for an existing file file, where file is not itself a directory. The implementation may specify additional constraints which must be satisfied before a file can be removed (e.g. the file may not be in use by other processes).

The operation may fail with:

  • HardwareFault A physical I/O error has occurred. [EIO]
  • InvalidArgument The operand is not a valid file name. [ENAMETOOLONG, ELOOP]
  • isDoesNotExistError The file does not exist. [ENOENT, ENOTDIR]
  • isPermissionError The process has insufficient privileges to perform the operation. [EROFS, EACCES, EPERM]
  • UnsatisfiedConstraints Implementation-dependent constraints are not satisfied. [EBUSY]
  • InappropriateType The operand refers to an existing directory. [EPERM, EINVAL]

renameFile :: FilePath -> FilePath -> IO () #

renameFile old new changes the name of an existing file system object from old to new. If the new object already exists, it is replaced by the old object. Neither path may refer to an existing directory. A conformant implementation need not support renaming files in all situations (e.g. renaming across different physical devices), but the constraints must be documented.

On Windows, this calls MoveFileEx with MOVEFILE_REPLACE_EXISTING set, which is not guaranteed to be atomic (https://github.com/haskell/directory/issues/109).

On other platforms, this operation is atomic.

The operation may fail with:

  • HardwareFault A physical I/O error has occurred. [EIO]
  • InvalidArgument Either operand is not a valid file name. [ENAMETOOLONG, ELOOP]
  • isDoesNotExistError The original file does not exist, or there is no path to the target. [ENOENT, ENOTDIR]
  • isPermissionError The process has insufficient privileges to perform the operation. [EROFS, EACCES, EPERM]
  • isFullError Insufficient resources are available to perform the operation. [EDQUOT, ENOSPC, ENOMEM, EMLINK]
  • UnsatisfiedConstraints Implementation-dependent constraints are not satisfied. [EBUSY]
  • UnsupportedOperation The implementation does not support renaming in this situation. [EXDEV]
  • InappropriateType Either path refers to an existing directory. [ENOTDIR, EISDIR, EINVAL, EEXIST, ENOTEMPTY]

copyFile #

Arguments

:: FilePath

Source filename

-> FilePath

Destination filename

-> IO () 

Copy a file with its permissions. If the destination file already exists, it is replaced atomically. Neither path may refer to an existing directory. No exceptions are thrown if the permissions could not be copied.

canonicalizePath :: FilePath -> IO FilePath #

Make a path absolute, normalize the path, and remove as many indirections from it as possible. Any trailing path separators are discarded via dropTrailingPathSeparator. Additionally, on Windows the letter case of the path is canonicalized.

Note: This function is a very big hammer. If you only need an absolute path, makeAbsolute is sufficient for removing dependence on the current working directory.

Indirections include the two special directories . and .., as well as any symbolic links (and junction points on Windows). The input path need not point to an existing file or directory. Canonicalization is performed on the longest prefix of the path that points to an existing file or directory. The remaining portion of the path that does not point to an existing file or directory will still be normalized, but case canonicalization and indirection removal are skipped as they are impossible to do on a nonexistent path.

Most programs should not worry about the canonicity of a path. In particular, despite the name, the function does not truly guarantee canonicity of the returned path due to the presence of hard links, mount points, etc.

If the path points to an existing file or directory, then the output path shall also point to the same file or directory, subject to the condition that the relevant parts of the file system do not change while the function is still running. In other words, the function is definitively not atomic. The results can be utterly wrong if the portions of the path change while this function is running.

Since some indirections (symbolic links on all systems, .. on non-Windows systems, and junction points on Windows) are dependent on the state of the existing filesystem, the function can only make a conservative attempt by removing such indirections from the longest prefix of the path that still points to an existing file or directory.

Note that on Windows parent directories .. are always fully expanded before the symbolic links, as consistent with the rest of the Windows API (such as GetFullPathName). In contrast, on POSIX systems parent directories .. are expanded alongside symbolic links from left to right. To put this more concretely: if L is a symbolic link for R/P, then on Windows L\.. refers to ., whereas on other operating systems L/.. refers to R.

Similar to normalise, passing an empty path is equivalent to passing the current directory.

canonicalizePath can resolve at least 64 indirections in a single path, more than what is supported by most operating systems. Therefore, it may return the fully resolved path even though the operating system itself would have long given up.

On Windows XP or earlier systems, junction expansion is not performed due to their lack of GetFinalPathNameByHandle.

Changes since 1.2.3.0: The function has been altered to be more robust and has the same exception behavior as makeAbsolute.

Changes since 1.3.0.0: The function no longer preserves the trailing path separator. File symbolic links that appear in the middle of a path are properly dereferenced. Case canonicalization and symbolic link expansion are now performed on Windows.

Existence tests

doesFileExist :: FilePath -> IO Bool #

The operation doesFileExist returns True if the argument file exists and is not a directory, and False otherwise.

doesDirectoryExist :: FilePath -> IO Bool #

The operation doesDirectoryExist returns True if the argument file exists and is either a directory or a symbolic link to a directory, and False otherwise.

Permissions

getPermissions :: FilePath -> IO Permissions #

Get the permissions of a file or directory.

On Windows, the writable permission corresponds to the "read-only" attribute. The executable permission is set if the file extension is of an executable file type. The readable permission is always set.

On POSIX systems, this returns the result of access.

The operation may fail with:

setPermissions :: FilePath -> Permissions -> IO () #

Set the permissions of a file or directory.

On Windows, this is only capable of changing the writable permission, which corresponds to the "read-only" attribute. Changing the other permissions has no effect.

On POSIX systems, this sets the owner permissions.

The operation may fail with:

copyPermissions :: FilePath -> FilePath -> IO () Source #

This function copy the permission of the first file to the second.

Timestamps

getCreationTime :: FilePath -> IO (Maybe UTCTime) Source #

The getCreationTime operation returns the UTC time at which the file or directory was created. The time is only available on Windows.

getChangeTime :: FilePath -> IO (Maybe UTCTime) Source #

The getChangeTime operation returns the UTC time at which the file or directory was changed. The time is only available on Unix and Mac. Note that Unix's rename() does not change ctime but MacOS's rename() does.

getModificationTime :: FilePath -> IO UTCTime Source #

The getModificationTime operation returns the UTC time at which the file or directory was last modified.

The operation may fail with:

  • isPermissionError if the user is not permitted to access the modification time; or
  • isDoesNotExistError if the file or directory does not exist.

getAccessTime :: FilePath -> IO UTCTime Source #

The getModificationTime operation returns the UTC time at which the file or directory was last accessed.

Size

getFileSize :: FilePath -> IO Word64 Source #

Getting the size of the file.

File/directory information

isSymlink :: FilePath -> IO Bool Source #

This function tells whether or not a file/directory is symbolic link.

getLinkCount :: FilePath -> IO (Maybe Int) Source #

This function returns the link counter of a file/directory.

hasSubDirectories :: FilePath -> IO (Maybe Bool) Source #

This function returns whether or not a directory has sub-directories.

Separator predicates

type FilePath = String #

File and directory names are values of type String, whose precise meaning is operating system dependent. Files can be opened, yielding a handle which can then be used to operate on the contents of that file.

pathSeparator :: Char Source #

The character that separates directories.

pathSeparator ==  '/'
isPathSeparator pathSeparator

pathSeparators :: [Char] Source #

The list of all possible separators.

Windows: pathSeparators == ['\\', '/']
Posix:   pathSeparators == ['/']
pathSeparator `elem` pathSeparators

isPathSeparator :: Char -> Bool Source #

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

isPathSeparator a == (a `elem` pathSeparators)

extSeparator :: Char Source #

File extension character

extSeparator == '.'

isExtSeparator :: Char -> Bool Source #

Is the character an extension character?

isExtSeparator a == (a == extSeparator)

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 -> String Source #

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 -> FilePath Source #

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 -> FilePath Source #

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

dropExtension x == fst (splitExtension x)

addExtension :: FilePath -> String -> FilePath Source #

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 -> Bool Source #

Does the given filename have an extension?

null (takeExtension x) == not (hasExtension x)

(<.>) :: FilePath -> String -> FilePath infixr 7 Source #

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 -> FilePath Source #

Drop all extensions

not $ hasExtension (dropExtensions x)

takeExtensions :: FilePath -> String Source #

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 "\\\\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") -- xxx
Posix:   splitDrive "/test" == ("/","test") -- xxx
Posix:   splitDrive "//test" == ("//","test")
Posix:   splitDrive "test/file" == ("","test/file")
Posix:   splitDrive "file" == ("","file")

joinDrive :: FilePath -> FilePath -> FilePath Source #

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" -- xxx
Windows: joinDrive "/:" "foo" == "/:/foo" -- xxx

takeDrive :: FilePath -> FilePath Source #

Get the drive from a filepath.

takeDrive x == fst (splitDrive x)

hasDrive :: FilePath -> Bool Source #

Does a path have a drive.

not (hasDrive x) == null (takeDrive x)

dropDrive :: FilePath -> FilePath Source #

Delete the drive, if it exists.

dropDrive x == snd (splitDrive x)

isDrive :: FilePath -> Bool Source #

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 -> FilePath Source #

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 -> FilePath Source #

Set the filename.

Valid x => replaceFileName x (takeFileName x) == x

dropFileName :: FilePath -> FilePath Source #

Drop the filename.

dropFileName x == fst (splitFileName x)

takeBaseName :: FilePath -> String Source #

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 -> FilePath Source #

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 -> FilePath Source #

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\\bar" -- xxx
Windows:  takeDirectory "C:/" == "C:/"

replaceDirectory :: FilePath -> String -> FilePath Source #

Set the directory, keeping the filename the same.

replaceDirectory x (takeDirectory x) `equalFilePath` x

combine :: FilePath -> FilePath -> FilePath Source #

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

Valid x => combine (takeDirectory x) (takeFileName x) `equalFilePath` x
combine "/" "test" == "/test"
combine "home" "bob" == "home/bob"

(</>) :: FilePath -> FilePath -> FilePath infixr 5 Source #

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] -> FilePath Source #

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 -> Bool Source #

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

hasTrailingPathSeparator "test" == False
hasTrailingPathSeparator "test/" == True

addTrailingPathSeparator :: FilePath -> FilePath Source #

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

hasTrailingPathSeparator (addTrailingPathSeparator x)
hasTrailingPathSeparator x ==> addTrailingPathSeparator x == x
addTrailingPathSeparator "test/rest" == "test/rest/"

dropTrailingPathSeparator :: FilePath -> FilePath Source #

Remove any trailing path separators

dropTrailingPathSeparator "file/test/" == "file/test"
not (hasTrailingPathSeparator (dropTrailingPathSeparator x)) || isDrive x
dropTrailingPathSeparator "/" == "/"

File name manipulators

normalise :: FilePath -> FilePath Source #

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" -- xxx
Windows: normalise "." == "."
Posix:   normalise "./" == "./"

equalFilePath :: FilePath -> FilePath -> Bool Source #

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 -> FilePath Source #

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" "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 -> Bool Source #

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 -> Bool Source #

not . isRelative
isAbsolute x == not (isRelative x)