paths-0.2.0.0: Library for representing and manipulating type-safe file paths

Safe HaskellSafe
LanguageHaskell2010

System.Path

Contents

Description

A more type-safe version of file paths

This module provides the basic Path abstraction. See also System.Path.IO which extends this module by thin wrappers wrappers around common IO operations.

Synopsis

Paths

data Path a Source #

Paths

A Path is a wrapped FilePath with a type-level tag indicating where this path is rooted (relative to the current directory, absolute path, relative to a web domain, whatever). Most operations on Path are just lifted versions of the operations on the underlying FilePath. The tag however allows us to give a lot of operations a more meaningful type. For instance, it does not make sense to append two absolute paths together; instead, we can only append an unrooted path to another path. It also means we avoid bugs where we use one kind of path where we expect another.

Instances

Eq (Path a) Source # 

Methods

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

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

Ord (Path a) Source # 

Methods

compare :: Path a -> Path a -> Ordering #

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

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

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

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

max :: Path a -> Path a -> Path a #

min :: Path a -> Path a -> Path a #

Show (Path a) Source # 

Methods

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

show :: Path a -> String #

showList :: [Path a] -> ShowS #

NFData (Path a) Source # 

Methods

rnf :: Path a -> () #

FilePath-like operations on paths with arbitrary roots

Operations aware of file-extensions

newtype FileExt Source #

Type to represent filepath extensions.

File extensions are usually a high-level convention and in most cases the low-level filesystem layer is agnostic to them.

Since: 0.2.0.0

Constructors

FileExt String 

(<.>) :: Path a -> FileExt -> Path a infixr 7 Source #

Wrapped <.>

(-<.>) :: Path a -> FileExt -> Path a infixr 7 Source #

Wrapped -<.>

Since: 0.2.0.0

splitExtensions :: Path a -> (Path a, Maybe FileExt) Source #

Wrapped splitExtensions

Since: 0.2.0.0

takeExtensions :: Path a -> Maybe FileExt Source #

Wrapped takeExtensions

Since: 0.2.0.0

takeBaseName :: Path a -> Path Unrooted Source #

Wrapped takeBaseName

Since: 0.2.0.0

stripExtension :: FileExt -> Path a -> Maybe (Path a) Source #

Wrapped stripExtension

Since: 0.2.0.0

isExtensionOf :: FileExt -> Path a -> Bool Source #

Wrapped isExtensionOf

Since: 0.2.0.0

Trailing slash functions

Unrooted paths

data Unrooted Source #

Type-level tag for unrooted paths

Unrooted paths need a root before they can be interpreted.

(</>) :: Path a -> Path Unrooted -> Path a infixr 5 Source #

Wrapped </>

The empty fragment fragment "" acts as the right-identity

root / fragment "" == root

This is the inverse to splitFileName.

unrootPath :: Path root -> Path Unrooted Source #

Forget a path's root

NOTE: If the original Path is considered an absolute POSIX style FilePath, it's automatically converted to a relative FilePath.

toUnrootedFilePath :: Path Unrooted -> FilePath Source #

Convert a relative/unrooted Path to a FilePath (using POSIX style directory separators).

See also toAbsoluteFilePath

fromUnrootedFilePath :: FilePath -> Path Unrooted Source #

Convert from a relative/unrooted FilePath (using POSIX style directory separators).

NOTE: If the argument is considered an absolute POSIX style FilePath, it's automatically converted to a relative FilePath.

fragment :: String -> Path Unrooted Source #

A path fragment (like a single directory or filename)

NOTE: If the argument would be considered an absolute POSIX style FilePath, it's automatically converted to a relative FilePath.

fragments :: [String] -> Path Unrooted Source #

Version of fragment taking a list of fragments

NOTE: If any argument would be considered an absolute POSIX style FilePath, it's automatically converted to a relative FilePath.

Since: 0.2.0.0

joinFragments :: [Path Unrooted] -> Path Unrooted Source #

Wrapped joinPath

Since: 0.2.0.0

normalise :: Path a -> Path a Source #

Normalise Path according to POSIX rules.

See documentation of normalise for details.

Since: 0.2.0.0

File-system paths

class FsRoot root where Source #

A file system root can be interpreted as an (absolute) FilePath

Minimal complete definition

toAbsoluteFilePath

Methods

toAbsoluteFilePath :: Path root -> IO FilePath Source #

Convert a Path to an absolute native FilePath (using native style directory separators).

This operation needs to be in IO for resolving paths with dynamic roots, such as CWD or HomeDir.

See also makeAbsolute

data FsPath Source #

Abstract over a file system root

FsPath can be constructed directly or via fromFilePath or fspath.

Constructors

FsRoot root => FsPath (Path root) 

Instances

NFData FsPath Source # 

Methods

rnf :: FsPath -> () #

data CWD Source #

Path tag for paths rooted at the current working directory

Since: 0.2.0.0

type Relative = CWD Source #

Deprecated: Please use CWD instead

Compatibility type-synonym

data Absolute Source #

Path tag for absolute paths

data HomeDir Source #

Path tag for paths rooted at $HOME

Conversions

toFilePath :: Path Absolute -> FilePath Source #

Export absolute path to a native FilePath.

This is the inverse to fromAbsoluteFilePath.

fromFilePath :: FilePath -> FsPath Source #

Construct a FsPath from a native FilePath.

NOTE: Native FilePaths whose first path component is a ~ (and not preceded by anything else) are interpreted to be relative to $HOME (even on non-POSIX systems).

makeAbsolute :: FsPath -> IO (Path Absolute) Source #

Export filesystem path to an absolute Path

See also toAbsoluteFilePath

fromAbsoluteFilePath :: FilePath -> Path Absolute Source #

Construct Absolute path from a native FilePath.

This is the inverse to toFilePath.

NOTE: If the argument is not an absolute path this function will throw an error.