pathtype-0.6: Type-safe replacement for System.FilePath etc

Safe HaskellSafe
LanguageHaskell98

System.Path.Windows

Contents

Description

This module provides type-safe access to filepath manipulations.

Normally you would import Path (which will use the default implementation for the host platform) instead of this. However, importing this explicitly allows for manipulation of non-native paths.

Synopsis

The main filepath (& dirpath) abstract type

data Path ar fd Source

This is the main filepath abstract datatype

Instances

(AbsRelClass ar, FileDirClass fd) => Eq (Path ar fd) Source 
(AbsRelClass ar, FileDirClass fd) => Ord (Path ar fd) Source 
(AbsRelClass ar, FileDirClass fd) => Read (Path ar fd) Source 
(AbsRelClass ar, FileDirClass fd) => Show (Path ar fd) Source 
(AbsRelClass ar, FileDirClass fd) => IsString (Path ar fd) Source

Allow use of OverloadedStrings if desired

(AbsRelClass ar, FileDirClass fd) => Arbitrary (Path ar fd) Source 
(AbsRelClass ar, FileDirClass fd) => NFData (Path ar fd) Source 

Phantom Types

Type Synonyms

type AbsPath fd = Path Abs fd Source

type RelPath fd = Path Rel fd Source

type FilePath ar = Path ar File Source

type DirPath ar = Path ar Dir Source

Classes

class Private ar => AbsRelClass ar where Source

This class allows selective behaviour for absolute and relative paths and is mostly for internal use.

Minimal complete definition

switchAbsRel

Methods

switchAbsRel :: f Abs -> f Rel -> f ar Source

absRel :: (AbsPath fd -> a) -> (RelPath fd -> a) -> Path ar fd -> a Source

Will become a top-level function in future

class Private fd => FileDirClass fd where Source

This class allows selective behaviour for file and directory paths and is mostly for internal use.

Minimal complete definition

switchFileDir

Methods

switchFileDir :: f File -> f Dir -> f fd Source

fileDir :: (FilePath ar -> a) -> (DirPath ar -> a) -> Path ar fd -> a Source

Will become a top-level function in future

Path to String conversion

getPathString :: (AbsRelClass ar, FileDirClass fd) => Path ar fd -> String Source

Convert the Path into a plain String as required for OS calls.

Constants

Unchecked Construction Functions

asPath :: (AbsRelClass ar, FileDirClass fd) => String -> Path ar fd Source

Use a String as a Path whose type is determined by its context.

> Posix.asPath "/tmp" == Posix.asAbsDir "/tmp"
> Posix.asPath "file.txt" == Posix.asRelFile "file.txt"
> Posix.isAbsolute (Posix.asAbsDir "/tmp")
> Posix.isRelative (Posix.asRelDir "/tmp")
> Posix.getPathString (Posix.asPath "/tmp" :: Posix.AbsDir) == "/tmp"
> Posix.getPathString (Posix.asPath "/tmp" :: Posix.RelDir) == "tmp"
> Windows.getPathString (Windows.asPath "\\tmp" :: Windows.AbsDir) == "\\tmp"
> Windows.getPathString (Windows.asPath "a:\\tmp" :: Windows.AbsDir) == "a:\\tmp"
> Windows.getPathString (Windows.asPath "tmp" :: Windows.RelDir) == "tmp"

asRelFile :: String -> RelFile Source

Use a String as a RelFile. No checking is done.

> Posix.getPathString (Posix.asRelFile "file.txt") == "file.txt"
> Posix.getPathString (Posix.asRelFile "/file.txt") == "file.txt"
> Posix.getPathString (Posix.asRelFile "tmp") == "tmp"
> Posix.getPathString (Posix.asRelFile "/tmp") == "tmp"

asRelDir :: String -> RelDir Source

Use a String as a RelDir. No checking is done.

