filepath-2.0.0.3: Library for manipulating FilePaths in a cross platform way.
Copyright© 2021 Julian Ospald
LicenseMIT
MaintainerJulian Ospald <hasufell@posteo.de>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

System.AbstractFilePath

Description

An implementation of the Abstract FilePath Proposal, which aims to supersede type FilePath = String for various reasons:

  1. it is more efficient and avoids memory fragmentation (uses unpinned ShortByteString under the hood)
  2. it is more type-safe (newtype over ShortByteString)
  3. avoids round-tripping issues by not converting to String (which is not total and loses the encoding)
  4. abstracts over unix and windows while keeping the original bytes

It is important to know that filenames/filepaths have different representations across platforms:

  • On Windows, filepaths are expected to be encoded as UTF16-LE as per the documentation, but may also include invalid surrogate pairs, in which case UCS-2 can be used. They are passed as wchar_t* to syscalls. AbstractFilePath only maintains the wide character invariant.
  • On Unix, filepaths don't have a predefined encoding (although they are often interpreted as UTF8) as per the POSIX specification and are passed as char[] to syscalls. AbstractFilePath maintains no invariant here. Some functions however, such as toAbstractFilePathUtf, may expect or produce UTF8.

Apart from encoding, filepaths have additional restrictions per platform:

