pathtype-0.8.1.3: Type-safe replacement for System.FilePath etc
Safe HaskellSafe-Inferred
LanguageHaskell98

System.Path

Synopsis

Documentation

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"

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"
\base p -> Default.toString p `isSuffixOf` Path.toString (Path.makeAbsolute base (Path.idFile p))
\base p -> Default.toString base `isPrefixOf` Path.toString (Path.makeAbsolute base (Path.idFile p))

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"

(</>) :: 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"

splitExtension :: FilePath os ar -> (FilePath os ar, String) Source #

Split on the extension. addExtension is the inverse.

forAllAbsRel $ \x -> uncurry (<.>) (Path.splitExtension x) == x
forAllAbsRel $ \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")

takeExtension :: FilePath os ar -> String Source #

Get the extension of a file, returns "" for no extension, .ext otherwise.

forAllAbsRel $ \x -> Path.takeExtension x == snd (Path.splitExtension x)
forAllAbsRel $ \x -> Path.takeExtension (Path.addExtension x "ext") == ".ext"
forAllAbsRel $ \x -> Path.takeExtension (Path.replaceExtension x "ext") == ".ext"

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"

(<.>) :: 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.

dropExtension :: FilePath os ar -> FilePath os ar Source #

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

forAllAbsRel $ \x -> Path.dropExtension x == fst (Path.splitExtension x)

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"

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

splitExtensions :: FilePath os ar -> (FilePath os ar, String) Source #

Split on all extensions

Path.splitExtensions (relFile "file.tar.gz") == (Posix.relFile "file",".tar.gz")
\p -> uncurry (<.>) (Path.splitExtension p) == (p::Default.AbsFile)

dropExtensions :: FilePath os ar -> FilePath os ar Source #

Drop all extensions

forAllAbsRel $ \x -> not $ Path.hasAnExtension (Path.dropExtensions x)

takeExtensions :: FilePath os ar -> String Source #

Get all extensions

Path.takeExtensions (Posix.relFile "file.tar.gz") == ".tar.gz"

splitFileName :: FilePath os ar -> (DirPath os ar, RelFile os) Source #

\p -> uncurry Path.combine (Path.splitFileName p) == (p::Default.AbsFile)

dropFileName :: FilePath os ar -> DirPath os ar Source #

Synonym for takeDirectory

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"
\p -> Path.toString (Path.takeFileName p) `isSuffixOf` Path.toString (p::Default.AbsFile)

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"

replaceDirectory :: FilePath os ar1 -> DirPath os ar2 -> FilePath os ar2 Source #

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.

\p -> Path.combine Path.currentDir p == (p::Default.RelDir)

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

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"

isValid :: (System os, AbsRel ar, FileDir fd) => Path os ar fd -> Bool Source #

Check internal integrity of the path data structure.

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

isAbsolute :: AbsRel ar => Path os ar fd -> Bool Source #

Test whether a Path ar fd is absolute.

Path.isAbsolute (Posix.absFile "/fred")
Path.isAbsolute (Windows.absFile "\\fred")
Path.isAbsolute (Windows.absFile "c:\\fred")
Path.isAbsolute (Windows.absFile "c:fred")

(<++>) :: FilePath os ar -> String -> FilePath os ar infixl 7 Source #

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.

idAbs :: AbsPath os fd -> AbsPath os fd Source #

idRel :: RelPath os fd -> RelPath os fd Source #

idFile :: FilePath os fd -> FilePath os fd Source #

idDir :: DirPath os fd -> DirPath 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"

mkAbsPathFromCwd :: (System os, FileDir fd) => String -> IO (AbsPath os fd) Source #

Deprecated: Use Path.dynamicMakeAbsoluteFromCwd instead.

Convert a String into an AbsPath by interpreting it as relative to the cwd if necessary.

splitDirName :: DirPath os ar -> Maybe (DirPath os ar, RelDir os) Source #

\p -> (uncurry Path.combine <$> Path.splitDirName p) == toMaybe (not $ Default.isDrive p) (p::Default.AbsDir)

takeDirName :: DirPath os ar -> Maybe (RelDir os) Source #

\p -> fmap (\d -> toString d `isSuffixOf` toString p) (takeDirName p) == toMaybe (not $ isDrive p) True

mapFileName :: (String -> String) -> FilePath os ar -> FilePath os ar Source #

mapFileNameF :: Functor f => (String -> f String) -> FilePath os ar -> f (FilePath os ar) Source #

makeRelativeMaybe :: (System os, FileDir fd) => AbsDir os -> AbsPath os fd -> Maybe (RelPath os fd) Source #

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.

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).

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"

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.

toFileDir :: FileDir fd => Path os ar fd -> FileDirPath os ar Source #

fromFileDir :: FileDir fd => FileDirPath os ar -> Maybe (Path os ar fd) Source #

toAbsRel :: AbsRel ar => Path os ar fd -> AbsRelPath os fd Source #

fromAbsRel :: AbsRel ar => AbsRelPath os fd -> Maybe (Path os ar fd) Source #

hasAnExtension :: FilePath os ar -> Bool Source #

Does the given filename have an extension?

forAllAbsRel $ \x -> null (Path.takeExtension x) == not (Path.hasAnExtension x)

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

genericDropExtension :: FileDir fd => Path os ar fd -> Path os ar fd Source #

genericDropExtensions :: FileDir fd => Path os ar fd -> Path os ar fd Source #

genericSplitExtension :: FileDir fd => Path os ar fd -> (Path os ar fd, String) Source #

genericSplitExtensions :: FileDir fd => Path os ar fd -> (Path os ar fd, String) Source #