> Posix.getPathString (Posix.asRelDir ".") == "."
> Posix.getPathString (Posix.asRelDir "file.txt") == "file.txt"
> Posix.getPathString (Posix.asRelDir "/file.txt") == "file.txt"
> Posix.getPathString (Posix.asRelDir "tmp") == "tmp"
> Posix.getPathString (Posix.asRelDir "/tmp") == "tmp"

asAbsFile :: String -> AbsFile Source

Use a String as an AbsFile. No checking is done.

> Posix.getPathString (Posix.asAbsFile "file.txt") == "/file.txt"
> Posix.getPathString (Posix.asAbsFile "/file.txt") == "/file.txt"
> Posix.getPathString (Posix.asAbsFile "tmp") == "/tmp"
> Posix.getPathString (Posix.asAbsFile "/tmp") == "/tmp"

asAbsDir :: String -> AbsDir Source

Use a String as an AbsDir. No checking is done.

> Posix.getPathString (Posix.asAbsDir "file.txt") == "/file.txt"
> Posix.getPathString (Posix.asAbsDir "/file.txt") == "/file.txt"
> Posix.getPathString (Posix.asAbsDir "tmp") == "/tmp"
> Posix.getPathString (Posix.asAbsDir "/tmp") == "/tmp"

asRelPath :: FileDirClass fd => String -> RelPath fd Source

Use a String as a 'RelPath fd'. No checking is done.

asAbsPath :: FileDirClass fd => String -> AbsPath fd Source

Use a String as an 'AbsPath fd'. No checking is done.

asFilePath :: AbsRelClass ar => String -> FilePath ar Source

Use a String as a 'FilePath ar'. No checking is done.

asDirPath :: AbsRelClass ar => String -> DirPath ar Source

Use a String as a 'DirPath ar'. No checking is done.

Checked Construction Functions

mkPathAbsOrRel :: FileDirClass fd => String -> Either (AbsPath fd) (RelPath fd) Source

Examines the supplied string and constructs an absolute or relative path as appropriate.

> Posix.mkPathAbsOrRel "/tmp" == Left (Posix.asAbsDir "/tmp")
> Posix.mkPathAbsOrRel  "tmp" == Right (Posix.asRelDir "tmp")
> Windows.mkPathAbsOrRel "\\tmp" == Left (Windows.asAbsDir "\\tmp")
> Windows.mkPathAbsOrRel "d:\\tmp" == Left (Windows.asAbsDir "d:\\tmp")
> Windows.mkPathAbsOrRel "tmp" == Right (Windows.asRelDir "tmp")

mkPathFileOrDir :: AbsRelClass ar => String -> IO (Maybe (Either (FilePath ar) (DirPath ar))) Source

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 :: FileDirClass fd => AbsDir -> String -> AbsPath fd Source

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

> Posix.mkAbsPath "/tmp" "foo.txt" == Posix.asAbsFile "/tmp/foo.txt"
> Posix.mkAbsPath "/tmp" "/etc/foo.txt" == Posix.asAbsFile "/etc/foo.txt"

mkAbsPathFromCwd :: FileDirClass fd => String -> IO (AbsPath fd) Source

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

Basic Manipulation Functions

(</>) :: DirPath ar -> RelPath fd -> Path ar fd Source

Infix variant of combine.

> Posix.getPathString (Posix.asAbsDir "/tmp" </> Posix.asRelFile "file.txt") == "/tmp/file.txt"
> Posix.getPathString (Posix.asAbsDir "/tmp" </> Posix.asRelDir "dir" </> Posix.asRelFile "file.txt") == "/tmp/dir/file.txt"
> Posix.getPathString (Posix.asRelDir "dir" </> Posix.asRelFile "file.txt") == "dir/file.txt"
> Windows.getPathString (Windows.asAbsDir "\\tmp" Windows.</> Windows.asRelFile "file.txt") == "\\tmp\\file.txt"
> Windows.getPathString (Windows.asAbsDir "c:\\tmp" Windows.</> Windows.asRelFile "file.txt") == "c:\\tmp\\file.txt"
> Windows.getPathString (Windows.asAbsDir "c:" Windows.</> Windows.asRelDir "tmp" Windows.</> Windows.asRelFile "file.txt") == "c:\\tmp\\file.txt"
> Windows.getPathString (Windows.asRelDir "dir" Windows.</> Windows.asRelFile "file.txt") == "dir\\file.txt"

