| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
System.OsPath.Posix
Synopsis
- data PosixString
- data PosixChar
- type PosixPath = PosixString
- encodeUtf :: MonadThrow m => String -> m PosixString
- encodeWith :: TextEncoding -> String -> Either EncodingException PosixString
- encodeFS :: String -> IO PosixString
- pstr :: QuasiQuoter
- pack :: [PosixChar] -> PosixString
- decodeUtf :: MonadThrow m => PosixString -> m String
- decodeWith :: TextEncoding -> PosixString -> Either EncodingException String
- decodeFS :: PosixString -> IO String
- unpack :: PosixString -> [PosixChar]
- unsafeFromChar :: Char -> PosixChar
- toChar :: PosixChar -> Char
- pathSeparator :: PosixChar
- pathSeparators :: [PosixChar]
- isPathSeparator :: PosixChar -> Bool
- searchPathSeparator :: PosixChar
- isSearchPathSeparator :: PosixChar -> Bool
- extSeparator :: PosixChar
- isExtSeparator :: PosixChar -> Bool
- splitSearchPath :: PosixString -> [PosixPath]
- splitExtension :: PosixPath -> (PosixPath, PosixString)
- takeExtension :: PosixPath -> PosixString
- replaceExtension :: PosixPath -> PosixString -> PosixPath
- (-<.>) :: PosixPath -> PosixString -> PosixPath
- dropExtension :: PosixPath -> PosixPath
- addExtension :: PosixPath -> PosixString -> PosixPath
- hasExtension :: PosixPath -> Bool
- (<.>) :: PosixPath -> PosixString -> PosixPath
- splitExtensions :: PosixPath -> (PosixPath, PosixString)
- dropExtensions :: PosixPath -> PosixPath
- takeExtensions :: PosixPath -> PosixString
- replaceExtensions :: PosixPath -> PosixString -> PosixPath
- isExtensionOf :: PosixString -> PosixPath -> Bool
- stripExtension :: PosixString -> PosixPath -> Maybe PosixPath
- splitFileName :: PosixPath -> (PosixPath, PosixPath)
- takeFileName :: PosixPath -> PosixPath
- replaceFileName :: PosixPath -> PosixString -> PosixPath
- dropFileName :: PosixPath -> PosixPath
- takeBaseName :: PosixPath -> PosixPath
- replaceBaseName :: PosixPath -> PosixString -> PosixPath
- takeDirectory :: PosixPath -> PosixPath
- replaceDirectory :: PosixPath -> PosixPath -> PosixPath
- combine :: PosixPath -> PosixPath -> PosixPath
- (</>) :: PosixPath -> PosixPath -> PosixPath
- splitPath :: PosixPath -> [PosixPath]
- joinPath :: [PosixPath] -> PosixPath
- splitDirectories :: PosixPath -> [PosixPath]
- splitDrive :: PosixPath -> (PosixPath, PosixPath)
- joinDrive :: PosixPath -> PosixPath -> PosixPath
- takeDrive :: PosixPath -> PosixPath
- hasDrive :: PosixPath -> Bool
- dropDrive :: PosixPath -> PosixPath
- isDrive :: PosixPath -> Bool
- hasTrailingPathSeparator :: PosixPath -> Bool
- addTrailingPathSeparator :: PosixPath -> PosixPath
- dropTrailingPathSeparator :: PosixPath -> PosixPath
- normalise :: PosixPath -> PosixPath
- equalFilePath :: PosixPath -> PosixPath -> Bool
- makeRelative :: PosixPath -> PosixPath -> PosixPath
- isRelative :: PosixPath -> Bool
- isAbsolute :: PosixPath -> Bool
- isValid :: PosixPath -> Bool
- makeValid :: PosixPath -> PosixPath
Types
data PosixString Source #
Commonly used Posix string as uninterpreted char[]
 array.
