Safe Haskell | None |
---|---|
Language | Haskell2010 |
This library provides a well-typed representation of paths in a filesystem directory tree.
Note: This module is for working with Posix style paths. Importing Path is usually better.
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.
Synopsis
- data Path b t
- data Abs
- data Rel
- data File
- data Dir
- data SomeBase t
- 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
- replaceProperPrefix :: MonadThrow m => Path b Dir -> Path b' Dir -> Path b t -> m (Path b' t)
- parent :: Path b t -> Path b Dir
- filename :: Path b File -> Path Rel File
- dirname :: Path b Dir -> Path Rel Dir
- addExtension :: MonadThrow m => String -> Path b File -> m (Path b File)
- splitExtension :: MonadThrow m => Path b File -> m (Path b File, String)
- fileExtension :: MonadThrow m => Path b File -> m String
- replaceExtension :: MonadThrow m => String -> Path b File -> m (Path b File)
- mapSomeBase :: (forall b. Path b t -> Path b t') -> SomeBase t -> SomeBase t'
- prjSomeBase :: (forall b. Path b t -> a) -> SomeBase t -> a
- 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)
- parseSomeDir :: MonadThrow m => FilePath -> m (SomeBase Dir)
- parseSomeFile :: MonadThrow m => FilePath -> m (SomeBase 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
- fromSomeDir :: SomeBase Dir -> FilePath
- fromSomeFile :: SomeBase 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
- 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)
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.
Instances
(Typeable b, Typeable t) => Lift (Path b t :: Type) Source # | |
Eq (Path b t) Source # | String equality. The following property holds: show x == show y ≡ x == y |
(Data b, Data t) => Data (Path b t) Source # | |
Defined in Path.Internal.Posix gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Path b t -> c (Path b t) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Path b t) # toConstr :: Path b t -> Constr # dataTypeOf :: Path b t -> DataType # dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (Path b t)) # dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (Path b t)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> Path b t -> Path b t # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Path b t -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Path b t -> r # gmapQ :: (forall d. Data d => d -> u) -> Path b t -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Path b t -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Path b t -> m (Path b t) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Path b t -> m (Path b t) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Path b t -> m (Path b t) # | |
Ord (Path b t) Source # | String ordering. The following property holds: show x `compare` show y ≡ x `compare` y |
Defined in Path.Internal.Posix | |
Show (Path b t) Source # | Same as 'show . Path.toFilePath'. The following property holds: x == y ≡ show x == show y |
Generic (Path b t) Source # | |
Hashable (Path b t) Source # | |
Defined in Path.Internal.Posix | |
ToJSON (Path b t) Source # | |
Defined in Path.Internal.Posix | |
ToJSONKey (Path b t) Source # | |
Defined in Path.Internal.Posix toJSONKey :: ToJSONKeyFunction (Path b t) # toJSONKeyList :: ToJSONKeyFunction [Path b t] # | |
FromJSON (Path Rel Dir) Source # | |
FromJSON (Path Rel File) Source # | |
FromJSON (Path Abs Dir) Source # | |
FromJSON (Path Abs File) Source # | |
FromJSONKey (Path Rel Dir) Source # | |
Defined in Path.Posix | |
FromJSONKey (Path Rel File) Source # | |
Defined in Path.Posix | |
FromJSONKey (Path Abs Dir) Source # | |
Defined in Path.Posix | |
FromJSONKey (Path Abs File) Source # | |
Defined in Path.Posix | |
NFData (Path b t) Source # | |
Defined in Path.Internal.Posix | |
type Rep (Path b t) Source # | |
Defined in Path.Internal.Posix |
An absolute path.
Instances
Data Abs Source # | |
Defined in Path.Posix gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Abs -> c Abs # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Abs # dataTypeOf :: Abs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Abs) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Abs) # gmapT :: (forall b. Data b => b -> b) -> Abs -> Abs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Abs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Abs -> r # gmapQ :: (forall d. Data d => d -> u) -> Abs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Abs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Abs -> m Abs # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Abs -> m Abs # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Abs -> m Abs # | |
FromJSON (Path Abs Dir) Source # | |
FromJSON (Path Abs File) Source # | |
FromJSONKey (Path Abs Dir) Source # | |
Defined in Path.Posix | |
FromJSONKey (Path Abs File) Source # | |
Defined in Path.Posix |
A relative path; one without a root. Note that a ..
path component to
represent the parent directory is not allowed by this library.
Instances
Data Rel Source # | |
Defined in Path.Posix gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Rel -> c Rel # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Rel # dataTypeOf :: Rel -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Rel) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Rel) # gmapT :: (forall b. Data b => b -> b) -> Rel -> Rel # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Rel -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Rel -> r # gmapQ :: (forall d. Data d => d -> u) -> Rel -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Rel -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Rel -> m Rel # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Rel -> m Rel # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Rel -> m Rel # | |
FromJSON (Path Rel Dir) Source # | |
FromJSON (Path Rel File) Source # | |
FromJSONKey (Path Rel Dir) Source # | |
Defined in Path.Posix | |
FromJSONKey (Path Rel File) Source # | |
Defined in Path.Posix |
A file path.
Instances
Data File Source # | |
Defined in Path.Posix gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> File -> c File # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c File # dataTypeOf :: File -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c File) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c File) # gmapT :: (forall b. Data b => b -> b) -> File -> File # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> File -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> File -> r # gmapQ :: (forall d. Data d => d -> u) -> File -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> File -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> File -> m File # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> File -> m File # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> File -> m File # | |
FromJSON (SomeBase File) Source # | |
FromJSON (Path Rel File) Source # | |
FromJSON (Path Abs File) Source # | |
FromJSONKey (Path Rel File) Source # | |
Defined in Path.Posix | |
FromJSONKey (Path Abs File) Source # | |
Defined in Path.Posix |
A directory path.
Instances
Data Dir Source # | |
Defined in Path.Posix gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Dir -> c Dir # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Dir # dataTypeOf :: Dir -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Dir) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Dir) # gmapT :: (forall b. Data b => b -> b) -> Dir -> Dir # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Dir -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Dir -> r # gmapQ :: (forall d. Data d => d -> u) -> Dir -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Dir -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Dir -> m Dir # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Dir -> m Dir # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Dir -> m Dir # | |
FromJSON (SomeBase Dir) Source # | |
FromJSON (Path Rel Dir) Source # | |
FromJSON (Path Abs Dir) Source # | |
FromJSONKey (Path Rel Dir) Source # | |
Defined in Path.Posix | |
FromJSONKey (Path Abs Dir) Source # | |
Defined in Path.Posix |
Path of some type. t
represents the type, whether file or
directory. Pattern match to find whether the path is absolute or
relative.
Instances
Eq (SomeBase t) Source # | |
Ord (SomeBase t) Source # | |
Show (SomeBase t) Source # | |
Generic (SomeBase t) Source # | |
Hashable (SomeBase t) Source # | |
Defined in Path.Posix | |
ToJSON (SomeBase t) Source # | |
Defined in Path.Posix | |
FromJSON (SomeBase Dir) Source # | |
FromJSON (SomeBase File) Source # | |
NFData (SomeBase t) Source # | |
Defined in Path.Posix | |
type Rep (SomeBase t) Source # | |
Defined in Path.Posix type Rep (SomeBase t) = D1 ('MetaData "SomeBase" "Path.Posix" "path-0.9.2-2Irdd6ZnAkFHzbRma7tm5z" 'False) (C1 ('MetaCons "Abs" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Path Abs t))) :+: C1 ('MetaCons "Rel" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Path Rel t)))) |
Exceptions
data PathException Source #
Exceptions that can occur during path operations.
Since: 0.6.0
Instances
Eq PathException Source # | |
Defined in Path.Posix (==) :: PathException -> PathException -> Bool # (/=) :: PathException -> PathException -> Bool # | |
Show PathException Source # | |
Defined in Path.Posix showsPrec :: Int -> PathException -> ShowS # show :: PathException -> String # showList :: [PathException] -> ShowS # | |
Exception PathException Source # | |
Defined in Path.Posix |
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
replaceProperPrefix :: MonadThrow m => Path b Dir -> Path b' Dir -> Path b t -> m (Path b' t) Source #
Change from one directory prefix to another.
Throw NotAProperPrefix
if the first argument is not a proper prefix of the
path.
>>>
replaceProperPrefix $(mkRelDir "foo") $(mkRelDir "bar") $(mkRelFile "foo/file.txt") == $(mkRelFile "bar/file.txt")
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.
>>>
addExtension ".foo" $(mkRelFile "name" ) == Just $(mkRelFile "name.foo" )
>>>
addExtension ".foo." $(mkRelFile "name" ) == Just $(mkRelFile "name.foo." )
>>>
addExtension ".foo.." $(mkRelFile "name" ) == Just $(mkRelFile "name.foo.." )
>>>
addExtension ".foo" $(mkRelFile "name.bar" ) == Just $(mkRelFile "name.bar.foo")
>>>
addExtension ".foo" $(mkRelFile ".name" ) == Just $(mkRelFile ".name.foo" )
>>>
addExtension ".foo" $(mkRelFile "name." ) == Just $(mkRelFile "name..foo" )
>>>
addExtension ".foo" $(mkRelFile "..." ) == Just $(mkRelFile "....foo" )
Throws an InvalidExtension
exception if the extension is not valid. A
valid extension starts with a .
followed by one or more characters not
including .
followed by zero or more .
in trailing position. Moreover,
an extension must be a valid filename, notably it cannot include path
separators. Particularly, .foo.bar
is an invalid extension, instead you
have to first set .foo
and then .bar
individually. Some examples of
invalid extensions are:
>>>
addExtension "foo" $(mkRelFile "name")
>>>
addExtension "..foo" $(mkRelFile "name")
>>>
addExtension ".foo.bar" $(mkRelFile "name")
>>>
addExtension ".foo/bar" $(mkRelFile "name")
Since: 0.7.0
splitExtension :: MonadThrow m => Path b File -> m (Path b File, String) Source #
splitExtension
is the inverse of addExtension
. It splits the given
file path into a valid filename and a valid extension.
>>>
splitExtension $(mkRelFile "name.foo" ) == Just ($(mkRelFile "name" ), ".foo" )
>>>
splitExtension $(mkRelFile "name.foo." ) == Just ($(mkRelFile "name" ), ".foo." )
>>>
splitExtension $(mkRelFile "name.foo.." ) == Just ($(mkRelFile "name" ), ".foo..")
>>>
splitExtension $(mkRelFile "name.bar.foo" ) == Just ($(mkRelFile "name.bar"), ".foo" )
>>>
splitExtension $(mkRelFile ".name.foo" ) == Just ($(mkRelFile ".name" ), ".foo" )
>>>
splitExtension $(mkRelFile "name..foo" ) == Just ($(mkRelFile "name." ), ".foo" )
>>>
splitExtension $(mkRelFile "....foo" ) == Just ($(mkRelFile "..." ), ".foo" )
Throws HasNoExtension
exception if the filename does not have an extension
or in other words it cannot be split into a valid filename and a valid
extension. The following cases throw an exception, please note that "." and
".." are not valid filenames:
>>>
splitExtension $(mkRelFile "name" )
>>>
splitExtension $(mkRelFile "name." )
>>>
splitExtension $(mkRelFile "name.." )
>>>
splitExtension $(mkRelFile ".name" )
>>>
splitExtension $(mkRelFile "..name" )
>>>
splitExtension $(mkRelFile "...name")
splitExtension
and addExtension
are inverses of each other, the
following laws hold:
uncurry addExtension . swap >=> splitExtension == return splitExtension >=> uncurry addExtension . swap == return
Since: 0.7.0
fileExtension :: MonadThrow m => Path b File -> m String Source #
Get extension from given file path. Throws HasNoExtension
exception if
the file does not have an extension. The following laws hold:
flip addExtension file >=> fileExtension == return fileExtension == (fmap snd) . splitExtension
Since: 0.5.11
:: MonadThrow m | |
=> String | Extension to set |
-> Path b File | Old file name |
-> m (Path b File) | New file name with the desired extension |
If the file has an extension replace it with the given extension otherwise
add the new extension to it. Throws an InvalidExtension
exception if the
new extension is not a valid extension (see fileExtension
for validity
rules).
The following law holds:
(fileExtension >=> flip replaceExtension file) file == return file
Since: 0.7.0
mapSomeBase :: (forall b. Path b t -> Path b t') -> SomeBase t -> SomeBase t' Source #
Helper to apply a function to the SomeBase object
>>>
mapSomeBase parent (Abs [absfile|/foo/bar/cow.moo|]) == Abs [absdir|"/foo/bar"|]
prjSomeBase :: (forall b. Path b t -> a) -> SomeBase t -> a Source #
Helper to project the contents out of a SomeBase object.
>>>
prjSomeBase toFilePath (Abs [absfile|/foo/bar/cow.moo|]) == "/foo/bar/cow.moo"
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
) - is all path separators
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
)
parseSomeDir :: MonadThrow m => FilePath -> m (SomeBase Dir) Source #
Convert an absolute or relative FilePath
to a normalized SomeBase
representing a directory.
Throws: InvalidDir
when the supplied path:
- contains a
..
path component representing the parent directory - is not a valid path (See
isValid
)
parseSomeFile :: MonadThrow m => FilePath -> m (SomeBase File) Source #
Convert an absolute or relative FilePath
to a normalized SomeBase
representing a file.
Throws: InvalidFile
when the supplied 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
)
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
.
:: 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 |
Deprecated: Please use addExtension instead.
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 |
Deprecated: Please use addExtension instead.
A synonym for addFileExtension
in the form of an infix 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 |
Deprecated: Please use replaceExtension instead.
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 |
Deprecated: Please use replaceExtension instead.
A synonym for setFileExtension
in the form of an operator.
Since: 0.6.0