(<.>) :: FilePath ar -> String -> FilePath ar 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 ar -> String -> FilePath ar Source

Add an extension, even if there is already one there. E.g. addExtension "foo.txt" "bat" -> "foo.txt.bat".

> Posix.addExtension (Posix.asRelFile "file.txt") "bib" == "file.txt.bib"
> Posix.addExtension (Posix.asRelFile "file.") ".bib" == "file..bib"
> Posix.addExtension (Posix.asRelFile "file") ".bib" == "file.bib"
> Posix.addExtension (Posix.asRelFile "") "bib" == ".bib"
> Posix.addExtension (Posix.asRelFile "") ".bib" == ".bib"
> Posix.takeFileName (Posix.addExtension (Posix.asRelFile "") "ext") == ".ext"

combine :: DirPath ar -> RelPath fd -> Path ar fd Source

Join an (absolute or relative) directory path with a relative (file or directory) path to form a new path.

dropExtension :: FilePath ar -> FilePath ar Source

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

> Posix.dropExtension x == fst (Posix.splitExtension x)

dropExtensions :: FilePath ar -> FilePath ar Source

Drop all extensions

> not $ Posix.hasAnExtension (Posix.dropExtensions x)

replaceExtension :: FilePath ar -> String -> FilePath ar Source

Set the extension of a file, overwriting one if already present.

> Posix.replaceExtension (Posix.asRelFile "file.txt") ".bob" == "file.bob"
> Posix.replaceExtension (Posix.asRelFile "file.txt") "bob" == "file.bob"
> Posix.replaceExtension (Posix.asRelFile "file") ".bob" == "file.bob"
> Posix.replaceExtension (Posix.asRelFile "file.txt") "" == "file"
> Posix.replaceExtension (Posix.asRelFile "file.fred.bob") "txt" == "file.fred.txt"

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

Split on the extension. addExtension is the inverse.

> uncurry (<.>) (Posix.splitExtension x) == x
> uncurry Posix.addExtension (Posix.splitExtension x) == x
> Posix.splitExtension (Posix.asRelFile "file.txt") == ("file",".txt")
> Posix.splitExtension (Posix.asRelFile "file") == ("file","")
> Posix.splitExtension (Posix.asRelFile "file/file.txt") == ("file/file",".txt")
> Posix.splitExtension (Posix.asRelFile "file.txt/boris") == ("file.txt/boris","")
> Posix.splitExtension (Posix.asRelFile "file.txt/boris.ext") == ("file.txt/boris",".ext")
> Posix.splitExtension (Posix.asRelFile "file/path.txt.bob.fred") == ("file/path.txt.bob",".fred")

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

Split on all extensions

> Posix.splitExtensions (Posix.asRelFile "file.tar.gz") == ("file",".tar.gz")

takeBaseName :: FilePath ar -> RelFile Source

Get the basename of a file

> Posix.takeBaseName (Posix.asAbsFile "/tmp/somedir/myfile.txt") == "myfile"
> Posix.takeBaseName (Posix.asRelFile "./myfile.txt") == "myfile"
> Posix.takeBaseName (Posix.asRelFile "myfile.txt") == "myfile"

takeExtension :: FilePath ar -> String Source

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

> Posix.takeExtension x == snd (Posix.splitExtension x)
> Posix.takeExtension (Posix.addExtension x "ext") == ".ext"
> Posix.takeExtension (Posix.replaceExtension x "ext") == ".ext"

takeExtensions :: FilePath ar -> String Source

Get all extensions

> Posix.takeExtensions (Posix.asRelFile "file.tar.gz") == ".tar.gz"