Instances
Instances
| Generic PosixChar Source # | |
| Show PosixChar Source # | |
| NFData PosixChar Source # | |
| Defined in System.OsString.Internal.Types | |
| Eq PosixChar Source # | |
| Ord PosixChar Source # | |
| type Rep PosixChar Source # | |
| Defined in System.OsString.Internal.Types | |
type PosixPath = PosixString Source #
Filepaths are char[] data on unix as passed to syscalls.
Filepath construction
encodeUtf :: MonadThrow m => String -> m PosixString Source #
Partial unicode friendly encoding.
This encodes as UTF8 (strictly), which is a good guess.
Throws an EncodingException if encoding fails.
encodeWith :: TextEncoding -> String -> Either EncodingException PosixString Source #
Encode a String with the specified encoding.
encodeFS :: String -> IO PosixString Source #
This mimics the behavior of the base library when doing filesystem operations, which uses shady PEP 383 style encoding (based on the current locale, but PEP 383 only works properly on UTF-8 encodings, so good luck).
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).
pstr :: QuasiQuoter Source #
pack :: [PosixChar] -> PosixString 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 => PosixString -> m String Source #
Partial unicode friendly decoding.
This decodes as UTF8 (strictly), which is a good guess. Note that filenames on unix are encoding agnostic char arrays.
Throws a EncodingException if decoding fails.
decodeWith :: TextEncoding -> PosixString -> Either EncodingException String Source #
Decode a PosixString with the specified encoding.
The String is forced into memory to catch all exceptions.
decodeFS :: PosixString -> IO String Source #
This mimics the behavior of the base library when doing filesystem operations, which uses shady PEP 383 style encoding (based on the current locale, but PEP 383 only works properly on UTF-8 encodings, so good luck).
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).
unpack :: PosixString -> [PosixChar] Source #
Unpack a platform string to a list of platform words.
Word construction
unsafeFromChar :: Char -> PosixChar Source #
Truncates to 1 octet.
Word deconstruction
Separator predicates
pathSeparator :: PosixChar Source #
The character that separates directories. In the case where more than
   one character is possible, pathSeparator is the 'ideal' one.
pathSeparator == '/'
pathSeparators :: [PosixChar] Source #
The list of all possible separators.
pathSeparators == ['/'] pathSeparator `elem` pathSeparators
isPathSeparator :: PosixChar -> Bool Source #
Rather than using (== , use this. Test if something
   is a path separator.pathSeparator)
isPathSeparator a == (a `elem` pathSeparators)
searchPathSeparator :: PosixChar Source #
The character that is used to separate the entries in the $PATH environment variable.
searchPathSeparator == ':'
isSearchPathSeparator :: PosixChar -> Bool Source #
Is the character a file separator?
isSearchPathSeparator a == (a == searchPathSeparator)
extSeparator :: PosixChar Source #
File extension character
extSeparator == '.'
isExtSeparator :: PosixChar -> Bool Source #
Is the character an extension character?
isExtSeparator a == (a == extSeparator)
$PATH methods
splitSearchPath :: PosixString -> [PosixPath] Source #
Take a string, split it on the searchPathSeparator character.
Blank items are converted to . on , and quotes are not
   treated specially.
