diff --git a/HPath-IO-Errors.html b/HPath-IO-Errors.html index 980ab2d..30cac9b 100644 --- a/HPath-IO-Errors.html +++ b/HPath-IO-Errors.html @@ -1,22 +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

Contents

Description

Provides error handling.

Synopsis

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. +

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 # 
Exception HPathIOException Source # 

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 + 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 + 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 + 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 + 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 + 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 index 36f4333..720ba64 100644 --- a/HPath-IO-Utils.html +++ b/HPath-IO-Utils.html @@ -1,6 +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

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 +

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

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 index 7a2c55b..8e9e195 100644 --- a/HPath-IO.html +++ b/HPath-IO.html @@ -16,44 +16,44 @@ window.onload = function () {pageLoad();setSynopsis("mini_HPath-IO.html");}; 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. + unreliable/unsafe. Check the documentation of those functions for details.

Types

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 + 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. + 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 + 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 + 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. + 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 + 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. + 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. + 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 + or Directory may be ignored

    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:

    Throws:

    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:

    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:

    Others

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

    Applies realpath on the given absolute path.

    Throws:

    \ No newline at end of file diff --git a/HPath.html b/HPath.html index 1f63629..a197e91 100644 --- a/HPath.html +++ b/HPath.html @@ -1,8 +1,8 @@ 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

    Contents

    Description

    Support for well-typed paths.

    Synopsis

    Types

    data Abs Source #

    An absolute path.

    data Path b Source #

    Path of some base and type.

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

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

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

    Instances

    Eq (Path b) Source #

    ByteString equality.

    The following property holds:

    show x == show y ≡ x == y

    Methods

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

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

    Ord (Path b) Source #

    ByteString ordering.

    The following property holds:

    show x `compare` show y ≡ x `compare` y

    Methods

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

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

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

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

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

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

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

    Show (Path b) Source #

    Same as toFilePath.

    The following property holds:

    x == y ≡ show x == show y

    Methods

    showsPrec :: Int -> Path b -> ShowS

    show :: Path b -> String

    showList :: [Path b] -> ShowS

    NFData (Path b) Source # 

    Methods

    rnf :: Path b -> ()

    data Rel Source #

    A relative path; one without a root.

    Instances

    data Fn Source #

    A filename, without any /.

    Instances

    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)
    +

    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

    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 "/"
    @@ -16,8 +16,8 @@ window.onload = function () {pageLoad();setSynopsis("mini_HPath.html");};
     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)
    +

    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 "..."
    @@ -37,7 +37,7 @@ window.onload = function () {pageLoad();setSynopsis("mini_HPath.html");};
     Nothing
     >>> parseFn ".."         :: Maybe (Path Fn)
     Nothing
    -

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

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

    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"
    @@ -57,7 +57,7 @@ window.onload = function () {pageLoad();setSynopsis("mini_HPath.html");};
     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 +

    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)
    @@ -76,7 +76,7 @@ window.onload = function () {pageLoad();setSynopsis("mini_HPath.html");};
     "/abc/def"
     >>> dirname (MkPath "/")
     "/"
    -

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

    Is p a parent of the given location? Implemented in terms of +

    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")
    @@ -102,4 +102,4 @@ window.onload = function () {pageLoad();setSynopsis("mini_HPath.html");};
     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 +

    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 index 8e91a88..073674d 100644 --- a/System-Posix-Directory-Foreign.html +++ b/System-Posix-Directory-Foreign.html @@ -1,9 +1,9 @@ System.Posix.Directory.Foreign

    hpath-0.7.3: Support for well-typed paths

    Safe HaskellSafe
    LanguageHaskell2010

    System.Posix.Directory.Foreign

    Synopsis

    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 +

    hpath-0.7.3: Support for well-typed paths

    Safe HaskellSafe
    LanguageHaskell2010

    System.Posix.Directory.Foreign

    Documentation

    newtype DirType Source #

    Constructors

    DirType Int 

    data Flags Source #

    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 #

    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 + throw an exception.)

    \ No newline at end of file diff --git a/System-Posix-Directory-Traversals.html b/System-Posix-Directory-Traversals.html index 66e1687..5a56805 100644 --- a/System-Posix-Directory-Traversals.html +++ b/System-Posix-Directory-Traversals.html @@ -1,11 +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 +

    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.

    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 + 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 + 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.

    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 index 409e78b..a888138 100644 --- a/System-Posix-FD.html +++ b/System-Posix-FD.html @@ -1,9 +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 +

    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 + low-level open(2) call, in contrast to the unix package.

    Synopsis

    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 index c2d7047..a16037e 100644 --- a/System-Posix-FilePath.html +++ b/System-Posix-FilePath.html @@ -1,7 +1,7 @@ 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. +

    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"]
    @@ -9,45 +9,45 @@ window.onload = function () {pageLoad();setSynopsis("mini_System-Posix-FilePath.
     ["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"
    +

    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"
    +
    \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"
    +

    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"
    +

    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"
    +

    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"
    +

    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 -> 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"
    +

    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, +

    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"
    @@ -60,27 +60,27 @@ window.onload = function () {pageLoad();setSynopsis("mini_System-Posix-FilePath.
     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 -> 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"
    +
    \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"
    +

    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"
    +

    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"
    +

    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 -> 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"
     "."
    @@ -88,33 +88,33 @@ window.onload = function () {pageLoad();setSynopsis("mini_System-Posix-FilePath.
     "/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"
    +

    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"
    +

    (</>) :: 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 -> 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"
    +

    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/"
    +

    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"
    +

    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/"
    +

    dropTrailingPathSeparator :: RawFilePath -> RawFilePath Source #

    Remove a trailing path separator

    >>> dropTrailingPathSeparator "/path/"
     "/path"
     >>> dropTrailingPathSeparator "/path////"
     "/path"
    @@ -122,7 +122,7 @@ window.onload = function () {pageLoad();setSynopsis("mini_System-Posix-FilePath.
     "/"
     >>> dropTrailingPathSeparator "//"
     "/"
    -

    File name manipulations

    normalise :: RawFilePath -> RawFilePath Source #

    Normalise a file.

    >>> normalise "/file/\\test////"
    +

    File name manipulations

    normalise :: RawFilePath -> RawFilePath Source #

    Normalise a file.

    >>> normalise "/file/\\test////"
     "/file/\\test/"
     >>> normalise "/file/./test"
     "/file/test"
    @@ -148,7 +148,7 @@ window.onload = function () {pageLoad();setSynopsis("mini_System-Posix-FilePath.
     "bob/fred/"
     >>> normalise "//home"
     "/home"
    -

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

    Contract a filename, based on a relative path. Note that the resulting +

    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 @@ -166,7 +166,7 @@ window.onload = function () {pageLoad();setSynopsis("mini_System-Posix-FilePath. "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 +

    \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/"
    @@ -181,23 +181,23 @@ window.onload = function () {pageLoad();setSynopsis("mini_System-Posix-FilePath.
     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"
    +
    \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 ""
    +

    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 :: 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 +

    \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 "."
    @@ -210,7 +210,7 @@ window.onload = function () {pageLoad();setSynopsis("mini_System-Posix-FilePath.
     False
     >>> isFileName "/random_ path:*"
     False
    -

    hasParentDir :: RawFilePath -> Bool Source #

    Check if the filepath has any parent directories in it.

    >>> hasParentDir "/.."
    +

    hasParentDir :: RawFilePath -> Bool Source #

    Check if the filepath has any parent directories in it.

    >>> hasParentDir "/.."
     True
     >>> hasParentDir "foo/bar/.."
     True
    @@ -224,7 +224,7 @@ window.onload = function () {pageLoad();setSynopsis("mini_System-Posix-FilePath.
     False
     >>> hasParentDir ".."
     False
    -

    hiddenFile :: RawFilePath -> Bool Source #

    Whether the file is a hidden file.

    >>> hiddenFile ".foo"
    +

    hiddenFile :: RawFilePath -> Bool Source #

    Whether the file is a hidden file.

    >>> hiddenFile ".foo"
     True
     >>> hiddenFile "..foo.bar"
     True
    @@ -240,4 +240,4 @@ window.onload = function () {pageLoad();setSynopsis("mini_System-Posix-FilePath.
     False
     >>> hiddenFile ""
     False
    -
    \ No newline at end of file +
    \ No newline at end of file diff --git a/hpath.haddock b/hpath.haddock index 34fb6f2..7cdf30e 100644 Binary files a/hpath.haddock and b/hpath.haddock differ