hpath-0.7.5: Support for well-typed paths

Copyright© 2015–2016 FP Complete, 2016 Julian Ospald
LicenseBSD 3 clause
MaintainerJulian Ospald <hasufell@posteo.de>
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

HPath

Contents

Description

Support for well-typed paths.

Synopsis

Types

data Abs Source #

An absolute path.

data Path b Source #

Path of some base and type.

Internally is a ByteString. The ByteString can be of two formats only:

  1. without trailing path separator: file.txt, foo/bar.txt, /foo/bar.txt
  2. with trailing path separator: foo/, /foo/bar/

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

Instances

Eq (Path b) Source #

ByteString equality.

The following property holds:

show x == show y ≡ x == y

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

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

Methods

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

show :: Path b -> String #

showList :: [Path b] -> ShowS #

NFData (Path b) Source # 

Methods

rnf :: Path b -> () #

data Rel Source #

A relative path; one without a root.

Instances

data Fn Source #

A filename, without any /.

Instances

class RelC m Source #

Instances

PatternSynonyms/ViewPatterns

pattern Path :: forall a. ByteString -> Path a Source #

Path Parsing

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

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

Throws: PathParseException

>>> parseAbs "/abc"          :: Maybe (Path Abs)
Just "/abc"
>>> parseAbs "/"             :: Maybe (Path Abs)
Just "/"
>>> parseAbs "/abc/def"      :: Maybe (Path Abs)
Just "/abc/def"
>>> parseAbs "/abc/def/.///" :: Maybe (Path Abs)
Just "/abc/def/"
>>> parseAbs "abc"           :: Maybe (Path Abs)
Nothing
>>> parseAbs ""              :: Maybe (Path Abs)
Nothing
>>> parseAbs "/abc/../foo"   :: Maybe (Path Abs)
Nothing

parseFn :: MonadThrow m => ByteString -> m (Path Fn) Source #

Parses a filename. Filenames must not contain slashes. Excludes . and '..'.

Throws: PathParseException

>>> parseFn "abc"        :: Maybe (Path Fn)
Just "abc"
>>> parseFn "..."        :: Maybe (Path Fn)
Just "..."
>>> parseFn "def/"       :: Maybe (Path Fn)
Nothing
>>> parseFn "abc/def"    :: Maybe (Path Fn)
Nothing
>>> parseFn "abc/def/."  :: Maybe (Path Fn)
Nothing
>>> parseFn "/abc"       :: Maybe (Path Fn)
Nothing
>>> parseFn ""           :: Maybe (Path Fn)
Nothing
>>> parseFn "abc/../foo" :: Maybe (Path Fn)
Nothing
>>> parseFn "."          :: Maybe (Path Fn)
Nothing
>>> parseFn ".."         :: Maybe (Path Fn)
Nothing

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 may not consist solely of ./. It also may not contain a single .. anywhere.

Throws: PathParseException

>>> parseRel "abc"        :: Maybe (Path Rel)
Just "abc"
>>> parseRel "def/"       :: Maybe (Path Rel)
Just "def/"
>>> parseRel "abc/def"    :: Maybe (Path Rel)
Just "abc/def"
>>> parseRel "abc/def/."  :: Maybe (Path Rel)
Just "abc/def/"
>>> parseRel "/abc"       :: Maybe (Path Rel)
Nothing
>>> parseRel ""           :: Maybe (Path Rel)
Nothing
>>> parseRel "abc/../foo" :: Maybe (Path Rel)
Nothing
>>> parseRel "."          :: Maybe (Path Rel)
Nothing
>>> parseRel ".."         :: Maybe (Path Rel)
Nothing

Path Conversion

fromAbs :: Path Abs -> ByteString Source #

Convert an absolute Path to a ByteString type.

fromRel :: RelC r => Path r -> ByteString Source #

Convert a relative Path to a ByteString type.

toFilePath :: Path b -> ByteString Source #

Convert any Path to a ByteString type.

Path Operations

(</>) :: RelC r => Path b -> Path r -> 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.

>>> (MkPath "/")        </> (MkPath "file"     :: Path Rel)
"/file"
>>> (MkPath "/path/to") </> (MkPath "file"     :: Path Rel)
"/path/to/file"
>>> (MkPath "/")        </> (MkPath "file/lal" :: Path Rel)
"/file/lal"
>>> (MkPath "/")        </> (MkPath "file/"    :: Path Rel)
"/file/"

basename :: MonadThrow m => Path b -> m (Path Fn) 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 (MkPath "/abc/def/dod") :: Maybe (Path Fn)
Just "dod"
>>> basename (MkPath "/")            :: Maybe (Path Fn)
Nothing

dirname :: Path Abs -> Path Abs Source #

Extract the directory name of a path.

The following properties hold:

dirname (p </> a) == dirname p
>>> dirname (MkPath "/abc/def/dod")
"/abc/def"
>>> dirname (MkPath "/")
"/"

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

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

>>> (MkPath "/lal/lad")     `isParentOf` (MkPath "/lal/lad/fad")
True
>>> (MkPath "lal/lad")      `isParentOf` (MkPath "lal/lad/fad")
True
>>> (MkPath "/")            `isParentOf` (MkPath "/")
False
>>> (MkPath "/lal/lad/fad") `isParentOf` (MkPath "/lal/lad")
False
>>> (MkPath "fad")          `isParentOf` (MkPath "fad")
False

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

Get all parents of a path.

>>> getAllParents (MkPath "/abs/def/dod")
["/abs/def","/abs","/"]
>>> getAllParents (MkPath "/")
[]

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.

>>> (MkPath "/lal/lad")     `stripDir` (MkPath "/lal/lad/fad") :: Maybe (Path Rel)
Just "fad"
>>> (MkPath "lal/lad")      `stripDir` (MkPath "lal/lad/fad")  :: Maybe (Path Rel)
Just "fad"
>>> (MkPath "/")            `stripDir` (MkPath "/")            :: Maybe (Path Rel)
Nothing
>>> (MkPath "/lal/lad/fad") `stripDir` (MkPath "/lal/lad")     :: Maybe (Path Rel)
Nothing
>>> (MkPath "fad")          `stripDir` (MkPath "fad")          :: Maybe (Path Rel)
Nothing

Path IO helpers

withFnPath :: Path Fn -> (ByteString -> IO a) -> IO a Source #