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

System.Path

Contents

Description

This module provides type-safe access to filepath manipulations.

It is designed to be imported instead of System.FilePath and System.Directory. (It is intended to provide versions of functions from those modules which have equivalent functionality but are more typesafe).

The heart of this module is the Path ar fd abstract type which represents file and directory paths. The idea is that there are two phantom type parameters - the first should be Abs or Rel, and the second File or Dir. A number of type synonyms are provided for common types:

 type AbsFile    = Path Abs File
 type RelFile    = Path Rel File
 type AbsDir     = Path Abs Dir
 type RelDir     = Path Rel Dir
 type RelPath fd = Path Rel fd
 type DirPath ar = Path ar Dir

The type of the combine (aka </>) function gives the idea:

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

Together this enables us to give more meaningful types to a lot of the functions, and (hopefully) catch a bunch more errors at compile time.

The basic API (and properties satisfied) are heavily influenced by Neil Mitchell's System.FilePath module.

WARNING --- THE API IS NOT YET STABLE --- WARNING

Ben Moseley - (c) Jan 2009

Synopsis

The main filepath (& dirpath) abstract type

data Path ar fd Source

This is the main filepath abstract datatype

Instances

Eq (Path ar fd) 
Ord (Path ar fd) 
AbsRelClass ar => Read (Path ar fd) 
AbsRelClass ar => Show (Path ar fd) 
Arbitrary (Path ar Dir) 
Arbitrary (Path ar File) 

Phantom Types

data Abs Source

Instances

AbsRelClass Abs 

data Rel Source

Instances

AbsRelClass Rel 

data File Source

Instances

FileDirClass File 
Arbitrary (Path ar File) 

data Dir Source

Instances

FileDirClass Dir 
Arbitrary (Path ar Dir) 

Type Synonyms

type AbsPath fd = Path Abs fdSource

type RelPath fd = Path Rel fdSource

type FilePath ar = Path ar FileSource

type DirPath ar = Path ar DirSource

Path to String conversion

getPathString :: AbsRelClass ar => Path ar fd -> StringSource

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

Constants

Unchecked Construction Functions

mkPath :: String -> Path ar fdSource

Convert a String into a Path whose type is determined by its context.

Checked Construction Functions

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

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

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.

Basic Manipulation Functions

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

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

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

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

addExtension :: FilePath ar -> String -> FilePath arSource

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

> addExtension (mkFile "file.txt") "bib" == (mkFile "file.txt.bib")
> addExtension (mkFile "file.") ".bib" == (mkFile "file..bib")
> addExtension (mkFile "file") ".bib" == (mkFile "file.bib")
> takeFileName (addExtension (mkFile "") "ext") == mkFile ".ext"
 Windows: addExtension "\\\\share" ".txt" == "\\\\share\\.txt"

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

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

dropExtension :: FilePath ar -> FilePath arSource

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

> dropExtension x == fst (splitExtension x)

dropExtensions :: FilePath ar -> FilePath arSource

Drop all extensions

> not $ hasExtension (dropExtensions x)

replaceExtension :: FilePath ar -> String -> FilePath arSource

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

> replaceExtension (mkFile "file.txt") ".bob" == (mkFile "file.bob")
> replaceExtension (mkFile "file.txt") "bob" == (mkFile "file.bob")
> replaceExtension (mkFile "file") ".bob" == (mkFile "file.bob")
> replaceExtension (mkFile "file.txt") "" == (mkFile "file")
> replaceExtension (mkFile "file.fred.bob") "txt" == (mkFile "file.fred.txt")

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

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

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

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 (mkFile "file.txt") == (mkFile "file",".txt")
> splitExtension (mkFile "file") == (mkFile "file","")
> splitExtension (mkFile "file/file.txt") == (mkFile "file/file",".txt")
> splitExtension (mkFile "file.txt/boris") == (mkFile "file.txt/boris","")
> splitExtension (mkFile "file.txt/boris.ext") == (mkFile "file.txt/boris",".ext")
> splitExtension (mkFile "file/path.txt.bob.fred") == (mkFile "file/path.txt.bob",".fred")

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

Split on all extensions

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

takeExtension :: FilePath ar -> StringSource

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

Get all extensions

> takeExtensions (mkFile "file.tar.gz") == ".tar.gz"

Auxillary Manipulation Functions

joinPath :: [String] -> Path ar fdSource

Constructs a Path from a list of components.

normalise :: Path ar fd -> Path ar fdSource

Currently just transforms:

> normalise (mkFile "/tmp/fred/./jim/./file") == mkFile "/tmp/fred/jim/file"

Path Predicates

isAbsolute :: AbsRelClass ar => Path ar fd -> BoolSource

isRelative :: AbsRelClass ar => Path ar fd -> BoolSource

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

hasExtension :: FilePath ar -> BoolSource

Does the given filename have an extension?

> null (takeExtension x) == not (hasExtension x)

Separators

addTrailingPathSeparator :: String -> StringSource

This is largely for System.FilePath compatability

dropTrailingPathSeparator :: String -> StringSource

This is largely for System.FilePath compatability

extSeparator :: CharSource

File extension character

> extSeparator == '.'

hasTrailingPathSeparator :: String -> BoolSource

This is largely for System.FilePath compatability

pathSeparator :: CharSource

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

 Windows: pathSeparator == '\\'
 Posix:   pathSeparator ==  '/'
> isPathSeparator pathSeparator

pathSeparators :: [Char]Source

The list of all possible separators.

 Windows: pathSeparators == ['\\', '/']
 Posix:   pathSeparators == ['/']
> pathSeparator `elem` pathSeparators

searchPathSeparator :: CharSource

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

 Windows: searchPathSeparator == ';'
 Posix:   searchPathSeparator == ':'

isExtSeparator :: Char -> BoolSource

Is the character an extension character?

> isExtSeparator a == (a == extSeparator)

isPathSeparator :: Char -> BoolSource

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

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

isSearchPathSeparator :: Char -> BoolSource

Is the character a file separator?

> isSearchPathSeparator a == (a == searchPathSeparator)

Flexible Manipulation Functions

addFileOrDirExtension :: Path ar fd -> String -> Path ar fdSource

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

> addFileOrDirExtension (mkFile "/") "x" == (mkFile "/.x")

System.Directory replacements

getDirectoryContents :: AbsRelClass ar => DirPath ar -> IO ([AbsDir], [AbsFile])Source

absDirectoryContents :: AbsRelClass ar => DirPath ar -> IO ([AbsDir], [AbsFile])Source

Retrieve the contents of a directory path (which may be relative) as absolute paths

relDirectoryContents :: AbsRelClass ar => DirPath ar -> IO ([RelDir], [RelFile])Source

Returns paths relative to the supplied (abs or relative) directory path. eg (for current working directory of /somewhere/cwd/):

 show (relDirectoryContents (mkRelDir "subDir1")) == (["subDir1A","subDir1B"],
                                                      ["file1A","file1B"])