Follows the recommendations in http://www.opengroup.org/onlinepubs/009695399/basedefs/xbd_chap08.html
splitSearchPath "File1:File2:File3" == ["File1","File2","File3"] splitSearchPath "File1::File2:File3" == ["File1",".","File2","File3"]
Extension functions
splitExtension :: PosixPath -> (PosixPath, PosixString) 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 :: PosixPath -> PosixString 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 :: PosixPath -> PosixString -> PosixPath 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
(-<.>) :: PosixPath -> PosixString -> PosixPath 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 :: PosixPath -> PosixPath Source #
Remove last extension, and the "." preceding it.
dropExtension "/directory/path.ext" == "/directory/path" dropExtension x == fst (splitExtension x)
addExtension :: PosixPath -> PosixString -> PosixPath 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"
hasExtension :: PosixPath -> Bool Source #
Does the given filename have an extension?
hasExtension "/directory/path.ext" == True hasExtension "/directory/path" == False null (takeExtension x) == not (hasExtension x)
(<.>) :: PosixPath -> PosixString -> PosixPath 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 :: PosixPath -> (PosixPath, PosixString) 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 :: PosixPath -> PosixPath 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 :: PosixPath -> PosixString Source #
Get all extensions.
takeExtensions "/directory/path.ext" == ".ext" takeExtensions "file.tar.gz" == ".tar.gz"
replaceExtensions :: PosixPath -> PosixString -> PosixPath 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 :: PosixString -> PosixPath -> 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 :: PosixString -> PosixPath -> Maybe PosixPath 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 :: PosixPath -> (PosixPath, PosixPath) 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 "/" == ("/","")takeFileName :: PosixPath -> PosixPath 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 :: PosixPath -> PosixString -> PosixPath Source #
Set the filename.
replaceFileName "/directory/other.txt" "file.ext" == "/directory/file.ext" Valid x => replaceFileName x (takeFileName x) == x
dropFileName :: PosixPath -> PosixPath 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 :: PosixPath -> PosixPath 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 :: PosixPath -> PosixString -> PosixPath 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 :: PosixPath -> PosixPath 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"replaceDirectory :: PosixPath -> PosixPath -> PosixPath 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
(</>) :: PosixPath -> PosixPath -> PosixPath 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" Valid x => (takeDirectory x </> takeFileName x) `equalFilePath` x
Combined:
"/" </> "test" == "/test" "home" </> "bob" == "home/bob" "x:" </> "foo" == "x:/foo"
Not combined:
"home" </> "/bob" == "/bob"
splitPath :: PosixPath -> [PosixPath] 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 "/file/test" == ["/","file/","test"]
joinPath :: [PosixPath] -> PosixPath Source #
Join path elements back together.
joinPath z == foldr (</>) "" z joinPath ["/","directory/","file.ext"] == "/directory/file.ext" Valid x => joinPath (splitPath x) == x joinPath [] == "" joinPath ["test","file","path"] == "test/file/path"
splitDirectories :: PosixPath -> [PosixPath] 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"] Valid x => joinPath (splitDirectories x) `equalFilePath` x splitDirectories "" == [] splitDirectories "/test///file" == ["/","test","file"]
Drive functions
splitDrive :: PosixPath -> (PosixPath, PosixPath) Source #
Split a path into a drive and a path. / is a Drive.
uncurry (<>) (splitDrive x) == x
splitDrive "/test" == ("/","test")
splitDrive "//test" == ("//","test")
splitDrive "test/file" == ("","test/file")
splitDrive "file" == ("","file")joinDrive :: PosixPath -> PosixPath -> PosixPath 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
takeDrive :: PosixPath -> PosixPath Source #
Get the drive from a filepath.
takeDrive x == fst (splitDrive x)
hasDrive :: PosixPath -> Bool Source #
Does a path have a drive.
not (hasDrive x) == null (takeDrive x) hasDrive "/foo" == True hasDrive "foo" == False hasDrive "" == False
dropDrive :: PosixPath -> PosixPath Source #
Delete the drive, if it exists.
dropDrive x == snd (splitDrive x)
isDrive :: PosixPath -> Bool Source #
Is an element a drive
isDrive "/" == True isDrive "/foo" == False isDrive "" == False
Trailing slash functions
hasTrailingPathSeparator :: PosixPath -> Bool Source #
Is an item either a directory or the last character a path separator?
hasTrailingPathSeparator "test" == False hasTrailingPathSeparator "test/" == True
addTrailingPathSeparator :: PosixPath -> PosixPath Source #
Add a trailing file path separator if one is not already present.
hasTrailingPathSeparator (addTrailingPathSeparator x) hasTrailingPathSeparator x ==> addTrailingPathSeparator x == x addTrailingPathSeparator "test/rest" == "test/rest/"
dropTrailingPathSeparator :: PosixPath -> PosixPath Source #
Remove any trailing path separators
dropTrailingPathSeparator "file/test/" == "file/test" dropTrailingPathSeparator "/" == "/" not (hasTrailingPathSeparator (dropTrailingPathSeparator x)) || isDrive x
File name manipulations
normalise :: PosixPath -> PosixPath Source #
Normalise a file
- // outside of the drive can be made blank
- / -> pathSeparator
- ./ -> ""
Does not remove "..", because of symlinks.
normalise "/file/\\test////" == "/file/\\test/" normalise "/file/./test" == "/file/test" normalise "/test/file/../bob/fred/" == "/test/file/../bob/fred/" normalise "../bob/fred/" == "../bob/fred/" normalise "/a/../c" == "/a/../c" normalise "./bob/fred/" == "bob/fred/" normalise "." == "." normalise "./" == "./" normalise "./." == "./" normalise "/./" == "/" normalise "/" == "/" normalise "bob/fred/." == "bob/fred/" normalise "//home" == "/home"
equalFilePath :: PosixPath -> PosixPath -> 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") not (equalFilePath "foo" "FOO")
makeRelative :: PosixPath -> PosixPath -> PosixPath 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 "/Home" "/home/bob" == "/home/bob" makeRelative "/home/" "/home/bob/foo/bar" == "bob/foo/bar" makeRelative "/fred" "bob" == "bob" makeRelative "/file/test" "/file/test/fred" == "fred" makeRelative "/file/test" "/file/test/fred/" == "fred/" makeRelative "some/path" "some/path/a/b/c" == "a/b/c"
isRelative :: PosixPath -> Bool Source #
Is a path relative, or is it fixed to the root?
isRelative "test/path" == True isRelative "/test" == False isRelative "/" == False
isAbsolute :: PosixPath -> Bool Source #
not . isRelativeisAbsolute x == not (isRelative x)
isValid :: PosixPath -> 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 "/random_ path:*" == True isValid x == not (null x)