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 theHOME
environment variable on Windows.
This module aims to resolve these problems and provides:
-
getModificationTime
,getAccessTime
,getChangeTime
, andgetCreationTime
. They returnUTCTime
. -
isSymlink
,getLinkCount
, andhasSubDirectories
. - '/' as the single
pathSeparator
. For instance,getCurrentDirectory
returns a path whose separator is '/' even on Windows. -
getHomeDirectory2
which refers theHOME
environment variable. - Necessary functions in System.Directory and System.FilePath.
This is alpha version. The specification would be changed in the future. Please send comments to:
http://github.com/kazu-yamamoto/easy-file/issues
- createDirectory :: FilePath -> IO ()
- createDirectoryIfMissing :: Bool -> FilePath -> IO ()
- removeDirectory :: FilePath -> IO ()
- removeDirectoryRecursive :: FilePath -> IO ()
- renameDirectory :: FilePath -> FilePath -> IO ()
- getDirectoryContents :: FilePath -> IO [FilePath]
- getCurrentDirectory :: IO FilePath
- setCurrentDirectory :: FilePath -> IO ()
- getHomeDirectory :: IO FilePath
- getHomeDirectory2 :: IO (Maybe FilePath)
- getAppUserDataDirectory :: String -> IO FilePath
- getUserDocumentsDirectory :: IO FilePath
- getTemporaryDirectory :: IO FilePath
- removeFile :: FilePath -> IO ()
- renameFile :: FilePath -> FilePath -> IO ()
- copyFile :: FilePath -> FilePath -> IO ()
- canonicalizePath :: FilePath -> IO FilePath
- doesFileExist :: FilePath -> IO Bool
- doesDirectoryExist :: FilePath -> IO Bool
- data Permissions
- getPermissions :: FilePath -> IO Permissions
- setPermissions :: FilePath -> Permissions -> IO ()
- copyPermissions :: FilePath -> FilePath -> IO ()
- getCreationTime :: FilePath -> IO (Maybe UTCTime)
- getChangeTime :: FilePath -> IO (Maybe UTCTime)
- getModificationTime :: FilePath -> IO UTCTime
- getAccessTime :: FilePath -> IO UTCTime
- isSymlink :: FilePath -> IO Bool
- getLinkCount :: FilePath -> IO (Maybe Int)
- hasSubDirectories :: FilePath -> IO (Maybe Bool)
- type FilePath = String
- pathSeparator :: Char
- pathSeparators :: [Char]
- isPathSeparator :: Char -> Bool
- extSeparator :: Char
- isExtSeparator :: Char -> Bool
- 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
Actions on directories
createDirectory :: FilePath -> IO ()
creates a new directory createDirectory
dirdir
which is
initially empty, or as near to empty as the operating system
allows.
The operation may fail with:
-
isPermissionError
/PermissionDenied
The process has insufficient privileges to perform the operation.[EROFS, EACCES]
-
isAlreadyExistsError
/AlreadyExists
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]
-
NoSuchThing
There is no path to the directory.[ENOENT, ENOTDIR]
-
ResourceExhausted
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]
creates a new directory
createDirectoryIfMissing
parents dirdir
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 ()
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).
removeDirectory
dir
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
/NoSuchThing
The directory does not exist.[ENOENT, ENOTDIR]
-
isPermissionError
/PermissionDenied
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 ()
removes an existing directory dir
together with its content and all subdirectories. Be careful,
if the directory contains symlinks, the function will follow them.
removeDirectoryRecursive
dir
renameDirectory :: FilePath -> FilePath -> IO ()
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
renameDirectory
old newremoveDirectory
. 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
/NoSuchThing
The original directory does not exist, or there is no path to the target.[ENOENT, ENOTDIR]
-
isPermissionError
/PermissionDenied
The process has insufficient privileges to perform the operation.[EROFS, EACCES, EPERM]
-
ResourceExhausted
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]
returns a list of all entries
in dir.
getDirectoryContents
dir
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
/NoSuchThing
The directory does not exist.[ENOENT, ENOTDIR]
-
isPermissionError
/PermissionDenied
The process has insufficient privileges to perform the operation.[EACCES]
-
ResourceExhausted
Insufficient resources are available to perform the operation.[EMFILE, ENFILE]
-
InappropriateType
The path refers to an existing non-directory object.[ENOTDIR]
getCurrentDirectory :: IO FilePathSource
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 ()
If the operating system has a notion of current directories,
changes the current
directory of the calling process to dir.
setCurrentDirectory
dir
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
/NoSuchThing
The directory does not exist.[ENOENT, ENOTDIR]
-
isPermissionError
/PermissionDenied
The process has insufficient privileges to perform the operation.[EACCES]
-
UnsupportedOperation
The operating system has no notion of current directory, or the current directory cannot be dynamically changed. -
InappropriateType
The path refers to an existing non-directory object.[ENOTDIR]
Pre-defined directories
getHomeDirectory :: IO FilePathSource
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 FilePathSource
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 FilePathSource
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 FilePathSource
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
/NoSuchThing
The file does not exist.[ENOENT, ENOTDIR]
-
isPermissionError
/PermissionDenied
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 ()
changes the name of an existing file system
object from old to new. If the new object already
exists, it is atomically 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.
renameFile
old new
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
/NoSuchThing
The original file does not exist, or there is no path to the target.[ENOENT, ENOTDIR]
-
isPermissionError
/PermissionDenied
The process has insufficient privileges to perform the operation.[EROFS, EACCES, EPERM]
-
ResourceExhausted
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 :: FilePath -> FilePath -> IO ()
copies the existing file from old to new.
If the new file already exists, it is atomically replaced by the old file.
Neither path may refer to an existing directory. The permissions of old are
copied to new, if possible.
copyFile
old new
canonicalizePath :: FilePath -> IO FilePath
Given path referring to a file or directory, returns a canonicalized path, with the intent that two paths referring to the same file/directory will map to the same canonicalized path. Note that it is impossible to guarantee that the implication (same file/dir <=> same canonicalizedPath) holds in either direction: this function can make only a best-effort attempt.
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 a directory, and False
otherwise.
Permissions
getPermissions :: FilePath -> IO Permissions
The getPermissions
operation returns the
permissions for the file or directory.
The operation may fail with:
-
isPermissionError
if the user is not permitted to access the permissions; or -
isDoesNotExistError
if the file or directory does not exist.
setPermissions :: FilePath -> Permissions -> IO ()
The setPermissions
operation sets the
permissions for the file or directory.
The operation may fail with:
-
isPermissionError
if the user is not permitted to set the permissions; or -
isDoesNotExistError
if the file or directory does not exist.
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 getCreationTime
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 UTCTimeSource
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 UTCTimeSource
The getModificationTime
operation returns the
UTC time at which the file or directory was last accessed.
File/directory information
isSymlink :: FilePath -> IO BoolSource
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
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.
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 -> BoolSource
Rather than using (==
, use this. Test if something
is a path separator.
pathSeparator
)
isPathSeparator a == (a `elem` pathSeparators)
File extension character
extSeparator == '.'
isExtSeparator :: Char -> BoolSource
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 -> 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 "\\\\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 -> 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" -- xxx Windows: joinDrive "/:" "foo" == "/:/foo" -- xxx
takeDrive :: FilePath -> FilePathSource
Get the drive from a filepath.
takeDrive x == fst (splitDrive x)
dropDrive :: FilePath -> FilePathSource
Delete the drive, if it exists.
dropDrive x == snd (splitDrive x)
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\\bar" -- xxx 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 combine "/" "test" == "/test" combine "home" "bob" == "home/bob"
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 addTrailingPathSeparator "test/rest" == "test/rest/"
dropTrailingPathSeparator :: FilePath -> FilePathSource
Remove any trailing path separators
dropTrailingPathSeparator "file/test/" == "file/test" not (hasTrailingPathSeparator (dropTrailingPathSeparator x)) || isDrive x 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" -- xxx Windows: normalise "." == "." Posix: normalise "./" == "./"
equalFilePath :: FilePath -> FilePath -> BoolSource
Equality of two FilePath
s.
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" "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)