Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data WindowsString
- data WindowsChar
- type WindowsPath = WindowsString
- encodeUtf :: MonadThrow m => String -> m WindowsString
- encodeWith :: TextEncoding -> String -> Either EncodingException WindowsString
- encodeFS :: String -> IO WindowsString
- pstr :: QuasiQuoter
- pack :: [WindowsChar] -> WindowsString
- decodeUtf :: MonadThrow m => WindowsString -> m String
- decodeWith :: TextEncoding -> WindowsString -> Either EncodingException String
- decodeFS :: WindowsString -> IO String
- unpack :: WindowsString -> [WindowsChar]
- unsafeFromChar :: Char -> WindowsChar
- toChar :: WindowsChar -> Char
- pathSeparator :: WindowsChar
- pathSeparators :: [WindowsChar]
- isPathSeparator :: WindowsChar -> Bool
- searchPathSeparator :: WindowsChar
- isSearchPathSeparator :: WindowsChar -> Bool
- extSeparator :: WindowsChar
- isExtSeparator :: WindowsChar -> Bool
- splitSearchPath :: WindowsString -> [WindowsPath]
- splitExtension :: WindowsPath -> (WindowsPath, WindowsString)
- takeExtension :: WindowsPath -> WindowsString
- replaceExtension :: WindowsPath -> WindowsString -> WindowsPath
- (-<.>) :: WindowsPath -> WindowsString -> WindowsPath
- dropExtension :: WindowsPath -> WindowsPath
- addExtension :: WindowsPath -> WindowsString -> WindowsPath
- hasExtension :: WindowsPath -> Bool
- (<.>) :: WindowsPath -> WindowsString -> WindowsPath
- splitExtensions :: WindowsPath -> (WindowsPath, WindowsString)
- dropExtensions :: WindowsPath -> WindowsPath
- takeExtensions :: WindowsPath -> WindowsString
- replaceExtensions :: WindowsPath -> WindowsString -> WindowsPath
- isExtensionOf :: WindowsString -> WindowsPath -> Bool
- stripExtension :: WindowsString -> WindowsPath -> Maybe WindowsPath
- splitFileName :: WindowsPath -> (WindowsPath, WindowsPath)
- takeFileName :: WindowsPath -> WindowsPath
- replaceFileName :: WindowsPath -> WindowsString -> WindowsPath
- dropFileName :: WindowsPath -> WindowsPath
- takeBaseName :: WindowsPath -> WindowsPath
- replaceBaseName :: WindowsPath -> WindowsString -> WindowsPath
- takeDirectory :: WindowsPath -> WindowsPath
- replaceDirectory :: WindowsPath -> WindowsPath -> WindowsPath
- combine :: WindowsPath -> WindowsPath -> WindowsPath
- (</>) :: WindowsPath -> WindowsPath -> WindowsPath
- splitPath :: WindowsPath -> [WindowsPath]
- joinPath :: [WindowsPath] -> WindowsPath
- splitDirectories :: WindowsPath -> [WindowsPath]
- splitDrive :: WindowsPath -> (WindowsPath, WindowsPath)
- joinDrive :: WindowsPath -> WindowsPath -> WindowsPath
- takeDrive :: WindowsPath -> WindowsPath
- hasDrive :: WindowsPath -> Bool
- dropDrive :: WindowsPath -> WindowsPath
- isDrive :: WindowsPath -> Bool
- hasTrailingPathSeparator :: WindowsPath -> Bool
- addTrailingPathSeparator :: WindowsPath -> WindowsPath
- dropTrailingPathSeparator :: WindowsPath -> WindowsPath
- normalise :: WindowsPath -> WindowsPath
- equalFilePath :: WindowsPath -> WindowsPath -> Bool
- makeRelative :: WindowsPath -> WindowsPath -> WindowsPath
- isRelative :: WindowsPath -> Bool
- isAbsolute :: WindowsPath -> Bool
- isValid :: WindowsPath -> Bool
- makeValid :: WindowsPath -> WindowsPath
Types
data WindowsString Source #
Commonly used windows string as wide character bytes.
Instances
data WindowsChar Source #
Instances
type WindowsPath = WindowsString Source #
Filepaths are wchar_t*
data on windows as passed to syscalls.
Filepath construction
encodeUtf :: MonadThrow m => String -> m WindowsString Source #
Partial unicode friendly encoding.
This encodes as UTF16-LE (strictly), which is a pretty good guess.
Throws an EncodingException
if encoding fails.
encodeWith :: TextEncoding -> String -> Either EncodingException WindowsString Source #
Encode a String
with the specified encoding.
encodeFS :: String -> IO WindowsString Source #
This mimics the behavior of the base library when doing filesystem operations, which does permissive UTF-16 encoding, where coding errors generate Chars in the surrogate range.
The reason this is in IO is because it unifies with the Posix counterpart,
which does require IO. This is safe to unsafePerformIO
/unsafeDupablePerformIO
.
pstr :: QuasiQuoter Source #
QuasiQuote a WindowsPath
. This accepts Unicode characters
and encodes as UTF-16LE. Runs isValid
on the input.
pack :: [WindowsChar] -> WindowsString Source #
Pack a list of platform words to a platform string.
Note that using this in conjunction with unsafeFromChar
to
convert from [Char]
to platform string is probably not what
you want, because it will truncate unicode code points.
Filepath deconstruction
decodeUtf :: MonadThrow m => WindowsString -> m String Source #
Partial unicode friendly decoding.
This decodes as UTF16-LE (strictly), which is a pretty good.
Throws a EncodingException
if decoding fails.
decodeWith :: TextEncoding -> WindowsString -> Either EncodingException String Source #
Decode a WindowsString
with the specified encoding.
The String is forced into memory to catch all exceptions.
decodeFS :: WindowsString -> IO String Source #
Like decodeUtf
, except this mimics the behavior of the base library when doing filesystem
operations, which does permissive UTF-16 encoding, where coding errors generate
Chars in the surrogate range.
The reason this is in IO is because it unifies with the Posix counterpart,
which does require IO. unsafePerformIO
/unsafeDupablePerformIO
are safe, however.
unpack :: WindowsString -> [WindowsChar] Source #
Unpack a platform string to a list of platform words.
Word construction
unsafeFromChar :: Char -> WindowsChar Source #
Truncates to 2 octets.
Word deconstruction
toChar :: WindowsChar -> Char Source #
Converts back to a unicode codepoint (total).
Separator predicates
pathSeparator :: WindowsChar Source #
The character that separates directories. In the case where more than
one character is possible, pathSeparator
is the 'ideal' one.
pathSeparator == '\\'S
pathSeparators :: [WindowsChar] Source #
The list of all possible separators.
pathSeparators == ['\\', '/'] pathSeparator `elem` pathSeparators
isPathSeparator :: WindowsChar -> Bool Source #
Rather than using (==
, use this. Test if something
is a path separator.pathSeparator
)
isPathSeparator a == (a `elem` pathSeparators)
searchPathSeparator :: WindowsChar Source #
The character that is used to separate the entries in the $PATH environment variable.
searchPathSeparator == ';'
isSearchPathSeparator :: WindowsChar -> Bool Source #
Is the character a file separator?
isSearchPathSeparator a == (a == searchPathSeparator)
extSeparator :: WindowsChar Source #
File extension character
extSeparator == '.'
isExtSeparator :: WindowsChar -> Bool Source #
Is the character an extension character?
isExtSeparator a == (a == extSeparator)
$PATH methods
splitSearchPath :: WindowsString -> [WindowsPath] Source #
Take a string, split it on the searchPathSeparator
character.
Blank items are ignored and path elements are stripped of quotes.
splitSearchPath "File1;File2;File3" == ["File1","File2","File3"] splitSearchPath "File1;;File2;File3" == ["File1","File2","File3"] splitSearchPath "File1;\"File2\";File3" == ["File1","File2","File3"]
Extension functions
splitExtension :: WindowsPath -> (WindowsPath, WindowsString) Source #
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 :: WindowsPath -> WindowsString Source #
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 :: WindowsPath -> WindowsString -> WindowsPath Source #
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
(-<.>) :: WindowsPath -> WindowsString -> WindowsPath Source #
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"
dropExtension :: WindowsPath -> WindowsPath Source #
Remove last extension, and the "." preceding it.
dropExtension "/directory/path.ext" == "/directory/path" dropExtension x == fst (splitExtension x)
addExtension :: WindowsPath -> WindowsString -> WindowsPath Source #
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"
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" addExtension "\\\\share" ".txt" == "\\\\share\\.txt"
hasExtension :: WindowsPath -> Bool Source #
Does the given filename have an extension?
hasExtension "/directory/path.ext" == True hasExtension "/directory/path" == False null (takeExtension x) == not (hasExtension x)
(<.>) :: WindowsPath -> WindowsString -> WindowsPath Source #
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"
splitExtensions :: WindowsPath -> (WindowsPath, WindowsString) Source #
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 :: WindowsPath -> WindowsPath Source #
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 :: WindowsPath -> WindowsString Source #
Get all extensions.
takeExtensions "/directory/path.ext" == ".ext" takeExtensions "file.tar.gz" == ".tar.gz"
replaceExtensions :: WindowsPath -> WindowsString -> WindowsPath Source #
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"
isExtensionOf :: WindowsString -> WindowsPath -> Bool Source #
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 :: WindowsString -> WindowsPath -> Maybe WindowsPath Source #
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
Filename/directory functions
splitFileName :: WindowsPath -> (WindowsPath, WindowsPath) Source #
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") splitFileName "c:" == ("c:","")
takeFileName :: WindowsPath -> WindowsPath Source #
Get the file name.
takeFileName "/directory/file.ext" == "file.ext" 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 :: WindowsPath -> WindowsString -> WindowsPath Source #
Set the filename.
replaceFileName "/directory/other.txt" "file.ext" == "/directory/file.ext" Valid x => replaceFileName x (takeFileName x) == x
dropFileName :: WindowsPath -> WindowsPath Source #
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)
takeBaseName :: WindowsPath -> WindowsPath Source #
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 :: WindowsPath -> WindowsString -> WindowsPath Source #
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
takeDirectory :: WindowsPath -> WindowsPath Source #
Get the directory name, move up one level.
takeDirectory "/directory/other.ext" == "/directory" takeDirectory x `isPrefixOf` 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" takeDirectory "foo\\bar" == "foo" takeDirectory "foo\\bar\\\\" == "foo\\bar" takeDirectory "C:\\" == "C:\\"
replaceDirectory :: WindowsPath -> WindowsPath -> WindowsPath Source #
Set the directory, keeping the filename the same.
replaceDirectory "root/file.ext" "/directory/" == "/directory/file.ext" Valid x => replaceDirectory x (takeDirectory x) `equalFilePath` x
combine :: WindowsPath -> WindowsPath -> WindowsPath Source #
An alias for </>
.
(</>) :: WindowsPath -> WindowsPath -> WindowsPath Source #
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
.
"/directory" </> "file.ext" == "/directory\\file.ext" "directory" </> "/file.ext" == "/file.ext" Valid x => (takeDirectory x </> takeFileName x) `equalFilePath` x
Combined:
"C:\\foo" </> "bar" == "C:\\foo\\bar" "home" </> "bob" == "home\\bob"
Not combined:
"home" </> "C:\\bob" == "C:\\bob"
Not combined (tricky):
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.
"home" </> "/bob" == "/bob" "home" </> "\\bob" == "\\bob" "C:\\home" </> "\\bob" == "\\bob"
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.
"D:\\foo" </> "C:bar" == "C:bar" "C:\\foo" </> "C:bar" == "C:bar"
splitPath :: WindowsPath -> [WindowsPath] Source #
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 "" == [] splitPath "c:\\test\\path" == ["c:\\","test\\","path"]
joinPath :: [WindowsPath] -> WindowsPath Source #
Join path elements back together.
joinPath z == foldr (</>) "" z joinPath ["/","directory/","file.ext"] == "/directory/file.ext" Valid x => joinPath (splitPath x) == x joinPath [] == ""
splitDirectories :: WindowsPath -> [WindowsPath] Source #
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"] splitDirectories "C:\\test\\file" == ["C:\\", "test", "file"] Valid x => joinPath (splitDirectories x) `equalFilePath` x splitDirectories "" == [] splitDirectories "C:\\test\\\\\\file" == ["C:\\", "test", "file"] splitDirectories "/test///file" == ["/","test","file"]
Drive functions
splitDrive :: WindowsPath -> (WindowsPath, WindowsPath) Source #
Split a path into a drive and a path.
uncurry (<>) (splitDrive x) == x splitDrive "file" == ("","file") splitDrive "c:/file" == ("c:/","file") splitDrive "c:\\file" == ("c:\\","file") splitDrive "\\\\shared\\test" == ("\\\\shared\\","test") splitDrive "\\\\shared" == ("\\\\shared","") splitDrive "\\\\?\\UNC\\shared\\file" == ("\\\\?\\UNC\\shared\\","file") splitDrive "\\\\?\\UNCshared\\file" == ("\\\\?\\","UNCshared\\file") splitDrive "\\\\?\\d:\\file" == ("\\\\?\\d:\\","file") splitDrive "/d" == ("","/d")
joinDrive :: WindowsPath -> WindowsPath -> WindowsPath Source #
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"
Join a drive and the rest of the path.
Valid x => uncurry joinDrive (splitDrive x) == x joinDrive "C:" "foo" == "C:foo" joinDrive "C:\\" "bar" == "C:\\bar" joinDrive "\\\\share" "foo" == "\\\\share\\foo" joinDrive "/:" "foo" == "/:\\foo"
takeDrive :: WindowsPath -> WindowsPath Source #
Get the drive from a filepath.
takeDrive x == fst (splitDrive x)
hasDrive :: WindowsPath -> Bool Source #
Does a path have a drive.
not (hasDrive x) == null (takeDrive x) hasDrive "C:\\foo" == True hasDrive "C:foo" == True hasDrive "foo" == False hasDrive "" == False
dropDrive :: WindowsPath -> WindowsPath Source #
Delete the drive, if it exists.
dropDrive x == snd (splitDrive x)
isDrive :: WindowsPath -> Bool Source #
Is an element a drive
isDrive "C:\\" == True isDrive "C:\\foo" == False isDrive "" == False
Trailing slash functions
hasTrailingPathSeparator :: WindowsPath -> Bool Source #
Is an item either a directory or the last character a path separator?
hasTrailingPathSeparator "test" == False hasTrailingPathSeparator "test/" == True
addTrailingPathSeparator :: WindowsPath -> WindowsPath Source #
Add a trailing file path separator if one is not already present.
hasTrailingPathSeparator (addTrailingPathSeparator x) hasTrailingPathSeparator x ==> addTrailingPathSeparator x == x
dropTrailingPathSeparator :: WindowsPath -> WindowsPath Source #
Remove any trailing path separators
dropTrailingPathSeparator "file/test/" == "file/test" dropTrailingPathSeparator "/" == "/" dropTrailingPathSeparator "\\" == "\\"
File name manipulations
normalise :: WindowsPath -> WindowsPath Source #
Normalise a file
- // outside of the drive can be made blank
- / ->
pathSeparator
- ./ -> ""
Does not remove ".."
, because of symlinks.
normalise "c:\\file/bob\\" == "C:\\file\\bob\\" normalise "c:\\" == "C:\\" normalise "C:.\\" == "C:" normalise "\\\\server\\test" == "\\\\server\\test" normalise "//server/test" == "\\\\server\\test" normalise "c:/file" == "C:\\file" normalise "/file" == "\\file" normalise "\\" == "\\" normalise "/./" == "\\" normalise "." == "."
equalFilePath :: WindowsPath -> WindowsPath -> 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.
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") equalFilePath "foo" "FOO" not (equalFilePath "C:" "C:/")
makeRelative :: WindowsPath -> WindowsPath -> WindowsPath Source #
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 makeRelative "C:\\Home" "c:\\home\\bob" == "bob" makeRelative "C:\\Home" "c:/home/bob" == "bob" makeRelative "C:\\Home" "D:\\Home\\Bob" == "D:\\Home\\Bob" makeRelative "C:\\Home" "C:Home\\Bob" == "C:Home\\Bob" makeRelative "/Home" "/home/bob" == "bob" makeRelative "/" "//" == "//"
isRelative :: WindowsPath -> Bool Source #
Is a path relative, or is it fixed to the root?
isRelative "path\\test" == True isRelative "c:\\test" == False isRelative "c:test" == True isRelative "c:\\" == False isRelative "c:/" == False isRelative "c:" == True isRelative "\\\\foo" == False isRelative "\\\\?\\foo" == False isRelative "\\\\?\\UNC\\foo" == False isRelative "/foo" == True isRelative "\\foo" == True
According to [1]:
- "A UNC name of any format [is never relative]."
- "You cannot use the "\?" prefix with a relative path."
isAbsolute :: WindowsPath -> Bool Source #
not . isRelative
isAbsolute x == not (isRelative x)
isValid :: WindowsPath -> Bool Source #
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 isValid "c:\\test" == True isValid "c:\\test:of_test" == False isValid "test*" == False isValid "c:\\test\\nul" == False isValid "c:\\test\\prn.txt" == False isValid "c:\\nul\\file" == False isValid "\\\\" == False isValid "\\\\\\foo" == False isValid "\\\\?\\D:file" == False isValid "foo\tbar" == False isValid "nul .txt" == False isValid " nul.txt" == True
makeValid :: WindowsPath -> WindowsPath Source #
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" makeValid "c:\\already\\/valid" == "c:\\already\\/valid" makeValid "c:\\test:of_test" == "c:\\test_of_test" makeValid "test*" == "test_" makeValid "c:\\test\\nul" == "c:\\test\\nul_" makeValid "c:\\test\\prn.txt" == "c:\\test\\prn_.txt" makeValid "c:\\test/prn.txt" == "c:\\test/prn_.txt" makeValid "c:\\nul\\file" == "c:\\nul_\\file" makeValid "\\\\\\foo" == "\\\\drive" makeValid "\\\\?\\D:file" == "\\\\?\\D:\\file" makeValid "nul .txt" == "nul _.txt"