Use isValid to check for these restrictions (AbstractFilePath doesn't maintain this invariant).

Also note that these restrictions are not exhaustive and further filesystem specific restrictions may apply on all platforms. This library makes no attempt at satisfying these. Library users may need to account for that, depending on what filesystems they want to support.

It is advised to follow these principles when dealing with filepaths/filenames:

  1. Avoid interpreting filenames that the OS returns, unless absolutely necessary. For example, the filepath separator is usually a predefined Word8, regardless of encoding. So even if we need to split filepaths, it might still not be necessary to understand the encoding of the filename.
  2. When interpreting OS returned filenames consider that these might not be UTF8 on unix or at worst don't have an ASCII compatible encoding. Some strategies here involve looking up the current locale and using that for decoding (fromAbstractFilePathFS does this). Otherwise it can be reasonable to assume UTF8 on unix (fromAbstractFilePathUtf does that) if your application specifically mentions that it requires a UTF8 compatible system. These things should be documented.
  3. When dealing with user input (e.g. on the command line) on unix as e.g. String the input encoding is lost. The output encoding (e.g. how we write a filename to disk) can then either follow the current locale again (toAbstractFilePathFS) or a fixed encoding (toAbstractFilePathUtf/toAbstractFilePathEnc). The decision should be clearly documented. If the input is in the form of a ByteString, then bytesToAFP may be of interest, unless the input needs further interpretation.
Synopsis

Types

type AbstractFilePath = OsString Source #

Type representing filenames/pathnames.

This type doesn't add any guarantees over OsString.

data OsString Source #

Newtype representing short operating system specific strings.

Internally this is either WindowsString or PosixString, depending on the platform. Both use unpinned ShortByteString for efficiency.

The constructor is only exported via System.OsString.Internal.Types, since dealing with the internals isn't generally recommended, but supported in case you need to write platform specific code.

Instances

Instances details
Eq OsString Source #

Byte equality of the internal representation.

Instance details

Defined in System.OsString.Internal.Types

Methods

(==) :: OsString -> OsString -> Bool

(/=) :: OsString -> OsString -> Bool

Ord OsString Source #

Byte ordering of the internal representation.

Instance details

Defined in System.OsString.Internal.Types

Methods

compare :: OsString -> OsString -> Ordering

(<) :: OsString -> OsString -> Bool

(<=) :: OsString -> OsString -> Bool

(>) :: OsString -> OsString -> Bool

(>=) :: OsString -> OsString -> Bool

max :: OsString -> OsString -> OsString

min :: OsString -> OsString -> OsString

Read OsString Source #

Encodes as UTF-8 on unix and UTF-16LE on windows.

Instance details

Defined in System.OsString.Internal.Types

Methods

readsPrec :: Int -> ReadS OsString

readList :: ReadS [OsString]

readPrec :: ReadPrec OsString

readListPrec :: ReadPrec [OsString]

Show OsString Source #

Decodes as UTF-16 on windows.

Decodes as UTF-8 on unix and replaces invalid chars with unicode replacement char U+FFFD.

Instance details

Defined in System.OsString.Internal.Types

Methods

showsPrec :: Int -> OsString -> ShowS

show :: OsString -> String

showList :: [OsString] -> ShowS

IsString OsString Source #

Encodes as UTF16 on windows and UTF8 on unix.

Instance details

Defined in System.OsString.Internal.Types

Methods

fromString :: String -> OsString

Generic OsString Source # 
Instance details

Defined in System.OsString.Internal.Types

Associated Types

type Rep OsString :: Type -> Type

Methods

from :: OsString -> Rep OsString x

to :: Rep OsString x -> OsString

Semigroup OsString Source # 
Instance details

Defined in System.OsString.Internal.Types

Methods

(<>) :: OsString -> OsString -> OsString

sconcat :: NonEmpty OsString -> OsString

stimes :: Integral b => b -> OsString -> OsString

Monoid OsString Source #

"String-Concatenation" for 'OsString. This is not the same as (</>).

Instance details

Defined in System.OsString.Internal.Types

NFData OsString Source # 
Instance details

Defined in System.OsString.Internal.Types

Methods

rnf :: OsString -> ()

Lift OsString Source # 
Instance details

Defined in System.OsString.Internal.Types

Methods

lift :: OsString -> Q Exp

liftTyped :: OsString -> Q (TExp OsString)

type Rep OsString Source # 
Instance details

Defined in System.OsString.Internal.Types

type Rep OsString = D1 ('MetaData "OsString" "System.OsString.Internal.Types" "filepath-2.0.0.3-inplace" 'True) (C1 ('MetaCons "OsString" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PlatformString)))

data OsChar Source #

Newtype representing a code unit.

On Windows, this is restricted to two-octet codepoints Word16, on POSIX one-octet (Word8).

Instances

Instances details
Eq OsChar Source #

Byte equality of the internal representation.

Instance details

Defined in System.OsString.Internal.Types

Methods

(==) :: OsChar -> OsChar -> Bool

(/=) :: OsChar -> OsChar -> Bool

Ord OsChar Source #

Byte ordering of the internal representation.

Instance details

Defined in System.OsString.Internal.Types

Methods

compare :: OsChar -> OsChar -> Ordering

(<) :: OsChar -> OsChar -> Bool

(<=) :: OsChar -> OsChar -> Bool

(>) :: OsChar -> OsChar -> Bool

(>=) :: OsChar -> OsChar -> Bool

max :: OsChar -> OsChar -> OsChar

min :: OsChar -> OsChar -> OsChar

Show OsChar Source # 
Instance details

Defined in System.OsString.Internal.Types

Methods

showsPrec :: Int -> OsChar -> ShowS

show :: OsChar -> String

showList :: [OsChar] -> ShowS

Generic OsChar Source # 
Instance details

Defined in System.OsString.Internal.Types

Associated Types

type Rep OsChar :: Type -> Type

Methods

from :: OsChar -> Rep OsChar x

to :: Rep OsChar x -> OsChar

NFData OsChar Source # 
Instance details

Defined in System.OsString.Internal.Types

Methods

rnf :: OsChar -> ()

type Rep OsChar Source # 
Instance details

Defined in System.OsString.Internal.Types

type Rep OsChar = D1 ('MetaData "OsChar" "System.OsString.Internal.Types" "filepath-2.0.0.3-inplace" 'True) (C1 ('MetaCons "OsChar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PlatformChar)))

Filepath construction

toAbstractFilePathUtf :: MonadThrow m => String -> m AbstractFilePath Source #

Convert a String.

On windows this encodes as UTF16, which is a pretty good guess. On unix this encodes as UTF8, which is a good guess.

Throws a EncodingException if encoding fails.

toAbstractFilePathEnc Source #

Arguments

:: TextEncoding

unix text encoding

-> TextEncoding

windows text encoding

-> String 
-> Either EncodingException AbstractFilePath 

Like toAbstractFilePathUtf, except allows to provide encodings.

toAbstractFilePathFS :: String -> IO AbstractFilePath Source #

Like toAbstractFilePathUtf, except on unix this uses the current filesystem locale for encoding instead of always UTF8.

Looking up the locale requires IO. If you're not worried about calls to setFileSystemEncoding, then unsafePerformIO may be feasible (make sure to deeply evaluate the result to catch exceptions).

Throws EncodingException if decoding fails.

afp :: QuasiQuoter Source #

QuasiQuote an AbstractFilePath. This accepts Unicode characters and encodes as UTF-8 on unix and UTF-16 on windows. Runs filepathIsValid on the input.

packAFP :: [OsChar] -> AbstractFilePath Source #

Pack a list of OsChar to an AbstractFilePath.

Note that using this in conjunction with unsafeFromChar to convert from [Char] to AbstractFilePath is probably not what you want, because it will truncate unicode code points.

Filepath deconstruction

fromAbstractFilePathUtf :: MonadThrow m => AbstractFilePath -> m String Source #

Partial unicode friendly decoding.

On windows this decodes as UTF16-LE (which is the expected filename encoding). On unix this decodes as UTF8 (which is a good guess). Note that filenames on unix are encoding agnostic char arrays.

Throws a EncodingException if decoding fails.

Note that filenames of different encodings may have the same String representation, although they're not the same byte-wise.

fromAbstractFilePathEnc Source #

Arguments

:: TextEncoding

unix text encoding

-> TextEncoding

windows text encoding

-> AbstractFilePath 
-> Either EncodingException String 

Like fromAbstractFilePathUtf, except on unix this uses the provided TextEncoding for decoding.

fromAbstractFilePathFS :: AbstractFilePath -> IO String Source #

Like fromAbstractFilePathUtf, except on unix this uses the current locale for decoding instead of always UTF8. On windows, uses UTF-16LE.

Looking up the locale requires IO. If you're not worried about calls to setFileSystemEncoding, then unsafePerformIO may be feasible (make sure to deeply evaluate the result to catch exceptions).

Throws EncodingException if decoding fails.

Word construction

unsafeFromChar :: Char -> OsChar Source #

Truncates on unix to 1 and on Windows to 2 octets.

Word deconstruction

toChar :: OsChar -> Char Source #

Converts back to a unicode codepoint (total).

Separator predicates

pathSeparator :: OsChar Source #

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 :: [OsChar] Source #

The list of all possible separators.

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

isPathSeparator :: OsChar -> Bool Source #

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

isPathSeparator a == (a `elem` pathSeparators)

searchPathSeparator :: OsChar Source #

Is the character a file separator?

isSearchPathSeparator a == (a == searchPathSeparator)

isSearchPathSeparator :: OsChar -> Bool Source #

Is the character a file separator?

isSearchPathSeparator a == (a == searchPathSeparator)

extSeparator :: OsChar Source #

File extension character

extSeparator == '.'

isExtSeparator :: OsChar -> Bool Source #

Is the character an extension character?

isExtSeparator a == (a == extSeparator)

$PATH methods

splitSearchPath :: OsString -> [AbstractFilePath] Source #

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"]

Extension functions

splitExtension :: AbstractFilePath -> (AbstractFilePath, OsString) 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 :: AbstractFilePath -> OsString 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 :: AbstractFilePath -> OsString -> AbstractFilePath 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

(-<.>) :: AbstractFilePath -> OsString -> AbstractFilePath 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 :: AbstractFilePath -> AbstractFilePath Source #

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

dropExtension "/directory/path.ext" == "/directory/path"
dropExtension x == fst (splitExtension x)

addExtension :: AbstractFilePath -> OsString -> AbstractFilePath 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"

hasExtension :: AbstractFilePath -> Bool Source #

Does the given filename have an extension?

hasExtension "/directory/path.ext" == True
hasExtension "/directory/path" == False
null (takeExtension x) == not (hasExtension x)

(<.>) :: AbstractFilePath -> OsString -> AbstractFilePath 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 :: AbstractFilePath -> (AbstractFilePath, OsString) 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 :: AbstractFilePath -> AbstractFilePath 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 :: AbstractFilePath -> OsString Source #

Get all extensions.

takeExtensions "/directory/path.ext" == ".ext"
takeExtensions "file.tar.gz" == ".tar.gz"

replaceExtensions :: AbstractFilePath -> OsString -> AbstractFilePath 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 :: OsString -> AbstractFilePath -> 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 :: OsString -> AbstractFilePath -> Maybe AbstractFilePath 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 :: AbstractFilePath -> (AbstractFilePath, AbstractFilePath) 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")
Posix:   splitFileName "/" == ("/","")
Windows: splitFileName "c:" == ("c:","")

takeFileName :: AbstractFilePath -> AbstractFilePath 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 :: AbstractFilePath -> OsString -> AbstractFilePath Source #

Set the filename.

replaceFileName "/directory/other.txt" "file.ext" == "/directory/file.ext"
Valid x => replaceFileName x (takeFileName x) == x

dropFileName :: AbstractFilePath -> AbstractFilePath 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 :: AbstractFilePath -> AbstractFilePath 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 :: AbstractFilePath -> OsString -> AbstractFilePath 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 :: AbstractFilePath -> AbstractFilePath 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"
Windows:  takeDirectory "foo\\bar" == "foo"
Windows:  takeDirectory "foo\\bar\\\\" == "foo\\bar"
Windows:  takeDirectory "C:\\" == "C:\\"

replaceDirectory :: AbstractFilePath -> AbstractFilePath -> AbstractFilePath 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

(</>) :: AbstractFilePath -> AbstractFilePath -> AbstractFilePath 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 </> file) will access the same file as 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` x

Combined:

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"

splitPath :: AbstractFilePath -> [AbstractFilePath] 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 "" == []
Windows: splitPath "c:\\test\\path" == ["c:\\","test\\","path"]
Posix:   splitPath "/file/test" == ["/","file/","test"]

joinPath :: [AbstractFilePath] -> AbstractFilePath Source #

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"

splitDirectories :: AbstractFilePath -> [AbstractFilePath] 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"]
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"]

Drive functions

splitDrive :: AbstractFilePath -> (AbstractFilePath, AbstractFilePath) Source #

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 :: AbstractFilePath -> AbstractFilePath -> AbstractFilePath 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"

takeDrive :: AbstractFilePath -> AbstractFilePath Source #

Get the drive from a filepath.

takeDrive x == fst (splitDrive x)

hasDrive :: AbstractFilePath -> Bool Source #

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 "" == False

dropDrive :: AbstractFilePath -> AbstractFilePath Source #

Delete the drive, if it exists.

dropDrive x == snd (splitDrive x)

isDrive :: AbstractFilePath -> Bool Source #

Is an element a drive

Posix:   isDrive "/" == True
Posix:   isDrive "/foo" == False
Windows: isDrive "C:\\" == True
Windows: isDrive "C:\\foo" == False
         isDrive "" == False

Trailing slash functions

hasTrailingPathSeparator :: AbstractFilePath -> Bool Source #

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

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

addTrailingPathSeparator :: AbstractFilePath -> AbstractFilePath Source #

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

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

dropTrailingPathSeparator :: AbstractFilePath -> AbstractFilePath Source #

Remove any trailing path separators

dropTrailingPathSeparator "file/test/" == "file/test"
          dropTrailingPathSeparator "/" == "/"
Windows:  dropTrailingPathSeparator "\\" == "\\"
Posix:    not (hasTrailingPathSeparator (dropTrailingPathSeparator x)) || isDrive x

File name manipulations

normalise :: AbstractFilePath -> AbstractFilePath Source #

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 "\\\\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"

equalFilePath :: AbstractFilePath -> AbstractFilePath -> 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")
Posix:   not (equalFilePath "foo" "FOO")
Windows: equalFilePath "foo" "FOO"
Windows: not (equalFilePath "C:" "C:/")

makeRelative :: AbstractFilePath -> AbstractFilePath -> AbstractFilePath 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
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"

isRelative :: AbstractFilePath -> 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:\\" == 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 :: AbstractFilePath -> Bool Source #

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

isValid :: AbstractFilePath -> 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
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" == True

makeValid :: AbstractFilePath -> AbstractFilePath 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"
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"