hpath-0.12.1: Support for well-typed paths
Copyright© 2015–2016 FP Complete 2016 Julian Ospald
LicenseBSD 3 clause
MaintainerJulian Ospald <hasufell@posteo.de>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

HPath

Description

Support for well-typed paths.

Synopsis

Types

data Path b Source #

The main Path type.

The type variable b is either:

  • Abs -- absolute path (starting with a "/")
  • Rel -- relative path (not starting with a "/")

Internally it is a ByteString. The path is guaranteed to be normalised and contain no trailing Path separators, except for the "/" root path.

There are no duplicate path separators "//", no "..", no "./", etc.

Two special paths exist:

The constructor is not exposed. Instead, use the smart constructors parseAbs, parseRel and parseAny.

Instances

Instances details
Typeable a => Lift (Path a :: Type) Source # 
Instance details

Defined in HPath

Methods

lift :: Path a -> Q Exp #

liftTyped :: Path a -> Q (TExp (Path a)) #

Eq (Path b) Source #

ByteString equality.

The following property holds:

show x == show y ≡ x == y
Instance details

Defined in HPath.Internal

Methods

(==) :: Path b -> Path b -> Bool #

(/=) :: Path b -> Path b -> Bool #

Ord (Path b) Source #

ByteString ordering.

The following property holds:

show x `compare` show y ≡ x `compare` y
Instance details

Defined in HPath.Internal

Methods

compare :: Path b -> Path b -> Ordering #

(<) :: Path b -> Path b -> Bool #

(<=) :: Path b -> Path b -> Bool #

(>) :: Path b -> Path b -> Bool #

(>=) :: Path b -> Path b -> Bool #

max :: Path b -> Path b -> Path b #

min :: Path b -> Path b -> Path b #

Show (Path b) Source #

Same as toFilePath.

The following property holds:

x == y ≡ show x == show y
Instance details

Defined in HPath.Internal

Methods

showsPrec :: Int -> Path b -> ShowS #

show :: Path b -> String #

showList :: [Path b] -> ShowS #

NFData (Path b) Source # 
Instance details

Defined in HPath.Internal

Methods

rnf :: Path b -> () #

data Abs Source #

An absolute path.

data Rel Source #

A relative path; one without a root.

PatternSynonyms/ViewPatterns

pattern Path :: ByteString -> Path a Source #

Path Construction

parseAbs :: MonadThrow m => ByteString -> m (Path Abs) Source #

Get a location for an absolute path. Produces a normalised path.

Throws: PathParseException

>>> parseAbs "/abc"
"/abc"
>>> parseAbs "/"
"/"
>>> parseAbs "/abc/def"
"/abc/def"
>>> parseAbs "/abc/def/.///"
"/abc/def"
>>> parseAbs "abc"
*** Exception: InvalidAbs "abc"
>>> parseAbs ""
*** Exception: InvalidAbs ""
>>> parseAbs "/abc/../foo"
*** Exception: InvalidAbs "/abc/../foo"

parseRel :: MonadThrow m => ByteString -> m (Path Rel) Source #

Get a location for a relative path. Produces a normalised path.

Note that filepath may contain any number of ./, but not a single .. anywhere.

Throws: PathParseException

>>> parseRel "abc"
"abc"
>>> parseRel "def/"
"def"
>>> parseRel "abc/def"
"abc/def"
>>> parseRel "abc/def/."
"abc/def"
>>> parseRel "/abc"
*** Exception: InvalidRel "/abc"
>>> parseRel ""
*** Exception: InvalidRel ""
>>> parseRel "abc/../foo"
*** Exception: InvalidRel "abc/../foo"
>>> parseRel "."
"."
>>> parseRel "././././."
"."
>>> parseRel "./..."
"..."
>>> parseRel ".."
*** Exception: InvalidRel ".."

parseAny :: MonadThrow m => ByteString -> m (Either (Path Abs) (Path Rel)) Source #

Parses a path, whether it's relative or absolute.

Throws: PathParseException

>>> parseAny "/abc"
Left "/abc"
>>> parseAny "..."
Right "..."
>>> parseAny "abc/def"
Right "abc/def"
>>> parseAny "abc/def/."
Right "abc/def"
>>> parseAny "/abc"
Left "/abc"
>>> parseAny ""
*** Exception: InvalidRel ""
>>> parseAny "abc/../foo"
*** Exception: InvalidRel "abc/../foo"
>>> parseAny "."
Right "."
>>> parseAny ".."
*** Exception: InvalidRel ".."

rootPath :: Path Abs Source #

The "/" root path.

pwdPath :: Path Rel Source #

The "." pwd path.

Path Conversion

fromAbs :: Path Abs -> ByteString Source #

Convert an absolute Path to a ByteString type.

fromRel :: Path Rel -> ByteString Source #

Convert a relative Path to a ByteString type.

toFilePath :: Path b -> ByteString Source #

Convert any Path to a ByteString type.

Path Operations

(</>) :: Path b -> Path Rel -> Path b Source #

Append two paths.

The second argument must always be a relative path, which ensures that undefinable things like `"abc" <> "/def"` cannot happen.

Technically, the first argument can be a path that points to a non-directory, because this library is IO-agnostic and makes no assumptions about file types.

