commit 1fd1427532ef640956c1f922466c01b570f5075c Author: Julian Ospald Date: Wed Jun 1 14:52:48 2016 +0200 Initial commit diff --git a/HPath-IO-Errors.html b/HPath-IO-Errors.html new file mode 100644 index 0000000..980ab2d --- /dev/null +++ b/HPath-IO-Errors.html @@ -0,0 +1,22 @@ +HPath.IO.Errors

hpath-0.7.3: Support for well-typed paths

Copyright© 2016 Julian Ospald
LicenseGPL-2
MaintainerJulian Ospald <hasufell@posteo.de>
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

HPath.IO.Errors

Description

Provides error handling.

Types

data HPathIOException Source #

Instances

Eq HPathIOException Source # 
Data HPathIOException Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HPathIOException -> c HPathIOException

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HPathIOException

toConstr :: HPathIOException -> Constr

dataTypeOf :: HPathIOException -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c HPathIOException)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HPathIOException)

gmapT :: (forall b. Data b => b -> b) -> HPathIOException -> HPathIOException

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HPathIOException -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HPathIOException -> r

gmapQ :: (forall d. Data d => d -> u) -> HPathIOException -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> HPathIOException -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HPathIOException -> m HPathIOException

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HPathIOException -> m HPathIOException

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HPathIOException -> m HPathIOException

Show HPathIOException Source # 

Methods

showsPrec :: Int -> HPathIOException -> ShowS

show :: HPathIOException -> String

showList :: [HPathIOException] -> ShowS

Exception HPathIOException Source # 

Methods

toException :: HPathIOException -> SomeException

fromException :: SomeException -> Maybe HPathIOException

displayException :: HPathIOException -> String

Exception identifiers

Path based functions

throwSameFile :: Path Abs -> Path Abs -> IO () Source #

Uses isSameFile and throws SameFile if it returns True.

sameFile :: Path Abs -> Path Abs -> IO Bool Source #

Check if the files are the same by examining device and file id. + This follows symbolic links.

throwDestinationInSource Source #

Arguments

:: Path Abs

source dir

-> Path Abs

full destination, dirname dest + must exist

-> IO () 

Checks whether the destination directory is contained + within the source directory by comparing the device+file ID of the + source directory with all device+file IDs of the parent directories + of the destination.

doesFileExist :: Path Abs -> IO Bool Source #

Checks if the given file exists and is not a directory. + Does not follow symlinks.

doesDirectoryExist :: Path Abs -> IO Bool Source #

Checks if the given file exists and is a directory. + Does not follow symlinks.

isWritable :: Path Abs -> IO Bool Source #

Checks whether a file or folder is writable.

canOpenDirectory :: Path Abs -> IO Bool Source #

Checks whether the directory at the given path exists and can be + opened. This invokes openDirStream which follows symlinks.

throwCantOpenDirectory :: Path Abs -> IO () Source #

Throws a Can'tOpenDirectory HPathIOException if the directory at the given + path cannot be opened.

Error handling functions

catchErrno Source #

Arguments

:: [Errno]

errno to catch

-> IO a

action to try, which can raise an IOException

-> IO a

action to carry out in case of an IOException and + if errno matches

-> IO a 

Carries out an action, then checks if there is an IOException and + a specific errno. If so, then it carries out another action, otherwise + it rethrows the error.

rethrowErrnoAs Source #

Arguments

:: Exception e 
=> [Errno]

errno to catch

-> e

rethrow as if errno matches

-> IO a

action to try

-> IO a 

Execute the given action and retrow IO exceptions as a new Exception + that have the given errno. If errno does not match the exception is rethrown + as is.

handleIOError :: (IOError -> IO a) -> IO a -> IO a Source #

Like catchIOError, with arguments swapped.

bracketeer Source #

Arguments

:: IO a

computation to run first

-> (a -> IO b)

computation to run last, when + no exception was raised

-> (a -> IO b)

computation to run last, + when an exception was raised

-> (a -> IO c)

computation to run in-between

-> IO c 

Like bracket, but allows to have different clean-up + actions depending on whether the in-between computation + has raised an exception or not.

reactOnError Source #

Arguments

:: IO a 
-> [(IOErrorType, IO a)]

reaction on IO errors

-> [(HPathIOException, IO a)]

reaction on HPathIOException

-> IO a 
\ No newline at end of file diff --git a/HPath-IO-Utils.html b/HPath-IO-Utils.html new file mode 100644 index 0000000..36f4333 --- /dev/null +++ b/HPath-IO-Utils.html @@ -0,0 +1,6 @@ +HPath.IO.Utils

hpath-0.7.3: Support for well-typed paths

Copyright© 2016 Julian Ospald
LicenseGPL-2
MaintainerJulian Ospald <hasufell@posteo.de>
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

HPath.IO.Utils

Description

Random and general IO/monad utilities.

Synopsis

  • whenM :: Monad m => m Bool -> m () -> m ()
  • unlessM :: Monad m => m Bool -> m () -> m ()

Documentation

whenM :: Monad m => m Bool -> m () -> m () Source #

If the value of the first argument is True, then execute the action + provided in the second argument, otherwise do nothing.

unlessM :: Monad m => m Bool -> m () -> m () Source #

If the value of the first argument is False, then execute the action + provided in the second argument, otherwise do nothing.

\ No newline at end of file diff --git a/HPath-IO.html b/HPath-IO.html new file mode 100644 index 0000000..7a2c55b --- /dev/null +++ b/HPath-IO.html @@ -0,0 +1,59 @@ +HPath.IO

hpath-0.7.3: Support for well-typed paths

Copyright© 2016 Julian Ospald
LicenseGPL-2
MaintainerJulian Ospald <hasufell@posteo.de>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

HPath.IO

Description

This module provides high-level IO related file operations like + copy, delete, move and so on. It only operates on Path Abs which + guarantees us well-typed paths which are absolute.

Some functions are just path-safe wrappers around + unix functions, others have stricter exception handling + and some implement functionality that doesn't have a unix + counterpart (like copyDirRecursive).

Some of these operations are due to their nature not atomic, which + means they may do multiple syscalls which form one context. Some + of them also have to examine the filetypes explicitly before the + syscalls, so a reasonable decision can be made. That means + the result is undefined if another process changes that context + while the non-atomic operation is still happening. However, where + possible, as few syscalls as possible are used and the underlying + exception handling is kept.

Note: BlockDevice, CharacterDevice, NamedPipe and Socket + are ignored by some of the more high-level functions (like easyCopy). + For other functions (like copyFile), the behavior on these file types is + unreliable/unsafe. Check the documentation of those functions for details.

Types

data FileType Source #

Instances

Eq FileType Source # 

Methods

(==) :: FileType -> FileType -> Bool

(/=) :: FileType -> FileType -> Bool

Show FileType Source # 

Methods

showsPrec :: Int -> FileType -> ShowS

show :: FileType -> String

showList :: [FileType] -> ShowS

File copying

copyDirRecursive Source #

Arguments

:: Path Abs

source dir

-> Path Abs

full destination

-> IO () 

Copies a directory recursively to the given destination. + Does not follow symbolic links.

For directory contents, this has the same behavior as easyCopy + and thus will ignore any file type that is not RegularFile, + SymbolicLink or Directory.

