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

Safe HaskellNone
LanguageHaskell98

System.Path.Posix

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

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

Allow use of OverloadedStrings if desired

Arbitrary (Path ar Dir) Source 
Arbitrary (Path ar File) 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.

Methods

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

class Private fd => FileDirClass fd where Source

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

Methods

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

Path to String conversion

getPathString :: AbsRelClass ar => Path ar fd -> String Source

Convert the Path into a plain String. This is simply an alias for show.

Constants

Unchecked Construction Functions

asPath :: String -> Path ar fd Source

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

> asPath "/tmp" == "/tmp"
> asPath "file.txt" == "file.txt"
> isAbsolute (asPath "/tmp" :: AbsDir) == True
> isAbsolute (asPath "/tmp" :: RelDir) == False
> getPathString (asPath "/tmp" :: AbsDir) == "/tmp"
> getPathString (asPath "/tmp" :: RelDir) == "tmp"

asRelFile :: String -> RelFile Source

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

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

asRelDir :: String -> RelDir Source

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

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

asAbsFile :: String -> AbsFile Source

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

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

asAbsDir :: String -> AbsDir Source

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

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

asRelPath :: String -> RelPath fd Source

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

asAbsPath :: String -> AbsPath fd Source

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

asFilePath :: String -> FilePath ar Source

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

asDirPath :: String -> DirPath ar Source

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

Checked Construction Functions

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

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

> either id (const "fred") (mkPathAbsOrRel "/tmp") == "/tmp"
> either id (const "fred") (mkPathAbsOrRel  "tmp") == "fred"

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

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

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

mkAbsPathFromCwd :: 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

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

(<.>) :: FilePath ar -> String -> FilePath ar Source

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

> addExtension "file.txt" "bib" == "file.txt.bib"
> addExtension "file." ".bib" == "file..bib"
> addExtension "file" ".bib" == "file.bib"
> takeFileName (addExtension "" "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.

> dropExtension x == fst (splitExtension x)

dropExtensions :: FilePath ar -> FilePath ar Source

Drop all extensions

> not $ hasAnExtension (dropExtensions x)

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

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

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

replaceBaseName :: Path ar fd -> String -> Path ar fd Source

replaceDirectory :: Path ar1 fd -> DirPath ar2 -> Path ar2 fd Source

replaceFileName :: Path ar fd -> String -> Path ar fd Source

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

Split on the extension. addExtension is the inverse.

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

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

Split on all extensions

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

splitFileName :: Path ar fd -> (DirPath ar, RelPath fd) Source

takeBaseName :: Path ar fd -> RelPath fd Source

Get the basename of a file

> takeBaseName "/tmp/somedir/myfile.txt" == "myfile"
> takeBaseName "./myfile.txt" == "myfile"
> takeBaseName "myfile.txt" == "myfile"

takeExtension :: FilePath ar -> String Source

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

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

takeExtensions :: FilePath ar -> String Source

Get all extensions

> takeExtensions "file.tar.gz" == ".tar.gz"

takeFileName :: Path ar fd -> RelPath fd Source

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

> takeFileName "/tmp/somedir/myfile.txt" == "myfile.txt"
> takeFileName "./myfile.txt" == "myfile.txt"
> takeFileName "myfile.txt" == "myfile.txt"

Auxillary Manipulation Functions

equalFilePath :: String -> String -> Bool Source

Check whether two strings are equal as file paths.

> equalFilePath "/tmp/" "/tmp" == True
> equalFilePath "/tmp"  "tmp"  == False

joinPath :: [String] -> Path ar fd Source

Constructs a Path from a list of components.

> joinPath ["/tmp","someDir","file.txt"] == "/tmp/someDir/file.txt"
> (joinPath ["/tmp","someDir","file.txt"] :: RelFile) == "tmp/someDir/file.txt"

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

Currently just transforms:

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

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

Deconstructs a path into its components.

> splitPath ("/tmp/someDir/myfile.txt" :: AbsDir)  == (["tmp","someDir","myfile.txt"],Nothing)
> splitPath ("/tmp/someDir/myfile.txt" :: AbsFile) == (["tmp","someDir"],Just "myfile.txt")
> splitPath (asAbsFile "/tmp/someDir/myfile.txt")  == (["tmp","someDir"],Just "myfile.txt")

makeRelative :: 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.

> makeRelative "/tmp/somedir" "/tmp/somedir/anotherdir/file.txt" == "anotherdir/file.txt"

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

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

> makeAbsolute "/tmp" "file.txt"      == "/tmp/file.txt"
> makeAbsolute "/tmp" "adir/file.txt" == "/tmp/adir/file.txt"

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

> genericMakeAbsolute "/tmp" (asRelFile "file.txt")       == "/tmp/file.txt"
> genericMakeAbsolute "/tmp" (asRelFile "adir/file.txt")  == "/tmp/adir/file.txt"
> genericMakeAbsolute "/tmp" (asAbsFile "adir/file.txt")  == "/adir/file.txt"
> genericMakeAbsolute "/tmp" (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 :: (String -> String) -> Path ar fd -> Path ar fd Source

Map over the components of the path.

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

Path Predicates

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

Test whether a Path ar fd is absolute.

> isAbsolute (asAbsFile "fred")  == True
> isAbsolute (asRelFile "fred")  == False
> isAbsolute (asAbsFile "/fred") == True
> isAbsolute (asRelFile "/fred") == False

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

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 (takeExtension x) == not (hasAnExtension x)

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

Does the given filename have the given extension?

> hasExtension ".hs" "MyCode.hs" == True
> hasExtension ".hs" "MyCode.hs.bak" == False
> hasExtension ".hs" "MyCode.bak.hs" == True

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

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

> isPathSeparator pathSeparator

pathSeparators :: [Char] Source

The list of all possible separators.

> pathSeparator `elem` 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?

> isExtSeparator a == (a == extSeparator)

isPathSeparator :: Char -> Bool Source

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

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

isSearchPathSeparator :: Char -> Bool Source

Is the character a file separator?

> isSearchPathSeparator a == (a == searchPathSeparator)

Generic Manipulation Functions

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

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

> genericAddExtension "/" "x" == "/.x"