takeFileName :: FilePath ar -> RelFile Source

Get the filename component of a file path (ie stripping all parent dirs)

> Posix.takeFileName (Posix.asAbsFile "/tmp/somedir/myfile.txt") == "myfile.txt"
> Posix.takeFileName (Posix.asRelFile "./myfile.txt") == "myfile.txt"
> Posix.takeFileName (Posix.asRelFile "myfile.txt") == "myfile.txt"

Auxillary Manipulation Functions

equalFilePath :: String -> String -> Bool Source

Check whether two strings are equal as file paths.

>       Posix.equalFilePath "/tmp/" "/tmp"
> not $ Posix.equalFilePath "/tmp" "tmp"
>       Windows.equalFilePath "file" "File"
> not $ Windows.equalFilePath "file" "dir"

joinPath :: FileDirClass fd => [String] -> RelPath 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.

> Posix.joinPath ["tmp","someDir","dir"] == Posix.asRelDir "tmp/someDir/dir"
> Posix.joinPath ["tmp","someDir","file.txt"] == Posix.asRelFile "tmp/someDir/file.txt"

normalise :: Path ar fd -> Path ar fd Source

Currently just transforms:

> Posix.normalise "/tmp/fred/./jim/./file" == Posix.asAbsFile "/tmp/fred/jim/file"

splitPath :: (AbsRelClass ar, FileDirClass fd) => Path ar fd -> (Bool, [RelDir], Maybe RelFile) Source

Deconstructs a path into its components.

> Posix.splitPath (Posix.asAbsDir "/tmp/someDir/mydir.dir") == (True, ["tmp","someDir","mydir.dir"], Nothing)
> Posix.splitPath (Posix.asAbsFile "/tmp/someDir/myfile.txt") == (True, ["tmp","someDir"], Just "myfile.txt")

makeRelative :: FileDirClass fd => AbsDir -> AbsPath fd -> RelPath 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.

> Posix.makeRelative "/tmp/somedir" "/tmp/somedir/anotherdir/file.txt" == Posix.asRelFile "anotherdir/file.txt"
> Posix.makeRelative "/tmp/somedir" "/tmp/somedir/anotherdir/dir" == Posix.asRelDir "anotherdir/dir"
> Windows.makeRelative "c:\\tmp\\somedir" "c:\\Tmp\\SomeDir\\AnotherDir\\File.txt" == Windows.asRelFile "AnotherDir\\File.txt"
> Windows.makeRelative "c:\\tmp\\somedir" "c:\\tmp\\somedir\\anotherdir\\dir" == Windows.asRelDir "anotherdir\\dir"

makeAbsolute :: AbsDir -> RelPath fd -> AbsPath fd Source

Joins an absolute directory with a relative path to construct a new absolute path.

> Posix.makeAbsolute "/tmp" "file.txt"      == Posix.asAbsFile "/tmp/file.txt"
> Posix.makeAbsolute "/tmp" "adir/file.txt" == Posix.asAbsFile "/tmp/adir/file.txt"
> Posix.makeAbsolute "/tmp" "adir/dir"      == Posix.asAbsDir "/tmp/adir/dir"

makeAbsoluteFromCwd :: RelPath fd -> IO (AbsPath fd) Source

Converts a relative path into an absolute one by prepending the current working directory.

genericMakeAbsolute :: AbsRelClass ar => AbsDir -> Path ar fd -> AbsPath fd Source

As for makeAbsolute, but for use when the path may already be absolute (in which case it is left unchanged).

> Posix.genericMakeAbsolute "/tmp" (Posix.asRelFile "file.txt")       == "/tmp/file.txt"
> Posix.genericMakeAbsolute "/tmp" (Posix.asRelFile "adir/file.txt")  == "/tmp/adir/file.txt"
> Posix.genericMakeAbsolute "/tmp" (Posix.asAbsFile "adir/file.txt")  == "/adir/file.txt"
> Posix.genericMakeAbsolute "/tmp" (Posix.asAbsFile "/adir/file.txt") == "/adir/file.txt"

