| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Development.Shake.FilePath
Description
A module for FilePath operations exposing System.FilePath plus some additional operations.
Windows note: The extension methods (<.>, takeExtension etc) use the Posix variants since on
Windows "//*" produces <.> "txt""//*\\.txt"
(which is bad for FilePattern values).
Synopsis
- type FilePath = String
- searchPathSeparator :: Char
- normalise :: FilePath -> FilePath
- dropTrailingPathSeparator :: FilePath -> FilePath
- makeRelative :: FilePath -> FilePath -> FilePath
- (</>) :: FilePath -> FilePath -> FilePath
- pathSeparator :: Char
- pathSeparators :: [Char]
- isPathSeparator :: Char -> Bool
- isSearchPathSeparator :: Char -> Bool
- extSeparator :: Char
- isExtSeparator :: Char -> Bool
- splitSearchPath :: String -> [FilePath]
- getSearchPath :: IO [FilePath]
- (-<.>) :: FilePath -> String -> FilePath
- isExtensionOf :: String -> FilePath -> Bool
- stripExtension :: String -> FilePath -> Maybe FilePath
- replaceExtensions :: FilePath -> String -> FilePath
- splitDrive :: FilePath -> (FilePath, FilePath)
- joinDrive :: FilePath -> FilePath -> FilePath
- takeDrive :: FilePath -> FilePath
- dropDrive :: FilePath -> FilePath
- hasDrive :: FilePath -> Bool
- isDrive :: FilePath -> Bool
- splitFileName :: FilePath -> (String, String)
- replaceFileName :: FilePath -> String -> FilePath
- dropFileName :: FilePath -> FilePath
- takeFileName :: FilePath -> FilePath
- takeBaseName :: FilePath -> String
- replaceBaseName :: FilePath -> String -> FilePath
- hasTrailingPathSeparator :: FilePath -> Bool
- addTrailingPathSeparator :: FilePath -> FilePath
- takeDirectory :: FilePath -> FilePath
- replaceDirectory :: FilePath -> String -> FilePath
- combine :: FilePath -> FilePath -> FilePath
- splitPath :: FilePath -> [FilePath]
- splitDirectories :: FilePath -> [FilePath]
- joinPath :: [FilePath] -> FilePath
- equalFilePath :: FilePath -> FilePath -> Bool
- isValid :: FilePath -> Bool
- makeValid :: FilePath -> FilePath
- isRelative :: FilePath -> Bool
- isAbsolute :: FilePath -> Bool
- splitExtension :: FilePath -> (String, String)
- takeExtension :: FilePath -> String
- replaceExtension :: FilePath -> String -> FilePath
- (<.>) :: FilePath -> String -> FilePath
- dropExtension :: FilePath -> FilePath
- addExtension :: FilePath -> String -> FilePath
- hasExtension :: FilePath -> Bool
- splitExtensions :: FilePath -> (FilePath, String)
- dropExtensions :: FilePath -> FilePath
- takeExtensions :: FilePath -> String
- dropDirectory1 :: FilePath -> FilePath
- takeDirectory1 :: FilePath -> FilePath
- replaceDirectory1 :: FilePath -> String -> FilePath
- makeRelativeEx :: FilePath -> FilePath -> IO (Maybe FilePath)
- normaliseEx :: FilePath -> FilePath
- toNative :: FilePath -> FilePath
- toStandard :: FilePath -> FilePath
- exe :: String
Documentation
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 is used to separate the entries in the $PATH environment variable.
Windows: searchPathSeparator == ';' Posix: searchPathSeparator == ':'
normalise :: FilePath -> FilePath #
Normalise a file
- // outside of the drive can be made blank
- / ->
pathSeparator - ./ -> ""
Does not remove "..", because of symlinks.
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 "/a/../c" == "/a/../c"
Posix: normalise "./bob/fred/" == "bob/fred/"
Windows: normalise "c:\\file/bob\\" == "C:\\file\\bob\\"
Windows: normalise "c:\\" == "C:\\"
Windows: normalise "c:\\\\\\\\" == "C:\\"
Windows: normalise "C:.\\" == "C:"
Windows: normalise "\\\\server\\test" == "\\\\server\\test"
Windows: normalise "//server/test" == "\\\\server\\test"
Windows: normalise "c:/file" == "C:\\file"
Windows: normalise "/file" == "\\file"
Windows: normalise "\\" == "\\"
Windows: normalise "/./" == "\\"
normalise "." == "."
Posix: normalise "./" == "./"
Posix: normalise "./." == "./"
Posix: normalise "/./" == "/"
Posix: normalise "/" == "/"
Posix: normalise "bob/fred/." == "bob/fred/"
Posix: normalise "//home" == "/home"dropTrailingPathSeparator :: FilePath -> FilePath #
Remove any trailing path separators
dropTrailingPathSeparator "file/test/" == "file/test"
dropTrailingPathSeparator "/" == "/"
Windows: dropTrailingPathSeparator "\\" == "\\"
Posix: not (hasTrailingPathSeparator (dropTrailingPathSeparator x)) || isDrive xmakeRelative :: FilePath -> FilePath -> FilePath #
Contract a filename, based on a relative path. Note that the resulting path
will never introduce .. paths, as the presence of symlinks means ../b
may not reach a/b if it starts from a/c. For a worked example see
this blog post.
The corresponding makeAbsolute function can be found in
System.Directory.
makeRelative "/directory" "/directory/file.ext" == "file.ext"
Valid x => makeRelative (takeDirectory x) x `equalFilePath` takeFileName x
makeRelative x x == "."
Valid x y => equalFilePath x y || (isRelative x && makeRelative y x == x) || equalFilePath (y </> makeRelative y x) 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"
Windows: makeRelative "/" "//" == "//"
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"(</>) :: FilePath -> FilePath -> FilePath infixr 5 #
Combine two paths with a path separator.
If the second path starts with a path separator or a drive letter, then it returns the second.
The intention is that readFile (dir will access the same file as
</> file)setCurrentDirectory dir; readFile file.
Posix: "/directory" </> "file.ext" == "/directory/file.ext"
Windows: "/directory" </> "file.ext" == "/directory\\file.ext"
"directory" </> "/file.ext" == "/file.ext"
Valid x => (takeDirectory x </> takeFileName x) `equalFilePath` xCombined:
Posix: "/" </> "test" == "/test" Posix: "home" </> "bob" == "home/bob" Posix: "x:" </> "foo" == "x:/foo" Windows: "C:\\foo" </> "bar" == "C:\\foo\\bar" Windows: "home" </> "bob" == "home\\bob"
Not combined:
Posix: "home" </> "/bob" == "/bob" Windows: "home" </> "C:\\bob" == "C:\\bob"
Not combined (tricky):
On Windows, if a filepath starts with a single slash, it is relative to the
root of the current drive. In [1], this is (confusingly) referred to as an
absolute path.
The current behavior of </> is to never combine these forms.
Windows: "home" </> "/bob" == "/bob" Windows: "home" </> "\\bob" == "\\bob" Windows: "C:\\home" </> "\\bob" == "\\bob"
On Windows, from [1]: "If a file name begins with only a disk designator
but not the backslash after the colon, it is interpreted as a relative path
to the current directory on the drive with the specified letter."
The current behavior of </> is to never combine these forms.
Windows: "D:\\foo" </> "C:bar" == "C:bar" Windows: "C:\\foo" </> "C:bar" == "C:bar"
pathSeparator :: Char #
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] #
The list of all possible separators.
Windows: pathSeparators == ['\\', '/'] Posix: pathSeparators == ['/'] pathSeparator `elem` pathSeparators
isPathSeparator :: Char -> Bool #
Rather than using (== , use this. Test if something
is a path separator.pathSeparator)
isPathSeparator a == (a `elem` pathSeparators)
isSearchPathSeparator :: Char -> Bool #
Is the character a file separator?
isSearchPathSeparator a == (a == searchPathSeparator)
extSeparator :: Char #
File extension character
extSeparator == '.'
isExtSeparator :: Char -> Bool #
Is the character an extension character?
isExtSeparator a == (a == extSeparator)
splitSearchPath :: String -> [FilePath] #
Take a string, split it on the searchPathSeparator character.
Blank items are ignored on Windows, and converted to . on Posix.
On Windows path elements are stripped of quotes.
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"] Windows: splitSearchPath "File1;\"File2\";File3" == ["File1","File2","File3"]
getSearchPath :: IO [FilePath] #
Get a list of FILEPATHs in the $PATH variable.
(-<.>) :: FilePath -> String -> FilePath infixr 7 #
Remove the current extension and add another, equivalent to replaceExtension.
"/directory/path.txt" -<.> "ext" == "/directory/path.ext" "/directory/path.txt" -<.> ".ext" == "/directory/path.ext" "foo.o" -<.> "c" == "foo.c"
isExtensionOf :: String -> FilePath -> Bool #
Does the given filename have the specified extension?
"png" `isExtensionOf` "/directory/file.png" == True ".png" `isExtensionOf` "/directory/file.png" == True ".tar.gz" `isExtensionOf` "bar/foo.tar.gz" == True "ar.gz" `isExtensionOf` "bar/foo.tar.gz" == False "png" `isExtensionOf` "/directory/file.png.jpg" == False "csv/table.csv" `isExtensionOf` "/data/csv/table.csv" == False
stripExtension :: String -> FilePath -> Maybe FilePath #
Drop the given extension from a FilePath, and the "." preceding it.
Returns Nothing if the FilePath does not have the given extension, or
Just and the part before the extension if it does.
This function can be more predictable than dropExtensions, especially if the filename
might itself contain . characters.
stripExtension "hs.o" "foo.x.hs.o" == Just "foo.x" stripExtension "hi.o" "foo.x.hs.o" == Nothing dropExtension x == fromJust (stripExtension (takeExtension x) x) dropExtensions x == fromJust (stripExtension (takeExtensions x) x) stripExtension ".c.d" "a.b.c.d" == Just "a.b" stripExtension ".c.d" "a.b..c.d" == Just "a.b." stripExtension "baz" "foo.bar" == Nothing stripExtension "bar" "foobar" == Nothing stripExtension "" x == Just x
replaceExtensions :: FilePath -> String -> FilePath #
Replace all extensions of a file with a new extension. Note
that replaceExtension and addExtension both work for adding
multiple extensions, so only required when you need to drop
all extensions first.
replaceExtensions "file.fred.bob" "txt" == "file.txt" replaceExtensions "file.fred.bob" "tar.gz" == "file.tar.gz"
splitDrive :: FilePath -> (FilePath, FilePath) #
Split a path into a drive and a path. On Posix, / 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 -> FilePath #
Join a drive and the rest of the path.
Valid x => 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"
hasDrive :: FilePath -> Bool #
Does a path have a drive.
not (hasDrive x) == null (takeDrive x)
Posix: hasDrive "/foo" == True
Windows: hasDrive "C:\\foo" == True
Windows: hasDrive "C:foo" == True
hasDrive "foo" == False
hasDrive "" == FalseIs an element a drive
Posix: isDrive "/" == True
Posix: isDrive "/foo" == False
Windows: isDrive "C:\\" == True
Windows: isDrive "C:\\foo" == False
isDrive "" == FalsesplitFileName :: FilePath -> (String, String) #
Split a filename into directory and file. </> is the inverse.
The first component will often end with a trailing slash.
splitFileName "/directory/file.ext" == ("/directory/","file.ext")
Valid x => uncurry (</>) (splitFileName x) == x || fst (splitFileName x) == "./"
Valid x => isValid (fst (splitFileName x))
splitFileName "file/bob.txt" == ("file/", "bob.txt")
splitFileName "file/" == ("file/", "")
splitFileName "bob" == ("./", "bob")
Posix: splitFileName "/" == ("/","")
Windows: splitFileName "c:" == ("c:","")
Windows: splitFileName "\\\\?\\A:\\fred" == ("\\\\?\\A:\\","fred")replaceFileName :: FilePath -> String -> FilePath #
Set the filename.
replaceFileName "/directory/other.txt" "file.ext" == "/directory/file.ext" Valid x => replaceFileName x (takeFileName x) == x
dropFileName :: FilePath -> FilePath #
Drop the filename. Unlike takeDirectory, this function will leave
a trailing path separator on the directory.
dropFileName "/directory/file.ext" == "/directory/" dropFileName x == fst (splitFileName x)
takeFileName :: FilePath -> FilePath #
Get the file name.
takeFileName "/directory/file.ext" == "file.ext" takeFileName "test/" == "" isSuffixOf (takeFileName x) x takeFileName x == snd (splitFileName x) Valid x => takeFileName (replaceFileName x "fred") == "fred" Valid x => takeFileName (x </> "fred") == "fred" Valid x => isRelative (takeFileName x)
takeBaseName :: FilePath -> String #
Get the base name, without an extension or path.
takeBaseName "/directory/file.ext" == "file" 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 #
Set the base name.
replaceBaseName "/directory/other.ext" "file" == "/directory/file.ext" replaceBaseName "file/test.txt" "bob" == "file/bob.txt" replaceBaseName "fred" "bill" == "bill" replaceBaseName "/dave/fred/bob.gz.tar" "new" == "/dave/fred/new.tar" Valid x => replaceBaseName x (takeBaseName x) == x
hasTrailingPathSeparator :: FilePath -> Bool #
Is an item either a directory or the last character a path separator?
hasTrailingPathSeparator "test" == False hasTrailingPathSeparator "test/" == True
addTrailingPathSeparator :: FilePath -> FilePath #
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/"
takeDirectory :: FilePath -> FilePath #
Get the directory name, move up one level.
takeDirectory "/directory/other.ext" == "/directory"
isPrefixOf (takeDirectory x) x || takeDirectory x == "."
takeDirectory "foo" == "."
takeDirectory "/" == "/"
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 -> FilePath #
Set the directory, keeping the filename the same.
replaceDirectory "root/file.ext" "/directory/" == "/directory/file.ext" Valid x => replaceDirectory x (takeDirectory x) `equalFilePath` x
splitPath :: FilePath -> [FilePath] #
Split a path by the directory separator.
splitPath "/directory/file.ext" == ["/","directory/","file.ext"] 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"]
splitDirectories :: FilePath -> [FilePath] #
Just as splitPath, but don't add the trailing slashes to each element.
splitDirectories "/directory/file.ext" == ["/","directory","file.ext"]
splitDirectories "test/file" == ["test","file"]
splitDirectories "/test/file" == ["/","test","file"]
Windows: splitDirectories "C:\\test\\file" == ["C:\\", "test", "file"]
Valid x => joinPath (splitDirectories x) `equalFilePath` x
splitDirectories "" == []
Windows: splitDirectories "C:\\test\\\\\\file" == ["C:\\", "test", "file"]
splitDirectories "/test///file" == ["/","test","file"]joinPath :: [FilePath] -> FilePath #
Join path elements back together.
joinPath z == foldr (</>) "" z joinPath ["/","directory/","file.ext"] == "/directory/file.ext" Valid x => joinPath (splitPath x) == x joinPath [] == "" Posix: joinPath ["test","file","path"] == "test/file/path"
equalFilePath :: FilePath -> FilePath -> Bool #
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.
Similar to normalise, this does not expand "..", because of symlinks.
x == y ==> equalFilePath x y
normalise x == normalise y ==> equalFilePath x y
equalFilePath "foo" "foo/"
not (equalFilePath "/a/../c" "/c")
not (equalFilePath "foo" "/foo")
Posix: not (equalFilePath "foo" "FOO")
Windows: equalFilePath "foo" "FOO"
Windows: not (equalFilePath "C:" "C:/")Is a FilePath valid, i.e. could you create a file like it? This function checks for invalid names, and invalid characters, but does not check if length limits are exceeded, as these are typically filesystem dependent.
isValid "" == False
isValid "\0" == 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
Windows: isValid "\\\\\\foo" == False
Windows: isValid "\\\\?\\D:file" == False
Windows: isValid "foo\tbar" == False
Windows: isValid "nul .txt" == False
Windows: isValid " nul.txt" == TruemakeValid :: FilePath -> FilePath #
Take a FilePath and make it valid; does not change already valid FILEPATHs.
isValid (makeValid x) isValid x ==> makeValid x == x makeValid "" == "_" makeValid "file\0name" == "file_name" Windows: makeValid "c:\\already\\/valid" == "c:\\already\\/valid" 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" Windows: makeValid "\\\\\\foo" == "\\\\drive" Windows: makeValid "\\\\?\\D:file" == "\\\\?\\D:\\file" Windows: makeValid "nul .txt" == "nul _.txt"
isRelative :: FilePath -> Bool #
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:\\" == False Windows: isRelative "c:/" == False Windows: isRelative "c:" == True Windows: isRelative "\\\\foo" == False Windows: isRelative "\\\\?\\foo" == False Windows: isRelative "\\\\?\\UNC\\foo" == False Windows: isRelative "/foo" == True Windows: isRelative "\\foo" == True Posix: isRelative "test/path" == True Posix: isRelative "/test" == False Posix: isRelative "/" == False
According to [1]:
- "A UNC name of any format [is never relative]."
- "You cannot use the "\?" prefix with a relative path."
isAbsolute :: FilePath -> Bool #
not . isRelativeisAbsolute x == not (isRelative x)
splitExtension :: FilePath -> (String, String) #
Split on the extension. addExtension is the inverse.
splitExtension "/directory/path.ext" == ("/directory/path",".ext")
uncurry (<>) (splitExtension x) == x
Valid 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 #
Get the extension of a file, returns "" for no extension, .ext otherwise.
takeExtension "/directory/path.ext" == ".ext" takeExtension x == snd (splitExtension x) Valid x => takeExtension (addExtension x "ext") == ".ext" Valid x => takeExtension (replaceExtension x "ext") == ".ext"
replaceExtension :: FilePath -> String -> FilePath #
Set the extension of a file, overwriting one if already present, equivalent to -<.>.
replaceExtension "/directory/path.txt" "ext" == "/directory/path.ext" replaceExtension "/directory/path.txt" ".ext" == "/directory/path.ext" 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" replaceExtension x y == addExtension (dropExtension x) y
(<.>) :: FilePath -> String -> FilePath infixr 7 #
Add an extension, even if there is already one there, equivalent to addExtension.
"/directory/path" <.> "ext" == "/directory/path.ext" "/directory/path" <.> ".ext" == "/directory/path.ext"
dropExtension :: FilePath -> FilePath #
Remove last extension, and the "." preceding it.
dropExtension "/directory/path.ext" == "/directory/path" dropExtension x == fst (splitExtension x)
addExtension :: FilePath -> String -> FilePath #
Add an extension, even if there is already one there, equivalent to <.>.
addExtension "/directory/path" "ext" == "/directory/path.ext" addExtension "file.txt" "bib" == "file.txt.bib" addExtension "file." ".bib" == "file..bib" addExtension "file" ".bib" == "file.bib" addExtension "/" "x" == "/.x" addExtension x "" == x Valid x => takeFileName (addExtension (addTrailingPathSeparator x) "ext") == ".ext" Windows: addExtension "\\\\share" ".txt" == "\\\\share\\.txt"
hasExtension :: FilePath -> Bool #
Does the given filename have an extension?
hasExtension "/directory/path.ext" == True hasExtension "/directory/path" == False null (takeExtension x) == not (hasExtension x)
splitExtensions :: FilePath -> (FilePath, String) #
Split on all extensions.
splitExtensions "/directory/path.ext" == ("/directory/path",".ext")
splitExtensions "file.tar.gz" == ("file",".tar.gz")
uncurry (<>) (splitExtensions x) == x
Valid x => uncurry addExtension (splitExtensions x) == x
splitExtensions "file.tar.gz" == ("file",".tar.gz")dropExtensions :: FilePath -> FilePath #
Drop all extensions.
dropExtensions "/directory/path.ext" == "/directory/path" dropExtensions "file.tar.gz" == "file" not $ hasExtension $ dropExtensions x not $ any isExtSeparator $ takeFileName $ dropExtensions x
takeExtensions :: FilePath -> String #
Get all extensions.
takeExtensions "/directory/path.ext" == ".ext" takeExtensions "file.tar.gz" == ".tar.gz"
dropDirectory1 :: FilePath -> FilePath Source #
Drop the first directory from a FilePath. Should only be used on
relative paths.
dropDirectory1 "aaa/bbb" == "bbb" dropDirectory1 "aaa/" == "" dropDirectory1 "aaa" == "" dropDirectory1 "" == ""
takeDirectory1 :: FilePath -> FilePath Source #
Take the first component of a FilePath. Should only be used on
relative paths.
takeDirectory1 "aaa/bbb" == "aaa" takeDirectory1 "aaa/" == "aaa" takeDirectory1 "aaa" == "aaa"
replaceDirectory1 :: FilePath -> String -> FilePath Source #
Replace the first component of a FilePath. Should only be used on
relative paths.
replaceDirectory1 "root/file.ext" "directory" == "directory/file.ext" replaceDirectory1 "root/foo/bar/file.ext" "directory" == "directory/foo/bar/file.ext"
makeRelativeEx :: FilePath -> FilePath -> IO (Maybe FilePath) Source #
Make a path relative. Returns Nothing only when the given paths are on different drives. This will try the pure function makeRelative first. If that fails, the paths are canonicalised (removing any indirection and symlinks) and a relative path is derived from there.
> -- Given that "/root/a/" is not a symlink > makeRelativeEx "/root/a/" "/root/b/file.out" Just "../b/file.out" > -- Given that "/root/c/" is a symlink to "/root/e/f/g/" > makeRelativeEx "/root/c/" "/root/b/file.out" Just "../../../b/file.out" > -- On Windows > makeRelativeEx "C:\\foo" "D:\\foo\\bar" Nothing
normaliseEx :: FilePath -> FilePath Source #
Normalise a FilePath, applying the rules:
- All
pathSeparatorsbecomepathSeparator(/on Linux,\on Windows) foo/bar/../bazbecomesfoo/baz(not universally true in the presence of symlinks)foo/./barbecomesfoo/barfoo//barbecomesfoo/bar
This function is not based on the normalise function from the filepath library, as that function
is quite broken.
toStandard :: FilePath -> FilePath Source #
Convert all path separators to /, even on Windows.