>>> [abs|/|] </> [rel|file|]
"/file"
>>> [abs|/path/to|] </> [rel|file|]
"/path/to/file"
>>> [abs|/|] </> [rel|file/lal|]
"/file/lal"
>>> [abs|/|] </> [rel|.|]
"/"
>>> [rel|.|] </> [rel|.|]
"."

basename :: MonadThrow m => Path b -> m (Path Rel) Source #

Extract the file part of a path.

The following properties hold:

basename (p </> a) == basename a

Throws: PathException if given the root path "/"

>>> basename [abs|/abc/def/dod|]
"dod"
>>> basename [rel|abc/def/dod|]
"dod"
>>> basename [rel|dod|]
"dod"
>>> basename [rel|.|]
"."
>>> basename [abs|/|]
*** Exception: RootDirHasNoBasename

basename' :: Path Rel -> Path Rel Source #

Extract the file part of a relative path.

The following properties hold:

basename' (p </> a) == basename' a
>>> basename' [rel|abc/def/dod|]
"dod"
>>> basename' [rel|dod|]
"dod"
>>> basename' [rel|.|]
"."

dirname :: Path Abs -> Path Abs Source #

Extract the directory name of a path.

>>> dirname [abs|/abc/def/dod|]
"/abc/def"
>>> dirname [abs|/|]
"/"

getAllParents :: Path Abs -> [Path Abs] Source #

Get all parents of a path.

>>> getAllParents [abs|/abs/def/dod|]
["/abs/def","/abs","/"]
>>> getAllParents [abs|/foo|]
["/"]
>>> getAllParents [abs|/|]
[]

getAllComponents :: Path Rel -> [Path Rel] Source #

Gets all path components.

>>> getAllComponents [rel|abs/def/dod|]
["abs","def","dod"]
>>> getAllComponents [rel|abs|]
["abs"]
>>> getAllComponents [rel|.|]
["."]

getAllComponentsAfterRoot :: Path Abs -> [Path Rel] Source #

Gets all path components after the "/" root directory.

>>> getAllComponentsAfterRoot [abs|/abs/def/dod|]
["abs","def","dod"]
>>> getAllComponentsAfterRoot [abs|/abs|]
["abs"]

stripDir :: MonadThrow m => Path b -> Path b -> m (Path Rel) Source #

Strip directory from path, making it relative to that directory. Throws Couldn'tStripPrefixDir if directory is not a parent of the path.

The bases must match.

>>> [abs|/lal/lad|]     `stripDir` [abs|/lal/lad/fad|]
"fad"
>>> [rel|lal/lad|]      `stripDir` [rel|lal/lad/fad|]
"fad"
>>> [abs|/|]            `stripDir` [abs|/|]
"."
>>> [abs|/lal/lad/fad|] `stripDir` [abs|/lal/lad|]
*** Exception: Couldn'tStripPrefixTPS "/lal/lad/fad" "/lal/lad"
>>> [abs|/abs|]         `stripDir` [abs|/lal/lad|]
*** Exception: Couldn'tStripPrefixTPS "/abs" "/lal/lad"
>>> [rel|fad|]          `stripDir` [rel|fad|]
"."
>>> [rel|.|]            `stripDir` [rel|.|]
"."
>>> [rel|.|]            `stripDir` [rel|.foo|]
*** Exception: Couldn'tStripPrefixTPS "." ".foo"

Path Examination

isParentOf :: Path b -> Path b -> Bool Source #

Is p a parent of the given location? Implemented in terms of stripDir. The bases must match.

>>> [abs|/lal/lad|]     `isParentOf` [abs|/lal/lad/fad|]
True
>>> [rel|lal/lad|]      `isParentOf` [rel|lal/lad/fad|]
True
>>> [abs|/|]            `isParentOf` [abs|/|]
False
>>> [abs|/lal/lad/fad|] `isParentOf` [abs|/lal/lad|]
False
>>> [rel|fad|]          `isParentOf` [rel|fad|]
False
>>> [rel|.|]            `isParentOf` [rel|.foo|]
False

isRootPath :: Path Abs -> Bool Source #

Check whether the given Path is the root "/" path.

>>> isRootPath [abs|/lal/lad|]
False
>>> isRootPath [abs|/|]
True

isPwdPath :: Path Rel -> Bool Source #

Check whether the given Path is the pwd "." path.

>>> isPwdPath [rel|lal/lad|]
False
>>> isPwdPath [rel|.|]
True

Path IO helpers

Quasiquoters

abs :: QuasiQuoter Source #

Quasiquote an absolute Path. This accepts Unicode Chars and will encode as UTF-8.

>>> [abs|/etc/profile|] :: Path Abs
"/etc/profile"
>>> [abs|/|] :: Path Abs
"/"
>>> [abs|/|] :: Path Abs
"/\239\131\144"

rel :: QuasiQuoter Source #

Quasiquote a relative Path. This accepts Unicode Chars and will encode as UTF-8.

>>> [rel|etc|] :: Path Rel
"etc"
>>> [rel|bar/baz|] :: Path Rel
"bar/baz"
>>> [rel||] :: Path Rel
"\239\131\144"

Orphan instances

Typeable a => Lift (Path a :: Type) Source # 
Instance details

Methods

lift :: Path a -> Q Exp #

liftTyped :: Path a -> Q (TExp (Path a)) #