genericMakeAbsoluteFromCwd :: AbsRelClass ar => Path ar fd -> IO (AbsPath fd) Source

As for makeAbsoluteFromCwd, but for use when the path may already be absolute (in which case it is left unchanged).

pathMap :: FileDirClass fd => (String -> String) -> Path ar fd -> Path ar fd Source

Map over the components of the path.

> Posix.pathMap (map toLower) "/tmp/Reports/SpreadSheets" == Posix.asAbsDir "/tmp/reports/spreadsheets"

Path Predicates

isAbsolute :: AbsRelClass ar => Path ar fd -> Bool Source

Test whether a Path ar fd is absolute.

> Posix.isAbsolute (Posix.asAbsFile "fred")
> Posix.isAbsolute (Posix.asAbsFile "/fred")
> Windows.isAbsolute (Windows.asAbsFile "\\fred")
> Windows.isAbsolute (Windows.asAbsFile "c:\\fred")

isAbsoluteString :: String -> Bool Source

Test whether the String would correspond to an absolute path if interpreted as a Path.

isRelative :: AbsRelClass ar => Path ar fd -> Bool Source

Invariant - this should return True iff arg is of type Path Rel _

 isRelative = not . isAbsolute
> Posix.isRelative (Posix.asRelFile "fred")
> Posix.isRelative (Posix.asRelFile "/fred")
> Windows.isRelative (Windows.asRelFile "fred")

isRelativeString :: String -> Bool Source

Test whether the String would correspond to a relative path if interpreted as a Path.

isRelativeString = not . isAbsoluteString

hasAnExtension :: FilePath ar -> Bool Source

Does the given filename have an extension?

> null (Posix.takeExtension x) == not (Posix.hasAnExtension x)

hasExtension :: String -> FilePath ar -> Bool Source

Does the given filename have the given extension?

> Posix.hasExtension ".hs" (Posix.asRelFile "MyCode.hs")
> Posix.hasExtension ".hs" (Posix.asRelFile "MyCode.bak.hs")
> not $ Posix.hasExtension ".hs" (Posix.asRelFile "MyCode.hs.bak")

Separators

addTrailingPathSeparator :: String -> String Source

This is largely for FilePath compatability

dropTrailingPathSeparator :: String -> String Source

This is largely for FilePath compatability

extSeparator :: Char Source

File extension character

> Posix.extSeparator == '.'

hasTrailingPathSeparator :: String -> Bool Source

This is largely for FilePath compatability

pathSeparator :: Char Source

The character that separates directories. In the case where more than one character is possible, pathSeparator is the 'ideal' one.

> Posix.isPathSeparator Posix.pathSeparator

pathSeparators :: [Char] Source

The list of all possible separators.

> Posix.pathSeparator `elem` Posix.pathSeparators

searchPathSeparator :: Char Source

The character that is used to separate the entries in the $PATH environment variable.

isExtSeparator :: Char -> Bool Source

Is the character an extension character?

> Posix.isExtSeparator a == (a == Posix.extSeparator)

isPathSeparator :: Char -> Bool Source

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

> Posix.isPathSeparator a == (a `elem` Posix.pathSeparators)

isSearchPathSeparator :: Char -> Bool Source

Is the character a file separator?

> Posix.isSearchPathSeparator a == (a == Posix.searchPathSeparator)

Generic Manipulation Functions

genericAddExtension :: FileDirClass fd => Path ar fd -> String -> Path ar fd Source

This is a more flexible variant of addExtension / <.> which can work with files or directories

> Posix.genericAddExtension "/" "x" == Posix.asAbsDir "/.x"
> Posix.genericAddExtension "/a" "x" == Posix.asAbsDir "/a.x"
> Posix.genericAddExtension "" "x" == Posix.asRelFile ".x"
> Posix.genericAddExtension "" "" == Posix.asRelFile ""