Safety/reliability concerns:

  • not atomic
  • examines filetypes explicitly
  • an explicit check throwDestinationInSource is carried out for the + top directory for basic sanity, because otherwise we might end up + with an infinite copy loop... however, this operation is not + carried out recursively (because it's slow)

Throws:

  • NoSuchThing if source directory does not exist
  • PermissionDenied if output directory is not writable
  • PermissionDenied if source directory can't be opened
  • InvalidArgument if source directory is wrong type (symlink)
  • InvalidArgument if source directory is wrong type (regular file)
  • AlreadyExists if destination already exists
  • SameFile if source and destination are the same file (HPathIOException)
  • DestinationInSource if destination is contained in source (HPathIOException)

copyDirRecursiveOverwrite Source #

Arguments

:: Path Abs

source dir

-> Path Abs

full destination

-> IO () 

Like copyDirRecursive except it overwrites contents of directories + if any.

For directory contents, this has the same behavior as easyCopyOverwrite + and thus will ignore any file type that is not RegularFile, + SymbolicLink or Directory.

Throws:

  • NoSuchThing if source directory does not exist
  • PermissionDenied if output directory is not writable
  • PermissionDenied if source directory can't be opened
  • InvalidArgument if source directory is wrong type (symlink)
  • InvalidArgument if source directory is wrong type (regular file)
  • SameFile if source and destination are the same file (HPathIOException)
  • DestinationInSource if destination is contained in source (HPathIOException)

recreateSymlink Source #

Arguments

:: Path Abs

the old symlink file

-> Path Abs

destination file

-> IO () 

Recreate a symlink.

Throws:

  • InvalidArgument if source file is wrong type (not a symlink)
  • PermissionDenied if output directory cannot be written to
  • PermissionDenied if source directory cannot be opened
  • AlreadyExists if destination file already exists
  • SameFile if source and destination are the same file (HPathIOException)

Note: calls symlink

copyFile Source #

Arguments

:: Path Abs

source file

-> Path Abs

destination file

-> IO () 

Copies the given regular file to the given destination. + Neither follows symbolic links, nor accepts them. + For "copying" symbolic links, use recreateSymlink instead.

Note that this is still sort of a low-level function and doesn't + examine file types. For a more high-level version, use easyCopy + instead.

Safety/reliability concerns:

  • when used on CharacterDevice, reads the "contents" and copies + them to a regular file, which might take indefinitely
  • when used on BlockDevice, may either read the "contents" + and copy them to a regular file (potentially hanging indefinitely) + or may create a regular empty destination file
  • when used on NamedPipe, will hang indefinitely

Throws:

  • NoSuchThing if source file does not exist
  • NoSuchThing if source file is a a Socket
  • PermissionDenied if output directory is not writable
  • PermissionDenied if source directory can't be opened
  • InvalidArgument if source file is wrong type (symlink or directory)
  • AlreadyExists if destination already exists
  • SameFile if source and destination are the same file (HPathIOException)

Note: calls sendfile and possibly read/write as fallback

copyFileOverwrite Source #

Arguments

:: Path Abs

source file

-> Path Abs

destination file

-> IO () 

Like copyFile except it overwrites the destination if it already + exists.

Safety/reliability concerns:

  • when used on CharacterDevice, reads the "contents" and copies + them to a regular file, which might take indefinitely
  • when used on BlockDevice, may either read the "contents" + and copy them to a regular file (potentially hanging indefinitely) + or may create a regular empty destination file
  • when used on NamedPipe, will hang indefinitely
  • not atomic, since it uses read/write

Throws:

  • NoSuchThing if source file does not exist
  • NoSuchThing if source file is a Socket
  • PermissionDenied if output directory is not writable
  • PermissionDenied if source directory can't be opened
  • InvalidArgument if source file is wrong type (symlink or directory)
  • SameFile if source and destination are the same file (HPathIOException)

Note: calls sendfile and possibly read/write as fallback

easyCopy :: Path Abs -> Path Abs -> IO () Source #

Copies a regular file, directory or symbolic link. In case of a + symbolic link it is just recreated, even if it points to a directory. + Any other file type is ignored.

Safety/reliability concerns:

easyCopyOverwrite :: Path Abs -> Path Abs -> IO () Source #

Like easyCopy except it overwrites the destination if it already exists. + For directories, this overwrites contents without pruning them, so the resulting + directory may have more files than have been copied.

Safety/reliability concerns:

File deletion

deleteFile :: Path Abs -> IO () Source #

Deletes the given file. Raises eISDIR + if run on a directory. Does not follow symbolic links.

Throws:

  • InappropriateType for wrong file type (directory)
  • NoSuchThing if the file does not exist
  • PermissionDenied if the directory cannot be read

deleteDir :: Path Abs -> IO () Source #

Deletes the given directory, which must be empty, never symlinks.

Throws:

  • InappropriateType for wrong file type (symlink to directory)
  • InappropriateType for wrong file type (regular file)
  • NoSuchThing if directory does not exist
  • UnsatisfiedConstraints if directory is not empty
  • PermissionDenied if we can't open or write to parent directory

Notes: calls rmdir

deleteDirRecursive :: Path Abs -> IO () Source #

Deletes the given directory recursively. Does not follow symbolic + links. Tries deleteDir first before attemtping a recursive + deletion.

On directory contents this behaves like easyDelete + and thus will ignore any file type that is not RegularFile, + SymbolicLink or Directory.

Safety/reliability concerns:

  • not atomic
  • examines filetypes explicitly

Throws:

  • InappropriateType for wrong file type (symlink to directory)
  • InappropriateType for wrong file type (regular file)
  • NoSuchThing if directory does not exist
  • PermissionDenied if we can't open or write to parent directory

easyDelete :: Path Abs -> IO () Source #

Deletes a file, directory or symlink. + In case of directory, performs recursive deletion. In case of + a symlink, the symlink file is deleted. + Any other file type is ignored.

Safety/reliability concerns:

File opening

openFile :: Path Abs -> IO ProcessID Source #

Opens a file appropriately by invoking xdg-open. The file type + is not checked. This forks a process.

executeFile Source #

Arguments

:: Path Abs

program

-> [ByteString]

arguments

-> IO ProcessID 

Executes a program with the given arguments. This forks a process.

File creation

createRegularFile :: Path Abs -> IO () Source #

Create an empty regular file at the given directory with the given filename.

Throws:

  • PermissionDenied if output directory cannot be written to
  • AlreadyExists if destination file already exists

createDir :: Path Abs -> IO () Source #

Create an empty directory at the given directory with the given filename.

Throws:

  • PermissionDenied if output directory cannot be written to
  • AlreadyExists if destination directory already exists

createSymlink Source #

Arguments

:: Path Abs

destination file

-> ByteString

path the symlink points to

-> IO () 

Create a symlink.

Throws:

  • PermissionDenied if output directory cannot be written to
  • AlreadyExists if destination file already exists

Note: calls symlink

File renaming/moving

renameFile :: Path Abs -> Path Abs -> IO () Source #

Rename a given file with the provided filename. Destination and source + must be on the same device, otherwise eXDEV will be raised.

Does not follow symbolic links, but renames the symbolic link file.

Safety/reliability concerns:

  • has a separate set of exception handling, apart from the syscall

Throws:

  • NoSuchThing if source file does not exist
  • PermissionDenied if output directory cannot be written to
  • PermissionDenied if source directory cannot be opened
  • UnsupportedOperation if source and destination are on different devices
  • FileDoesExist if destination file already exists (HPathIOException)
  • DirDoesExist if destination directory already exists (HPathIOException)
  • SameFile if destination and source are the same file (HPathIOException)

Note: calls rename (but does not allow to rename over existing files)

moveFile Source #

Arguments

:: Path Abs

file to move

-> Path Abs

destination

-> IO () 

Move a file. This also works across devices by copy-delete fallback. + And also works on directories.

Does not follow symbolic links, but renames the symbolic link file.

Safety/reliability concerns:

Throws:

Note: calls rename (but does not allow to rename over existing files)

moveFileOverwrite Source #

Arguments

:: Path Abs

file to move

-> Path Abs

destination

-> IO () 

Like moveFile, but overwrites the destination if it exists.

Does not follow symbolic links, but renames the symbolic link file.

Ignores any file type that is not RegularFile, SymbolicLink or + Directory.

Safety/reliability concerns:

  • copy-delete fallback is inherently non-atomic
  • checks for file types and destination file existence explicitly

Throws:

  • NoSuchThing if source file does not exist
  • PermissionDenied if output directory cannot be written to
  • PermissionDenied if source directory cannot be opened
  • SameFile if destination and source are the same file (HPathIOException)

Note: calls rename (but does not allow to rename over existing files)

File permissions

newFilePerms :: FileMode Source #

Default permissions for a new file.

newDirPerms :: FileMode Source #

Default permissions for a new directory.

Directory reading

getDirsFiles Source #

Arguments

:: Path Abs

dir to read

-> IO [Path Abs] 

Gets all filenames of the given directory. This excludes "." and "..". + This version does not follow symbolic links.

Throws:

  • NoSuchThing if directory does not exist
  • InappropriateType if file type is wrong (file)
  • InappropriateType if file type is wrong (symlink to file)
  • InappropriateType if file type is wrong (symlink to dir)
  • PermissionDenied if directory cannot be opened

Filetype operations

getFileType :: Path Abs -> IO FileType Source #

Get the file type of the file located at the given path. Does + not follow symbolic links.

Throws:

  • NoSuchThing if the file does not exist
  • PermissionDenied if any part of the path is not accessible

Others

canonicalizePath :: Path Abs -> IO (Path Abs) Source #

Applies realpath on the given absolute path.

Throws:

  • NoSuchThing if the file at the given path does not exist
  • NoSuchThing if the symlink is broken
\ No newline at end of file diff --git a/HPath.html b/HPath.html new file mode 100644 index 0000000..1f63629 --- /dev/null +++ b/HPath.html @@ -0,0 +1,105 @@ +HPath

hpath-0.7.3: 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

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

data PathParseException Source #

Exception when parsing a location.

Instances

Show PathParseException Source # 

Methods

showsPrec :: Int -> PathParseException -> ShowS

show :: PathParseException -> String

showList :: [PathParseException] -> ShowS

Exception PathParseException Source # 

Methods

toException :: PathParseException -> SomeException

fromException :: SomeException -> Maybe PathParseException

displayException :: PathParseException -> String

data PathException Source #

Instances

Show PathException Source # 

Methods

showsPrec :: Int -> PathException -> ShowS

show :: PathException -> String

showList :: [PathException] -> ShowS

Exception PathException Source # 

Methods

toException :: PathException -> SomeException

fromException :: SomeException -> Maybe PathException

displayException :: PathException -> String

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

withAbsPath :: Path Abs -> (ByteString -> IO a) -> IO a Source #

withRelPath :: Path Rel -> (ByteString -> IO a) -> IO a Source #

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

\ No newline at end of file diff --git a/System-Posix-Directory-Foreign.html b/System-Posix-Directory-Foreign.html new file mode 100644 index 0000000..8e91a88 --- /dev/null +++ b/System-Posix-Directory-Foreign.html @@ -0,0 +1,9 @@ +System.Posix.Directory.Foreign

hpath-0.7.3: Support for well-typed paths

Safe HaskellSafe
LanguageHaskell2010

System.Posix.Directory.Foreign

Documentation

newtype DirType Source #

Constructors

DirType Int 

Instances

Eq DirType Source # 

Methods

(==) :: DirType -> DirType -> Bool

(/=) :: DirType -> DirType -> Bool

Show DirType Source # 

Methods

showsPrec :: Int -> DirType -> ShowS

show :: DirType -> String

showList :: [DirType] -> ShowS

data Flags Source #

Constructors

Flags Int 
UnsupportedFlag String 

Instances

Eq Flags Source # 

Methods

(==) :: Flags -> Flags -> Bool

(/=) :: Flags -> Flags -> Bool

Show Flags Source # 

Methods

showsPrec :: Int -> Flags -> ShowS

show :: Flags -> String

showList :: [Flags] -> ShowS

unFlags :: Flags -> Int Source #

isSupported :: Flags -> Bool Source #

Returns True if posix-paths was compiled with support for the provided + flag. (As of this writing, the only flag for which this check may be + necessary is oCloexec; all other flags will always yield True.)

oCloexec :: Flags Source #

O_CLOEXEC is not supported on every POSIX platform. Use + isSupported oCloexec to determine if support for O_CLOEXEC was + compiled into your version of posix-paths. (If not, using oCloexec will + throw an exception.)

unionFlags :: [Flags] -> CInt Source #

\ No newline at end of file diff --git a/System-Posix-Directory-Traversals.html b/System-Posix-Directory-Traversals.html new file mode 100644 index 0000000..66e1687 --- /dev/null +++ b/System-Posix-Directory-Traversals.html @@ -0,0 +1,11 @@ +System.Posix.Directory.Traversals

hpath-0.7.3: Support for well-typed paths

Copyright© 2016 Julian Ospald
LicenseBSD3
MaintainerJulian Ospald <hasufell@posteo.de>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

System.Posix.Directory.Traversals

Description

Traversal and read operations on directories.

Synopsis

Documentation

getDirectoryContents :: RawFilePath -> IO [(DirType, RawFilePath)] Source #

Gets all directory contents (not recursively).

getDirectoryContents' :: Fd -> IO [(DirType, RawFilePath)] Source #

Like getDirectoryContents except for a file descriptor.

To avoid complicated error checks, the file descriptor is + always closed, even if fdOpendir fails. Usually, this + only happens on successful fdOpendir and after the directory + stream is closed. Also see the manpage of fdopendir(3) for + more details.

allDirectoryContents :: RawFilePath -> IO [RawFilePath] Source #

Get all files from a directory and its subdirectories.

Upon entering a directory, allDirectoryContents will get all entries + strictly. However the returned list is lazy in that directories will only + be accessed on demand.

Follows symbolic links for the input dir.

allDirectoryContents' :: RawFilePath -> IO [RawFilePath] Source #

Get all files from a directory and its subdirectories strictly.

Follows symbolic links for the input dir.

traverseDirectory :: (s -> RawFilePath -> IO s) -> s -> RawFilePath -> IO s Source #

Recursively apply the action to the parent directory and all + files/subdirectories.

This function allows for memory-efficient traversals.

Follows symbolic links for the input dir.

readDirEnt :: DirStream -> IO (DirType, RawFilePath) Source #

packDirStream :: Ptr CDir -> DirStream Source #

unpackDirStream :: DirStream -> Ptr CDir Source #

fdOpendir :: Fd -> IO DirStream Source #

Binding to fdopendir(3).

realpath :: RawFilePath -> IO RawFilePath Source #

return the canonicalized absolute pathname

like canonicalizePath, but uses realpath(3)

\ No newline at end of file diff --git a/System-Posix-FD.html b/System-Posix-FD.html new file mode 100644 index 0000000..409e78b --- /dev/null +++ b/System-Posix-FD.html @@ -0,0 +1,9 @@ +System.Posix.FD

hpath-0.7.3: Support for well-typed paths

Copyright© 2016 Julian Ospald
LicenseBSD3
MaintainerJulian Ospald <hasufell@posteo.de>
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

System.Posix.FD

Description

Provides an alternative for openFd + which gives us more control on what status flags to pass to the + low-level open(2) call, in contrast to the unix package.

Synopsis

  • openFd :: RawFilePath -> OpenMode -> [Flags] -> Maybe FileMode -> IO Fd

Documentation

openFd Source #

Arguments

:: RawFilePath 
-> OpenMode 
-> [Flags]

status flags of open(2)

-> Maybe FileMode

Just x => creates the file with the given modes, Nothing => the file must exist.

-> IO Fd 

Open and optionally create this file. See Files + for information on how to use the FileMode type.

Note that passing Just x as the 4th argument triggers the + oCreat status flag, which must be set when you pass in oExcl + to the status flags. Also see the manpage for open(2).

\ No newline at end of file diff --git a/System-Posix-FilePath.html b/System-Posix-FilePath.html new file mode 100644 index 0000000..c2d7047 --- /dev/null +++ b/System-Posix-FilePath.html @@ -0,0 +1,243 @@ +System.Posix.FilePath

hpath-0.7.3: Support for well-typed paths

Copyright© 2016 Julian Ospald
LicenseBSD3
MaintainerJulian Ospald <hasufell@posteo.de>
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

System.Posix.FilePath

Description

The equivalent of System.FilePath on raw (byte string) file paths.

Not all functions of System.FilePath are implemented yet. Feel free to contribute!

Synopsis

Separator predicates

pathSeparator :: Word8 Source #

Path separator character

isPathSeparator :: Word8 -> Bool Source #

Check if a character is the path separator

\n ->  (_chr n == '/') == isPathSeparator n

searchPathSeparator :: Word8 Source #

Search path separator

isSearchPathSeparator :: Word8 -> Bool Source #

Check if a character is the search path separator

\n -> (_chr n == ':') == isSearchPathSeparator n

extSeparator :: Word8 Source #

File extension separator

isExtSeparator :: Word8 -> Bool Source #

Check if a character is the file extension separator

\n -> (_chr n == '.') == isExtSeparator n

$PATH methods

splitSearchPath :: ByteString -> [RawFilePath] Source #

Take a ByteString, split it on the searchPathSeparator. + Blank items are converted to ..

Follows the recommendations in + http://www.opengroup.org/onlinepubs/009695399/basedefs/xbd_chap08.html

>>> splitSearchPath "File1:File2:File3"
+["File1","File2","File3"]
+>>> splitSearchPath "File1::File2:File3"
+["File1",".","File2","File3"]
+>>> splitSearchPath ""
+["."]
+

getSearchPath :: IO [RawFilePath] Source #

Get a list of RawFilePaths in the $PATH variable.

Extension functions

splitExtension :: RawFilePath -> (RawFilePath, ByteString) Source #

Split a RawFilePath into a path+filename and extension

>>> splitExtension "file.exe"
+("file",".exe")
+>>> splitExtension "file"
+("file","")
+>>> splitExtension "/path/file.tar.gz"
+("/path/file.tar",".gz")
+
\path -> uncurry (BS.append) (splitExtension path) == path

takeExtension :: RawFilePath -> ByteString Source #

Get the final extension from a RawFilePath

>>> takeExtension "file.exe"
+".exe"
+>>> takeExtension "file"
+""
+>>> takeExtension "/path/file.tar.gz"
+".gz"
+

replaceExtension :: RawFilePath -> ByteString -> RawFilePath Source #

Change a file's extension

\path -> let ext = takeExtension path in replaceExtension path ext == path

dropExtension :: RawFilePath -> RawFilePath Source #

Drop the final extension from a RawFilePath

>>> dropExtension "file.exe"
+"file"
+>>> dropExtension "file"
+"file"
+>>> dropExtension "/path/file.tar.gz"
+"/path/file.tar"
+

addExtension :: RawFilePath -> ByteString -> RawFilePath Source #

Add an extension to a RawFilePath

>>> addExtension "file" ".exe"
+"file.exe"
+>>> addExtension "file.tar" ".gz"
+"file.tar.gz"
+>>> addExtension "/path/" ".ext"
+"/path/.ext"
+

hasExtension :: RawFilePath -> Bool Source #

Check if a RawFilePath has an extension

>>> hasExtension "file"
+False
+>>> hasExtension "file.tar"
+True
+>>> hasExtension "/path.part1/"
+False
+

(<.>) :: RawFilePath -> ByteString -> RawFilePath Source #

Operator version of addExtension

splitExtensions :: RawFilePath -> (RawFilePath, ByteString) Source #

Split a RawFilePath on the first extension.

>>> splitExtensions "/path/file.tar.gz"
+("/path/file",".tar.gz")
+
\path -> uncurry addExtension (splitExtensions path) == path

dropExtensions :: RawFilePath -> RawFilePath Source #

Remove all extensions from a RawFilePath

>>> dropExtensions "/path/file.tar.gz"
+"/path/file"
+

takeExtensions :: RawFilePath -> ByteString Source #

Take all extensions from a RawFilePath

>>> takeExtensions "/path/file.tar.gz"
+".tar.gz"
+

stripExtension :: ByteString -> RawFilePath -> Maybe RawFilePath Source #

Drop the given extension from a FilePath, and the "." preceding it. + Returns Nothing if the FilePath does not have the given extension, or + Just and the part before the extension if it does.

This function can be more predictable than dropExtensions, + especially if the filename might itself contain . characters.

>>> stripExtension "hs.o" "foo.x.hs.o"
+Just "foo.x"
+>>> stripExtension "hi.o" "foo.x.hs.o"
+Nothing
+>>> stripExtension ".c.d" "a.b.c.d"
+Just "a.b"
+>>> stripExtension ".c.d" "a.b..c.d"
+Just "a.b."
+>>> stripExtension "baz"  "foo.bar"
+Nothing
+>>> stripExtension "bar"  "foobar"
+Nothing
+
\path -> stripExtension "" path == Just path
\path -> dropExtension path  == fromJust (stripExtension (takeExtension path) path)
\path -> dropExtensions path == fromJust (stripExtension (takeExtensions path) path)

Filename/directory functions

splitFileName :: RawFilePath -> (RawFilePath, RawFilePath) Source #

Split a RawFilePath into (path,file). combine is the inverse

>>> splitFileName "path/file.txt"
+("path/","file.txt")
+>>> splitFileName "path/"
+("path/","")
+>>> splitFileName "file.txt"
+("./","file.txt")
+
\path -> uncurry combine (splitFileName path) == path || fst (splitFileName path) == "./"

takeFileName :: RawFilePath -> RawFilePath Source #

Get the file name

>>> takeFileName "path/file.txt"
+"file.txt"
+>>> takeFileName "path/"
+""
+

replaceFileName :: RawFilePath -> ByteString -> RawFilePath Source #

Change the file name

\path -> replaceFileName path (takeFileName path) == path

dropFileName :: RawFilePath -> RawFilePath Source #

Drop the file name

>>> dropFileName "path/file.txt"
+"path/"
+>>> dropFileName "file.txt"
+"./"
+

takeBaseName :: RawFilePath -> ByteString Source #

Get the file name, without a trailing extension

>>> takeBaseName "path/file.tar.gz"
+"file.tar"
+>>> takeBaseName ""
+""
+

replaceBaseName :: RawFilePath -> ByteString -> RawFilePath Source #

Change the base name

>>> replaceBaseName "path/file.tar.gz" "bob"
+"path/bob.gz"
+
\path -> replaceBaseName path (takeBaseName path) == path

takeDirectory :: RawFilePath -> RawFilePath Source #

Get the directory, moving up one level if it's already a directory

>>> takeDirectory "path/file.txt"
+"path"
+>>> takeDirectory "file"
+"."
+>>> takeDirectory "/path/to/"
+"/path/to"
+>>> takeDirectory "/path/to"
+"/path"
+

replaceDirectory :: RawFilePath -> ByteString -> RawFilePath Source #

Change the directory component of a RawFilePath

\path -> replaceDirectory path (takeDirectory path) `equalFilePath` path || takeDirectory path == "."

combine :: RawFilePath -> RawFilePath -> RawFilePath Source #

Join two paths together

>>> combine "/" "file"
+"/file"
+>>> combine "/path/to" "file"
+"/path/to/file"
+>>> combine "file" "/absolute/path"
+"/absolute/path"
+

(</>) :: RawFilePath -> RawFilePath -> RawFilePath Source #

Operator version of combine

splitPath :: RawFilePath -> [RawFilePath] Source #

Split a path into a list of components:

>>> splitPath "/path/to/file.txt"
+["/","path/","to/","file.txt"]
+
\path -> BS.concat (splitPath path) == path

joinPath :: [RawFilePath] -> RawFilePath Source #

Join a split path back together

\path -> joinPath (splitPath path) == path
>>> joinPath ["path","to","file.txt"]
+"path/to/file.txt"
+

splitDirectories :: RawFilePath -> [RawFilePath] Source #

Like splitPath, but without trailing slashes

>>> splitDirectories "/path/to/file.txt"
+["/","path","to","file.txt"]
+>>> splitDirectories ""
+[]
+

Trailing slash functions

hasTrailingPathSeparator :: RawFilePath -> Bool Source #

Check if the last character of a RawFilePath is /.

>>> hasTrailingPathSeparator "/path/"
+True
+>>> hasTrailingPathSeparator "/"
+True
+>>> hasTrailingPathSeparator "/path"
+False
+

addTrailingPathSeparator :: RawFilePath -> RawFilePath Source #

Add a trailing path separator.

>>> addTrailingPathSeparator "/path"
+"/path/"
+>>> addTrailingPathSeparator "/path/"
+"/path/"
+>>> addTrailingPathSeparator "/"
+"/"
+

dropTrailingPathSeparator :: RawFilePath -> RawFilePath Source #

Remove a trailing path separator

>>> dropTrailingPathSeparator "/path/"
+"/path"
+>>> dropTrailingPathSeparator "/path////"
+"/path"
+>>> dropTrailingPathSeparator "/"
+"/"
+>>> dropTrailingPathSeparator "//"
+"/"
+

File name manipulations

normalise :: RawFilePath -> RawFilePath Source #

Normalise a file.

>>> normalise "/file/\\test////"
+"/file/\\test/"
+>>> normalise "/file/./test"
+"/file/test"
+>>> normalise "/test/file/../bob/fred/"
+"/test/file/../bob/fred/"
+>>> normalise "../bob/fred/"
+"../bob/fred/"
+>>> normalise "./bob/fred/"
+"bob/fred/"
+>>> normalise "./bob////.fred/./...///./..///#."
+"bob/.fred/.../../#."
+>>> normalise "."
+"."
+>>> normalise "./"
+"./"
+>>> normalise "./."
+"./"
+>>> normalise "/./"
+"/"
+>>> normalise "/"
+"/"
+>>> normalise "bob/fred/."
+"bob/fred/"
+>>> normalise "//home"
+"/home"
+

makeRelative :: RawFilePath -> RawFilePath -> RawFilePath Source #

Contract a filename, based on a relative path. Note that the resulting + path will never introduce .. paths, as the presence of symlinks + means ../b may not reach a/b if it starts from a/c. For a + worked example see + this blog post.

>>> makeRelative "/directory" "/directory/file.ext"
+"file.ext"
+>>> makeRelative "/Home" "/home/bob"
+"/home/bob"
+>>> makeRelative "/home/" "/home/bob/foo/bar"
+"bob/foo/bar"
+>>> makeRelative "/fred" "bob"
+"bob"
+>>> makeRelative "/file/test" "/file/test/fred"
+"fred"
+>>> makeRelative "/file/test" "/file/test/fred/"
+"fred/"
+>>> makeRelative "some/path" "some/path/a/b/c"
+"a/b/c"
+
\p -> makeRelative p p == "."
\p -> makeRelative (takeDirectory p) p `equalFilePath` takeFileName p

prop x y -> equalFilePath x y || (isRelative x && makeRelative y x == x) || equalFilePath (y / makeRelative y x) x

equalFilePath :: RawFilePath -> RawFilePath -> Bool Source #

Equality of two filepaths. The filepaths are normalised + and trailing path separators are dropped.

>>> equalFilePath "foo" "foo"
+True
+>>> equalFilePath "foo" "foo/"
+True
+>>> equalFilePath "foo" "./foo"
+True
+>>> equalFilePath "" ""
+True
+>>> equalFilePath "foo" "/foo"
+False
+>>> equalFilePath "foo" "FOO"
+False
+>>> equalFilePath "foo" "../foo"
+False
+
\p -> equalFilePath p p

isRelative :: RawFilePath -> Bool Source #

Check if a path is relative

\path -> isRelative path /= isAbsolute path

isAbsolute :: RawFilePath -> Bool Source #

Check if a path is absolute

>>> isAbsolute "/path"
+True
+>>> isAbsolute "path"
+False
+>>> isAbsolute ""
+False
+

isValid :: RawFilePath -> Bool Source #

Is a FilePath valid, i.e. could you create a file like it?

>>> isValid ""
+False
+>>> isValid "\0"
+False
+>>> isValid "/random_ path:*"
+True
+

makeValid :: RawFilePath -> RawFilePath Source #

Take a FilePath and make it valid; does not change already valid FilePaths.

>>> makeValid ""
+"_"
+>>> makeValid "file\0name"
+"file_name"
+
\p -> if isValid p then makeValid p == p else makeValid p /= p
\p -> isValid (makeValid p)

isFileName :: RawFilePath -> Bool Source #

Is the given path a valid filename? This includes + "." and "..".

>>> isFileName "lal"
+True
+>>> isFileName "."
+True
+>>> isFileName ".."
+True
+>>> isFileName ""
+False
+>>> isFileName "\0"
+False
+>>> isFileName "/random_ path:*"
+False
+

hasParentDir :: RawFilePath -> Bool Source #

Check if the filepath has any parent directories in it.

>>> hasParentDir "/.."
+True
+>>> hasParentDir "foo/bar/.."
+True
+>>> hasParentDir "foo/../bar/."
+True
+>>> hasParentDir "foo/bar"
+False
+>>> hasParentDir "foo"
+False
+>>> hasParentDir ""
+False
+>>> hasParentDir ".."
+False
+

hiddenFile :: RawFilePath -> Bool Source #

Whether the file is a hidden file.

>>> hiddenFile ".foo"
+True
+>>> hiddenFile "..foo.bar"
+True
+>>> hiddenFile "some/path/.bar"
+True
+>>> hiddenFile "..."
+True
+>>> hiddenFile "dod.bar"
+False
+>>> hiddenFile "."
+False
+>>> hiddenFile ".."
+False
+>>> hiddenFile ""
+False
+
\ No newline at end of file diff --git a/doc-index-60.html b/doc-index-60.html new file mode 100644 index 0000000..fa15375 --- /dev/null +++ b/doc-index-60.html @@ -0,0 +1,4 @@ +hpath-0.7.3: Support for well-typed paths (Index - <)

hpath-0.7.3: Support for well-typed paths

Index - <

<.>System.Posix.FilePath
</> 
1 (Function)System.Posix.FilePath
2 (Function)HPath
\ No newline at end of file diff --git a/doc-index-A.html b/doc-index-A.html new file mode 100644 index 0000000..d1bf764 --- /dev/null +++ b/doc-index-A.html @@ -0,0 +1,4 @@ +hpath-0.7.3: Support for well-typed paths (Index - A)

hpath-0.7.3: Support for well-typed paths

Index - A

AbsHPath
addExtensionSystem.Posix.FilePath
addTrailingPathSeparatorSystem.Posix.FilePath
allDirectoryContentsSystem.Posix.Directory.Traversals
allDirectoryContents'System.Posix.Directory.Traversals
\ No newline at end of file diff --git a/doc-index-All.html b/doc-index-All.html new file mode 100644 index 0000000..3cf9553 --- /dev/null +++ b/doc-index-All.html @@ -0,0 +1,4 @@ +hpath-0.7.3: Support for well-typed paths (Index)

hpath-0.7.3: Support for well-typed paths

Index

<.>System.Posix.FilePath
</> 
1 (Function)System.Posix.FilePath
2 (Function)HPath
AbsHPath
addExtensionSystem.Posix.FilePath
addTrailingPathSeparatorSystem.Posix.FilePath
allDirectoryContentsSystem.Posix.Directory.Traversals
allDirectoryContents'System.Posix.Directory.Traversals
basenameHPath
BlockDeviceHPath.IO
bracketeerHPath.IO.Errors
Can'tOpenDirectoryHPath.IO.Errors
canonicalizePathHPath.IO
canOpenDirectoryHPath.IO.Errors
catchErrnoHPath.IO.Errors
CharacterDeviceHPath.IO
combineSystem.Posix.FilePath
copyDirRecursiveHPath.IO
copyDirRecursiveOverwriteHPath.IO
CopyFailedHPath.IO.Errors
copyFileHPath.IO
copyFileOverwriteHPath.IO
createDirHPath.IO
createRegularFileHPath.IO
createSymlinkHPath.IO
deleteDirHPath.IO
deleteDirRecursiveHPath.IO
deleteFileHPath.IO
DestinationInSourceHPath.IO.Errors
DirDoesExistHPath.IO.Errors
DirDoesNotExistHPath.IO.Errors
DirectoryHPath.IO
dirnameHPath
DirType 
1 (Type/Class)System.Posix.Directory.Foreign
2 (Data Constructor)System.Posix.Directory.Foreign
doesDirectoryExistHPath.IO.Errors
doesFileExistHPath.IO.Errors
dropExtensionSystem.Posix.FilePath
dropExtensionsSystem.Posix.FilePath
dropFileNameSystem.Posix.FilePath
dropTrailingPathSeparatorSystem.Posix.FilePath
dtBlkSystem.Posix.Directory.Foreign
dtChrSystem.Posix.Directory.Foreign
dtDirSystem.Posix.Directory.Foreign
dtFifoSystem.Posix.Directory.Foreign
dtLnkSystem.Posix.Directory.Foreign
dtRegSystem.Posix.Directory.Foreign
dtSockSystem.Posix.Directory.Foreign
dtUnknownSystem.Posix.Directory.Foreign
easyCopyHPath.IO
easyCopyOverwriteHPath.IO
easyDeleteHPath.IO
equalFilePathSystem.Posix.FilePath
executeFileHPath.IO
extSeparatorSystem.Posix.FilePath
fdOpendirSystem.Posix.Directory.Traversals
FileDoesExistHPath.IO.Errors
FileDoesNotExistHPath.IO.Errors
FileTypeHPath.IO
Flags 
1 (Type/Class)System.Posix.Directory.Foreign
2 (Data Constructor)System.Posix.Directory.Foreign
FnHPath
fromAbsHPath
fromRelHPath
getAllParentsHPath
getDirectoryContentsSystem.Posix.Directory.Traversals
getDirectoryContents'System.Posix.Directory.Traversals
getDirsFilesHPath.IO
getFileTypeHPath.IO
getSearchPathSystem.Posix.FilePath
handleIOErrorHPath.IO.Errors
hasExtensionSystem.Posix.FilePath
hasParentDirSystem.Posix.FilePath
hasTrailingPathSeparatorSystem.Posix.FilePath
hiddenFileSystem.Posix.FilePath
HPathIOExceptionHPath.IO.Errors
InvalidOperationHPath.IO.Errors
isAbsoluteSystem.Posix.FilePath
isCan'tOpenDirectoryHPath.IO.Errors
isCopyFailedHPath.IO.Errors
isDestinationInSourceHPath.IO.Errors
isDirDoesExistHPath.IO.Errors
isDirDoesNotExistHPath.IO.Errors
isExtSeparatorSystem.Posix.FilePath
isFileDoesExistHPath.IO.Errors
isFileDoesNotExistHPath.IO.Errors
isFileNameSystem.Posix.FilePath
isInvalidOperationHPath.IO.Errors
isParentOfHPath
isPathSeparatorSystem.Posix.FilePath
isRelativeSystem.Posix.FilePath
isSameFileHPath.IO.Errors
isSearchPathSeparatorSystem.Posix.FilePath
isSupportedSystem.Posix.Directory.Foreign
isValidSystem.Posix.FilePath
isWritableHPath.IO.Errors
joinPathSystem.Posix.FilePath
makeRelativeSystem.Posix.FilePath
makeValidSystem.Posix.FilePath
moveFileHPath.IO
moveFileOverwriteHPath.IO
NamedPipeHPath.IO
newDirPermsHPath.IO
newFilePermsHPath.IO
normaliseSystem.Posix.FilePath
oAppendSystem.Posix.Directory.Foreign
oAsyncSystem.Posix.Directory.Foreign
oCloexecSystem.Posix.Directory.Foreign
oCreatSystem.Posix.Directory.Foreign
oDirectorySystem.Posix.Directory.Foreign
oExclSystem.Posix.Directory.Foreign
oNocttySystem.Posix.Directory.Foreign
oNofollowSystem.Posix.Directory.Foreign
oNonblockSystem.Posix.Directory.Foreign
openFdSystem.Posix.FD
openFileHPath.IO
oRdonlySystem.Posix.Directory.Foreign
oRdwrSystem.Posix.Directory.Foreign
oSyncSystem.Posix.Directory.Foreign
oTruncSystem.Posix.Directory.Foreign
oWronlySystem.Posix.Directory.Foreign
packDirStreamSystem.Posix.Directory.Traversals
parseAbsHPath
parseFnHPath
parseRelHPath
Path 
1 (Type/Class)HPath
2 (Data Constructor)HPath
PathExceptionHPath
pathMaxSystem.Posix.Directory.Foreign
PathParseExceptionHPath
pathSeparatorSystem.Posix.FilePath
peekFilePathSystem.Posix.FilePath
peekFilePathLenSystem.Posix.FilePath
RawFilePathSystem.Posix.FilePath
reactOnErrorHPath.IO.Errors
readDirEntSystem.Posix.Directory.Traversals
realpathSystem.Posix.Directory.Traversals
recreateSymlinkHPath.IO
RegularFileHPath.IO
RelHPath
RelCHPath
renameFileHPath.IO
replaceBaseNameSystem.Posix.FilePath
replaceDirectorySystem.Posix.FilePath
replaceExtensionSystem.Posix.FilePath
replaceFileNameSystem.Posix.FilePath
rethrowErrnoAsHPath.IO.Errors
SameFileHPath.IO.Errors
sameFileHPath.IO.Errors
searchPathSeparatorSystem.Posix.FilePath
SocketHPath.IO
splitDirectoriesSystem.Posix.FilePath
splitExtensionSystem.Posix.FilePath
splitExtensionsSystem.Posix.FilePath
splitFileNameSystem.Posix.FilePath
splitPathSystem.Posix.FilePath
splitSearchPathSystem.Posix.FilePath
stripDirHPath
stripExtensionSystem.Posix.FilePath
SymbolicLinkHPath.IO
takeBaseNameSystem.Posix.FilePath
takeDirectorySystem.Posix.FilePath
takeExtensionSystem.Posix.FilePath
takeExtensionsSystem.Posix.FilePath
takeFileNameSystem.Posix.FilePath
throwCantOpenDirectoryHPath.IO.Errors
throwDestinationInSourceHPath.IO.Errors
throwDirDoesExistHPath.IO.Errors
throwDirDoesNotExistHPath.IO.Errors
throwErrnoPathSystem.Posix.FilePath
throwErrnoPathIfSystem.Posix.FilePath
throwErrnoPathIfMinus1System.Posix.FilePath
throwErrnoPathIfMinus1RetrySystem.Posix.FilePath
throwErrnoPathIfMinus1Retry_System.Posix.FilePath
throwErrnoPathIfMinus1_System.Posix.FilePath
throwErrnoPathIfNullSystem.Posix.FilePath
throwErrnoPathIfNullRetrySystem.Posix.FilePath
throwErrnoPathIfRetrySystem.Posix.FilePath
throwErrnoPathIf_System.Posix.FilePath
throwFileDoesExistHPath.IO.Errors
throwFileDoesNotExistHPath.IO.Errors
throwSameFileHPath.IO.Errors
toFilePathHPath
traverseDirectorySystem.Posix.Directory.Traversals
unFlagsSystem.Posix.Directory.Foreign
unionFlagsSystem.Posix.Directory.Foreign
unlessMHPath.IO.Utils
unpackDirStreamSystem.Posix.Directory.Traversals
UnsupportedFlagSystem.Posix.Directory.Foreign
whenMHPath.IO.Utils
withAbsPathHPath
withFilePathSystem.Posix.FilePath
withFnPathHPath
withRelPathHPath
\ No newline at end of file diff --git a/doc-index-B.html b/doc-index-B.html new file mode 100644 index 0000000..bfae52e --- /dev/null +++ b/doc-index-B.html @@ -0,0 +1,4 @@ +hpath-0.7.3: Support for well-typed paths (Index - B)

hpath-0.7.3: Support for well-typed paths

Index - B

basenameHPath
BlockDeviceHPath.IO
bracketeerHPath.IO.Errors
\ No newline at end of file diff --git a/doc-index-C.html b/doc-index-C.html new file mode 100644 index 0000000..a90e692 --- /dev/null +++ b/doc-index-C.html @@ -0,0 +1,4 @@ +hpath-0.7.3: Support for well-typed paths (Index - C)

hpath-0.7.3: Support for well-typed paths

Index - C

Can'tOpenDirectoryHPath.IO.Errors
canonicalizePathHPath.IO
canOpenDirectoryHPath.IO.Errors
catchErrnoHPath.IO.Errors
CharacterDeviceHPath.IO
combineSystem.Posix.FilePath
copyDirRecursiveHPath.IO
copyDirRecursiveOverwriteHPath.IO
CopyFailedHPath.IO.Errors
copyFileHPath.IO
copyFileOverwriteHPath.IO
createDirHPath.IO
createRegularFileHPath.IO
createSymlinkHPath.IO
\ No newline at end of file diff --git a/doc-index-D.html b/doc-index-D.html new file mode 100644 index 0000000..c7f0b22 --- /dev/null +++ b/doc-index-D.html @@ -0,0 +1,4 @@ +hpath-0.7.3: Support for well-typed paths (Index - D)

hpath-0.7.3: Support for well-typed paths

\ No newline at end of file diff --git a/doc-index-E.html b/doc-index-E.html new file mode 100644 index 0000000..f858615 --- /dev/null +++ b/doc-index-E.html @@ -0,0 +1,4 @@ +hpath-0.7.3: Support for well-typed paths (Index - E)

hpath-0.7.3: Support for well-typed paths

Index - E

easyCopyHPath.IO
easyCopyOverwriteHPath.IO
easyDeleteHPath.IO
equalFilePathSystem.Posix.FilePath
executeFileHPath.IO
extSeparatorSystem.Posix.FilePath
\ No newline at end of file diff --git a/doc-index-F.html b/doc-index-F.html new file mode 100644 index 0000000..7e73530 --- /dev/null +++ b/doc-index-F.html @@ -0,0 +1,4 @@ +hpath-0.7.3: Support for well-typed paths (Index - F)

hpath-0.7.3: Support for well-typed paths

Index - F

fdOpendirSystem.Posix.Directory.Traversals
FileDoesExistHPath.IO.Errors
FileDoesNotExistHPath.IO.Errors
FileTypeHPath.IO
Flags 
1 (Type/Class)System.Posix.Directory.Foreign
2 (Data Constructor)System.Posix.Directory.Foreign
FnHPath
fromAbsHPath
fromRelHPath
\ No newline at end of file diff --git a/doc-index-G.html b/doc-index-G.html new file mode 100644 index 0000000..39cd299 --- /dev/null +++ b/doc-index-G.html @@ -0,0 +1,4 @@ +hpath-0.7.3: Support for well-typed paths (Index - G)

hpath-0.7.3: Support for well-typed paths

Index - G

getAllParentsHPath
getDirectoryContentsSystem.Posix.Directory.Traversals
getDirectoryContents'System.Posix.Directory.Traversals
getDirsFilesHPath.IO
getFileTypeHPath.IO
getSearchPathSystem.Posix.FilePath
\ No newline at end of file diff --git a/doc-index-H.html b/doc-index-H.html new file mode 100644 index 0000000..7ab6e8f --- /dev/null +++ b/doc-index-H.html @@ -0,0 +1,4 @@ +hpath-0.7.3: Support for well-typed paths (Index - H)

hpath-0.7.3: Support for well-typed paths

Index - H

handleIOErrorHPath.IO.Errors
hasExtensionSystem.Posix.FilePath
hasParentDirSystem.Posix.FilePath
hasTrailingPathSeparatorSystem.Posix.FilePath
hiddenFileSystem.Posix.FilePath
HPathIOExceptionHPath.IO.Errors
\ No newline at end of file diff --git a/doc-index-I.html b/doc-index-I.html new file mode 100644 index 0000000..b795585 --- /dev/null +++ b/doc-index-I.html @@ -0,0 +1,4 @@ +hpath-0.7.3: Support for well-typed paths (Index - I)

hpath-0.7.3: Support for well-typed paths

Index - I

InvalidOperationHPath.IO.Errors
isAbsoluteSystem.Posix.FilePath
isCan'tOpenDirectoryHPath.IO.Errors
isCopyFailedHPath.IO.Errors
isDestinationInSourceHPath.IO.Errors
isDirDoesExistHPath.IO.Errors
isDirDoesNotExistHPath.IO.Errors
isExtSeparatorSystem.Posix.FilePath
isFileDoesExistHPath.IO.Errors
isFileDoesNotExistHPath.IO.Errors
isFileNameSystem.Posix.FilePath
isInvalidOperationHPath.IO.Errors
isParentOfHPath
isPathSeparatorSystem.Posix.FilePath
isRelativeSystem.Posix.FilePath
isSameFileHPath.IO.Errors
isSearchPathSeparatorSystem.Posix.FilePath
isSupportedSystem.Posix.Directory.Foreign
isValidSystem.Posix.FilePath
isWritableHPath.IO.Errors
\ No newline at end of file diff --git a/doc-index-J.html b/doc-index-J.html new file mode 100644 index 0000000..521d4d4 --- /dev/null +++ b/doc-index-J.html @@ -0,0 +1,4 @@ +hpath-0.7.3: Support for well-typed paths (Index - J)

hpath-0.7.3: Support for well-typed paths

Index - J

joinPathSystem.Posix.FilePath
\ No newline at end of file diff --git a/doc-index-M.html b/doc-index-M.html new file mode 100644 index 0000000..f43058a --- /dev/null +++ b/doc-index-M.html @@ -0,0 +1,4 @@ +hpath-0.7.3: Support for well-typed paths (Index - M)

hpath-0.7.3: Support for well-typed paths

Index - M

makeRelativeSystem.Posix.FilePath
makeValidSystem.Posix.FilePath
moveFileHPath.IO
moveFileOverwriteHPath.IO
\ No newline at end of file diff --git a/doc-index-N.html b/doc-index-N.html new file mode 100644 index 0000000..131807b --- /dev/null +++ b/doc-index-N.html @@ -0,0 +1,4 @@ +hpath-0.7.3: Support for well-typed paths (Index - N)

hpath-0.7.3: Support for well-typed paths

Index - N

NamedPipeHPath.IO
newDirPermsHPath.IO
newFilePermsHPath.IO
normaliseSystem.Posix.FilePath
\ No newline at end of file diff --git a/doc-index-O.html b/doc-index-O.html new file mode 100644 index 0000000..5406a08 --- /dev/null +++ b/doc-index-O.html @@ -0,0 +1,4 @@ +hpath-0.7.3: Support for well-typed paths (Index - O)

hpath-0.7.3: Support for well-typed paths

\ No newline at end of file diff --git a/doc-index-P.html b/doc-index-P.html new file mode 100644 index 0000000..7933f1b --- /dev/null +++ b/doc-index-P.html @@ -0,0 +1,4 @@ +hpath-0.7.3: Support for well-typed paths (Index - P)

hpath-0.7.3: Support for well-typed paths

Index - P

packDirStreamSystem.Posix.Directory.Traversals
parseAbsHPath
parseFnHPath
parseRelHPath
Path 
1 (Type/Class)HPath
2 (Data Constructor)HPath
PathExceptionHPath
pathMaxSystem.Posix.Directory.Foreign
PathParseExceptionHPath
pathSeparatorSystem.Posix.FilePath
peekFilePathSystem.Posix.FilePath
peekFilePathLenSystem.Posix.FilePath
\ No newline at end of file diff --git a/doc-index-R.html b/doc-index-R.html new file mode 100644 index 0000000..4bd0f6c --- /dev/null +++ b/doc-index-R.html @@ -0,0 +1,4 @@ +hpath-0.7.3: Support for well-typed paths (Index - R)

hpath-0.7.3: Support for well-typed paths

Index - R

RawFilePathSystem.Posix.FilePath
reactOnErrorHPath.IO.Errors
readDirEntSystem.Posix.Directory.Traversals
realpathSystem.Posix.Directory.Traversals
recreateSymlinkHPath.IO
RegularFileHPath.IO
RelHPath
RelCHPath
renameFileHPath.IO
replaceBaseNameSystem.Posix.FilePath
replaceDirectorySystem.Posix.FilePath
replaceExtensionSystem.Posix.FilePath
replaceFileNameSystem.Posix.FilePath
rethrowErrnoAsHPath.IO.Errors
\ No newline at end of file diff --git a/doc-index-S.html b/doc-index-S.html new file mode 100644 index 0000000..f9a1816 --- /dev/null +++ b/doc-index-S.html @@ -0,0 +1,4 @@ +hpath-0.7.3: Support for well-typed paths (Index - S)

hpath-0.7.3: Support for well-typed paths

Index - S

SameFileHPath.IO.Errors
sameFileHPath.IO.Errors
searchPathSeparatorSystem.Posix.FilePath
SocketHPath.IO
splitDirectoriesSystem.Posix.FilePath
splitExtensionSystem.Posix.FilePath
splitExtensionsSystem.Posix.FilePath
splitFileNameSystem.Posix.FilePath
splitPathSystem.Posix.FilePath
splitSearchPathSystem.Posix.FilePath
stripDirHPath
stripExtensionSystem.Posix.FilePath
SymbolicLinkHPath.IO
\ No newline at end of file diff --git a/doc-index-T.html b/doc-index-T.html new file mode 100644 index 0000000..64b376e --- /dev/null +++ b/doc-index-T.html @@ -0,0 +1,4 @@ +hpath-0.7.3: Support for well-typed paths (Index - T)

hpath-0.7.3: Support for well-typed paths

Index - T

takeBaseNameSystem.Posix.FilePath
takeDirectorySystem.Posix.FilePath
takeExtensionSystem.Posix.FilePath
takeExtensionsSystem.Posix.FilePath
takeFileNameSystem.Posix.FilePath
throwCantOpenDirectoryHPath.IO.Errors
throwDestinationInSourceHPath.IO.Errors
throwDirDoesExistHPath.IO.Errors
throwDirDoesNotExistHPath.IO.Errors
throwErrnoPathSystem.Posix.FilePath
throwErrnoPathIfSystem.Posix.FilePath
throwErrnoPathIfMinus1System.Posix.FilePath
throwErrnoPathIfMinus1RetrySystem.Posix.FilePath
throwErrnoPathIfMinus1Retry_System.Posix.FilePath
throwErrnoPathIfMinus1_System.Posix.FilePath
throwErrnoPathIfNullSystem.Posix.FilePath
throwErrnoPathIfNullRetrySystem.Posix.FilePath
throwErrnoPathIfRetrySystem.Posix.FilePath
throwErrnoPathIf_System.Posix.FilePath
throwFileDoesExistHPath.IO.Errors
throwFileDoesNotExistHPath.IO.Errors
throwSameFileHPath.IO.Errors
toFilePathHPath
traverseDirectorySystem.Posix.Directory.Traversals
\ No newline at end of file diff --git a/doc-index-U.html b/doc-index-U.html new file mode 100644 index 0000000..609a00a --- /dev/null +++ b/doc-index-U.html @@ -0,0 +1,4 @@ +hpath-0.7.3: Support for well-typed paths (Index - U)

hpath-0.7.3: Support for well-typed paths

\ No newline at end of file diff --git a/doc-index-W.html b/doc-index-W.html new file mode 100644 index 0000000..7031f1e --- /dev/null +++ b/doc-index-W.html @@ -0,0 +1,4 @@ +hpath-0.7.3: Support for well-typed paths (Index - W)

hpath-0.7.3: Support for well-typed paths

Index - W

whenMHPath.IO.Utils
withAbsPathHPath
withFilePathSystem.Posix.FilePath
withFnPathHPath
withRelPathHPath
\ No newline at end of file diff --git a/doc-index.html b/doc-index.html new file mode 100644 index 0000000..0ae4126 --- /dev/null +++ b/doc-index.html @@ -0,0 +1,4 @@ +hpath-0.7.3: Support for well-typed paths (Index)

hpath-0.7.3: Support for well-typed paths

\ No newline at end of file diff --git a/frames.html b/frames.html new file mode 100644 index 0000000..e86edb6 --- /dev/null +++ b/frames.html @@ -0,0 +1,30 @@ + + + + + + + + + + + + + + + diff --git a/haddock-util.js b/haddock-util.js new file mode 100644 index 0000000..fc7743f --- /dev/null +++ b/haddock-util.js @@ -0,0 +1,344 @@ +// Haddock JavaScript utilities + +var rspace = /\s\s+/g, + rtrim = /^\s+|\s+$/g; + +function spaced(s) { return (" " + s + " ").replace(rspace, " "); } +function trim(s) { return s.replace(rtrim, ""); } + +function hasClass(elem, value) { + var className = spaced(elem.className || ""); + return className.indexOf( " " + value + " " ) >= 0; +} + +function addClass(elem, value) { + var className = spaced(elem.className || ""); + if ( className.indexOf( " " + value + " " ) < 0 ) { + elem.className = trim(className + " " + value); + } +} + +function removeClass(elem, value) { + var className = spaced(elem.className || ""); + className = className.replace(" " + value + " ", " "); + elem.className = trim(className); +} + +function toggleClass(elem, valueOn, valueOff, bool) { + if (bool == null) { bool = ! hasClass(elem, valueOn); } + if (bool) { + removeClass(elem, valueOff); + addClass(elem, valueOn); + } + else { + removeClass(elem, valueOn); + addClass(elem, valueOff); + } + return bool; +} + + +function makeClassToggle(valueOn, valueOff) +{ + return function(elem, bool) { + return toggleClass(elem, valueOn, valueOff, bool); + } +} + +toggleShow = makeClassToggle("show", "hide"); +toggleCollapser = makeClassToggle("collapser", "expander"); + +function toggleSection(id) +{ + var b = toggleShow(document.getElementById("section." + id)); + toggleCollapser(document.getElementById("control." + id), b); + rememberCollapsed(id, b); + return b; +} + +var collapsed = {}; +function rememberCollapsed(id, b) +{ + if(b) + delete collapsed[id] + else + collapsed[id] = null; + + var sections = []; + for(var i in collapsed) + { + if(collapsed.hasOwnProperty(i)) + sections.push(i); + } + // cookie specific to this page; don't use setCookie which sets path=/ + document.cookie = "collapsed=" + escape(sections.join('+')); +} + +function restoreCollapsed() +{ + var cookie = getCookie("collapsed"); + if(!cookie) + return; + + var ids = cookie.split('+'); + for(var i in ids) + { + if(document.getElementById("section." + ids[i])) + toggleSection(ids[i]); + } +} + +function setCookie(name, value) { + document.cookie = name + "=" + escape(value) + ";path=/;"; +} + +function clearCookie(name) { + document.cookie = name + "=;path=/;expires=Thu, 01-Jan-1970 00:00:01 GMT;"; +} + +function getCookie(name) { + var nameEQ = name + "="; + var ca = document.cookie.split(';'); + for(var i=0;i < ca.length;i++) { + var c = ca[i]; + while (c.charAt(0)==' ') c = c.substring(1,c.length); + if (c.indexOf(nameEQ) == 0) { + return unescape(c.substring(nameEQ.length,c.length)); + } + } + return null; +} + + + +var max_results = 75; // 50 is not enough to search for map in the base libraries +var shown_range = null; +var last_search = null; + +function quick_search() +{ + perform_search(false); +} + +function full_search() +{ + perform_search(true); +} + + +function perform_search(full) +{ + var text = document.getElementById("searchbox").value.toLowerCase(); + if (text == last_search && !full) return; + last_search = text; + + var table = document.getElementById("indexlist"); + var status = document.getElementById("searchmsg"); + var children = table.firstChild.childNodes; + + // first figure out the first node with the prefix + var first = bisect(-1); + var last = (first == -1 ? -1 : bisect(1)); + + if (first == -1) + { + table.className = ""; + status.innerHTML = "No results found, displaying all"; + } + else if (first == 0 && last == children.length - 1) + { + table.className = ""; + status.innerHTML = ""; + } + else if (last - first >= max_results && !full) + { + table.className = ""; + status.innerHTML = "More than " + max_results + ", press Search to display"; + } + else + { + // decide what you need to clear/show + if (shown_range) + setclass(shown_range[0], shown_range[1], "indexrow"); + setclass(first, last, "indexshow"); + shown_range = [first, last]; + table.className = "indexsearch"; + status.innerHTML = ""; + } + + + function setclass(first, last, status) + { + for (var i = first; i <= last; i++) + { + children[i].className = status; + } + } + + + // do a binary search, treating 0 as ... + // return either -1 (no 0's found) or location of most far match + function bisect(dir) + { + var first = 0, finish = children.length - 1; + var mid, success = false; + + while (finish - first > 3) + { + mid = Math.floor((finish + first) / 2); + + var i = checkitem(mid); + if (i == 0) i = dir; + if (i == -1) + finish = mid; + else + first = mid; + } + var a = (dir == 1 ? first : finish); + var b = (dir == 1 ? finish : first); + for (var i = b; i != a - dir; i -= dir) + { + if (checkitem(i) == 0) return i; + } + return -1; + } + + + // from an index, decide what the result is + // 0 = match, -1 is lower, 1 is higher + function checkitem(i) + { + var s = getitem(i).toLowerCase().substr(0, text.length); + if (s == text) return 0; + else return (s > text ? -1 : 1); + } + + + // from an index, get its string + // this abstracts over alternates + function getitem(i) + { + for ( ; i >= 0; i--) + { + var s = children[i].firstChild.firstChild.data; + if (s.indexOf(' ') == -1) + return s; + } + return ""; // should never be reached + } +} + +function setSynopsis(filename) { + if (parent.window.synopsis && parent.window.synopsis.location) { + if (parent.window.synopsis.location.replace) { + // In Firefox this avoids adding the change to the history. + parent.window.synopsis.location.replace(filename); + } else { + parent.window.synopsis.location = filename; + } + } +} + +function addMenuItem(html) { + var menu = document.getElementById("page-menu"); + if (menu) { + var btn = menu.firstChild.cloneNode(false); + btn.innerHTML = html; + menu.appendChild(btn); + } +} + +function adjustForFrames() { + var bodyCls; + + if (parent.location.href == window.location.href) { + // not in frames, so add Frames button + addMenuItem("Frames"); + bodyCls = "no-frame"; + } + else { + bodyCls = "in-frame"; + } + addClass(document.body, bodyCls); +} + +function reframe() { + setCookie("haddock-reframe", document.URL); + window.location = "frames.html"; +} + +function postReframe() { + var s = getCookie("haddock-reframe"); + if (s) { + parent.window.main.location = s; + clearCookie("haddock-reframe"); + } +} + +function styles() { + var i, a, es = document.getElementsByTagName("link"), rs = []; + for (i = 0; a = es[i]; i++) { + if(a.rel.indexOf("style") != -1 && a.title) { + rs.push(a); + } + } + return rs; +} + +function addStyleMenu() { + var as = styles(); + var i, a, btns = ""; + for(i=0; a = as[i]; i++) { + btns += "
  • " + + a.title + "
  • " + } + if (as.length > 1) { + var h = "
    " + + "Style ▾" + + "" + + "
    "; + addMenuItem(h); + } +} + +function setActiveStyleSheet(title) { + var as = styles(); + var i, a, found; + for(i=0; a = as[i]; i++) { + a.disabled = true; + // need to do this always, some browsers are edge triggered + if(a.title == title) { + found = a; + } + } + if (found) { + found.disabled = false; + setCookie("haddock-style", title); + } + else { + as[0].disabled = false; + clearCookie("haddock-style"); + } + styleMenu(false); +} + +function resetStyle() { + var s = getCookie("haddock-style"); + if (s) setActiveStyleSheet(s); +} + + +function styleMenu(show) { + var m = document.getElementById('style-menu'); + if (m) toggleShow(m, show); +} + + +function pageLoad() { + addStyleMenu(); + adjustForFrames(); + resetStyle(); + restoreCollapsed(); +} + diff --git a/hpath.haddock b/hpath.haddock new file mode 100644 index 0000000..34fb6f2 Binary files /dev/null and b/hpath.haddock differ diff --git a/hslogo-16.png b/hslogo-16.png new file mode 100644 index 0000000..0ff8579 Binary files /dev/null and b/hslogo-16.png differ diff --git a/index-frames.html b/index-frames.html new file mode 100644 index 0000000..1ccae3b --- /dev/null +++ b/index-frames.html @@ -0,0 +1,4 @@ +hpath-0.7.3: Support for well-typed paths

    Modules

    \ No newline at end of file diff --git a/index.html b/index.html new file mode 100644 index 0000000..ebb52d5 --- /dev/null +++ b/index.html @@ -0,0 +1,4 @@ +hpath-0.7.3: Support for well-typed paths

    hpath-0.7.3: Support for well-typed paths

    hpath-0.7.3: Support for well-typed paths

    Support for well-typed paths, utilizing ByteString under the hood.

    \ No newline at end of file diff --git a/mini_HPath-IO-Errors.html b/mini_HPath-IO-Errors.html new file mode 100644 index 0000000..52b65ce --- /dev/null +++ b/mini_HPath-IO-Errors.html @@ -0,0 +1,4 @@ +HPath.IO.Errors

    HPath.IO.Errors

    Types

    Exception identifiers

    Path based functions

    Error handling functions

    \ No newline at end of file diff --git a/mini_HPath-IO-Utils.html b/mini_HPath-IO-Utils.html new file mode 100644 index 0000000..1ce788b --- /dev/null +++ b/mini_HPath-IO-Utils.html @@ -0,0 +1,4 @@ +HPath.IO.Utils

    HPath.IO.Utils

    \ No newline at end of file diff --git a/mini_HPath-IO.html b/mini_HPath-IO.html new file mode 100644 index 0000000..b3bedc4 --- /dev/null +++ b/mini_HPath-IO.html @@ -0,0 +1,4 @@ +HPath.IO

    HPath.IO

    Types

    File copying

    File deletion

    File opening

    File creation

    File renaming/moving

    File permissions

    Directory reading

    Filetype operations

    Others

    \ No newline at end of file diff --git a/mini_HPath.html b/mini_HPath.html new file mode 100644 index 0000000..f1b0237 --- /dev/null +++ b/mini_HPath.html @@ -0,0 +1,4 @@ +HPath

    HPath

    Types

    data Abs

    data Path b

    data Rel

    data Fn

    class RelC m

    PatternSynonyms/ViewPatterns

    Path Parsing

    Path Conversion

    Path Operations

    Path IO helpers

    \ No newline at end of file diff --git a/mini_System-Posix-Directory-Foreign.html b/mini_System-Posix-Directory-Foreign.html new file mode 100644 index 0000000..991dcbd --- /dev/null +++ b/mini_System-Posix-Directory-Foreign.html @@ -0,0 +1,4 @@ +System.Posix.Directory.Foreign

    System.Posix.Directory.Foreign

    data DirType

    data Flags

    \ No newline at end of file diff --git a/mini_System-Posix-Directory-Traversals.html b/mini_System-Posix-Directory-Traversals.html new file mode 100644 index 0000000..281fb1a --- /dev/null +++ b/mini_System-Posix-Directory-Traversals.html @@ -0,0 +1,4 @@ +System.Posix.Directory.Traversals

    System.Posix.Directory.Traversals

    \ No newline at end of file diff --git a/mini_System-Posix-FD.html b/mini_System-Posix-FD.html new file mode 100644 index 0000000..6c7914a --- /dev/null +++ b/mini_System-Posix-FD.html @@ -0,0 +1,4 @@ +System.Posix.FD

    System.Posix.FD

    \ No newline at end of file diff --git a/mini_System-Posix-FilePath.html b/mini_System-Posix-FilePath.html new file mode 100644 index 0000000..e1d7491 --- /dev/null +++ b/mini_System-Posix-FilePath.html @@ -0,0 +1,4 @@ +System.Posix.FilePath

    System.Posix.FilePath

    Separator predicates

    $PATH methods

    Extension functions

    Filename/directory functions

    Trailing slash functions

    File name manipulations

    \ No newline at end of file diff --git a/minus.gif b/minus.gif new file mode 100644 index 0000000..1deac2f Binary files /dev/null and b/minus.gif differ diff --git a/ocean.css b/ocean.css new file mode 100644 index 0000000..3ebb14d --- /dev/null +++ b/ocean.css @@ -0,0 +1,610 @@ +/* @group Fundamentals */ + +* { margin: 0; padding: 0 } + +/* Is this portable? */ +html { + background-color: white; + width: 100%; + height: 100%; +} + +body { + background: white; + color: black; + text-align: left; + min-height: 100%; + position: relative; +} + +p { + margin: 0.8em 0; +} + +ul, ol { + margin: 0.8em 0 0.8em 2em; +} + +dl { + margin: 0.8em 0; +} + +dt { + font-weight: bold; +} +dd { + margin-left: 2em; +} + +a { text-decoration: none; } +a[href]:link { color: rgb(196,69,29); } +a[href]:visited { color: rgb(171,105,84); } +a[href]:hover { text-decoration:underline; } + +a[href].def:link, a[href].def:visited { color: black; } +a[href].def:hover { color: rgb(78, 98, 114); } + +/* @end */ + +/* @group Fonts & Sizes */ + +/* Basic technique & IE workarounds from YUI 3 + For reasons, see: + http://yui.yahooapis.com/3.1.1/build/cssfonts/fonts.css + */ + +body { + font:13px/1.4 sans-serif; + *font-size:small; /* for IE */ + *font:x-small; /* for IE in quirks mode */ +} + +h1 { font-size: 146.5%; /* 19pt */ } +h2 { font-size: 131%; /* 17pt */ } +h3 { font-size: 116%; /* 15pt */ } +h4 { font-size: 100%; /* 13pt */ } +h5 { font-size: 100%; /* 13pt */ } + +select, input, button, textarea { + font:99% sans-serif; +} + +table { + font-size:inherit; + font:100%; +} + +pre, code, kbd, samp, tt, .src { + font-family:monospace; + *font-size:108%; + line-height: 124%; +} + +.links, .link { + font-size: 85%; /* 11pt */ +} + +#module-header .caption { + font-size: 182%; /* 24pt */ +} + +.info { + font-size: 85%; /* 11pt */ +} + +#table-of-contents, #synopsis { + /* font-size: 85%; /* 11pt */ +} + + +/* @end */ + +/* @group Common */ + +.caption, h1, h2, h3, h4, h5, h6 { + font-weight: bold; + color: rgb(78,98,114); + margin: 0.8em 0 0.4em; +} + +* + h1, * + h2, * + h3, * + h4, * + h5, * + h6 { + margin-top: 2em; +} + +h1 + h2, h2 + h3, h3 + h4, h4 + h5, h5 + h6 { + margin-top: inherit; +} + +ul.links { + list-style: none; + text-align: left; + float: right; + display: inline-table; + margin: 0 0 0 1em; +} + +ul.links li { + display: inline; + border-left: 1px solid #d5d5d5; + white-space: nowrap; + padding: 0; +} + +ul.links li a { + padding: 0.2em 0.5em; +} + +.hide { display: none; } +.show { display: inherit; } +.clear { clear: both; } + +.collapser { + background-image: url(minus.gif); + background-repeat: no-repeat; +} +.expander { + background-image: url(plus.gif); + background-repeat: no-repeat; +} +.collapser, .expander { + padding-left: 14px; + margin-left: -14px; + cursor: pointer; +} +p.caption.collapser, +p.caption.expander { + background-position: 0 0.4em; +} + +.instance.collapser, .instance.expander { + margin-left: 0px; + background-position: left center; + min-width: 9px; + min-height: 9px; +} + + +pre { + padding: 0.25em; + margin: 0.8em 0; + background: rgb(229,237,244); + overflow: auto; + border-bottom: 0.25em solid white; + /* white border adds some space below the box to compensate + for visual extra space that paragraphs have between baseline + and the bounding box */ +} + +.src { + background: #f0f0f0; + padding: 0.2em 0.5em; +} + +.keyword { font-weight: normal; } +.def { font-weight: bold; } + +@media print { + #footer { display: none; } +} + +/* @end */ + +/* @group Page Structure */ + +#content { + margin: 0 auto; + padding: 0 2em 6em; +} + +#package-header { + background: rgb(41,56,69); + border-top: 5px solid rgb(78,98,114); + color: #ddd; + padding: 0.2em; + position: relative; + text-align: left; +} + +#package-header .caption { + background: url(hslogo-16.png) no-repeat 0em; + color: white; + margin: 0 2em; + font-weight: normal; + font-style: normal; + padding-left: 2em; +} + +#package-header a:link, #package-header a:visited { color: white; } +#package-header a:hover { background: rgb(78,98,114); } + +#module-header .caption { + color: rgb(78,98,114); + font-weight: bold; + border-bottom: 1px solid #ddd; +} + +table.info { + float: right; + padding: 0.5em 1em; + border: 1px solid #ddd; + color: rgb(78,98,114); + background-color: #fff; + max-width: 40%; + border-spacing: 0; + position: relative; + top: -0.5em; + margin: 0 0 0 2em; +} + +.info th { + padding: 0 1em 0 0; +} + +div#style-menu-holder { + position: relative; + z-index: 2; + display: inline; +} + +#style-menu { + position: absolute; + z-index: 1; + overflow: visible; + background: #374c5e; + margin: 0; + text-align: center; + right: 0; + padding: 0; + top: 1.25em; +} + +#style-menu li { + display: list-item; + border-style: none; + margin: 0; + padding: 0; + color: #000; + list-style-type: none; +} + +#style-menu li + li { + border-top: 1px solid #919191; +} + +#style-menu a { + width: 6em; + padding: 3px; + display: block; +} + +#footer { + background: #ddd; + border-top: 1px solid #aaa; + padding: 0.5em 0; + color: #666; + text-align: center; + position: absolute; + bottom: 0; + width: 100%; + height: 3em; +} + +/* @end */ + +/* @group Front Matter */ + +#table-of-contents { + float: right; + clear: right; + background: #faf9dc; + border: 1px solid #d8d7ad; + padding: 0.5em 1em; + max-width: 20em; + margin: 0.5em 0 1em 1em; +} + +#table-of-contents .caption { + text-align: center; + margin: 0; +} + +#table-of-contents ul { + list-style: none; + margin: 0; +} + +#table-of-contents ul ul { + margin-left: 2em; +} + +#description .caption { + display: none; +} + +#synopsis { + display: none; +} + +.no-frame #synopsis { + display: block; + position: fixed; + right: 0; + height: 80%; + top: 10%; + padding: 0; + max-width: 75%; +} + +#synopsis .caption { + float: left; + width: 29px; + color: rgba(255,255,255,0); + height: 110px; + margin: 0; + font-size: 1px; + padding: 0; +} + +#synopsis p.caption.collapser { + background: url(synopsis.png) no-repeat -64px -8px; +} + +#synopsis p.caption.expander { + background: url(synopsis.png) no-repeat 0px -8px; +} + +#synopsis ul { + height: 100%; + overflow: auto; + padding: 0.5em; + margin: 0; +} + +#synopsis ul ul { + overflow: hidden; +} + +#synopsis ul, +#synopsis ul li.src { + background-color: #faf9dc; + white-space: nowrap; + list-style: none; + margin-left: 0; +} + +/* @end */ + +/* @group Main Content */ + +#interface div.top { margin: 2em 0; } +#interface h1 + div.top, +#interface h2 + div.top, +#interface h3 + div.top, +#interface h4 + div.top, +#interface h5 + div.top { + margin-top: 1em; +} +#interface .src .selflink, +#interface .src .link { + float: right; + color: #919191; + background: #f0f0f0; + padding: 0 0.5em 0.2em; + margin: 0 -0.5em 0 0; +} +#interface .src .selflink { + border-left: 1px solid #919191; + margin: 0 -0.5em 0 0.5em; +} + +#interface span.fixity { + color: #919191; + border-left: 1px solid #919191; + padding: 0.2em 0.5em 0.2em 0.5em; + margin: 0 -1em 0 1em; +} + +#interface span.rightedge { + border-left: 1px solid #919191; + padding: 0.2em 0 0.2em 0; + margin: 0 0 0 1em; +} + +#interface table { border-spacing: 2px; } +#interface td { + vertical-align: top; + padding-left: 0.5em; +} +#interface td.src { + white-space: nowrap; +} +#interface td.doc p { + margin: 0; +} +#interface td.doc p + p { + margin-top: 0.8em; +} + +.clearfix:after { + clear: both; + content: " "; + display: block; + height: 0; + visibility: hidden; +} + +.subs ul { + list-style: none; + display: table; + margin: 0; +} + +.subs ul li { + display: table-row; +} + +.subs ul li dfn { + display: table-cell; + font-style: normal; + font-weight: bold; + margin: 1px 0; + white-space: nowrap; +} + +.subs ul li > .doc { + display: table-cell; + padding-left: 0.5em; + margin-bottom: 0.5em; +} + +.subs ul li > .doc p { + margin: 0; +} + +/* Render short-style data instances */ +.inst ul { + height: 100%; + padding: 0.5em; + margin: 0; +} + +.inst, .inst li { + list-style: none; + margin-left: 1em; +} + +/* Workaround for bug in Firefox (issue #384) */ +.inst-left { + float: left; +} + +.top p.src { + border-top: 1px solid #ccc; +} + +.subs, .doc { + /* use this selector for one level of indent */ + padding-left: 2em; +} + +.warning { + color: red; +} + +.arguments { + margin-top: -0.4em; +} +.arguments .caption { + display: none; +} + +.fields { padding-left: 1em; } + +.fields .caption { display: none; } + +.fields p { margin: 0 0; } + +/* this seems bulky to me +.methods, .constructors { + background: #f8f8f8; + border: 1px solid #eee; +} +*/ + +/* @end */ + +/* @group Auxillary Pages */ + + +.extension-list { + list-style-type: none; + margin-left: 0; +} + +#mini { + margin: 0 auto; + padding: 0 1em 1em; +} + +#mini > * { + font-size: 93%; /* 12pt */ +} + +#mini #module-list .caption, +#mini #module-header .caption { + font-size: 125%; /* 15pt */ +} + +#mini #interface h1, +#mini #interface h2, +#mini #interface h3, +#mini #interface h4 { + font-size: 109%; /* 13pt */ + margin: 1em 0 0; +} + +#mini #interface .top, +#mini #interface .src { + margin: 0; +} + +#mini #module-list ul { + list-style: none; + margin: 0; +} + +#alphabet ul { + list-style: none; + padding: 0; + margin: 0.5em 0 0; + text-align: center; +} + +#alphabet li { + display: inline; + margin: 0 0.25em; +} + +#alphabet a { + font-weight: bold; +} + +#index .caption, +#module-list .caption { font-size: 131%; /* 17pt */ } + +#index table { + margin-left: 2em; +} + +#index .src { + font-weight: bold; +} +#index .alt { + font-size: 77%; /* 10pt */ + font-style: italic; + padding-left: 2em; +} + +#index td + td { + padding-left: 1em; +} + +#module-list ul { + list-style: none; + margin: 0 0 0 2em; +} + +#module-list li { + clear: right; +} + +#module-list span.collapser, +#module-list span.expander { + background-position: 0 0.3em; +} + +#module-list .package { + float: right; +} + +/* @end */ diff --git a/plus.gif b/plus.gif new file mode 100644 index 0000000..2d15c14 Binary files /dev/null and b/plus.gif differ diff --git a/src/HPath-IO-Errors.html b/src/HPath-IO-Errors.html new file mode 100644 index 0000000..3ed858a --- /dev/null +++ b/src/HPath-IO-Errors.html @@ -0,0 +1,370 @@ + + + + + +src/HPath/IO/Errors.hs + + + +
    -- |
    +-- Module      :  HPath.IO.Errors
    +-- Copyright   :  © 2016 Julian Ospald
    +-- License     :  GPL-2
    +--
    +-- Maintainer  :  Julian Ospald <hasufell@posteo.de>
    +-- Stability   :  experimental
    +-- Portability :  portable
    +--
    +-- Provides error handling.
    +
    +{-# LANGUAGE DeriveDataTypeable #-}
    +{-# LANGUAGE ScopedTypeVariables #-}
    +
    +module HPath.IO.Errors
    +  (
    +  -- * Types
    +    HPathIOException(..)
    +
    +  -- * Exception identifiers
    +  , isFileDoesNotExist
    +  , isDirDoesNotExist
    +  , isSameFile
    +  , isDestinationInSource
    +  , isFileDoesExist
    +  , isDirDoesExist
    +  , isInvalidOperation
    +  , isCan'tOpenDirectory
    +  , isCopyFailed
    +
    +  -- * Path based functions
    +  , throwFileDoesExist
    +  , throwDirDoesExist
    +  , throwFileDoesNotExist
    +  , throwDirDoesNotExist
    +  , throwSameFile
    +  , sameFile
    +  , throwDestinationInSource
    +  , doesFileExist
    +  , doesDirectoryExist
    +  , isWritable
    +  , canOpenDirectory
    +  , throwCantOpenDirectory
    +
    +  -- * Error handling functions
    +  , catchErrno
    +  , rethrowErrnoAs
    +  , handleIOError
    +  , bracketeer
    +  , reactOnError
    +  )
    +  where
    +
    +
    +import Control.Applicative
    +  (
    +    (<$>)
    +  )
    +import Control.Exception
    +import Control.Monad
    +  (
    +    forM
    +  , when
    +  )
    +import Data.ByteString
    +  (
    +    ByteString
    +  )
    +import Data.ByteString.UTF8
    +  (
    +    toString
    +  )
    +import Data.Data
    +  (
    +    Data(..)
    +  )
    +import Data.Typeable
    +import Foreign.C.Error
    +  (
    +    getErrno
    +  , Errno
    +  )
    +import GHC.IO.Exception
    +  (
    +    IOErrorType
    +  )
    +import HPath
    +import {-# SOURCE #-} HPath.IO
    +  (
    +    canonicalizePath
    +  )
    +import HPath.IO.Utils
    +import System.IO.Error
    +  (
    +    catchIOError
    +  , ioeGetErrorType
    +  )
    +
    +import qualified System.Posix.Directory.ByteString as PFD
    +import System.Posix.Files.ByteString
    +  (
    +    fileAccess
    +  , getFileStatus
    +  )
    +import qualified System.Posix.Files.ByteString as PF
    +
    +
    +data HPathIOException = FileDoesNotExist ByteString
    +                      | DirDoesNotExist ByteString
    +                      | SameFile ByteString ByteString
    +                      | DestinationInSource ByteString ByteString
    +                      | FileDoesExist ByteString
    +                      | DirDoesExist ByteString
    +                      | InvalidOperation String
    +                      | Can'tOpenDirectory ByteString
    +                      | CopyFailed String
    +  deriving (Typeable, Eq, Data)
    +
    +
    +instance Show HPathIOException where
    +  show (FileDoesNotExist fp) = "File does not exist:" ++ toString fp
    +  show (DirDoesNotExist fp) = "Directory does not exist: "
    +                              ++ toString fp
    +  show (SameFile fp1 fp2) = toString fp1
    +                            ++ " and " ++ toString fp2
    +                            ++ " are the same file!"
    +  show (DestinationInSource fp1 fp2) = toString fp1
    +                                       ++ " is contained in "
    +                                       ++ toString fp2
    +  show (FileDoesExist fp) = "File does exist: " ++ toString fp
    +  show (DirDoesExist fp) = "Directory does exist: " ++ toString fp
    +  show (InvalidOperation str) = "Invalid operation: " ++ str
    +  show (Can'tOpenDirectory fp) = "Can't open directory: "
    +                                 ++ toString fp
    +  show (CopyFailed str) = "Copying failed: " ++ str
    +
    +
    +
    +instance Exception HPathIOException
    +
    +
    +
    +
    +
    +    -----------------------------
    +    --[ Exception identifiers ]--
    +    -----------------------------
    +
    +isFileDoesNotExist, isDirDoesNotExist, isSameFile, isDestinationInSource, isFileDoesExist, isDirDoesExist, isInvalidOperation, isCan'tOpenDirectory, isCopyFailed :: HPathIOException -> Bool
    +isFileDoesNotExist ex = toConstr (ex :: HPathIOException) == toConstr FileDoesNotExist{}
    +isDirDoesNotExist ex = toConstr (ex :: HPathIOException) == toConstr DirDoesNotExist{}
    +isSameFile ex = toConstr (ex :: HPathIOException) == toConstr SameFile{}
    +isDestinationInSource ex = toConstr (ex :: HPathIOException) == toConstr DestinationInSource{}
    +isFileDoesExist ex = toConstr (ex :: HPathIOException) == toConstr FileDoesExist{}
    +isDirDoesExist ex = toConstr (ex :: HPathIOException) == toConstr DirDoesExist{}
    +isInvalidOperation ex = toConstr (ex :: HPathIOException) == toConstr InvalidOperation{}
    +isCan'tOpenDirectory ex = toConstr (ex :: HPathIOException) == toConstr Can'tOpenDirectory{}
    +isCopyFailed ex = toConstr (ex :: HPathIOException) == toConstr CopyFailed{}
    +
    +
    +
    +
    +    ----------------------------
    +    --[ Path based functions ]--
    +    ----------------------------
    +
    +
    +throwFileDoesExist :: Path Abs -> IO ()
    +throwFileDoesExist fp =
    +  whenM (doesFileExist fp) (throwIO . FileDoesExist
    +                                    . fromAbs $ fp)
    +
    +
    +throwDirDoesExist :: Path Abs -> IO ()
    +throwDirDoesExist fp =
    +  whenM (doesDirectoryExist fp) (throwIO . DirDoesExist
    +                                         . fromAbs $ fp)
    +
    +
    +throwFileDoesNotExist :: Path Abs -> IO ()
    +throwFileDoesNotExist fp =
    +  unlessM (doesFileExist fp) (throwIO . FileDoesNotExist
    +                                      . fromAbs $ fp)
    +
    +
    +throwDirDoesNotExist :: Path Abs -> IO ()
    +throwDirDoesNotExist fp =
    +  unlessM (doesDirectoryExist fp) (throwIO . DirDoesNotExist
    +                                           . fromAbs $ fp)
    +
    +
    +-- |Uses `isSameFile` and throws `SameFile` if it returns True.
    +throwSameFile :: Path Abs
    +              -> Path Abs
    +              -> IO ()
    +throwSameFile fp1 fp2 =
    +  whenM (sameFile fp1 fp2)
    +        (throwIO $ SameFile (fromAbs fp1) (fromAbs fp2))
    +
    +
    +-- |Check if the files are the same by examining device and file id.
    +-- This follows symbolic links.
    +sameFile :: Path Abs -> Path Abs -> IO Bool
    +sameFile fp1 fp2 =
    +  withAbsPath fp1 $ \fp1' -> withAbsPath fp2 $ \fp2' ->
    +    handleIOError (\_ -> return False) $ do
    +      fs1 <- getFileStatus fp1'
    +      fs2 <- getFileStatus fp2'
    +
    +      if ((PF.deviceID fs1, PF.fileID fs1) ==
    +          (PF.deviceID fs2, PF.fileID fs2))
    +        then return True
    +        else return False
    +
    +
    +-- TODO: make this more robust when destination does not exist
    +-- |Checks whether the destination directory is contained
    +-- within the source directory by comparing the device+file ID of the
    +-- source directory with all device+file IDs of the parent directories
    +-- of the destination.
    +throwDestinationInSource :: Path Abs -- ^ source dir
    +                         -> Path Abs -- ^ full destination, @dirname dest@
    +                                     --   must exist
    +                         -> IO ()
    +throwDestinationInSource source dest = do
    +  dest'   <- (\x -> maybe x (\y -> x </> y) $ basename dest)
    +             <$> (canonicalizePath $ dirname dest)
    +  dids <- forM (getAllParents dest') $ \p -> do
    +          fs <- PF.getSymbolicLinkStatus (fromAbs p)
    +          return (PF.deviceID fs, PF.fileID fs)
    +  sid <- fmap (\x -> (PF.deviceID x, PF.fileID x))
    +              $ PF.getFileStatus (fromAbs source)
    +  when (elem sid dids)
    +       (throwIO $ DestinationInSource (fromAbs dest)
    +                                      (fromAbs source))
    +
    +
    +-- |Checks if the given file exists and is not a directory.
    +-- Does not follow symlinks.
    +doesFileExist :: Path Abs -> IO Bool
    +doesFileExist fp =
    +  handleIOError (\_ -> return False) $ do
    +    fs  <- PF.getSymbolicLinkStatus (fromAbs fp)
    +    return $ not . PF.isDirectory $ fs
    +
    +
    +-- |Checks if the given file exists and is a directory.
    +-- Does not follow symlinks.
    +doesDirectoryExist :: Path Abs -> IO Bool
    +doesDirectoryExist fp =
    +  handleIOError (\_ -> return False) $ do
    +    fs  <- PF.getSymbolicLinkStatus (fromAbs fp)
    +    return $ PF.isDirectory fs
    +
    +
    +-- |Checks whether a file or folder is writable.
    +isWritable :: Path Abs -> IO Bool
    +isWritable fp =
    +  handleIOError (\_ -> return False) $
    +    fileAccess (fromAbs fp) False True False
    +
    +
    +-- |Checks whether the directory at the given path exists and can be
    +-- opened. This invokes `openDirStream` which follows symlinks.
    +canOpenDirectory :: Path Abs -> IO Bool
    +canOpenDirectory fp =
    +  handleIOError (\_ -> return False) $ do
    +    bracket (PFD.openDirStream . fromAbs $ fp)
    +            PFD.closeDirStream
    +            (\_ -> return ())
    +    return True
    +
    +
    +-- |Throws a `Can'tOpenDirectory` HPathIOException if the directory at the given
    +-- path cannot be opened.
    +throwCantOpenDirectory :: Path Abs -> IO ()
    +throwCantOpenDirectory fp =
    +  unlessM (canOpenDirectory fp)
    +          (throwIO . Can'tOpenDirectory . fromAbs $ fp)
    +
    +
    +
    +    --------------------------------
    +    --[ Error handling functions ]--
    +    --------------------------------
    +
    +
    +-- |Carries out an action, then checks if there is an IOException and
    +-- a specific errno. If so, then it carries out another action, otherwise
    +-- it rethrows the error.
    +catchErrno :: [Errno] -- ^ errno to catch
    +           -> IO a    -- ^ action to try, which can raise an IOException
    +           -> IO a    -- ^ action to carry out in case of an IOException and
    +                      --   if errno matches
    +           -> IO a
    +catchErrno en a1 a2 =
    +  catchIOError a1 $ \e -> do
    +    errno <- getErrno
    +    if errno `elem` en
    +      then a2
    +      else ioError e
    +
    +
    +-- |Execute the given action and retrow IO exceptions as a new Exception
    +-- that have the given errno. If errno does not match the exception is rethrown
    +-- as is.
    +rethrowErrnoAs :: Exception e
    +               => [Errno]       -- ^ errno to catch
    +               -> e             -- ^ rethrow as if errno matches
    +               -> IO a          -- ^ action to try
    +               -> IO a
    +rethrowErrnoAs en fmex action = catchErrno en action (throwIO fmex)
    +
    +
    +
    +-- |Like `catchIOError`, with arguments swapped.
    +handleIOError :: (IOError -> IO a) -> IO a -> IO a
    +handleIOError = flip catchIOError
    +
    +
    +-- |Like `bracket`, but allows to have different clean-up
    +-- actions depending on whether the in-between computation
    +-- has raised an exception or not. 
    +bracketeer :: IO a        -- ^ computation to run first
    +           -> (a -> IO b) -- ^ computation to run last, when
    +                          --   no exception was raised
    +           -> (a -> IO b) -- ^ computation to run last,
    +                          --   when an exception was raised
    +           -> (a -> IO c) -- ^ computation to run in-between
    +           -> IO c
    +bracketeer before after afterEx thing =
    +  mask $ \restore -> do
    +    a <- before
    +    r <- restore (thing a) `onException` afterEx a
    +    _ <- after a
    +    return r
    +
    +
    +reactOnError :: IO a
    +             -> [(IOErrorType, IO a)]      -- ^ reaction on IO errors
    +             -> [(HPathIOException, IO a)] -- ^ reaction on HPathIOException
    +             -> IO a
    +reactOnError a ios fmios =
    +  a `catches` [iohandler, fmiohandler]
    +  where
    +    iohandler = Handler $
    +      \(ex :: IOException) ->
    +         foldr (\(t, a') y -> if ioeGetErrorType ex == t
    +                                then a'
    +                                else y)
    +               (throwIO ex)
    +               ios
    +    fmiohandler = Handler $
    +      \(ex :: HPathIOException) ->
    +         foldr (\(t, a') y -> if toConstr ex == toConstr t
    +                                then a'
    +                                else y)
    +               (throwIO ex)
    +               fmios
    +
    + diff --git a/src/HPath-IO-Utils.html b/src/HPath-IO-Utils.html new file mode 100644 index 0000000..cb08e89 --- /dev/null +++ b/src/HPath-IO-Utils.html @@ -0,0 +1,43 @@ + + + + + +src/HPath/IO/Utils.hs + + + +
    -- |
    +-- Module      :  HPath.IO.Utils
    +-- Copyright   :  © 2016 Julian Ospald
    +-- License     :  GPL-2
    +--
    +-- Maintainer  :  Julian Ospald <hasufell@posteo.de>
    +-- Stability   :  experimental
    +-- Portability :  portable
    +--
    +-- Random and general IO/monad utilities.
    +
    +
    +module HPath.IO.Utils where
    +
    +
    +import Control.Monad
    +  (
    +    when
    +  , unless
    +  )
    +
    +
    +-- |If the value of the first argument is True, then execute the action
    +-- provided in the second argument, otherwise do nothing.
    +whenM :: Monad m => m Bool -> m () -> m ()
    +whenM mb a = mb >>= (`when` a)
    +
    +
    +-- |If the value of the first argument is False, then execute the action
    +-- provided in the second argument, otherwise do nothing.
    +unlessM :: Monad m => m Bool -> m () -> m ()
    +unlessM mb a = mb >>= (`unless` a)
    +
    + diff --git a/src/HPath-IO.html b/src/HPath-IO.html new file mode 100644 index 0000000..d10b9fb --- /dev/null +++ b/src/HPath-IO.html @@ -0,0 +1,909 @@ + + + + + +src/HPath/IO.hs + + + +
    -- |
    +-- Module      :  HPath.IO
    +-- Copyright   :  © 2016 Julian Ospald
    +-- License     :  GPL-2
    +--
    +-- Maintainer  :  Julian Ospald <hasufell@posteo.de>
    +-- Stability   :  experimental
    +-- Portability :  portable
    +--
    +-- This module provides high-level IO related file operations like
    +-- copy, delete, move and so on. It only operates on /Path Abs/ which
    +-- guarantees us well-typed paths which are absolute.
    +--
    +-- Some functions are just path-safe wrappers around
    +-- unix functions, others have stricter exception handling
    +-- and some implement functionality that doesn't have a unix
    +-- counterpart (like `copyDirRecursive`).
    +--
    +-- Some of these operations are due to their nature __not atomic__, which
    +-- means they may do multiple syscalls which form one context. Some
    +-- of them also have to examine the filetypes explicitly before the
    +-- syscalls, so a reasonable decision can be made. That means
    +-- the result is undefined if another process changes that context
    +-- while the non-atomic operation is still happening. However, where
    +-- possible, as few syscalls as possible are used and the underlying
    +-- exception handling is kept.
    +--
    +-- Note: `BlockDevice`, `CharacterDevice`, `NamedPipe` and `Socket`
    +-- are ignored by some of the more high-level functions (like `easyCopy`).
    +-- For other functions (like `copyFile`), the behavior on these file types is
    +-- unreliable/unsafe. Check the documentation of those functions for details.
    +
    +{-# LANGUAGE PackageImports #-}
    +{-# LANGUAGE OverloadedStrings #-}
    +
    +module HPath.IO
    +  (
    +  -- * Types
    +    FileType(..)
    +  -- * File copying
    +  , copyDirRecursive
    +  , copyDirRecursiveOverwrite
    +  , recreateSymlink
    +  , copyFile
    +  , copyFileOverwrite
    +  , easyCopy
    +  , easyCopyOverwrite
    +  -- * File deletion
    +  , deleteFile
    +  , deleteDir
    +  , deleteDirRecursive
    +  , easyDelete
    +  -- * File opening
    +  , openFile
    +  , executeFile
    +  -- * File creation
    +  , createRegularFile
    +  , createDir
    +  , createSymlink
    +  -- * File renaming/moving
    +  , renameFile
    +  , moveFile
    +  , moveFileOverwrite
    +  -- * File permissions
    +  , newFilePerms
    +  , newDirPerms
    +  -- * Directory reading
    +  , getDirsFiles
    +  -- * Filetype operations
    +  , getFileType
    +  -- * Others
    +  , canonicalizePath
    +  )
    +  where
    +
    +
    +import Control.Applicative
    +  (
    +    (<$>)
    +  )
    +import Control.Exception
    +  (
    +    bracket
    +  , throwIO
    +  )
    +import Control.Monad
    +  (
    +    void
    +  , when
    +  )
    +import Data.ByteString
    +  (
    +    ByteString
    +  )
    +import Data.Foldable
    +  (
    +    for_
    +  )
    +import Data.Maybe
    +  (
    +    catMaybes
    +  )
    +import Data.Word
    +  (
    +    Word8
    +  )
    +import Foreign.C.Error
    +  (
    +    eEXIST
    +  , eINVAL
    +  , eNOSYS
    +  , eNOTEMPTY
    +  , eXDEV
    +  )
    +import Foreign.C.Types
    +  (
    +    CSize
    +  )
    +import Foreign.Marshal.Alloc
    +  (
    +    allocaBytes
    +  )
    +import Foreign.Ptr
    +  (
    +    Ptr
    +  )
    +import GHC.IO.Exception
    +  (
    +    IOErrorType(..)
    +  )
    +import HPath
    +import HPath.Internal
    +import HPath.IO.Errors
    +import HPath.IO.Utils
    +import Prelude hiding (readFile)
    +import System.IO.Error
    +  (
    +    catchIOError
    +  , ioeGetErrorType
    +  )
    +import System.Linux.Sendfile
    +  (
    +    sendfileFd
    +  , FileRange(..)
    +  )
    +import System.Posix.ByteString
    +  (
    +    exclusive
    +  )
    +import System.Posix.Directory.ByteString
    +  (
    +    createDirectory
    +  , removeDirectory
    +  )
    +import System.Posix.Directory.Traversals
    +  (
    +    getDirectoryContents'
    +  )
    +import System.Posix.Files.ByteString
    +  (
    +    createSymbolicLink
    +  , fileMode
    +  , getFdStatus
    +  , groupExecuteMode
    +  , groupReadMode
    +  , groupWriteMode
    +  , otherExecuteMode
    +  , otherReadMode
    +  , otherWriteMode
    +  , ownerModes
    +  , ownerReadMode
    +  , ownerWriteMode
    +  , readSymbolicLink
    +  , removeLink
    +  , rename
    +  , setFileMode
    +  , unionFileModes
    +  )
    +import qualified System.Posix.Files.ByteString as PF
    +import qualified "unix" System.Posix.IO.ByteString as SPI
    +import qualified "unix-bytestring" System.Posix.IO.ByteString as SPB
    +import System.Posix.FD
    +  (
    +    openFd
    +  )
    +import qualified System.Posix.Directory.Traversals as SPDT
    +import qualified System.Posix.Directory.Foreign as SPDF
    +import qualified System.Posix.Process.ByteString as SPP
    +import System.Posix.Types
    +  (
    +    FileMode
    +  , ProcessID
    +  , Fd
    +  )
    +
    +
    +
    +
    +
    +    -------------
    +    --[ Types ]--
    +    -------------
    +
    +
    +data FileType = Directory
    +              | RegularFile
    +              | SymbolicLink
    +              | BlockDevice
    +              | CharacterDevice
    +              | NamedPipe
    +              | Socket
    +  deriving (Eq, Show)
    +
    +
    +
    +
    +
    +    --------------------
    +    --[ File Copying ]--
    +    --------------------
    +
    +
    +
    +-- |Copies a directory recursively to the given destination.
    +-- Does not follow symbolic links.
    +--
    +-- For directory contents, this has the same behavior as `easyCopy`
    +-- and thus will ignore any file type that is not `RegularFile`,
    +-- `SymbolicLink` or `Directory`.
    +--
    +-- Safety/reliability concerns:
    +--
    +--    * not atomic
    +--    * examines filetypes explicitly
    +--    * an explicit check `throwDestinationInSource` is carried out for the
    +--      top directory for basic sanity, because otherwise we might end up
    +--      with an infinite copy loop... however, this operation is not
    +--      carried out recursively (because it's slow)
    +--
    +-- Throws:
    +--
    +--    - `NoSuchThing` if source directory does not exist
    +--    - `PermissionDenied` if output directory is not writable
    +--    - `PermissionDenied` if source directory can't be opened
    +--    - `InvalidArgument` if source directory is wrong type (symlink)
    +--    - `InvalidArgument` if source directory is wrong type (regular file)
    +--    - `AlreadyExists` if destination already exists
    +--    - `SameFile` if source and destination are the same file (`HPathIOException`)
    +--    - `DestinationInSource` if destination is contained in source (`HPathIOException`)
    +copyDirRecursive :: Path Abs  -- ^ source dir
    +                 -> Path Abs  -- ^ full destination
    +                 -> IO ()
    +copyDirRecursive fromp destdirp
    +  = do
    +    -- for performance, sanity checks are only done for the top dir
    +    throwSameFile fromp destdirp
    +    throwDestinationInSource fromp destdirp
    +    go fromp destdirp
    +  where
    +    go :: Path Abs -> Path Abs -> IO ()
    +    go fromp' destdirp' = do
    +      -- order is important here, so we don't get empty directories
    +      -- on failure
    +      contents <- getDirsFiles fromp'
    +
    +      fmode' <- PF.fileMode <$> PF.getSymbolicLinkStatus (fromAbs fromp')
    +      createDirectory (fromAbs destdirp') fmode'
    +
    +      -- we can't use `easyCopy` here, because we want to call `go`
    +      -- recursively to skip the top-level sanity checks
    +      for_ contents $ \f -> do
    +        ftype <- getFileType f
    +        newdest <- (destdirp' </>) <$> basename f
    +        case ftype of
    +          SymbolicLink -> recreateSymlink f newdest
    +          Directory    -> go f newdest
    +          RegularFile  -> copyFile f newdest
    +          _            -> return ()
    +
    +
    +-- |Like `copyDirRecursive` except it overwrites contents of directories
    +-- if any.
    +--
    +-- For directory contents, this has the same behavior as `easyCopyOverwrite`
    +-- and thus will ignore any file type that is not `RegularFile`,
    +-- `SymbolicLink` or `Directory`.
    +--
    +-- Throws:
    +--
    +--    - `NoSuchThing` if source directory does not exist
    +--    - `PermissionDenied` if output directory is not writable
    +--    - `PermissionDenied` if source directory can't be opened
    +--    - `InvalidArgument` if source directory is wrong type (symlink)
    +--    - `InvalidArgument` if source directory is wrong type (regular file)
    +--    - `SameFile` if source and destination are the same file (`HPathIOException`)
    +--    - `DestinationInSource` if destination is contained in source (`HPathIOException`)
    +copyDirRecursiveOverwrite :: Path Abs  -- ^ source dir
    +                          -> Path Abs  -- ^ full destination
    +                          -> IO ()
    +copyDirRecursiveOverwrite fromp destdirp
    +  = do
    +    -- for performance, sanity checks are only done for the top dir
    +    throwSameFile fromp destdirp
    +    throwDestinationInSource fromp destdirp
    +    go fromp destdirp
    +  where
    +    go :: Path Abs -> Path Abs -> IO ()
    +    go fromp' destdirp' = do
    +      -- order is important here, so we don't get empty directories
    +      -- on failure
    +      contents <- getDirsFiles fromp'
    +
    +      fmode' <- PF.fileMode <$> PF.getSymbolicLinkStatus (fromAbs fromp')
    +      catchIOError (createDirectory (fromAbs destdirp') fmode') $ \e ->
    +        case ioeGetErrorType e of
    +          AlreadyExists -> setFileMode (fromAbs destdirp') fmode'
    +          _             -> ioError e
    +
    +      -- we can't use `easyCopyOverwrite` here, because we want to call `go`
    +      -- recursively to skip the top-level sanity checks
    +      for_ contents $ \f -> do
    +        ftype <- getFileType f
    +        newdest <- (destdirp' </>) <$> basename f
    +        case ftype of
    +          SymbolicLink -> whenM (doesFileExist newdest) (deleteFile newdest)
    +                          >> recreateSymlink f newdest
    +          Directory    -> go f newdest
    +          RegularFile  -> copyFileOverwrite f newdest
    +          _            -> return ()
    +
    +
    +-- |Recreate a symlink.
    +--
    +-- Throws:
    +--
    +--    - `InvalidArgument` if source file is wrong type (not a symlink)
    +--    - `PermissionDenied` if output directory cannot be written to
    +--    - `PermissionDenied` if source directory cannot be opened
    +--    - `AlreadyExists` if destination file already exists
    +--    - `SameFile` if source and destination are the same file (`HPathIOException`)
    +--
    +-- Note: calls `symlink`
    +recreateSymlink :: Path Abs  -- ^ the old symlink file
    +                -> Path Abs  -- ^ destination file
    +                -> IO ()
    +recreateSymlink symsource newsym
    +  = do
    +    throwSameFile symsource newsym
    +    sympoint <- readSymbolicLink (fromAbs symsource)
    +    createSymbolicLink sympoint (fromAbs newsym)
    +
    +
    +-- |Copies the given regular file to the given destination.
    +-- Neither follows symbolic links, nor accepts them.
    +-- For "copying" symbolic links, use `recreateSymlink` instead.
    +--
    +-- Note that this is still sort of a low-level function and doesn't
    +-- examine file types. For a more high-level version, use `easyCopy`
    +-- instead.
    +--
    +-- Safety/reliability concerns:
    +--
    +--    * when used on `CharacterDevice`, reads the "contents" and copies
    +--      them to a regular file, which might take indefinitely
    +--    * when used on `BlockDevice`, may either read the "contents"
    +--      and copy them to a regular file (potentially hanging indefinitely)
    +--      or may create a regular empty destination file
    +--    * when used on `NamedPipe`, will hang indefinitely
    +--
    +-- Throws:
    +--
    +--    - `NoSuchThing` if source file does not exist
    +--    - `NoSuchThing` if source file is a a `Socket`
    +--    - `PermissionDenied` if output directory is not writable
    +--    - `PermissionDenied` if source directory can't be opened
    +--    - `InvalidArgument` if source file is wrong type (symlink or directory)
    +--    - `AlreadyExists` if destination already exists
    +--    - `SameFile` if source and destination are the same file (`HPathIOException`)
    +--
    +-- Note: calls `sendfile` and possibly `read`/`write` as fallback
    +copyFile :: Path Abs  -- ^ source file
    +         -> Path Abs  -- ^ destination file
    +         -> IO ()
    +copyFile from to = do
    +  throwSameFile from to
    +  _copyFile [SPDF.oNofollow]
    +            [SPDF.oNofollow, SPDF.oExcl]
    +            from to
    +
    +
    +-- |Like `copyFile` except it overwrites the destination if it already
    +-- exists.
    +--
    +-- Safety/reliability concerns:
    +--
    +--    * when used on `CharacterDevice`, reads the "contents" and copies
    +--      them to a regular file, which might take indefinitely
    +--    * when used on `BlockDevice`, may either read the "contents"
    +--      and copy them to a regular file (potentially hanging indefinitely)
    +--      or may create a regular empty destination file
    +--    * when used on `NamedPipe`, will hang indefinitely
    +--    * not atomic, since it uses read/write
    +--
    +-- Throws:
    +--
    +--    - `NoSuchThing` if source file does not exist
    +--    - `NoSuchThing` if source file is a `Socket`
    +--    - `PermissionDenied` if output directory is not writable
    +--    - `PermissionDenied` if source directory can't be opened
    +--    - `InvalidArgument` if source file is wrong type (symlink or directory)
    +--    - `SameFile` if source and destination are the same file (`HPathIOException`)
    +--
    +-- Note: calls `sendfile` and possibly `read`/`write` as fallback
    +copyFileOverwrite :: Path Abs  -- ^ source file
    +                  -> Path Abs  -- ^ destination file
    +                  -> IO ()
    +copyFileOverwrite from to = do
    +  throwSameFile from to
    +  catchIOError (_copyFile [SPDF.oNofollow]
    +                          [SPDF.oNofollow, SPDF.oTrunc]
    +                          from to) $ \e ->
    +    case ioeGetErrorType e of
    +      -- if the destination file is not writable, we need to
    +      -- figure out if we can still copy by deleting it first
    +      PermissionDenied -> do
    +        exists   <- doesFileExist to
    +        writable <- isWritable (dirname to)
    +        if exists && writable
    +          then deleteFile to >> copyFile from to
    +          else ioError e
    +      _ -> ioError e
    +
    +
    +_copyFile :: [SPDF.Flags]
    +          -> [SPDF.Flags]
    +          -> Path Abs  -- ^ source file
    +          -> Path Abs  -- ^ destination file
    +          -> IO ()
    +_copyFile sflags dflags from to
    +  =
    +    -- from sendfile(2) manpage:
    +    --   Applications  may  wish  to  fall back to read(2)/write(2) in the case
    +    --   where sendfile() fails with EINVAL or ENOSYS.
    +    withAbsPath to $ \to' -> withAbsPath from $ \from' ->
    +      catchErrno [eINVAL, eNOSYS]
    +                 (sendFileCopy from' to')
    +                 (void $ readWriteCopy from' to')
    +  where
    +    copyWith copyAction source dest =
    +      bracket (openFd source SPI.ReadOnly sflags Nothing)
    +              SPI.closeFd
    +              $ \sfd -> do
    +                fileM <- System.Posix.Files.ByteString.fileMode
    +                         <$> getFdStatus sfd
    +                bracketeer (openFd dest SPI.WriteOnly
    +                             dflags $ Just fileM)
    +                           SPI.closeFd
    +                           (\fd -> SPI.closeFd fd >> deleteFile to)
    +                           $ \dfd -> copyAction sfd dfd
    +    -- this is low-level stuff utilizing sendfile(2) for speed
    +    sendFileCopy :: ByteString -> ByteString -> IO ()
    +    sendFileCopy = copyWith
    +      (\sfd dfd -> sendfileFd dfd sfd EntireFile $ return ())
    +    -- low-level copy operation utilizing read(2)/write(2)
    +    -- in case `sendFileCopy` fails/is unsupported
    +    readWriteCopy :: ByteString -> ByteString -> IO Int
    +    readWriteCopy = copyWith
    +      (\sfd dfd -> allocaBytes (fromIntegral bufSize)
    +                     $ \buf -> write' sfd dfd buf 0)
    +      where
    +        bufSize :: CSize
    +        bufSize = 8192
    +        write' :: Fd -> Fd -> Ptr Word8 -> Int -> IO Int
    +        write' sfd dfd buf totalsize = do
    +            size <- SPB.fdReadBuf sfd buf bufSize
    +            if size == 0
    +              then return $ fromIntegral totalsize
    +              else do rsize <- SPB.fdWriteBuf dfd buf size
    +                      when (rsize /= size) (throwIO . CopyFailed $ "wrong size!")
    +                      write' sfd dfd buf (totalsize + fromIntegral size)
    +
    +
    +-- |Copies a regular file, directory or symbolic link. In case of a
    +-- symbolic link it is just recreated, even if it points to a directory.
    +-- Any other file type is ignored.
    +--
    +-- Safety/reliability concerns:
    +--
    +--    * examines filetypes explicitly
    +--    * calls `copyDirRecursive` for directories
    +easyCopy :: Path Abs
    +         -> Path Abs
    +         -> IO ()
    +easyCopy from to = do
    +  ftype <- getFileType from
    +  case ftype of
    +       SymbolicLink -> recreateSymlink from to
    +       RegularFile  -> copyFile from to
    +       Directory    -> copyDirRecursive from to
    +       _            -> return ()
    +
    +
    +-- |Like `easyCopy` except it overwrites the destination if it already exists.
    +-- For directories, this overwrites contents without pruning them, so the resulting
    +-- directory may have more files than have been copied.
    +--
    +-- Safety/reliability concerns:
    +--
    +--    * examines filetypes explicitly
    +--    * calls `copyDirRecursive` for directories
    +easyCopyOverwrite :: Path Abs
    +                  -> Path Abs
    +                  -> IO ()
    +easyCopyOverwrite from to = do
    +  ftype <- getFileType from
    +  case ftype of
    +       SymbolicLink -> whenM (doesFileExist to) (deleteFile to)
    +                       >> recreateSymlink from to
    +       RegularFile  -> copyFileOverwrite from to
    +       Directory    -> copyDirRecursiveOverwrite from to
    +       _            -> return ()
    +
    +
    +
    +
    +
    +
    +    ---------------------
    +    --[ File Deletion ]--
    +    ---------------------
    +
    +
    +-- |Deletes the given file. Raises `eISDIR`
    +-- if run on a directory. Does not follow symbolic links.
    +--
    +-- Throws:
    +--
    +--    - `InappropriateType` for wrong file type (directory)
    +--    - `NoSuchThing` if the file does not exist
    +--    - `PermissionDenied` if the directory cannot be read
    +deleteFile :: Path Abs -> IO ()
    +deleteFile p = withAbsPath p removeLink
    +
    +
    +-- |Deletes the given directory, which must be empty, never symlinks.
    +--
    +-- Throws:
    +--
    +--    - `InappropriateType` for wrong file type (symlink to directory)
    +--    - `InappropriateType` for wrong file type (regular file)
    +--    - `NoSuchThing` if directory does not exist
    +--    - `UnsatisfiedConstraints` if directory is not empty
    +--    - `PermissionDenied` if we can't open or write to parent directory
    +--
    +-- Notes: calls `rmdir`
    +deleteDir :: Path Abs -> IO ()
    +deleteDir p = withAbsPath p removeDirectory
    +
    +
    +-- |Deletes the given directory recursively. Does not follow symbolic
    +-- links. Tries `deleteDir` first before attemtping a recursive
    +-- deletion.
    +--
    +-- On directory contents this behaves like `easyDelete`
    +-- and thus will ignore any file type that is not `RegularFile`,
    +-- `SymbolicLink` or `Directory`.
    +--
    +-- Safety/reliability concerns:
    +--
    +--    * not atomic
    +--    * examines filetypes explicitly
    +--
    +-- Throws:
    +--
    +--    - `InappropriateType` for wrong file type (symlink to directory)
    +--    - `InappropriateType` for wrong file type (regular file)
    +--    - `NoSuchThing` if directory does not exist
    +--    - `PermissionDenied` if we can't open or write to parent directory
    +deleteDirRecursive :: Path Abs -> IO ()
    +deleteDirRecursive p =
    +  catchErrno [eNOTEMPTY, eEXIST]
    +             (deleteDir p)
    +    $ do
    +      files <- getDirsFiles p
    +      for_ files $ \file -> do
    +        ftype <- getFileType file
    +        case ftype of
    +          SymbolicLink -> deleteFile file
    +          Directory    -> deleteDirRecursive file
    +          RegularFile  -> deleteFile file
    +          _            -> return ()
    +      removeDirectory . toFilePath $ p
    +
    +
    +-- |Deletes a file, directory or symlink.
    +-- In case of directory, performs recursive deletion. In case of
    +-- a symlink, the symlink file is deleted.
    +-- Any other file type is ignored.
    +--
    +-- Safety/reliability concerns:
    +--
    +--    * examines filetypes explicitly
    +--    * calls `deleteDirRecursive` for directories
    +easyDelete :: Path Abs -> IO ()
    +easyDelete p = do
    +  ftype <- getFileType p
    +  case ftype of
    +    SymbolicLink -> deleteFile p
    +    Directory    -> deleteDirRecursive p
    +    RegularFile  -> deleteFile p
    +    _            -> return ()
    +
    +
    +
    +
    +    --------------------
    +    --[ File Opening ]--
    +    --------------------
    +
    +
    +-- |Opens a file appropriately by invoking xdg-open. The file type
    +-- is not checked. This forks a process.
    +openFile :: Path Abs
    +         -> IO ProcessID
    +openFile p =
    +  withAbsPath p $ \fp ->
    +    SPP.forkProcess $ SPP.executeFile "xdg-open" True [fp] Nothing
    +
    +
    +-- |Executes a program with the given arguments. This forks a process.
    +executeFile :: Path Abs        -- ^ program
    +            -> [ByteString]    -- ^ arguments
    +            -> IO ProcessID
    +executeFile fp args
    +  = withAbsPath fp $ \fpb ->
    +      SPP.forkProcess
    +      $ SPP.executeFile fpb True args Nothing
    +
    +
    +
    +
    +    ---------------------
    +    --[ File Creation ]--
    +    ---------------------
    +
    +
    +-- |Create an empty regular file at the given directory with the given filename.
    +--
    +-- Throws:
    +--
    +--    - `PermissionDenied` if output directory cannot be written to
    +--    - `AlreadyExists` if destination file already exists
    +createRegularFile :: Path Abs -> IO ()
    +createRegularFile dest =
    +  bracket (SPI.openFd (fromAbs dest) SPI.WriteOnly (Just newFilePerms)
    +                      (SPI.defaultFileFlags { exclusive = True }))
    +          SPI.closeFd
    +          (\_ -> return ())
    +
    +
    +-- |Create an empty directory at the given directory with the given filename.
    +--
    +-- Throws:
    +--
    +--    - `PermissionDenied` if output directory cannot be written to
    +--    - `AlreadyExists` if destination directory already exists
    +createDir :: Path Abs -> IO ()
    +createDir dest = createDirectory (fromAbs dest) newDirPerms
    +
    +
    +-- |Create a symlink.
    +--
    +-- Throws:
    +--
    +--    - `PermissionDenied` if output directory cannot be written to
    +--    - `AlreadyExists` if destination file already exists
    +--
    +-- Note: calls `symlink`
    +createSymlink :: Path Abs   -- ^ destination file
    +              -> ByteString -- ^ path the symlink points to
    +              -> IO ()
    +createSymlink dest sympoint
    +  = createSymbolicLink sympoint (fromAbs dest)
    +
    +
    +
    +    ----------------------------
    +    --[ File Renaming/Moving ]--
    +    ----------------------------
    +
    +
    +-- |Rename a given file with the provided filename. Destination and source
    +-- must be on the same device, otherwise `eXDEV` will be raised.
    +--
    +-- Does not follow symbolic links, but renames the symbolic link file.
    +--
    +-- Safety/reliability concerns:
    +--
    +--    * has a separate set of exception handling, apart from the syscall
    +--
    +-- Throws:
    +--
    +--     - `NoSuchThing` if source file does not exist
    +--     - `PermissionDenied` if output directory cannot be written to
    +--     - `PermissionDenied` if source directory cannot be opened
    +--     - `UnsupportedOperation` if source and destination are on different devices
    +--     - `FileDoesExist` if destination file already exists (`HPathIOException`)
    +--     - `DirDoesExist` if destination directory already exists (`HPathIOException`)
    +--     - `SameFile` if destination and source are the same file (`HPathIOException`)
    +--
    +-- Note: calls `rename` (but does not allow to rename over existing files)
    +renameFile :: Path Abs -> Path Abs -> IO ()
    +renameFile fromf tof = do
    +  throwSameFile fromf tof
    +  throwFileDoesExist tof
    +  throwDirDoesExist tof
    +  rename (fromAbs fromf) (fromAbs tof)
    +
    +
    +-- |Move a file. This also works across devices by copy-delete fallback.
    +-- And also works on directories.
    +--
    +-- Does not follow symbolic links, but renames the symbolic link file.
    +--
    +--
    +-- Safety/reliability concerns:
    +--
    +--    * copy-delete fallback is inherently non-atomic
    +--    * since this function calls `easyCopy` and `easyDelete` as a fallback
    +--      to `renameFile`, file types that are not `RegularFile`, `SymbolicLink`
    +--      or `Directory` may be ignored
    +--
    +-- Throws:
    +--
    +--     - `NoSuchThing` if source file does not exist
    +--     - `PermissionDenied` if output directory cannot be written to
    +--     - `PermissionDenied` if source directory cannot be opened
    +--     - `FileDoesExist` if destination file already exists (`HPathIOException`)
    +--     - `DirDoesExist` if destination directory already exists (`HPathIOException`)
    +--     - `SameFile` if destination and source are the same file (`HPathIOException`)
    +--
    +-- Note: calls `rename` (but does not allow to rename over existing files)
    +moveFile :: Path Abs  -- ^ file to move
    +         -> Path Abs  -- ^ destination
    +         -> IO ()
    +moveFile from to = do
    +  throwSameFile from to
    +  catchErrno [eXDEV] (renameFile from to) $ do
    +    easyCopy from to
    +    easyDelete from
    +
    +
    +-- |Like `moveFile`, but overwrites the destination if it exists.
    +--
    +-- Does not follow symbolic links, but renames the symbolic link file.
    +--
    +-- Ignores any file type that is not `RegularFile`, `SymbolicLink` or
    +-- `Directory`.
    +--
    +-- Safety/reliability concerns:
    +--
    +--    * copy-delete fallback is inherently non-atomic
    +--    * checks for file types and destination file existence explicitly
    +--
    +-- Throws:
    +--
    +--     - `NoSuchThing` if source file does not exist
    +--     - `PermissionDenied` if output directory cannot be written to
    +--     - `PermissionDenied` if source directory cannot be opened
    +--     - `SameFile` if destination and source are the same file (`HPathIOException`)
    +--
    +-- Note: calls `rename` (but does not allow to rename over existing files)
    +moveFileOverwrite :: Path Abs  -- ^ file to move
    +                  -> Path Abs  -- ^ destination
    +                  -> IO ()
    +moveFileOverwrite from to = do
    +  throwSameFile from to
    +  ft <- getFileType from
    +  writable <- isWritable $ dirname to
    +  case ft of
    +    RegularFile -> do
    +      exists <- doesFileExist to
    +      when (exists && writable) (deleteFile to)
    +    SymbolicLink -> do
    +      exists <- doesFileExist to
    +      when (exists && writable) (deleteFile to)
    +    Directory -> do
    +      exists <- doesDirectoryExist to
    +      when (exists && writable) (deleteDir to)
    +    _ -> return ()
    +  moveFile from to
    +
    +
    +
    +
    +    -----------------------
    +    --[ File Permissions]--
    +    -----------------------
    +
    +
    +-- |Default permissions for a new file.
    +newFilePerms :: FileMode
    +newFilePerms
    +  =                  ownerWriteMode
    +    `unionFileModes` ownerReadMode
    +    `unionFileModes` groupWriteMode
    +    `unionFileModes` groupReadMode
    +    `unionFileModes` otherWriteMode
    +    `unionFileModes` otherReadMode
    +
    +
    +-- |Default permissions for a new directory.
    +newDirPerms :: FileMode
    +newDirPerms
    +  =                  ownerModes
    +    `unionFileModes` groupExecuteMode
    +    `unionFileModes` groupReadMode
    +    `unionFileModes` otherExecuteMode
    +    `unionFileModes` otherReadMode
    +
    +
    +
    +    -------------------------
    +    --[ Directory reading ]--
    +    -------------------------
    +
    +
    +-- |Gets all filenames of the given directory. This excludes "." and "..".
    +-- This version does not follow symbolic links.
    +--
    +-- Throws:
    +--
    +--     - `NoSuchThing` if directory does not exist
    +--     - `InappropriateType` if file type is wrong (file)
    +--     - `InappropriateType` if file type is wrong (symlink to file)
    +--     - `InappropriateType` if file type is wrong (symlink to dir)
    +--     - `PermissionDenied` if directory cannot be opened
    +getDirsFiles :: Path Abs        -- ^ dir to read
    +             -> IO [Path Abs]
    +getDirsFiles p =
    +  withAbsPath p $ \fp -> do
    +    fd <- openFd fp SPI.ReadOnly [SPDF.oNofollow] Nothing
    +    return
    +      . catMaybes
    +      .   fmap (\x -> (</>) p <$> (parseMaybe . snd $ x))
    +      =<< getDirectoryContents' fd
    +  where
    +    parseMaybe :: ByteString -> Maybe (Path Fn)
    +    parseMaybe = parseFn
    +
    +
    +
    +
    +    ---------------------------
    +    --[ FileType operations ]--
    +    ---------------------------
    +
    +
    +-- |Get the file type of the file located at the given path. Does
    +-- not follow symbolic links.
    +--
    +-- Throws:
    +--
    +--    - `NoSuchThing` if the file does not exist
    +--    - `PermissionDenied` if any part of the path is not accessible
    +getFileType :: Path Abs -> IO FileType
    +getFileType p = do
    +  fs <- PF.getSymbolicLinkStatus (fromAbs p)
    +  decide fs
    +  where
    +    decide fs
    +      | PF.isDirectory fs       = return Directory
    +      | PF.isRegularFile fs     = return RegularFile
    +      | PF.isSymbolicLink fs    = return SymbolicLink
    +      | PF.isBlockDevice fs     = return BlockDevice
    +      | PF.isCharacterDevice fs = return CharacterDevice
    +      | PF.isNamedPipe fs       = return NamedPipe
    +      | PF.isSocket fs          = return Socket
    +      | otherwise               = ioError $ userError "No filetype?!"
    +
    +
    +
    +    --------------
    +    --[ Others ]--
    +    --------------
    +
    +
    +
    +-- |Applies `realpath` on the given absolute path.
    +--
    +-- Throws:
    +--
    +--    - `NoSuchThing` if the file at the given path does not exist
    +--    - `NoSuchThing` if the symlink is broken
    +canonicalizePath :: Path Abs -> IO (Path Abs)
    +canonicalizePath (MkPath l) = do
    +  nl <- SPDT.realpath l
    +  return $ MkPath nl
    +
    + diff --git a/src/HPath-Internal.html b/src/HPath-Internal.html new file mode 100644 index 0000000..a0b68c4 --- /dev/null +++ b/src/HPath-Internal.html @@ -0,0 +1,62 @@ + + + + + +src/HPath/Internal.hs + + + +
    {-# LANGUAGE DeriveDataTypeable #-}
    +
    +-- | Internal types and functions.
    +
    +module HPath.Internal
    +  (Path(..))
    +  where
    +
    +import Control.DeepSeq (NFData (..))
    +import Data.ByteString (ByteString)
    +import Data.Data
    +
    +-- | 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.
    +data Path b = MkPath ByteString
    +  deriving (Typeable)
    +
    +-- | ByteString equality.
    +--
    +-- The following property holds:
    +--
    +-- @show x == show y ≡ x == y@
    +instance Eq (Path b) where
    +  (==) (MkPath x) (MkPath y) = x == y
    +
    +-- | ByteString ordering.
    +--
    +-- The following property holds:
    +--
    +-- @show x \`compare\` show y ≡ x \`compare\` y@
    +instance Ord (Path b) where
    +  compare (MkPath x) (MkPath y) = compare x y
    +
    +-- | Same as 'HPath.toFilePath'.
    +--
    +-- The following property holds:
    +--
    +-- @x == y ≡ show x == show y@
    +instance Show (Path b) where
    +  show (MkPath x) = show x
    +
    +instance NFData (Path b) where
    +  rnf (MkPath x) = rnf x
    +
    +
    + diff --git a/src/HPath.html b/src/HPath.html new file mode 100644 index 0000000..39f452c --- /dev/null +++ b/src/HPath.html @@ -0,0 +1,383 @@ + + + + + +src/HPath.hs + + + +
    -- |
    +-- Module      :  HPath
    +-- Copyright   :  © 2015–2016 FP Complete, 2016 Julian Ospald
    +-- License     :  BSD 3 clause
    +--
    +-- Maintainer  :  Julian Ospald <hasufell@posteo.de>
    +-- Stability   :  experimental
    +-- Portability :  portable
    +--
    +-- Support for well-typed paths.
    +
    +
    +{-# LANGUAGE CPP #-}
    +{-# LANGUAGE DeriveDataTypeable #-}
    +{-# LANGUAGE EmptyDataDecls #-}
    +{-# LANGUAGE PatternSynonyms #-}
    +
    +module HPath
    +  (
    +  -- * Types
    +   Abs
    +  ,Path
    +  ,Rel
    +  ,Fn
    +  ,PathParseException
    +  ,PathException
    +  ,RelC
    +  -- * PatternSynonyms/ViewPatterns
    +  ,pattern Path
    +   -- * Path Parsing
    +  ,parseAbs
    +  ,parseFn
    +  ,parseRel
    +  -- * Path Conversion
    +  ,fromAbs
    +  ,fromRel
    +  ,toFilePath
    +  -- * Path Operations
    +  ,(</>)
    +  ,basename
    +  ,dirname
    +  ,isParentOf
    +  ,getAllParents
    +  ,stripDir
    +  -- * Path IO helpers
    +  ,withAbsPath
    +  ,withRelPath
    +  ,withFnPath
    +  )
    +  where
    +
    +import           Control.Exception (Exception)
    +import           Control.Monad.Catch (MonadThrow(..))
    +#if MIN_VERSION_bytestring(0,10,8)
    +import           Data.ByteString(ByteString, stripPrefix)
    +#else
    +import           Data.ByteString(ByteString)
    +import qualified Data.List as L
    +#endif
    +import qualified Data.ByteString as BS
    +import           Data.Data
    +import           Data.Maybe
    +import           Data.Word8
    +import           HPath.Internal
    +import           System.Posix.FilePath hiding ((</>))
    +
    +
    +--------------------------------------------------------------------------------
    +-- Types
    +
    +-- | An absolute path.
    +data Abs deriving (Typeable)
    +
    +-- | A relative path; one without a root.
    +data Rel deriving (Typeable)
    +
    +-- | A filename, without any '/'.
    +data Fn deriving (Typeable)
    +
    +-- | Exception when parsing a location.
    +data PathParseException
    +  = InvalidAbs ByteString
    +  | InvalidRel ByteString
    +  | InvalidFn ByteString
    +  | Couldn'tStripPrefixTPS ByteString ByteString
    +  deriving (Show,Typeable)
    +instance Exception PathParseException
    +
    +data PathException = RootDirHasNoBasename
    +  deriving (Show,Typeable)
    +instance Exception PathException
    +
    +class RelC m
    +
    +instance RelC Rel
    +instance RelC Fn
    +
    +--------------------------------------------------------------------------------
    +-- PatternSynonyms
    +
    +#if __GLASGOW_HASKELL__ >= 710
    +pattern Path :: ByteString -> Path a
    +#endif
    +pattern Path x <- (MkPath x)
    +
    +--------------------------------------------------------------------------------
    +-- Path Parsers
    +
    +
    +
    +-- | 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
    +parseAbs :: MonadThrow m
    +         => ByteString -> m (Path Abs)
    +parseAbs filepath =
    +  if isAbsolute filepath &&
    +     isValid filepath &&
    +     not (hasParentDir filepath)
    +     then return (MkPath $ normalise filepath)
    +     else throwM (InvalidAbs filepath)
    +
    +
    +-- | 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
    +parseRel :: MonadThrow m
    +         => ByteString -> m (Path Rel)
    +parseRel filepath =
    +  if not (isAbsolute filepath) &&
    +     filepath /= BS.singleton _period &&
    +     filepath /= BS.pack [_period, _period] &&
    +     not (hasParentDir filepath) &&
    +     isValid filepath
    +     then return (MkPath $ normalise filepath)
    +     else throwM (InvalidRel filepath)
    +
    +
    +-- | 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
    +parseFn :: MonadThrow m
    +        => ByteString -> m (Path Fn)
    +parseFn filepath =
    +  if isFileName filepath &&
    +     filepath /= BS.singleton _period &&
    +     filepath /= BS.pack [_period, _period] &&
    +     isValid filepath
    +     then return (MkPath filepath)
    +     else throwM (InvalidFn filepath)
    +
    +
    +
    +--------------------------------------------------------------------------------
    +-- Path Conversion
    +
    +-- | Convert any Path to a ByteString type.
    +toFilePath :: Path b -> ByteString
    +toFilePath (MkPath l) = l
    +
    +-- | Convert an absolute Path to a ByteString type.
    +fromAbs :: Path Abs -> ByteString
    +fromAbs = toFilePath
    +
    +-- | Convert a relative Path to a ByteString type.
    +fromRel :: RelC r => Path r -> ByteString
    +fromRel = toFilePath
    +
    +
    +
    +--------------------------------------------------------------------------------
    +-- Path Operations
    +
    +-- | 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/"
    +(</>) :: RelC r => Path b -> Path r -> Path b
    +(</>) (MkPath a) (MkPath b) = MkPath (a' `BS.append` b)
    +  where
    +    a' = if BS.last a == pathSeparator
    +         then a
    +         else addTrailingPathSeparator a
    +
    +-- | 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
    +stripDir :: MonadThrow m
    +         => Path b -> Path b -> m (Path Rel)
    +stripDir (MkPath p) (MkPath l) =
    +  case stripPrefix p' l of
    +    Nothing -> throwM (Couldn'tStripPrefixTPS p' l)
    +    Just ok -> if BS.null ok
    +                 then throwM (Couldn'tStripPrefixTPS p' l)
    +                 else return (MkPath ok)
    +  where
    +    p' = addTrailingPathSeparator p
    +
    +-- | 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
    +isParentOf :: Path b -> Path b -> Bool
    +isParentOf p l = isJust (stripDir p l :: Maybe (Path Rel))
    +
    +
    +-- |Get all parents of a path.
    +--
    +-- >>> getAllParents (MkPath "/abs/def/dod")
    +-- ["/abs/def","/abs","/"]
    +-- >>> getAllParents (MkPath "/")
    +-- []
    +getAllParents :: Path Abs -> [Path Abs]
    +getAllParents (MkPath p)
    +  | np == BS.singleton pathSeparator = []
    +  | otherwise = dirname (MkPath np) : getAllParents (dirname $ MkPath np)
    +  where
    +    np = dropTrailingPathSeparator . normalise $ p
    +
    +
    +-- | 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 "/")
    +-- "/"
    +dirname :: Path Abs -> Path Abs
    +dirname (MkPath fp) = MkPath (takeDirectory $ dropTrailingPathSeparator fp)
    +
    +-- | 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
    +basename :: MonadThrow m => Path b -> m (Path Fn)
    +basename (MkPath l)
    +  | not (isAbsolute rl) = return $ MkPath rl
    +  | otherwise           = throwM RootDirHasNoBasename
    +  where
    +    rl = last . splitPath . dropTrailingPathSeparator $ l
    +
    +
    +--------------------------------------------------------------------------------
    +-- Path IO helpers
    +
    +
    +withAbsPath :: Path Abs -> (ByteString -> IO a) -> IO a
    +withAbsPath (MkPath p) action = action p
    +
    +
    +withRelPath :: Path Rel -> (ByteString -> IO a) -> IO a
    +withRelPath (MkPath p) action = action p
    +
    +
    +withFnPath :: Path Fn -> (ByteString -> IO a) -> IO a
    +withFnPath (MkPath p) action = action p
    +
    +
    +------------------------
    +-- ByteString helpers
    +
    +#if MIN_VERSION_bytestring(0,10,8)
    +#else
    +stripPrefix :: ByteString -> ByteString -> Maybe ByteString
    +stripPrefix a b = BS.pack `fmap` L.stripPrefix (BS.unpack a) (BS.unpack b)
    +#endif
    +
    + diff --git a/src/System-Posix-Directory-Foreign.html b/src/System-Posix-Directory-Foreign.html new file mode 100644 index 0000000..1fc6df5 --- /dev/null +++ b/src/System-Posix-Directory-Foreign.html @@ -0,0 +1,118 @@ + + + + + +dist/build/System/Posix/Directory/Foreign.hs + + + +
    {-# LINE 1 "src/System/Posix/Directory/Foreign.hsc" #-}
    +module System.Posix.Directory.Foreign where
    +{-# LINE 2 "src/System/Posix/Directory/Foreign.hsc" #-}
    +
    +import Data.Bits
    +import Data.List (foldl')
    +import Foreign.C.Types
    +
    +
    +{-# LINE 8 "src/System/Posix/Directory/Foreign.hsc" #-}
    +
    +{-# LINE 9 "src/System/Posix/Directory/Foreign.hsc" #-}
    +
    +{-# LINE 10 "src/System/Posix/Directory/Foreign.hsc" #-}
    +
    +{-# LINE 11 "src/System/Posix/Directory/Foreign.hsc" #-}
    +
    +{-# LINE 12 "src/System/Posix/Directory/Foreign.hsc" #-}
    +
    +{-# LINE 13 "src/System/Posix/Directory/Foreign.hsc" #-}
    +
    +newtype DirType = DirType Int deriving (Eq, Show)
    +data Flags = Flags Int | UnsupportedFlag String deriving (Eq, Show)
    +
    +unFlags :: Flags -> Int
    +unFlags (Flags i) = i
    +unFlags (UnsupportedFlag name) = error (name ++ " is not supported on this platform")
    +
    +-- |Returns @True@ if posix-paths was compiled with support for the provided
    +-- flag. (As of this writing, the only flag for which this check may be
    +-- necessary is 'oCloexec'; all other flags will always yield @True@.)
    +isSupported :: Flags -> Bool
    +isSupported (Flags _) = True
    +isSupported _ = False
    +
    +-- |@O_CLOEXEC@ is not supported on every POSIX platform. Use
    +-- @'isSupported' oCloexec@ to determine if support for @O_CLOEXEC@ was
    +-- compiled into your version of posix-paths. (If not, using @oCloexec@ will
    +-- throw an exception.)
    +oCloexec :: Flags
    +
    +{-# LINE 34 "src/System/Posix/Directory/Foreign.hsc" #-}
    +oCloexec = Flags 524288
    +{-# LINE 35 "src/System/Posix/Directory/Foreign.hsc" #-}
    +
    +{-# LINE 40 "src/System/Posix/Directory/Foreign.hsc" #-}
    +
    +
    +
    +-- If these enum declarations occur earlier in the file, haddock
    +-- gets royally confused about the above doc comments.
    +-- Probably http://trac.haskell.org/haddock/ticket/138
    +
    +dtBlk :: DirType
    +dtBlk = DirType 6
    +dtChr :: DirType
    +dtChr = DirType 2
    +dtDir :: DirType
    +dtDir = DirType 4
    +dtFifo :: DirType
    +dtFifo = DirType 1
    +dtLnk :: DirType
    +dtLnk = DirType 10
    +dtReg :: DirType
    +dtReg = DirType 8
    +dtSock :: DirType
    +dtSock = DirType 12
    +dtUnknown :: DirType
    +dtUnknown = DirType 0
    +
    +{-# LINE 48 "src/System/Posix/Directory/Foreign.hsc" #-}
    +
    +oAppend :: Flags
    +oAppend = Flags 1024
    +oAsync :: Flags
    +oAsync = Flags 8192
    +oCreat :: Flags
    +oCreat = Flags 64
    +oDirectory :: Flags
    +oDirectory = Flags 65536
    +oExcl :: Flags
    +oExcl = Flags 128
    +oNoctty :: Flags
    +oNoctty = Flags 256
    +oNofollow :: Flags
    +oNofollow = Flags 131072
    +oNonblock :: Flags
    +oNonblock = Flags 2048
    +oRdonly :: Flags
    +oRdonly = Flags 0
    +oWronly :: Flags
    +oWronly = Flags 1
    +oRdwr :: Flags
    +oRdwr = Flags 2
    +oSync :: Flags
    +oSync = Flags 1052672
    +oTrunc :: Flags
    +oTrunc = Flags 512
    +
    +{-# LINE 50 "src/System/Posix/Directory/Foreign.hsc" #-}
    +
    +pathMax :: Int
    +pathMax = 4096
    +{-# LINE 53 "src/System/Posix/Directory/Foreign.hsc" #-}
    +
    +unionFlags :: [Flags] -> CInt
    +unionFlags = fromIntegral . foldl' ((. unFlags) . (.|.)) 0
    +
    + diff --git a/src/System-Posix-Directory-Traversals.html b/src/System-Posix-Directory-Traversals.html new file mode 100644 index 0000000..12a4f80 --- /dev/null +++ b/src/System-Posix-Directory-Traversals.html @@ -0,0 +1,271 @@ + + + + + +src/System/Posix/Directory/Traversals.hs + + + +
    -- |
    +-- Module      :  System.Posix.Directory.Traversals
    +-- Copyright   :  © 2016 Julian Ospald
    +-- License     :  BSD3
    +--
    +-- Maintainer  :  Julian Ospald <hasufell@posteo.de>
    +-- Stability   :  experimental
    +-- Portability :  portable
    +--
    +-- Traversal and read operations on directories.
    +
    +
    +{-# LANGUAGE ForeignFunctionInterface #-}
    +{-# LANGUAGE OverloadedStrings #-}
    +{-# LANGUAGE PackageImports #-}
    +{-# LANGUAGE TupleSections #-}
    +{-# LANGUAGE ViewPatterns #-}
    +
    +{-# OPTIONS_GHC -Wall #-}
    +
    +
    +module System.Posix.Directory.Traversals (
    +
    +  getDirectoryContents
    +, getDirectoryContents'
    +
    +, allDirectoryContents
    +, allDirectoryContents'
    +, traverseDirectory
    +
    +-- lower-level stuff
    +, readDirEnt
    +, packDirStream
    +, unpackDirStream
    +, fdOpendir
    +
    +, realpath
    +) where
    +
    +import Control.Applicative
    +import Control.Monad
    +import System.Posix.FilePath ((</>))
    +import System.Posix.Directory.Foreign
    +
    +import qualified System.Posix as Posix
    +import System.IO.Error
    +import Control.Exception
    +import qualified Data.ByteString.Char8 as BS
    +import System.Posix.ByteString.FilePath
    +import System.Posix.Directory.ByteString as PosixBS
    +import System.Posix.Files.ByteString
    +
    +import System.IO.Unsafe
    +import "unix" System.Posix.IO.ByteString (closeFd)
    +import Unsafe.Coerce (unsafeCoerce)
    +import Foreign.C.Error
    +import Foreign.C.String
    +import Foreign.C.Types
    +import Foreign.Marshal.Alloc (alloca,allocaBytes)
    +import Foreign.Ptr
    +import Foreign.Storable
    +
    +
    +
    +
    +----------------------------------------------------------
    +
    +-- | Get all files from a directory and its subdirectories.
    +--
    +-- Upon entering a directory, 'allDirectoryContents' will get all entries
    +-- strictly.  However the returned list is lazy in that directories will only
    +-- be accessed on demand.
    +--
    +-- Follows symbolic links for the input dir.
    +allDirectoryContents :: RawFilePath -> IO [RawFilePath]
    +allDirectoryContents topdir = do
    +    namesAndTypes <- getDirectoryContents topdir
    +    let properNames = filter ((`notElem` [".", ".."]) . snd) namesAndTypes
    +    paths <- forM properNames $ \(typ,name) -> unsafeInterleaveIO $ do
    +        let path = topdir </> name
    +        case () of
    +            () | typ == dtDir -> allDirectoryContents path
    +               | typ == dtUnknown -> do
    +                    isDir <- isDirectory <$> getFileStatus path
    +                    if isDir
    +                        then allDirectoryContents path
    +                        else return [path]
    +               | otherwise -> return [path]
    +    return (topdir : concat paths)
    +
    +-- | Get all files from a directory and its subdirectories strictly.
    +--
    +-- Follows symbolic links for the input dir.
    +allDirectoryContents' :: RawFilePath -> IO [RawFilePath]
    +allDirectoryContents' = fmap reverse . traverseDirectory (\acc fp -> return (fp:acc)) []
    +-- this uses traverseDirectory because it's more efficient than forcing the
    +-- lazy version.
    +
    +-- | Recursively apply the 'action' to the parent directory and all
    +-- files/subdirectories.
    +--
    +-- This function allows for memory-efficient traversals.
    +--
    +-- Follows symbolic links for the input dir.
    +traverseDirectory :: (s -> RawFilePath -> IO s) -> s -> RawFilePath -> IO s
    +traverseDirectory act s0 topdir = toploop
    +  where
    +    toploop = do
    +        isDir <- isDirectory <$> getFileStatus topdir
    +        s' <- act s0 topdir
    +        if isDir then actOnDirContents topdir s' loop
    +                 else return s'
    +    loop typ path acc = do
    +        isDir <- case () of
    +            () | typ == dtDir     -> return True
    +               | typ == dtUnknown -> isDirectory <$> getFileStatus path
    +               | otherwise        -> return False
    +        if isDir
    +          then act acc path >>= \acc' -> actOnDirContents path acc' loop
    +          else act acc path
    +
    +actOnDirContents :: RawFilePath
    +                 -> b
    +                 -> (DirType -> RawFilePath -> b -> IO b)
    +                 -> IO b
    +actOnDirContents pathRelToTop b f =
    +  modifyIOError ((`ioeSetFileName` (BS.unpack pathRelToTop)) .
    +                 (`ioeSetLocation` "findBSTypRel")) $
    +    bracket
    +      (openDirStream pathRelToTop)
    +      Posix.closeDirStream
    +      (\dirp -> loop dirp b)
    + where
    +  loop dirp b' = do
    +    (typ,e) <- readDirEnt dirp
    +    if (e == "")
    +      then return b'
    +      else
    +          if (e == "." || e == "..")
    +              then loop dirp b'
    +              else f typ (pathRelToTop </> e) b' >>= loop dirp
    +
    +
    +----------------------------------------------------------
    +-- dodgy stuff
    +
    +type CDir = ()
    +type CDirent = ()
    +
    +-- Posix doesn't export DirStream, so to re-use that type we need to use
    +-- unsafeCoerce.  It's just a newtype, so this is a legitimate usage.
    +-- ugly trick.
    +unpackDirStream :: DirStream -> Ptr CDir
    +unpackDirStream = unsafeCoerce
    +
    +packDirStream :: Ptr CDir -> DirStream
    +packDirStream = unsafeCoerce
    +
    +-- the __hscore_* functions are defined in the unix package.  We can import them and let
    +-- the linker figure it out.
    +foreign import ccall unsafe "__hscore_readdir"
    +  c_readdir  :: Ptr CDir -> Ptr (Ptr CDirent) -> IO CInt
    +
    +foreign import ccall unsafe "__hscore_free_dirent"
    +  c_freeDirEnt  :: Ptr CDirent -> IO ()
    +
    +foreign import ccall unsafe "__hscore_d_name"
    +  c_name :: Ptr CDirent -> IO CString
    +
    +foreign import ccall unsafe "__posixdir_d_type"
    +  c_type :: Ptr CDirent -> IO DirType
    +
    +foreign import ccall "realpath"
    +  c_realpath :: CString -> CString -> IO CString
    +
    +foreign import ccall unsafe "fdopendir"
    +  c_fdopendir :: Posix.Fd -> IO (Ptr ())
    +
    +----------------------------------------------------------
    +-- less dodgy but still lower-level
    +
    +
    +readDirEnt :: DirStream -> IO (DirType, RawFilePath)
    +readDirEnt (unpackDirStream -> dirp) =
    +  alloca $ \ptr_dEnt  -> loop ptr_dEnt
    + where
    +  loop ptr_dEnt = do
    +    resetErrno
    +    r <- c_readdir dirp ptr_dEnt
    +    if (r == 0)
    +       then do
    +         dEnt <- peek ptr_dEnt
    +         if (dEnt == nullPtr)
    +            then return (dtUnknown,BS.empty)
    +            else do
    +                 dName <- c_name dEnt >>= peekFilePath
    +                 dType <- c_type dEnt
    +                 c_freeDirEnt dEnt
    +                 return (dType, dName)
    +       else do
    +         errno <- getErrno
    +         if (errno == eINTR)
    +            then loop ptr_dEnt
    +            else do
    +                 let (Errno eo) = errno
    +                 if (eo == 0)
    +                    then return (dtUnknown,BS.empty)
    +                    else throwErrno "readDirEnt"
    +
    +
    +-- |Gets all directory contents (not recursively).
    +getDirectoryContents :: RawFilePath -> IO [(DirType, RawFilePath)]
    +getDirectoryContents path =
    +  modifyIOError ((`ioeSetFileName` (BS.unpack path)) .
    +                 (`ioeSetLocation` "System.Posix.Directory.Traversals.getDirectoryContents")) $
    +    bracket
    +      (PosixBS.openDirStream path)
    +      PosixBS.closeDirStream
    +      _dirloop
    +
    +
    +-- |Binding to @fdopendir(3)@.
    +fdOpendir :: Posix.Fd -> IO DirStream
    +fdOpendir fd =
    +    packDirStream <$> throwErrnoIfNull "fdOpendir" (c_fdopendir fd)
    +
    +
    +-- |Like `getDirectoryContents` except for a file descriptor.
    +--
    +-- To avoid complicated error checks, the file descriptor is
    +-- __always__ closed, even if `fdOpendir` fails. Usually, this
    +-- only happens on successful `fdOpendir` and after the directory
    +-- stream is closed. Also see the manpage of @fdopendir(3)@ for
    +-- more details.
    +getDirectoryContents' :: Posix.Fd -> IO [(DirType, RawFilePath)]
    +getDirectoryContents' fd = do
    +  dirstream <- fdOpendir fd `catchIOError` \e -> do
    +    closeFd fd
    +    ioError e
    +  -- closeDirStream closes the filedescriptor
    +  finally (_dirloop dirstream) (PosixBS.closeDirStream dirstream)
    +
    +
    +_dirloop :: DirStream -> IO [(DirType, RawFilePath)]
    +{-# INLINE _dirloop #-}
    +_dirloop dirp = do
    +   t@(_typ,e) <- readDirEnt dirp
    +   if BS.null e then return [] else do
    +     es <- _dirloop dirp
    +     return (t:es)
    +
    +
    +-- | return the canonicalized absolute pathname
    +--
    +-- like canonicalizePath, but uses @realpath(3)@
    +realpath :: RawFilePath -> IO RawFilePath
    +realpath inp =
    +    allocaBytes pathMax $ \tmp -> do
    +        void $ BS.useAsCString inp $ \cstr -> throwErrnoIfNull "realpath" $ c_realpath cstr tmp
    +        BS.packCString tmp
    +
    + diff --git a/src/System-Posix-FD.html b/src/System-Posix-FD.html new file mode 100644 index 0000000..b626fc6 --- /dev/null +++ b/src/System-Posix-FD.html @@ -0,0 +1,86 @@ + + + + + +src/System/Posix/FD.hs + + + +
    -- |
    +-- Module      :  System.Posix.FD
    +-- Copyright   :  © 2016 Julian Ospald
    +-- License     :  BSD3
    +--
    +-- Maintainer  :  Julian Ospald <hasufell@posteo.de>
    +-- Stability   :  experimental
    +-- Portability :  portable
    +--
    +-- Provides an alternative for `System.Posix.IO.ByteString.openFd`
    +-- which gives us more control on what status flags to pass to the
    +-- low-level @open(2)@ call, in contrast to the unix package.
    +
    +
    +{-# LANGUAGE ForeignFunctionInterface #-}
    +{-# LANGUAGE OverloadedStrings #-}
    +{-# LANGUAGE TupleSections #-}
    +
    +{-# OPTIONS_GHC -Wall #-}
    +
    +
    +module System.Posix.FD (
    +    openFd
    +) where
    +
    +
    +import Foreign.C.String
    +import Foreign.C.Types
    +import System.Posix.Directory.Foreign
    +import qualified System.Posix as Posix
    +import System.Posix.ByteString.FilePath
    +
    +
    +foreign import ccall unsafe "open"
    +   c_open :: CString -> CInt -> Posix.CMode -> IO CInt
    +
    +
    +open_  :: CString
    +       -> Posix.OpenMode
    +       -> [Flags]
    +       -> Maybe Posix.FileMode
    +       -> IO Posix.Fd
    +open_ str how optional_flags maybe_mode = do
    +    fd <- c_open str all_flags mode_w
    +    return (Posix.Fd fd)
    +  where
    +    all_flags  = unionFlags $ optional_flags ++ [open_mode] ++ creat
    +
    +
    +    (creat, mode_w) = case maybe_mode of
    +                        Nothing -> ([],0)
    +                        Just x  -> ([oCreat], x)
    +
    +    open_mode = case how of
    +                   Posix.ReadOnly  -> oRdonly
    +                   Posix.WriteOnly -> oWronly
    +                   Posix.ReadWrite -> oRdwr
    +
    +
    +-- |Open and optionally create this file. See 'System.Posix.Files'
    +-- for information on how to use the 'FileMode' type.
    +--
    +-- Note that passing @Just x@ as the 4th argument triggers the
    +-- `oCreat` status flag, which must be set when you pass in `oExcl`
    +-- to the status flags. Also see the manpage for @open(2)@.
    +openFd :: RawFilePath
    +       -> Posix.OpenMode
    +       -> [Flags]               -- ^ status flags of @open(2)@
    +       -> Maybe Posix.FileMode  -- ^ @Just x@ => creates the file with the given modes, Nothing => the file must exist.
    +       -> IO Posix.Fd
    +openFd name how optional_flags maybe_mode =
    +   withFilePath name $ \str ->
    +     throwErrnoPathIfMinus1Retry "openFd" name $
    +       open_ str how optional_flags maybe_mode
    +
    +
    + diff --git a/src/System-Posix-FilePath.html b/src/System-Posix-FilePath.html new file mode 100644 index 0000000..9451055 --- /dev/null +++ b/src/System-Posix-FilePath.html @@ -0,0 +1,834 @@ + + + + + +src/System/Posix/FilePath.hs + + + +
    -- |
    +-- Module      :  System.Posix.FilePath
    +-- Copyright   :  © 2016 Julian Ospald
    +-- License     :  BSD3
    +--
    +-- Maintainer  :  Julian Ospald <hasufell@posteo.de>
    +-- Stability   :  experimental
    +-- Portability :  portable
    +--
    +-- The equivalent of "System.FilePath" on raw (byte string) file paths.
    +--
    +-- Not all functions of "System.FilePath" are implemented yet. Feel free to contribute!
    +
    +
    +{-# LANGUAGE CPP #-}
    +{-# LANGUAGE TupleSections #-}
    +
    +{-# OPTIONS_GHC -Wall #-}
    +
    +
    +module System.Posix.FilePath (
    +
    +  -- * Separator predicates
    +  pathSeparator
    +, isPathSeparator
    +, searchPathSeparator
    +, isSearchPathSeparator
    +, extSeparator
    +, isExtSeparator
    +
    +  -- * $PATH methods
    +, splitSearchPath
    +, getSearchPath
    +
    +  -- * Extension functions
    +, splitExtension
    +, takeExtension
    +, replaceExtension
    +, dropExtension
    +, addExtension
    +, hasExtension
    +, (<.>)
    +, splitExtensions
    +, dropExtensions
    +, takeExtensions
    +, stripExtension
    +
    +  -- * Filename\/directory functions
    +, splitFileName
    +, takeFileName
    +, replaceFileName
    +, dropFileName
    +, takeBaseName
    +, replaceBaseName
    +, takeDirectory
    +, replaceDirectory
    +, combine
    +, (</>)
    +, splitPath
    +, joinPath
    +, splitDirectories
    +
    +  -- * Trailing slash functions
    +, hasTrailingPathSeparator
    +, addTrailingPathSeparator
    +, dropTrailingPathSeparator
    +
    +  -- * File name manipulations
    +, normalise
    +, makeRelative
    +, equalFilePath
    +, isRelative
    +, isAbsolute
    +, isValid
    +, makeValid
    +, isFileName
    +, hasParentDir
    +, hiddenFile
    +
    +, module System.Posix.ByteString.FilePath
    +) where
    +
    +import           Data.ByteString (ByteString)
    +import qualified Data.ByteString as BS
    +import Data.String (fromString)
    +import           System.Posix.ByteString.FilePath
    +import qualified System.Posix.Env.ByteString as PE
    +
    +import           Data.Maybe (isJust)
    +import           Data.Word8
    +#if !MIN_VERSION_bytestring(0,10,8)
    +import qualified Data.List as L
    +#endif
    +import           Control.Arrow (second)
    +
    +-- $setup
    +-- >>> import Data.Char
    +-- >>> import Data.Maybe
    +-- >>> import Test.QuickCheck
    +-- >>> import Control.Applicative
    +-- >>> import qualified Data.ByteString as BS
    +-- >>> instance Arbitrary ByteString where arbitrary = BS.pack <$> arbitrary
    +-- >>> instance CoArbitrary ByteString where coarbitrary = coarbitrary . BS.unpack
    +--
    +-- >>> let _chr :: Word8 -> Char; _chr = chr . fromIntegral
    +
    +
    +
    +------------------------
    +-- Separator predicates
    +
    +
    +-- | Path separator character
    +pathSeparator :: Word8
    +pathSeparator = _slash
    +
    +
    +-- | Check if a character is the path separator
    +--
    +-- prop> \n ->  (_chr n == '/') == isPathSeparator n
    +isPathSeparator :: Word8 -> Bool
    +isPathSeparator = (== pathSeparator)
    +
    +
    +-- | Search path separator
    +searchPathSeparator :: Word8
    +searchPathSeparator = _colon
    +
    +
    +-- | Check if a character is the search path separator
    +--
    +-- prop> \n -> (_chr n == ':') == isSearchPathSeparator n
    +isSearchPathSeparator :: Word8 -> Bool
    +isSearchPathSeparator = (== searchPathSeparator)
    +
    +
    +-- | File extension separator
    +extSeparator :: Word8
    +extSeparator = _period
    +
    +
    +-- | Check if a character is the file extension separator
    +--
    +-- prop> \n -> (_chr n == '.') == isExtSeparator n
    +isExtSeparator :: Word8 -> Bool
    +isExtSeparator = (== extSeparator)
    +
    +
    +
    +------------------------
    +-- $PATH methods
    +
    +
    +-- | Take a ByteString, split it on the 'searchPathSeparator'.
    +-- Blank items are converted to @.@.
    +--
    +-- Follows the recommendations in
    +-- <http://www.opengroup.org/onlinepubs/009695399/basedefs/xbd_chap08.html>
    +--
    +-- >>> splitSearchPath "File1:File2:File3"
    +-- ["File1","File2","File3"]
    +-- >>> splitSearchPath "File1::File2:File3"
    +-- ["File1",".","File2","File3"]
    +-- >>> splitSearchPath ""
    +-- ["."]
    +splitSearchPath :: ByteString -> [RawFilePath]
    +splitSearchPath = f
    +  where
    +    f bs = let (pre, post) = BS.break isSearchPathSeparator bs
    +           in if BS.null post
    +                 then g pre
    +                 else g pre ++ f (BS.tail post)
    +    g x
    +      | BS.null x = [BS.singleton _period]
    +      | otherwise = [x]
    +
    +
    +-- | Get a list of 'RawFilePath's in the $PATH variable.
    +getSearchPath :: IO [RawFilePath]
    +getSearchPath = fmap (maybe [] splitSearchPath) (PE.getEnv $ fromString "PATH")
    +
    +
    +
    +------------------------
    +-- Extension functions
    +
    +-- | Split a 'RawFilePath' into a path+filename and extension
    +--
    +-- >>> splitExtension "file.exe"
    +-- ("file",".exe")
    +-- >>> splitExtension "file"
    +-- ("file","")
    +-- >>> splitExtension "/path/file.tar.gz"
    +-- ("/path/file.tar",".gz")
    +--
    +-- prop> \path -> uncurry (BS.append) (splitExtension path) == path
    +splitExtension :: RawFilePath -> (RawFilePath, ByteString)
    +splitExtension x = if BS.null basename
    +    then (x,BS.empty)
    +    else (BS.append path (BS.init basename),BS.cons extSeparator fileExt)
    +  where
    +    (path,file) = splitFileNameRaw x
    +    (basename,fileExt) = BS.breakEnd isExtSeparator file
    +
    +
    +-- | Get the final extension from a 'RawFilePath'
    +--
    +-- >>> takeExtension "file.exe"
    +-- ".exe"
    +-- >>> takeExtension "file"
    +-- ""
    +-- >>> takeExtension "/path/file.tar.gz"
    +-- ".gz"
    +takeExtension :: RawFilePath -> ByteString
    +takeExtension = snd . splitExtension
    +
    +
    +-- | Change a file's extension
    +--
    +-- prop> \path -> let ext = takeExtension path in replaceExtension path ext == path
    +replaceExtension :: RawFilePath -> ByteString -> RawFilePath
    +replaceExtension path ext = dropExtension path <.> ext
    +
    +
    +-- | Drop the final extension from a 'RawFilePath'
    +--
    +-- >>> dropExtension "file.exe"
    +-- "file"
    +-- >>> dropExtension "file"
    +-- "file"
    +-- >>> dropExtension "/path/file.tar.gz"
    +-- "/path/file.tar"
    +dropExtension :: RawFilePath -> RawFilePath
    +dropExtension = fst . splitExtension
    +
    +
    +-- | Add an extension to a 'RawFilePath'
    +--
    +-- >>> addExtension "file" ".exe"
    +-- "file.exe"
    +-- >>> addExtension "file.tar" ".gz"
    +-- "file.tar.gz"
    +-- >>> addExtension "/path/" ".ext"
    +-- "/path/.ext"
    +addExtension :: RawFilePath -> ByteString -> RawFilePath
    +addExtension file ext
    +    | BS.null ext = file
    +    | isExtSeparator (BS.head ext) = BS.append file ext
    +    | otherwise = BS.intercalate (BS.singleton extSeparator) [file, ext]
    +
    +
    +-- | Check if a 'RawFilePath' has an extension
    +--
    +-- >>> hasExtension "file"
    +-- False
    +-- >>> hasExtension "file.tar"
    +-- True
    +-- >>> hasExtension "/path.part1/"
    +-- False
    +hasExtension :: RawFilePath -> Bool
    +hasExtension = isJust . BS.elemIndex extSeparator . takeFileName
    +
    +
    +-- | Operator version of 'addExtension'
    +(<.>) :: RawFilePath -> ByteString -> RawFilePath
    +(<.>) = addExtension
    +
    +
    +-- | Split a 'RawFilePath' on the first extension.
    +--
    +-- >>> splitExtensions "/path/file.tar.gz"
    +-- ("/path/file",".tar.gz")
    +--
    +-- prop> \path -> uncurry addExtension (splitExtensions path) == path
    +splitExtensions :: RawFilePath -> (RawFilePath, ByteString)
    +splitExtensions x = if BS.null basename
    +    then (path,fileExt)
    +    else (BS.append path basename,fileExt)
    +  where
    +    (path,file) = splitFileNameRaw x
    +    (basename,fileExt) = BS.break isExtSeparator file
    +
    +
    +-- | Remove all extensions from a 'RawFilePath'
    +--
    +-- >>> dropExtensions "/path/file.tar.gz"
    +-- "/path/file"
    +dropExtensions :: RawFilePath -> RawFilePath
    +dropExtensions = fst . splitExtensions
    +
    +
    +-- | Take all extensions from a 'RawFilePath'
    +--
    +-- >>> takeExtensions "/path/file.tar.gz"
    +-- ".tar.gz"
    +takeExtensions :: RawFilePath -> ByteString
    +takeExtensions = snd . splitExtensions
    +
    +
    +-- | Drop the given extension from a FilePath, and the @\".\"@ preceding it.
    +-- Returns 'Nothing' if the FilePath does not have the given extension, or
    +-- 'Just' and the part before the extension if it does.
    +--
    +-- This function can be more predictable than 'dropExtensions',
    +-- especially if the filename might itself contain @.@ characters.
    +--
    +-- >>> stripExtension "hs.o" "foo.x.hs.o"
    +-- Just "foo.x"
    +-- >>> stripExtension "hi.o" "foo.x.hs.o"
    +-- Nothing
    +-- >>> stripExtension ".c.d" "a.b.c.d"
    +-- Just "a.b"
    +-- >>> stripExtension ".c.d" "a.b..c.d"
    +-- Just "a.b."
    +-- >>> stripExtension "baz"  "foo.bar"
    +-- Nothing
    +-- >>> stripExtension "bar"  "foobar"
    +-- Nothing
    +--
    +-- prop> \path -> stripExtension "" path == Just path
    +-- prop> \path -> dropExtension path  == fromJust (stripExtension (takeExtension path) path)
    +-- prop> \path -> dropExtensions path == fromJust (stripExtension (takeExtensions path) path)
    +stripExtension :: ByteString -> RawFilePath -> Maybe RawFilePath
    +stripExtension bs path
    +  | BS.null bs = Just path
    +  | otherwise  = stripSuffix' dotExt path
    +  where
    +    dotExt = if isExtSeparator $ BS.head bs
    +                then bs
    +                else extSeparator `BS.cons` bs
    +#if MIN_VERSION_bytestring(0,10,8)
    +    stripSuffix' = BS.stripSuffix
    +#else
    +    stripSuffix' xs ys = fmap (BS.pack . reverse) $ L.stripPrefix (reverse $ BS.unpack xs) (reverse $ BS.unpack ys)
    +#endif
    +
    +
    +------------------------
    +-- Filename/directory functions
    +
    +
    +-- | Split a 'RawFilePath' into (path,file).  'combine' is the inverse
    +--
    +-- >>> splitFileName "path/file.txt"
    +-- ("path/","file.txt")
    +-- >>> splitFileName "path/"
    +-- ("path/","")
    +-- >>> splitFileName "file.txt"
    +-- ("./","file.txt")
    +--
    +-- prop> \path -> uncurry combine (splitFileName path) == path || fst (splitFileName path) == "./"
    +splitFileName :: RawFilePath -> (RawFilePath, RawFilePath)
    +splitFileName x = if BS.null path
    +    then (dotSlash, file)
    +    else (path,file)
    +  where
    +    (path,file) = splitFileNameRaw x
    +    dotSlash = _period `BS.cons` (BS.singleton pathSeparator)
    +
    +
    +-- | Get the file name
    +--
    +-- >>> takeFileName "path/file.txt"
    +-- "file.txt"
    +-- >>> takeFileName "path/"
    +-- ""
    +takeFileName :: RawFilePath -> RawFilePath
    +takeFileName = snd . splitFileName
    +
    +
    +-- | Change the file name
    +--
    +-- prop> \path -> replaceFileName path (takeFileName path) == path
    +replaceFileName :: RawFilePath -> ByteString -> RawFilePath
    +replaceFileName x y = fst (splitFileNameRaw x) </> y
    +
    +
    +-- | Drop the file name
    +--
    +-- >>> dropFileName "path/file.txt"
    +-- "path/"
    +-- >>> dropFileName "file.txt"
    +-- "./"
    +dropFileName :: RawFilePath -> RawFilePath
    +dropFileName = fst . splitFileName
    +
    +
    +-- | Get the file name, without a trailing extension
    +--
    +-- >>> takeBaseName "path/file.tar.gz"
    +-- "file.tar"
    +-- >>> takeBaseName ""
    +-- ""
    +takeBaseName :: RawFilePath -> ByteString
    +takeBaseName = dropExtension . takeFileName
    +
    +
    +-- | Change the base name
    +--
    +-- >>> replaceBaseName "path/file.tar.gz" "bob"
    +-- "path/bob.gz"
    +--
    +-- prop> \path -> replaceBaseName path (takeBaseName path) == path
    +replaceBaseName :: RawFilePath -> ByteString -> RawFilePath
    +replaceBaseName path name = combineRaw dir (name <.> ext)
    +  where
    +    (dir,file) = splitFileNameRaw path
    +    ext = takeExtension file
    +
    +
    +-- | Get the directory, moving up one level if it's already a directory
    +--
    +-- >>> takeDirectory "path/file.txt"
    +-- "path"
    +-- >>> takeDirectory "file"
    +-- "."
    +-- >>> takeDirectory "/path/to/"
    +-- "/path/to"
    +-- >>> takeDirectory "/path/to"
    +-- "/path"
    +takeDirectory :: RawFilePath -> RawFilePath
    +takeDirectory x = case () of
    +    () | x == BS.singleton pathSeparator -> x
    +       | BS.null res && not (BS.null file) -> file
    +       | otherwise -> res
    +  where
    +    res = fst $ BS.spanEnd isPathSeparator file
    +    file = dropFileName x
    +
    +
    +-- | Change the directory component of a 'RawFilePath'
    +--
    +-- prop> \path -> replaceDirectory path (takeDirectory path) `equalFilePath` path || takeDirectory path == "."
    +replaceDirectory :: RawFilePath -> ByteString -> RawFilePath
    +replaceDirectory file dir = combineRaw dir (takeFileName file)
    +
    +
    +-- | Join two paths together
    +--
    +-- >>> combine "/" "file"
    +-- "/file"
    +-- >>> combine "/path/to" "file"
    +-- "/path/to/file"
    +-- >>> combine "file" "/absolute/path"
    +-- "/absolute/path"
    +combine :: RawFilePath -> RawFilePath -> RawFilePath
    +combine a b | not (BS.null b) && isPathSeparator (BS.head b) = b
    +            | otherwise = combineRaw a b
    +
    +
    +-- | Operator version of combine
    +(</>) :: RawFilePath -> RawFilePath -> RawFilePath
    +(</>) = combine
    +
    +-- | Split a path into a list of components:
    +--
    +-- >>> splitPath "/path/to/file.txt"
    +-- ["/","path/","to/","file.txt"]
    +--
    +-- prop> \path -> BS.concat (splitPath path) == path
    +splitPath :: RawFilePath -> [RawFilePath]
    +splitPath = splitter
    +  where
    +    splitter x
    +      | BS.null x = []
    +      | otherwise = case BS.elemIndex pathSeparator x of
    +            Nothing -> [x]
    +            Just ix -> case BS.findIndex (not . isPathSeparator) $ BS.drop (ix+1) x of
    +                          Nothing -> [x]
    +                          Just runlen -> uncurry (:) . second splitter $ BS.splitAt (ix+1+runlen) x
    +
    +
    +-- | Join a split path back together
    +--
    +-- prop> \path -> joinPath (splitPath path) == path
    +--
    +-- >>> joinPath ["path","to","file.txt"]
    +-- "path/to/file.txt"
    +joinPath :: [RawFilePath] -> RawFilePath
    +joinPath = foldr (</>) BS.empty
    +
    +
    +-- | Like 'splitPath', but without trailing slashes
    +--
    +-- >>> splitDirectories "/path/to/file.txt"
    +-- ["/","path","to","file.txt"]
    +-- >>> splitDirectories ""
    +-- []
    +splitDirectories :: RawFilePath -> [RawFilePath]
    +splitDirectories x
    +    | BS.null x = []
    +    | isPathSeparator (BS.head x) = let (root,rest) = BS.splitAt 1 x
    +                                    in root : splitter rest
    +    | otherwise = splitter x
    +  where
    +    splitter = filter (not . BS.null) . BS.split pathSeparator
    +
    +
    +
    +------------------------
    +-- Trailing slash functions
    +
    +-- | Check if the last character of a 'RawFilePath' is '/'.
    +--
    +-- >>> hasTrailingPathSeparator "/path/"
    +-- True
    +-- >>> hasTrailingPathSeparator "/"
    +-- True
    +-- >>> hasTrailingPathSeparator "/path"
    +-- False
    +hasTrailingPathSeparator :: RawFilePath -> Bool
    +hasTrailingPathSeparator x
    +  | BS.null x = False
    +  | otherwise = isPathSeparator $ BS.last x
    +
    +
    +-- | Add a trailing path separator.
    +--
    +-- >>> addTrailingPathSeparator "/path"
    +-- "/path/"
    +-- >>> addTrailingPathSeparator "/path/"
    +-- "/path/"
    +-- >>> addTrailingPathSeparator "/"
    +-- "/"
    +addTrailingPathSeparator :: RawFilePath -> RawFilePath
    +addTrailingPathSeparator x = if hasTrailingPathSeparator x
    +    then x
    +    else x `BS.snoc` pathSeparator
    +
    +
    +-- | Remove a trailing path separator
    +--
    +-- >>> dropTrailingPathSeparator "/path/"
    +-- "/path"
    +-- >>> dropTrailingPathSeparator "/path////"
    +-- "/path"
    +-- >>> dropTrailingPathSeparator "/"
    +-- "/"
    +-- >>> dropTrailingPathSeparator "//"
    +-- "/"
    +dropTrailingPathSeparator :: RawFilePath -> RawFilePath
    +dropTrailingPathSeparator x
    +  | x == BS.singleton pathSeparator = x
    +  | otherwise = if hasTrailingPathSeparator x
    +                  then dropTrailingPathSeparator $ BS.init x
    +                  else x
    +
    +
    +
    +------------------------
    +-- File name manipulations
    +
    +
    +-- |Normalise a file.
    +--
    +-- >>> normalise "/file/\\test////"
    +-- "/file/\\test/"
    +-- >>> normalise "/file/./test"
    +-- "/file/test"
    +-- >>> normalise "/test/file/../bob/fred/"
    +-- "/test/file/../bob/fred/"
    +-- >>> normalise "../bob/fred/"
    +-- "../bob/fred/"
    +-- >>> normalise "./bob/fred/"
    +-- "bob/fred/"
    +-- >>> normalise "./bob////.fred/./...///./..///#."
    +-- "bob/.fred/.../../#."
    +-- >>> normalise "."
    +-- "."
    +-- >>> normalise "./"
    +-- "./"
    +-- >>> normalise "./."
    +-- "./"
    +-- >>> normalise "/./"
    +-- "/"
    +-- >>> normalise "/"
    +-- "/"
    +-- >>> normalise "bob/fred/."
    +-- "bob/fred/"
    +-- >>> normalise "//home"
    +-- "/home"
    +normalise :: RawFilePath -> RawFilePath
    +normalise filepath =
    +  result `BS.append`
    +  (if addPathSeparator
    +       then BS.singleton pathSeparator
    +       else BS.empty)
    +  where
    +    result = let n = f filepath
    +             in if BS.null n
    +                then BS.singleton _period
    +                else n
    +    addPathSeparator = isDirPath filepath &&
    +      not (hasTrailingPathSeparator result)
    +    isDirPath xs = hasTrailingPathSeparator xs
    +        || not (BS.null xs) && BS.last xs == _period
    +           && hasTrailingPathSeparator (BS.init xs)
    +    f = joinPath . dropDots . propSep . splitDirectories
    +    propSep :: [ByteString] -> [ByteString]
    +    propSep (x:xs)
    +      | BS.all (== pathSeparator) x = BS.singleton pathSeparator : xs
    +      | otherwise                   = x : xs
    +    propSep [] = []
    +    dropDots :: [ByteString] -> [ByteString]
    +    dropDots = filter (BS.singleton _period /=)
    +
    +
    +
    +-- | Contract a filename, based on a relative path. Note that the resulting
    +-- path will never introduce @..@ paths, as the presence of symlinks
    +-- means @..\/b@ may not reach @a\/b@ if it starts from @a\/c@. For a
    +-- worked example see
    +-- <http://neilmitchell.blogspot.co.uk/2015/10/filepaths-are-subtle-symlinks-are-hard.html this blog post>.
    +--
    +-- >>> makeRelative "/directory" "/directory/file.ext"
    +-- "file.ext"
    +-- >>> makeRelative "/Home" "/home/bob"
    +-- "/home/bob"
    +-- >>> makeRelative "/home/" "/home/bob/foo/bar"
    +-- "bob/foo/bar"
    +-- >>> makeRelative "/fred" "bob"
    +-- "bob"
    +-- >>> makeRelative "/file/test" "/file/test/fred"
    +-- "fred"
    +-- >>> makeRelative "/file/test" "/file/test/fred/"
    +-- "fred/"
    +-- >>> makeRelative "some/path" "some/path/a/b/c"
    +-- "a/b/c"
    +--
    +-- prop> \p -> makeRelative p p == "."
    +-- prop> \p -> makeRelative (takeDirectory p) p `equalFilePath` takeFileName p
    +-- prop \x y -> equalFilePath x y || (isRelative x && makeRelative y x == x) || equalFilePath (y </> makeRelative y x) x
    +makeRelative :: RawFilePath -> RawFilePath -> RawFilePath
    +makeRelative root path
    +  | equalFilePath root path = BS.singleton _period
    +  | takeAbs root /= takeAbs path = path
    +  | otherwise = f (dropAbs root) (dropAbs path)
    +  where
    +    f x y
    +      | BS.null x = BS.dropWhile isPathSeparator y
    +      | otherwise = let (x1,x2) = g x
    +                        (y1,y2) = g y
    +                    in if equalFilePath x1 y1 then f x2 y2 else path
    +    g x = (BS.dropWhile isPathSeparator a, BS.dropWhile isPathSeparator b)
    +      where (a, b) = BS.break isPathSeparator $ BS.dropWhile isPathSeparator x
    +    dropAbs x = snd $ BS.span (== _slash) x
    +    takeAbs x = fst $ BS.span (== _slash) x
    +
    +
    +-- |Equality of two filepaths. The filepaths are normalised
    +-- and trailing path separators are dropped.
    +--
    +-- >>> equalFilePath "foo" "foo"
    +-- True
    +-- >>> equalFilePath "foo" "foo/"
    +-- True
    +-- >>> equalFilePath "foo" "./foo"
    +-- True
    +-- >>> equalFilePath "" ""
    +-- True
    +-- >>> equalFilePath "foo" "/foo"
    +-- False
    +-- >>> equalFilePath "foo" "FOO"
    +-- False
    +-- >>> equalFilePath "foo" "../foo"
    +-- False
    +--
    +-- prop> \p -> equalFilePath p p
    +equalFilePath :: RawFilePath -> RawFilePath -> Bool
    +equalFilePath p1 p2 = f p1 == f p2
    +  where
    +    f x = dropTrailingPathSeparator $ normalise x
    +
    +
    +-- | Check if a path is relative
    +--
    +-- prop> \path -> isRelative path /= isAbsolute path
    +isRelative :: RawFilePath -> Bool
    +isRelative = not . isAbsolute
    +
    +
    +-- | Check if a path is absolute
    +--
    +-- >>> isAbsolute "/path"
    +-- True
    +-- >>> isAbsolute "path"
    +-- False
    +-- >>> isAbsolute ""
    +-- False
    +isAbsolute :: RawFilePath -> Bool
    +isAbsolute x
    +    | BS.length x > 0 = isPathSeparator (BS.head x)
    +    | otherwise = False
    +
    +
    +-- | Is a FilePath valid, i.e. could you create a file like it?
    +--
    +-- >>> isValid ""
    +-- False
    +-- >>> isValid "\0"
    +-- False
    +-- >>> isValid "/random_ path:*"
    +-- True
    +isValid :: RawFilePath -> Bool
    +isValid filepath
    +  | BS.null filepath        = False
    +  | _nul `BS.elem` filepath = False
    +  | otherwise               = True
    +
    +
    +-- | Take a FilePath and make it valid; does not change already valid FilePaths.
    +--
    +-- >>> makeValid ""
    +-- "_"
    +-- >>> makeValid "file\0name"
    +-- "file_name"
    +--
    +-- prop> \p -> if isValid p then makeValid p == p else makeValid p /= p
    +-- prop> \p -> isValid (makeValid p)
    +makeValid :: RawFilePath -> RawFilePath
    +makeValid path
    +  | BS.null path = BS.singleton _underscore
    +  | otherwise    = BS.map (\x -> if x == _nul then _underscore else x) path
    +
    +
    +-- | Is the given path a valid filename? This includes
    +-- "." and "..".
    +--
    +-- >>> isFileName "lal"
    +-- True
    +-- >>> isFileName "."
    +-- True
    +-- >>> isFileName ".."
    +-- True
    +-- >>> isFileName ""
    +-- False
    +-- >>> isFileName "\0"
    +-- False
    +-- >>> isFileName "/random_ path:*"
    +-- False
    +isFileName :: RawFilePath -> Bool
    +isFileName filepath =
    +  not (BS.singleton pathSeparator `BS.isInfixOf` filepath) &&
    +  not (BS.null filepath) &&
    +  not (_nul `BS.elem` filepath)
    +
    +
    +-- | Check if the filepath has any parent directories in it.
    +--
    +-- >>> hasParentDir "/.."
    +-- True
    +-- >>> hasParentDir "foo/bar/.."
    +-- True
    +-- >>> hasParentDir "foo/../bar/."
    +-- True
    +-- >>> hasParentDir "foo/bar"
    +-- False
    +-- >>> hasParentDir "foo"
    +-- False
    +-- >>> hasParentDir ""
    +-- False
    +-- >>> hasParentDir ".."
    +-- False
    +hasParentDir :: RawFilePath -> Bool
    +hasParentDir filepath =
    +    (pathSeparator `BS.cons` pathDoubleDot)
    +     `BS.isSuffixOf` filepath
    +   ||
    +    (BS.singleton pathSeparator
    +        `BS.append` pathDoubleDot
    +        `BS.append` BS.singleton pathSeparator)
    +     `BS.isInfixOf`  filepath
    +   ||
    +    (pathDoubleDot `BS.append` BS.singleton pathSeparator)
    +      `BS.isPrefixOf` filepath
    +  where
    +    pathDoubleDot = BS.pack [_period, _period]
    +
    +
    +-- | Whether the file is a hidden file.
    +--
    +-- >>> hiddenFile ".foo"
    +-- True
    +-- >>> hiddenFile "..foo.bar"
    +-- True
    +-- >>> hiddenFile "some/path/.bar"
    +-- True
    +-- >>> hiddenFile "..."
    +-- True
    +-- >>> hiddenFile "dod.bar"
    +-- False
    +-- >>> hiddenFile "."
    +-- False
    +-- >>> hiddenFile ".."
    +-- False
    +-- >>> hiddenFile ""
    +-- False
    +hiddenFile :: RawFilePath -> Bool
    +hiddenFile fp
    +  | fn == BS.pack [_period, _period] = False
    +  | fn == BS.pack [_period]          = False
    +  | otherwise                        = BS.pack [extSeparator]
    +                                         `BS.isPrefixOf` fn
    +  where
    +    fn = takeFileName fp
    +
    +
    +
    +------------------------
    +-- internal stuff
    +
    +-- Just split the input FileName without adding/normalizing or changing
    +-- anything.
    +splitFileNameRaw :: RawFilePath -> (RawFilePath, RawFilePath)
    +splitFileNameRaw = BS.breakEnd isPathSeparator
    +
    +-- | Combine two paths, assuming rhs is NOT absolute.
    +combineRaw :: RawFilePath -> RawFilePath -> RawFilePath
    +combineRaw a b | BS.null a = b
    +                  | BS.null b = a
    +                  | isPathSeparator (BS.last a) = BS.append a b
    +                  | otherwise = BS.intercalate (BS.singleton pathSeparator) [a, b]
    +
    +
    + diff --git a/src/hscolour.css b/src/hscolour.css new file mode 100644 index 0000000..c15919e --- /dev/null +++ b/src/hscolour.css @@ -0,0 +1,5 @@ +.hs-keyglyph, .hs-layout {color: red;} +.hs-keyword {color: blue;} +.hs-comment, .hs-comment a {color: green;} +.hs-str, .hs-chr {color: teal;} +.hs-keyword, .hs-conid, .hs-varid, .hs-conop, .hs-varop, .hs-num, .hs-cpp, .hs-sel, .hs-definition {} diff --git a/synopsis.png b/synopsis.png new file mode 100644 index 0000000..85fb86e Binary files /dev/null and b/synopsis.png differ