Safe Haskell | None |
---|---|
Language | Haskell2010 |
This library provides a well-typed representation of paths in a filesystem
directory tree. A path is represented by a number of path components
separated by a path separator which is a /
on POSIX systems and can be a
/
or \
on Windows.
The root of the tree is represented by a /
on POSIX and a drive letter
followed by a /
or \
on Windows (e.g. C:\
). Paths can be absolute
or relative. An absolute path always starts from the root of the tree (e.g.
/x/y
) whereas a relative path never starts with the root (e.g. x/y
).
Just like we represent the notion of an absolute root by "/
", the same way
we represent the notion of a relative root by ".
". The relative root denotes
the directory which contains the first component of a relative path.
- data Path b t
- data Abs
- data Rel
- data File
- data Dir
- data PathException
- absdir :: QuasiQuoter
- reldir :: QuasiQuoter
- absfile :: QuasiQuoter
- relfile :: QuasiQuoter
- (</>) :: Path b Dir -> Path Rel t -> Path b t
- stripProperPrefix :: MonadThrow m => Path b Dir -> Path b t -> m (Path Rel t)
- isProperPrefixOf :: Path b Dir -> Path b t -> Bool
- parent :: Path b t -> Path b Dir
- filename :: Path b File -> Path Rel File
- dirname :: Path b Dir -> Path Rel Dir
- fileExtension :: Path b File -> String
- addFileExtension :: MonadThrow m => String -> Path b File -> m (Path b File)
- (<.>) :: MonadThrow m => Path b File -> String -> m (Path b File)
- setFileExtension :: MonadThrow m => String -> Path b File -> m (Path b File)
- (-<.>) :: MonadThrow m => Path b File -> String -> m (Path b File)
- parseAbsDir :: MonadThrow m => FilePath -> m (Path Abs Dir)
- parseRelDir :: MonadThrow m => FilePath -> m (Path Rel Dir)
- parseAbsFile :: MonadThrow m => FilePath -> m (Path Abs File)
- parseRelFile :: MonadThrow m => FilePath -> m (Path Rel File)
- toFilePath :: Path b t -> FilePath
- fromAbsDir :: Path Abs Dir -> FilePath
- fromRelDir :: Path Rel Dir -> FilePath
- fromAbsFile :: Path Abs File -> FilePath
- fromRelFile :: Path Rel File -> FilePath
- mkAbsDir :: FilePath -> Q Exp
- mkRelDir :: FilePath -> Q Exp
- mkAbsFile :: FilePath -> Q Exp
- mkRelFile :: FilePath -> Q Exp
- type PathParseException = PathException
- stripDir :: MonadThrow m => Path b Dir -> Path b t -> m (Path Rel t)
- isParentOf :: Path b Dir -> Path b t -> Bool
Types
Path of some base and type.
The type variables are:
b
— base, the base location of the path; absolute or relative.t
— type, whether file or directory.
Internally is a string. The string can be of two formats only:
- File format:
file.txt
,foo/bar.txt
,/foo/bar.txt
- Directory format:
foo/
,/foo/bar/
All directories end in a trailing separator. There are no duplicate
path separators //
, no ..
, no ./
, no ~/
, etc.
Eq (Path b t) Source # | String equality. The following property holds: show x == show y ≡ x == y |
Ord (Path b t) Source # | String ordering. The following property holds: show x `compare` show y ≡ x `compare` y |
Show (Path b t) Source # | Same as 'show . Path.toFilePath'. The following property holds: x == y ≡ show x == show y |
Hashable (Path b t) Source # | |
ToJSON (Path b t) Source # | |
FromJSON (Path Rel Dir) # | |
FromJSON (Path Rel File) # | |
FromJSON (Path Abs Dir) # | |
FromJSON (Path Abs File) # | |
NFData (Path b t) Source # | |
An absolute path.
A relative path; one without a root. Note that a ..
path component to
represent the parent directory is not allowed by this library.
A directory path.
Exceptions
data PathException Source #
Exceptions that can occur during path operations.
Since: 0.6.0
QuasiQuoters
Using the following requires the QuasiQuotes language extension.
For Windows users, the QuasiQuoters are especially beneficial because they
prevent Haskell from treating \
as an escape character.
This makes Windows paths easier to write.
[absfile|C:\chris\foo.txt|]
absdir :: QuasiQuoter Source #
reldir :: QuasiQuoter Source #
Operations
(</>) :: Path b Dir -> Path Rel t -> Path b t infixr 5 Source #
Append two paths.
The following cases are valid and the equalities hold:
$(mkAbsDir x) </> $(mkRelDir y) = $(mkAbsDir (x ++ "/" ++ y))
$(mkAbsDir x) </> $(mkRelFile y) = $(mkAbsFile (x ++ "/" ++ y))
$(mkRelDir x) </> $(mkRelDir y) = $(mkRelDir (x ++ "/" ++ y))
$(mkRelDir x) </> $(mkRelFile y) = $(mkRelFile (x ++ "/" ++ y))
The following are proven not possible to express:
$(mkAbsFile …) </> x
$(mkRelFile …) </> x
x </> $(mkAbsFile …)
x </> $(mkAbsDir …)
stripProperPrefix :: MonadThrow m => Path b Dir -> Path b t -> m (Path Rel t) Source #
If the directory in the first argument is a proper prefix of the path in
the second argument strip it from the second argument, generating a path
relative to the directory.
Throws NotAProperPrefix
if the directory is not a proper prefix of the
path.
The following properties hold:
stripProperPrefix x (x </> y) = y
Cases which are proven not possible:
stripProperPrefix (a :: Path Abs …) (b :: Path Rel …)
stripProperPrefix (a :: Path Rel …) (b :: Path Abs …)
In other words the bases must match.
Since: 0.6.0
isProperPrefixOf :: Path b Dir -> Path b t -> Bool Source #
Determines if the path in the first parameter is a proper prefix of the path in the second parameter.
The following properties hold:
not (x `isProperPrefixOf` x)
x `isProperPrefixOf` (x </> y)
Since: 0.6.0
parent :: Path b t -> Path b Dir Source #
Take the parent path component from a path.
The following properties hold:
parent (x </> y) == x parent "/x" == "/" parent "x" == "."
On the root (absolute or relative), getting the parent is idempotent:
parent "/" = "/" parent "." = "."
filename :: Path b File -> Path Rel File Source #
Extract the file part of a path.
The following properties hold:
filename (p </> a) == filename a
dirname :: Path b Dir -> Path Rel Dir Source #
Extract the last directory name of a path.
The following properties hold:
dirname $(mkRelDir ".") == $(mkRelDir ".")
dirname (p </> a) == dirname a
:: MonadThrow m | |
=> String | Extension to add |
-> Path b File | Old file name |
-> m (Path b File) | New file name with the desired extension added at the end |
Add extension to given file path. Throws if the resulting filename does not parse.
>>>
addFileExtension "txt $(mkRelFile "foo")
"foo.txt">>>
addFileExtension "symbols" $(mkRelFile "Data.List")
"Data.List.symbols">>>
addFileExtension ".symbols" $(mkRelFile "Data.List")
"Data.List.symbols">>>
addFileExtension "symbols" $(mkRelFile "Data.List.")
"Data.List..symbols">>>
addFileExtension ".symbols" $(mkRelFile "Data.List.")
"Data.List..symbols">>>
addFileExtension "evil/" $(mkRelFile "Data.List")
*** Exception: InvalidRelFile "Data.List.evil/"
Since: 0.6.1
:: MonadThrow m | |
=> Path b File | Old file name |
-> String | Extension to add |
-> m (Path b File) | New file name with the desired extension added at the end |
A synonym for addFileExtension
in the form of an operator.
See more examples there.
>>>
$(mkRelFile "Data.List") <.> "symbols"
"Data.List.symbols">>>
$(mkRelFile "Data.List") <.> "evil/"
*** Exception: InvalidRelFile "Data.List.evil/"
Since: 0.6.1
:: MonadThrow m | |
=> String | Extension to set |
-> Path b File | Old file name |
-> m (Path b File) | New file name with the desired extension |
Replace/add extension to given file path. Throws if the resulting filename does not parse.
Since: 0.5.11
:: MonadThrow m | |
=> Path b File | Old file name |
-> String | Extension to set |
-> m (Path b File) | New file name with the desired extension |
A synonym for setFileExtension
in the form of an operator.
Since: 0.6.0
Parsing
parseAbsDir :: MonadThrow m => FilePath -> m (Path Abs Dir) Source #
Convert an absolute FilePath
to a normalized absolute dir Path
.
Throws: InvalidAbsDir
when the supplied path:
- is not an absolute path
- contains a
..
path component representing the parent directory - is not a valid path (See
isValid
)
parseRelDir :: MonadThrow m => FilePath -> m (Path Rel Dir) Source #
Convert a relative FilePath
to a normalized relative dir Path
.
Throws: InvalidRelDir
when the supplied path:
- is not a relative path
- is
""
- contains a
..
path component representing the parent directory - is not a valid path (See
isValid
)
parseAbsFile :: MonadThrow m => FilePath -> m (Path Abs File) Source #
Convert an absolute FilePath
to a normalized absolute file Path
.
Throws: InvalidAbsFile
when the supplied path:
- is not an absolute path
is a directory path i.e.
- has a trailing path separator
- is
.
or ends in/.
- contains a
..
path component representing the parent directory - is not a valid path (See
isValid
)
parseRelFile :: MonadThrow m => FilePath -> m (Path Rel File) Source #
Convert a relative FilePath
to a normalized relative file Path
.
Throws: InvalidRelFile
when the supplied path:
- is not a relative path
- is
""
is a directory path i.e.
- has a trailing path separator
- is
.
or ends in/.
- contains a
..
path component representing the parent directory - is not a valid path (See
isValid
)
Conversion
toFilePath :: Path b t -> FilePath Source #
Convert to a FilePath
type.
All directories have a trailing slash, so if you want no trailing
slash, you can use dropTrailingPathSeparator
from
the filepath package.
TemplateHaskell constructors
These require the TemplateHaskell language extension.
Deprecated
type PathParseException = PathException Source #
Deprecated: Please use PathException instead.
Same as PathException
.
stripDir :: MonadThrow m => Path b Dir -> Path b t -> m (Path Rel t) Source #
Deprecated: Please use stripProperPrefix instead.
Same as stripProperPrefix
.
isParentOf :: Path b Dir -> Path b t -> Bool Source #
Deprecated: Please use isProperPrefixOf instead.
Same as isProperPrefixOf
.