Safe Haskell | None |
---|---|
Language | Haskell98 |
Path
Description
A normalizing well-typed path type.
- data Path b t
- data Abs
- data Rel
- data File
- data Dir
- 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)
- data PathParseException
- mkAbsDir :: FilePath -> Q Exp
- mkRelDir :: FilePath -> Q Exp
- mkAbsFile :: FilePath -> Q Exp
- mkRelFile :: FilePath -> Q Exp
- (</>) :: Path b Dir -> Path Rel t -> Path b t
- stripDir :: Path b Dir -> Path b t -> Maybe (Path Rel t)
- isParentOf :: Path b Dir -> Path b t -> Bool
- parentAbs :: Path Abs t -> Path Abs Dir
- filename :: Path b File -> Path Rel File
- toFilePath :: Path b t -> FilePath
Types
Path of some base and type.
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.
Instances
Eq (Path b t) | String equality. The following property holds: show x == show y ≡ x == y |
Ord (Path b t) | String ordering. The following property holds: show x `compare` show y ≡ x `compare` y |
Show (Path b t) | Same as The following property holds: x == y ≡ show x == show y |
Generic (Path b t) | |
Typeable (* -> * -> *) Path | |
type Rep (Path b t) |
Parsing
parseAbsDir :: MonadThrow m => FilePath -> m (Path Abs Dir) Source
Get a location for an absolute directory. Produces a normalized path which always ends in a path separator.
Throws: PathParseException
parseRelDir :: MonadThrow m => FilePath -> m (Path Rel Dir) Source
Get a location for a relative directory. Produces a normalized path which always ends in a path separator.
Throws: PathParseException
parseAbsFile :: MonadThrow m => FilePath -> m (Path Abs File) Source
Get a location for an absolute file.
Throws: PathParseException
parseRelFile :: MonadThrow m => FilePath -> m (Path Rel File) Source
Get a location for a relative file.
Throws: PathParseException
data PathParseException Source
Exception when parsing a location.
Constructors
mkAbsDir :: FilePath -> Q Exp Source
Make a 'Path Abs Dir'.
Remember: due to the nature of absolute paths this (e.g. /home/foo
)
may compile on your platform, but it may not compile on another
platform (Windows).
mkAbsFile :: FilePath -> Q Exp Source
Make a 'Path Abs File'.
Remember: due to the nature of absolute paths this (e.g. /home/foo
)
may compile on your platform, but it may not compile on another
platform (Windows).
Operations
(</>) :: Path b Dir -> Path Rel t -> Path b t 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 …)
stripDir :: Path b Dir -> Path b t -> Maybe (Path Rel t) Source
Strip directory from path, making it relative to that directory.
Returns Nothing
if directory is not a parent of the path.
The following properties hold:
stripDir parent (parent </> child) = child
Cases which are proven not possible:
stripDir (a :: Path Abs …) (b :: Path Rel …)
stripDir (a :: Path Rel) (b :: Path Abs …)
In other words the bases must match.
isParentOf :: Path b Dir -> Path b t -> Bool Source
Is p a parent of the given location? Implemented in terms of
stripDir
. The bases must match.
parentAbs :: Path Abs t -> Path Abs Dir Source
Take the absolute parent directory from the absolute path.
The following properties hold:
parentAbs (parent </> child) == parent
On the root, getting the parent is idempotent:
parentAbs (parentAbs "/") = "/"
filename :: Path b File -> Path Rel File Source
Extract the relative filename from a given location.
The following properties hold:
filename (parent </> filename a) == a
Conversion
toFilePath :: Path b t -> FilePath Source
Convert to a FilePath
type.