Safe Haskell | Safe |
---|---|
Language | Haskell98 |
Synopsis
- module System.Path.Posix
- pathMap :: FileDir fd => (String -> String) -> Path os ar fd -> Path os ar fd
- withAbsRel :: AbsRel ar => (AbsPath os fd -> a) -> (RelPath os fd -> a) -> Path os ar fd -> a
- withFileDir :: FileOrDir fd => (FilePath os ar -> a) -> (DirPath os ar -> a) -> Path os ar fd -> a
- getPathString :: (System os, AbsRel ar, FileDir fd) => Path os ar fd -> String
- idAbsRel :: AbsRelPath os fd -> AbsRelPath os fd
- idAbs :: AbsPath os fd -> AbsPath os fd
- idRel :: RelPath os fd -> RelPath os fd
- idFileDir :: FileDirPath os fd -> FileDirPath os fd
- idFile :: FilePath os fd -> FilePath os fd
- idDir :: DirPath os fd -> DirPath os fd
- mkPathAbsOrRel :: (System os, FileDir fd) => String -> Either (AbsPath os fd) (RelPath os fd)
- mkPathFileOrDir :: (System os, AbsRel ar) => String -> IO (Maybe (Either (FilePath os ar) (DirPath os ar)))
- mkAbsPath :: (System os, FileDir fd) => AbsDir os -> String -> AbsPath os fd
- mkAbsPathFromCwd :: (System os, FileDir fd) => String -> IO (AbsPath os fd)
- (</>) :: DirPath os ar -> RelPath os fd -> Path os ar fd
- (<.>) :: FilePath os ar -> String -> FilePath os ar
- (<++>) :: FilePath os ar -> String -> FilePath os ar
- addExtension :: FilePath os ar -> String -> FilePath os ar
- combine :: DirPath os ar -> RelPath os fd -> Path os ar fd
- dropExtension :: FilePath os ar -> FilePath os ar
- dropExtensions :: FilePath os ar -> FilePath os ar
- dropFileName :: FilePath os ar -> DirPath os ar
- replaceExtension :: FilePath os ar -> String -> FilePath os ar
- replaceBaseName :: FilePath os ar -> String -> FilePath os ar
- replaceDirectory :: FilePath os ar1 -> DirPath os ar2 -> FilePath os ar2
- replaceFileName :: FilePath os ar -> String -> FilePath os ar
- splitExtension :: FilePath os ar -> (FilePath os ar, String)
- splitExtensions :: FilePath os ar -> (FilePath os ar, String)
- splitFileName :: FilePath os ar -> (DirPath os ar, RelFile os)
- splitDirName :: DirPath os ar -> Maybe (DirPath os ar, RelDir os)
- takeBaseName :: FilePath os ar -> RelFile os
- takeDirectory :: FilePath os ar -> DirPath os ar
- takeSuperDirectory :: DirPath os ar -> Maybe (DirPath os ar)
- takeExtension :: FilePath os ar -> String
- takeExtensions :: FilePath os ar -> String
- takeFileName :: FilePath os ar -> RelFile os
- takeDirName :: DirPath os ar -> Maybe (RelDir os)
- mapFileName :: (String -> String) -> FilePath os ar -> FilePath os ar
- mapFileNameF :: Functor f => (String -> f String) -> FilePath os ar -> f (FilePath os ar)
- joinPath :: FileDir fd => [String] -> RelPath os fd
- normalise :: System os => Path os ar fd -> Path os ar fd
- splitPath :: (AbsRel ar, FileOrDir fd) => Path os ar fd -> (Bool, [RelDir os], Maybe (RelFile os))
- makeRelative :: (System os, FileDir fd) => AbsDir os -> AbsPath os fd -> RelPath os fd
- makeRelativeMaybe :: (System os, FileDir fd) => AbsDir os -> AbsPath os fd -> Maybe (RelPath os fd)
- makeAbsolute :: System os => AbsDir os -> RelPath os fd -> AbsPath os fd
- makeAbsoluteFromCwd :: System os => RelPath os fd -> IO (AbsPath os fd)
- dynamicMakeAbsolute :: System os => AbsDir os -> AbsRelPath os fd -> AbsPath os fd
- dynamicMakeAbsoluteFromCwd :: System os => AbsRelPath os fd -> IO (AbsPath os fd)
- genericMakeAbsolute :: (System os, AbsRel ar) => AbsDir os -> Path os ar fd -> AbsPath os fd
- genericMakeAbsoluteFromCwd :: (System os, AbsRel ar) => Path os ar fd -> IO (AbsPath os fd)
- dirFromFile :: FilePath os ar -> DirPath os ar
- fileFromDir :: DirPath os ar -> Maybe (FilePath os ar)
- toFileDir :: FileDir fd => Path os ar fd -> FileDirPath os ar
- fromFileDir :: FileDir fd => FileDirPath os ar -> Maybe (Path os ar fd)
- fileFromFileDir :: FileDirPath os ar -> Maybe (FilePath os ar)
- dirFromFileDir :: FileDirPath os ar -> DirPath os ar
- toAbsRel :: AbsRel ar => Path os ar fd -> AbsRelPath os fd
- fromAbsRel :: AbsRel ar => AbsRelPath os fd -> Maybe (Path os ar fd)
- isAbsolute :: AbsRel ar => Path os ar fd -> Bool
- isRelative :: AbsRel ar => Path os ar fd -> Bool
- hasAnExtension :: FilePath os ar -> Bool
- hasExtension :: String -> FilePath os ar -> Bool
- genericAddExtension :: FileDir fd => Path os ar fd -> String -> Path os ar fd
- genericDropExtension :: FileDir fd => Path os ar fd -> Path os ar fd
- genericDropExtensions :: FileDir fd => Path os ar fd -> Path os ar fd
- genericSplitExtension :: FileDir fd => Path os ar fd -> (Path os ar fd, String)
- genericSplitExtensions :: FileDir fd => Path os ar fd -> (Path os ar fd, String)
- genericTakeExtension :: FileDir fd => Path os ar fd -> String
- genericTakeExtensions :: FileDir fd => Path os ar fd -> String
- isValid :: (System os, AbsRel ar, FileDir fd) => Path os ar fd -> Bool
Documentation
module System.Path.Posix
pathMap :: FileDir fd => (String -> String) -> Path os ar fd -> Path os ar fd Source #
Map over the components of the path.
> Path.pathMap (map toLower) (absDir "/tmp/Reports/SpreadSheets") == Posix.absDir "/tmp/reports/spreadsheets"
withAbsRel :: AbsRel ar => (AbsPath os fd -> a) -> (RelPath os fd -> a) -> Path os ar fd -> a Source #
withFileDir :: FileOrDir fd => (FilePath os ar -> a) -> (DirPath os ar -> a) -> Path os ar fd -> a Source #
getPathString :: (System os, AbsRel ar, FileDir fd) => Path os ar fd -> String Source #
Deprecated: Use Path.toString instead.
Synonym of toString
intended for unqualified use.
idAbsRel :: AbsRelPath os fd -> AbsRelPath os fd Source #
idFileDir :: FileDirPath os fd -> FileDirPath os fd Source #
mkPathAbsOrRel :: (System os, FileDir fd) => String -> Either (AbsPath os fd) (RelPath os fd) Source #
Deprecated: Use Path.absRel instead.
Examines the supplied string and constructs an absolute or relative path as appropriate.
> Path.mkPathAbsOrRel "/tmp" == Left (Posix.absDir "/tmp") > Path.mkPathAbsOrRel "tmp" == Right (Posix.relDir "tmp") > Path.mkPathAbsOrRel "\\tmp" == Left (Windows.absDir "\\tmp") > Path.mkPathAbsOrRel "d:\\tmp" == Left (Windows.absDir "d:\\tmp") > Path.mkPathAbsOrRel "d:tmp" == Left (Windows.absDir "d:tmp") > Path.mkPathAbsOrRel "tmp" == Right (Windows.relDir "tmp")
mkPathFileOrDir :: (System os, AbsRel ar) => String -> IO (Maybe (Either (FilePath os ar) (DirPath os ar))) Source #
Deprecated: Don't let the path type depend on current file system content. Instead choose the path type according to the needed disk object type.
Searches for a file or directory with the supplied path string
and returns a File
or Dir
path as appropriate. If neither exists
at the supplied path, Nothing
is returned.
mkAbsPath :: (System os, FileDir fd) => AbsDir os -> String -> AbsPath os fd Source #
Deprecated: Use Path.dynamicMakeAbsolute instead.
Convert a String
into an AbsPath
by interpreting it as
relative to the supplied directory if necessary.
> Path.mkAbsPath (absDir "/tmp") "foo.txt" == Posix.absFile "/tmp/foo.txt" > Path.mkAbsPath (absDir "/tmp") "/etc/foo.txt" == Posix.absFile "/etc/foo.txt"
(</>) :: DirPath os ar -> RelPath os fd -> Path os ar fd infixr 5 Source #
Infix variant of combine
.
> Posix.toString (Posix.absDir "/tmp" </> Posix.relFile "file.txt") == "/tmp/file.txt" > Posix.toString (Posix.absDir "/tmp" </> Posix.relDir "dir" </> Posix.relFile "file.txt") == "/tmp/dir/file.txt" > Posix.toString (Posix.relDir "dir" </> Posix.relFile "file.txt") == "dir/file.txt" > Windows.toString (Windows.absDir "\\tmp" </> Windows.relFile "file.txt") == "\\tmp\\file.txt" > Windows.toString (Windows.absDir "c:\\tmp" </> Windows.relFile "file.txt") == "c:\\tmp\\file.txt" > Windows.toString (Windows.absDir "c:tmp" </> Windows.relFile "file.txt") == "c:tmp\\file.txt" > Windows.toString (Windows.absDir "c:\\" </> Windows.relDir "tmp" </> Windows.relFile "file.txt") == "c:\\tmp\\file.txt" > Windows.toString (Windows.absDir "c:" </> Windows.relDir "tmp" </> Windows.relFile "file.txt") == "c:tmp\\file.txt" > Windows.toString (Windows.relDir "dir" </> Windows.relFile "file.txt") == "dir\\file.txt"
(<.>) :: FilePath os ar -> String -> FilePath os ar infixl 7 Source #
Infix variant of addExtension
.
We only allow files (and not directories) to have extensions added
by this function. This is because it's the vastly common case and
an attempt to add one to a directory will - more often than not -
represent an error.
We don't however want to prevent the corresponding operation on
directories, and so we provide a function that is more flexible:
genericAddExtension
.
addExtension :: FilePath os ar -> String -> FilePath os ar Source #
Add an extension, even if there is already one there.
E.g. addExtension "foo.txt" "bat" -> "foo.txt.bat"
.
> Path.addExtension (relFile "file.txt") "bib" == Posix.relFile "file.txt.bib" > Path.addExtension (relFile "file.") ".bib" == Posix.relFile "file..bib" > Path.addExtension (relFile "file") ".bib" == Posix.relFile "file.bib" > Path.addExtension Path.emptyFile "bib" == Posix.relFile ".bib" > Path.addExtension Path.emptyFile ".bib" == Posix.relFile ".bib" > Path.takeFileName (Path.addExtension Path.emptyFile "ext") == Posix.relFile ".ext"
combine :: DirPath os ar -> RelPath os fd -> Path os ar fd Source #
Join an (absolute or relative) directory path with a relative (file or directory) path to form a new path.
dropExtension :: FilePath os ar -> FilePath os ar Source #
Remove last extension, and the "." preceding it.
> Path.dropExtension x == fst (Path.splitExtension x)
dropExtensions :: FilePath os ar -> FilePath os ar Source #
Drop all extensions
> not $ Path.hasAnExtension (Path.dropExtensions x)
dropFileName :: FilePath os ar -> DirPath os ar Source #
Synonym for takeDirectory
replaceExtension :: FilePath os ar -> String -> FilePath os ar Source #
Set the extension of a file, overwriting one if already present.
> Path.replaceExtension (relFile "file.txt") ".bob" == Posix.relFile "file.bob" > Path.replaceExtension (relFile "file.txt") "bob" == Posix.relFile "file.bob" > Path.replaceExtension (relFile "file") ".bob" == Posix.relFile "file.bob" > Path.replaceExtension (relFile "file.txt") "" == Posix.relFile "file" > Path.replaceExtension (relFile "file.fred.bob") "txt" == Posix.relFile "file.fred.txt"
splitExtension :: FilePath os ar -> (FilePath os ar, String) Source #
Split on the extension. addExtension
is the inverse.
> uncurry (<.>) (Path.splitExtension x) == x > uncurry Path.addExtension (Path.splitExtension x) == x > Path.splitExtension (relFile "file.txt") == (Posix.relFile "file",".txt") > Path.splitExtension (relFile ".bashrc") == (Posix.emptyFile, ".bashrc") > Path.splitExtension (relFile "file") == (Posix.relFile "file","") > Path.splitExtension (relFile "file/file.txt") == (Posix.relFile "file/file",".txt") > Path.splitExtension (relFile "file.txt/boris") == (Posix.relFile "file.txt/boris","") > Path.splitExtension (relFile "file.txt/boris.ext") == (Posix.relFile "file.txt/boris",".ext") > Path.splitExtension (relFile "file/path.txt.bob.fred") == (Posix.relFile "file/path.txt.bob",".fred")
splitExtensions :: FilePath os ar -> (FilePath os ar, String) Source #
Split on all extensions
> Path.splitExtensions (relFile "file.tar.gz") == (Posix.relFile "file",".tar.gz")
takeBaseName :: FilePath os ar -> RelFile os Source #
Get the basename of a file
> Path.takeBaseName (absFile "/tmp/somedir/myfile.txt") == Posix.relFile "myfile" > Path.takeBaseName (relFile "./myfile.txt") == Posix.relFile "myfile" > Path.takeBaseName (relFile "myfile.txt") == Posix.relFile "myfile"
takeDirectory :: FilePath os ar -> DirPath os ar Source #
takeExtension :: FilePath os ar -> String Source #
Get the extension of a file, returns ""
for no extension, .ext
otherwise.
> Path.takeExtension x == snd (Path.splitExtension x) > Path.takeExtension (Path.addExtension x "ext") == ".ext" > Path.takeExtension (Path.replaceExtension x "ext") == ".ext"
takeExtensions :: FilePath os ar -> String Source #
Get all extensions
> Path.takeExtensions (Posix.relFile "file.tar.gz") == ".tar.gz"
takeFileName :: FilePath os ar -> RelFile os Source #
Get the filename component of a file path (ie stripping all parent dirs)
> Path.takeFileName (absFile "/tmp/somedir/myfile.txt") == Posix.relFile "myfile.txt" > Path.takeFileName (relFile "./myfile.txt") == Posix.relFile "myfile.txt" > Path.takeFileName (relFile "myfile.txt") == Posix.relFile "myfile.txt"
joinPath :: FileDir fd => [String] -> RelPath os fd Source #
Constructs a RelPath
from a list of components.
It is an unchecked error if the path components contain path separators.
It is an unchecked error if a RelFile
path is empty.
> Path.joinPath ["tmp","someDir","dir"] == Posix.relDir "tmp/someDir/dir" > Path.joinPath ["tmp","someDir","file.txt"] == Posix.relFile "tmp/someDir/file.txt"
normalise :: System os => Path os ar fd -> Path os ar fd Source #
Currently just transforms:
> Path.normalise (absFile "/tmp/fred/./jim/./file") == Posix.absFile "/tmp/fred/jim/file"
splitPath :: (AbsRel ar, FileOrDir fd) => Path os ar fd -> (Bool, [RelDir os], Maybe (RelFile os)) Source #
Deconstructs a path into its components.
> Path.splitPath (Posix.absDir "/tmp/someDir/mydir.dir") == (True, map relDir ["tmp","someDir","mydir.dir"], Nothing) > Path.splitPath (Posix.absFile "/tmp/someDir/myfile.txt") == (True, map relDir ["tmp","someDir"], Just $ relFile "myfile.txt")
makeRelative :: (System os, FileDir fd) => AbsDir os -> AbsPath os fd -> RelPath os fd Source #
This function can be used to construct a relative path by removing
the supplied AbsDir
from the front. It is a runtime error
if the
supplied AbsPath
doesn't start with the AbsDir
.
> Path.makeRelative (absDir "/tmp/somedir") (absFile "/tmp/somedir/anotherdir/file.txt") == Posix.relFile "anotherdir/file.txt" > Path.makeRelative (absDir "/tmp/somedir") (absDir "/tmp/somedir/anotherdir/dir") == Posix.relDir "anotherdir/dir" > Path.makeRelative (absDir "c:\\tmp\\somedir") (absFile "C:\\Tmp\\SomeDir\\AnotherDir\\File.txt") == Windows.relFile "AnotherDir\\File.txt" > Path.makeRelative (absDir "c:\\tmp\\somedir") (absDir "c:\\tmp\\somedir\\anotherdir\\dir") == Windows.relDir "anotherdir\\dir" > Path.makeRelative (absDir "c:tmp\\somedir") (absDir "c:tmp\\somedir\\anotherdir\\dir") == Windows.relDir "anotherdir\\dir"
makeRelativeMaybe :: (System os, FileDir fd) => AbsDir os -> AbsPath os fd -> Maybe (RelPath os fd) Source #
makeAbsolute :: System os => AbsDir os -> RelPath os fd -> AbsPath os fd Source #
Joins an absolute directory with a relative path to construct a new absolute path.
> Path.makeAbsolute (absDir "/tmp") (relFile "file.txt") == Posix.absFile "/tmp/file.txt" > Path.makeAbsolute (absDir "/tmp") (relFile "adir/file.txt") == Posix.absFile "/tmp/adir/file.txt" > Path.makeAbsolute (absDir "/tmp") (relDir "adir/dir") == Posix.absDir "/tmp/adir/dir"
makeAbsoluteFromCwd :: System os => RelPath os fd -> IO (AbsPath os fd) Source #
Converts a relative path into an absolute one by prepending the current working directory.
dynamicMakeAbsolute :: System os => AbsDir os -> AbsRelPath os fd -> AbsPath os fd Source #
dynamicMakeAbsoluteFromCwd :: System os => AbsRelPath os fd -> IO (AbsPath os fd) Source #
genericMakeAbsolute :: (System os, AbsRel ar) => AbsDir os -> Path os ar fd -> AbsPath os fd Source #
As for makeAbsolute
, but for use when the path may already be
absolute (in which case it is left unchanged).
You should avoid the use of genericMakeAbsolute
-type functions,
because then you avoid to absolutize a path that was already absolutized.
> Path.genericMakeAbsolute (absDir "/tmp") (relFile "file.txt") == Posix.absFile "/tmp/file.txt" > Path.genericMakeAbsolute (absDir "/tmp") (relFile "adir/file.txt") == Posix.absFile "/tmp/adir/file.txt" > Path.genericMakeAbsolute (absDir "/tmp") (absFile "/adir/file.txt") == Posix.absFile "/adir/file.txt"
genericMakeAbsoluteFromCwd :: (System os, AbsRel ar) => Path os ar fd -> IO (AbsPath os fd) Source #
As for makeAbsoluteFromCwd
, but for use when the path may already be
absolute (in which case it is left unchanged).
dirFromFile :: FilePath os ar -> DirPath os ar Source #
Convert a file to a directory path. Obviously, the corresponding disk object won't change accordingly. The purpose of this function is to be an intermediate step when deriving a directory name from a file name.
fileFromDir :: DirPath os ar -> Maybe (FilePath os ar) Source #
Convert a directory to a file path.
The function returns Nothing
if the directory path is empty.
The purpose of this function is to be an intermediate step
when deriving a file name from a directory name.
fromFileDir :: FileDir fd => FileDirPath os ar -> Maybe (Path os ar fd) Source #
fileFromFileDir :: FileDirPath os ar -> Maybe (FilePath os ar) Source #
dirFromFileDir :: FileDirPath os ar -> DirPath os ar Source #
fromAbsRel :: AbsRel ar => AbsRelPath os fd -> Maybe (Path os ar fd) Source #
isAbsolute :: AbsRel ar => Path os ar fd -> Bool Source #
Test whether a
is absolute.Path
ar fd
> Path.isAbsolute (Posix.absFile "/fred") > Path.isAbsolute (Windows.absFile "\\fred") > Path.isAbsolute (Windows.absFile "c:\\fred") > Path.isAbsolute (Windows.absFile "c:fred")
isRelative :: AbsRel ar => Path os ar fd -> Bool Source #
Invariant - this should return True iff arg is of type Path
Part.Rel _
isRelative = not . isAbsolute > Path.isRelative (Posix.relFile "fred") > Path.isRelative (Windows.relFile "fred")
hasAnExtension :: FilePath os ar -> Bool Source #
Does the given filename have an extension?
> null (Path.takeExtension x) == not (Path.hasAnExtension x)
hasExtension :: String -> FilePath os ar -> Bool Source #
Does the given filename have the given extension?
> Path.hasExtension ".hs" (Posix.relFile "MyCode.hs") > Path.hasExtension ".hs" (Posix.relFile "MyCode.bak.hs") > not $ Path.hasExtension ".hs" (Posix.relFile "MyCode.hs.bak")
genericAddExtension :: FileDir fd => Path os ar fd -> String -> Path os ar fd Source #
This is a more flexible variant of addExtension
/ <.>
which can
work with files or directories
> Path.genericAddExtension (absDir "/") "x" == Posix.absDir "/.x" > Path.genericAddExtension (absDir "/a") "x" == Posix.absDir "/a.x" > Path.genericAddExtension Path.emptyFile "x" == Posix.relFile ".x" > Path.genericAddExtension Path.emptyFile "" == Posix.emptyFile