Safe Haskell | None |
---|---|
Language | Haskell98 |
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.
- data Path ar fd
- data Abs
- data Rel
- data File
- data Dir
- type AbsFile = Path Abs File
- type RelFile = Path Rel File
- type AbsDir = Path Abs Dir
- type RelDir = Path Rel Dir
- type AbsPath fd = Path Abs fd
- type RelPath fd = Path Rel fd
- type FilePath ar = Path ar File
- type DirPath ar = Path ar Dir
- class Private ar => AbsRelClass ar where
- class Private fd => FileDirClass fd where
- getPathString :: AbsRelClass ar => Path ar fd -> String
- rootDir :: AbsDir
- currentDir :: RelDir
- asPath :: String -> Path ar fd
- asRelFile :: String -> RelFile
- asRelDir :: String -> RelDir
- asAbsFile :: String -> AbsFile
- asAbsDir :: String -> AbsDir
- asRelPath :: String -> RelPath fd
- asAbsPath :: String -> AbsPath fd
- asFilePath :: String -> FilePath ar
- asDirPath :: String -> DirPath ar
- mkPathAbsOrRel :: String -> Either (AbsPath fd) (RelPath fd)
- mkPathFileOrDir :: AbsRelClass ar => String -> IO (Maybe (Either (FilePath ar) (DirPath ar)))
- mkAbsPath :: AbsDir -> String -> AbsPath fd
- mkAbsPathFromCwd :: String -> IO (AbsPath fd)
- (</>) :: DirPath ar -> RelPath fd -> Path ar fd
- (<.>) :: FilePath ar -> String -> FilePath ar
- addExtension :: FilePath ar -> String -> FilePath ar
- combine :: DirPath ar -> RelPath fd -> Path ar fd
- dropExtension :: FilePath ar -> FilePath ar
- dropExtensions :: FilePath ar -> FilePath ar
- dropFileName :: Path ar fd -> DirPath ar
- replaceExtension :: FilePath ar -> String -> FilePath ar
- replaceBaseName :: Path ar fd -> String -> Path ar fd
- replaceDirectory :: Path ar1 fd -> DirPath ar2 -> Path ar2 fd
- replaceFileName :: Path ar fd -> String -> Path ar fd
- splitExtension :: FilePath ar -> (FilePath ar, String)
- splitExtensions :: FilePath ar -> (FilePath ar, String)
- splitFileName :: Path ar fd -> (DirPath ar, RelPath fd)
- takeBaseName :: Path ar fd -> RelPath fd
- takeDirectory :: Path ar fd -> DirPath ar
- takeExtension :: FilePath ar -> String
- takeExtensions :: FilePath ar -> String
- takeFileName :: Path ar fd -> RelPath fd
- equalFilePath :: String -> String -> Bool
- joinPath :: [String] -> Path ar fd
- normalise :: Path ar fd -> Path ar fd
- splitPath :: FileDirClass fd => Path ar fd -> ([RelDir], Maybe RelFile)
- makeRelative :: AbsDir -> AbsPath fd -> RelPath fd
- makeAbsolute :: AbsDir -> RelPath fd -> AbsPath fd
- makeAbsoluteFromCwd :: RelPath fd -> IO (AbsPath fd)
- genericMakeAbsolute :: AbsRelClass ar => AbsDir -> Path ar fd -> AbsPath fd
- genericMakeAbsoluteFromCwd :: AbsRelClass ar => Path ar fd -> IO (AbsPath fd)
- pathMap :: (String -> String) -> Path ar fd -> Path ar fd
- isAbsolute :: AbsRelClass ar => Path ar fd -> Bool
- isAbsoluteString :: String -> Bool
- isRelative :: AbsRelClass ar => Path ar fd -> Bool
- isRelativeString :: String -> Bool
- hasAnExtension :: FilePath ar -> Bool
- hasExtension :: String -> FilePath ar -> Bool
- addTrailingPathSeparator :: String -> String
- dropTrailingPathSeparator :: String -> String
- extSeparator :: Char
- hasTrailingPathSeparator :: String -> Bool
- pathSeparator :: Char
- pathSeparators :: [Char]
- searchPathSeparator :: Char
- isExtSeparator :: Char -> Bool
- isPathSeparator :: Char -> Bool
- isSearchPathSeparator :: Char -> Bool
- genericAddExtension :: Path ar fd -> String -> Path ar fd
- genericDropExtension :: Path ar fd -> Path ar fd
- genericDropExtensions :: Path ar fd -> Path ar fd
- genericSplitExtension :: Path ar fd -> (Path ar fd, String)
- genericSplitExtensions :: Path ar fd -> (Path ar fd, String)
- genericTakeExtension :: Path ar fd -> String
- genericTakeExtensions :: Path ar fd -> String
The main filepath (& dirpath) abstract type
This is the main filepath abstract datatype
Phantom Types
Type Synonyms
Classes
class Private ar => AbsRelClass ar where Source
This class allows selective behaviour for absolute and relative paths and is mostly for internal use.
class Private fd => FileDirClass fd where Source
This class allows selective behaviour for file and directory paths and is mostly for internal use.
Path to String conversion
getPathString :: AbsRelClass ar => Path ar fd -> String Source
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"
asFilePath :: String -> FilePath ar Source
Use a String
as a 'FilePath 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
mkAbsPathFromCwd :: String -> IO (AbsPath fd) Source
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)
dropFileName :: Path ar fd -> DirPath ar Source
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"
takeDirectory :: Path ar fd -> DirPath ar Source
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
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
is absolute.Path
ar fd
> isAbsolute (asAbsFile "fred") == True > isAbsolute (asRelFile "fred") == False > isAbsolute (asAbsFile "/fred") == True > isAbsolute (asRelFile "/fred") == False
isAbsoluteString :: String -> Bool Source
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
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
File extension character
> extSeparator == '.'
hasTrailingPathSeparator :: String -> Bool Source
This is largely for FilePath
compatability
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 (==
, use this. Test if something
is a path separator.pathSeparator
)
> 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"
genericDropExtension :: Path ar fd -> Path ar fd Source
genericDropExtensions :: Path ar fd -> Path ar fd Source
genericSplitExtension :: Path ar fd -> (Path ar fd, String) Source
genericSplitExtensions :: Path ar fd -> (Path ar fd, String) Source
genericTakeExtension :: Path ar fd -> String Source
genericTakeExtensions :: Path ar fd -> String Source