hackage-security-0.1.0.0: Hackage security library

Safe HaskellNone
LanguageHaskell2010

Hackage.Security.Util.Path

Contents

Description

A more type-safe version of file paths

This module is intended to replace imports of System.FilePath, and additionally exports thin wrappers around common IO functions. To facilitate importing this module unqualified we also re-export some definitions from System.IO (importing both would likely lead to name clashes).

Note that his module does not import any other modules from Hackage.Security; everywhere else we use Path instead of FilePath directly.

Synopsis

Path fragments

data Fragment Source

Path fragments

Path fragments must be non-empty and not contain any path delimiters.

Paths

data Path a Source

Paths

A path consists of an optional root and a list of fragments. Alternatively, think of it as a list with two kinds of nil-constructors.

Instances

Monad m => FromObjectKey m (Path (Rooted root)) 
Monad m => FromObjectKey m (Path Unrooted) 
Monad m => ToObjectKey m (Path (Rooted root)) 
Monad m => ToObjectKey m (Path Unrooted) 
Eq (Path a) 
Ord (Path a) 
Show (Path a) 
IsRoot root => Pretty (Path (Rooted root))

Turn a path into a human-readable string

data Unrooted Source

Unrooted paths

Unrooted paths need a root before they can be interpreted.

data Rooted a Source

Rooted paths

The a parameter is a phantom argument; Rooted is effectively a proxy.

Constructors

Rooted 

Instances

Monad m => FromObjectKey m (Path (Rooted root)) 
Monad m => ToObjectKey m (Path (Rooted root)) 
Show (Rooted a) 
Show (Rooted TarballRoot) 
IsRoot root => Pretty (Path (Rooted root))

Turn a path into a human-readable string

Construcion and destruction

fragment' :: String -> UnrootedPath Source

For convenience: combine fragment and mkFragment

This can therefore throw the same runtime errors as mkFragment.

rootPath :: forall root. Rooted root -> UnrootedPath -> Path (Rooted root) Source

castRoot :: Path (Rooted root) -> Path (Rooted root') Source

Reinterpret the root of a path

Unrooted paths

FilePath-like operations

(<.>) :: Path a -> String -> Path a Source

File-system paths

class IsRoot root => IsFileSystemRoot root Source

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

Minimal complete definition

interpretRoot

data FileSystemPath where Source

Abstract over a file system root

see fromFilePath

Constructors

FileSystemPath :: IsFileSystemRoot root => Path (Rooted root) -> FileSystemPath 

Conversions

Wrappers around System.IO

openTempFile :: forall root. IsFileSystemRoot root => Path (Rooted root) -> String -> IO (AbsolutePath, Handle) Source

Wrapper around openBinaryTempFileWithDefaultPermissions

withFileInReadMode :: IsFileSystemRoot root => Path (Rooted root) -> (Handle -> IO r) -> IO r Source

Open a file in read mode

We don't wrap the general withFile to encourage using atomic file ops.

Wrappers around Data.ByteString.*

Wrappers around System.Directory

getDirectoryContents :: IsFileSystemRoot root => Path (Rooted root) -> IO [UnrootedPath] Source

Return the immediate children of a directory

Filters out "." and "..".

getRecursiveContents :: IsFileSystemRoot root => Path (Rooted root) -> IO [UnrootedPath] Source

Recursive traverse a directory structure

Returns a set of paths relative to the directory specified. TODO: Not sure about the memory behaviour with large file systems.

renameFile Source

Arguments

:: (IsFileSystemRoot root, IsFileSystemRoot root1) 
=> Path (Rooted root)

Old

-> Path (Rooted root1)

New

-> IO () 

Wrappers around Codec.Archive.Tar.*

tarAppend Source

Arguments

:: (IsFileSystemRoot root, IsFileSystemRoot root') 
=> Path (Rooted root)

Path of the .tar file

-> Path (Rooted root')

Base directory

-> [TarballPath]

Files to add, relative to the base dir

-> IO () 

Paths in URIs

Re-exports

data BufferMode :: *

Three kinds of buffering are supported: line-buffering, block-buffering or no-buffering. These modes have the following effects. For output, items are written out, or flushed, from the internal buffer according to the buffer mode:

  • line-buffering: the entire output buffer is flushed whenever a newline is output, the buffer overflows, a hFlush is issued, or the handle is closed.
  • block-buffering: the entire buffer is written out whenever it overflows, a hFlush is issued, or the handle is closed.
  • no-buffering: output is written immediately, and never stored in the buffer.

An implementation is free to flush the buffer more frequently, but not less frequently, than specified above. The output buffer is emptied as soon as it has been written out.

Similarly, input occurs according to the buffer mode for the handle:

  • line-buffering: when the buffer for the handle is not empty, the next item is obtained from the buffer; otherwise, when the buffer is empty, characters up to and including the next newline character are read into the buffer. No characters are available until the newline character is available or the buffer is full.
  • block-buffering: when the buffer for the handle becomes empty, the next block of data is read into the buffer.
  • no-buffering: the next input item is read and returned. The hLookAhead operation implies that even a no-buffered handle may require a one-character buffer.

The default buffering mode when a handle is opened is implementation-dependent and may depend on the file system object which is attached to that handle. For most implementations, physical files will normally be block-buffered and terminals will normally be line-buffered.

Constructors

NoBuffering

buffering is disabled if possible.

LineBuffering

line-buffering should be enabled if possible.

BlockBuffering (Maybe Int)

block-buffering should be enabled if possible. The size of the buffer is n items if the argument is Just n and is otherwise implementation-dependent.

data Handle :: *

Haskell defines operations to read and write characters from and to files, represented by values of type Handle. Each value of this type is a handle: a record used by the Haskell run-time system to manage I/O with file system objects. A handle has at least the following properties:

  • whether it manages input or output or both;
  • whether it is open, closed or semi-closed;
  • whether the object is seekable;
  • whether buffering is disabled, or enabled on a line or block basis;
  • a buffer (whose length may be zero).

Most handles will also have a current I/O position indicating where the next input or output operation will occur. A handle is readable if it manages only input or both input and output; likewise, it is writable if it manages only output or both input and output. A handle is open when first allocated. Once it is closed it can no longer be used for either input or output, though an implementation cannot re-use its storage while references remain to it. Handles are in the Show and Eq classes. The string produced by showing a handle is system dependent; it should include enough information to identify the handle for debugging. A handle is equal according to == only to itself; no attempt is made to compare the internal state of different handles for equality.

hSetBuffering :: Handle -> BufferMode -> IO ()

Computation hSetBuffering hdl mode sets the mode of buffering for handle hdl on subsequent reads and writes.

If the buffer mode is changed from BlockBuffering or LineBuffering to NoBuffering, then

  • if hdl is writable, the buffer is flushed as for hFlush;
  • if hdl is not writable, the contents of the buffer is discarded.

This operation may fail with:

  • isPermissionError if the handle has already been used for reading or writing and the implementation does not allow the buffering mode to be changed.

hClose :: Handle -> IO ()

Computation hClose hdl makes handle hdl closed. Before the computation finishes, if hdl is writable its buffer is flushed as for hFlush. Performing hClose on a handle that has already been closed has no effect; doing so is not an error. All other operations on a closed handle will fail. If hClose fails for any reason, any further operations (apart from hClose) on the handle will still fail as if hdl had been successfully closed.

hFileSize :: Handle -> IO Integer

For a handle hdl which attached to a physical file, hFileSize hdl returns the size of that file in 8-bit bytes.