pipes-cliff-0.12.0.0: Streaming to and from subprocesses using Pipes

Safe HaskellSafe
LanguageHaskell2010

Pipes.Cliff.Core

Contents

Description

This contains the innards of Cliff. You shouldn't need anything that's in this module; instead, use Pipes.Cliff.

Exit code and waiting for processes: as of base 4.7, there was a bug in waitForProcess which may arise if you have multiple threads waiting for a single process to finish. Thus this module is set up so that only one thread does the wait, and it places the result in an MVar. See

http://ghc.haskell.org/trac/ghc/ticket/9292

Synopsis

Data types

Errors

data Activity Source #

When dealing with a Handle, errors can occur when reading from, writing to, or closing the handle.

Constructors

Reading 
Writing 
Closing 

data HandleDesc Source #

Describes a handle. From the perspective of the subprocess; for example, Input means that this handle is connected to the process's standard input.

Constructors

Input 
Outbound Outbound 

data Oopsie Source #

Describes all IO exceptions. The Oopsie contains the IOException itself, along with the CmdSpec that was running when the exception occurred.

The exceptions that are caught and placed into an Oopsie may arise from reading data from or writing data to a Handle. In these errors, the associated Producer or Consumer will terminate (which may trigger various cleanup actions in the MonadSafe computation) but the exception itself is not re-thrown; rather, it is passed to the handler. Similarly, an exception may occur while closing a handle; these exceptions are caught, not rethrown, and are passed to the handler. If an exception arises when terminating a process (I'm not sure this is possible) then it is also caught, not rethrown, and passed to the handler.

If an exception arises when creating a process--such as a command not being found--the exception is not caught, handled, or passed to the handler. In addition, no exceptions are caught if they originated during a waitForProcess. (I can't conceive of how any synchronous exceptions could arise from waitForProcess, but if they do, Cliff does not handle them.) Also, an Oopsie is created only for an IOException; no other exceptions of any kind are caught or handled. However, exceptions of any kind will still trigger appropriate cleanup actions in the MonadSafe computation.

Instances

renderOopsie Source #

Arguments

:: String

The name of the currently runnning program

-> Oopsie 
-> String 

Formats an Oopsie for display.

defaultHandler :: Oopsie -> IO () Source #

The default handler when receiving an Oopsie; simply uses renderOopsie to format it nicely and put it on standard error.

Side effects: gets the program name from the environment, and prints the Oopsie to standard error.

Configuration types

data NonPipe Source #

How will the subprocess get its information for this stream? A NonPipe is used for streams that will not be assigned to a Proxy but, instead, will be inherited from the parent or directed from an existing Handle.

Constructors

Inherit

Use whatever stream that the parent process has.

UseHandle Handle

Use the given handle for input or output

data CreateProcess Source #

Like CreateProcess in System.Process, this gives the necessary information to create a subprocess. All but one of these fields is also present in CreateProcess, and they all have the same meaning; the only field that is different is the handler field.

Constructors

CreateProcess 

Fields

  • cmdspec :: CmdSpec

    Executable and arguments, or shell command

  • cwd :: Maybe FilePath

    A new current working directory for the subprocess; if Nothing, use the calling process's working directory.

  • env :: Maybe [(String, String)]

    The environment for the subprocess; if Nothing, use the calling process's working directory.

  • close_fds :: Bool

    If True, close all file descriptors other than the standard descriptors. See the documentation for close_fds for details on how this works in Windows.

  • create_group :: Bool

    If True, create a new process group.

  • delegate_ctlc :: Bool

    See delegate_ctlc in the System.Process module for details.

  • detach_console :: Bool

    Use the windows DETACHED_PROCESS flag when creating the process; does nothing on other platforms.

  • create_new_console :: Bool

    Use the windows CREATE_NEW_CONSOLE flag when creating the process; does nothing on other platforms.

  • new_session :: Bool

    Use posix setsid to start the new process in a new session; does nothing on other platforms.

  • child_group :: Maybe GroupID

    Use posix setgid to set child process's group id; does nothing on other platforms.

  • child_user :: Maybe UserID

    Use posix setuid to set child process's user id; does nothing on other platforms.

  • handler :: Oopsie -> IO ()

    Whenever an IO exception arises during the course of various IO actions, the exception is caught and placed into an Oopsie that indicates why and where the exception happened. The handler determines what happens when an Oopsie comes in. See Oopsie for details.

    The default handler created by procSpec is defaultHandler, which will simply print the exceptions to standard error. You may not want to see the exceptions at all. For example, many exceptions come from broken pipes. A broken pipe might be entirely normal in your circumstance. For example, if you are streaming a large set of values to a pager such as less and you expect that the user will often quit the pager without viewing the whole result, a broken pipe will result, which will print a warning message. That can be a nuisance.

    If you don't want to see the exceptions at all, just set handler to squelch, which simply discards the exceptions.

    Conceivably you could rig up an elaborate mechanism that puts the Oopsies into a Pipes.Concurrent mailbox or something. Indeed, when using defaultHandler each thread will print its warnings to standard error at any time. If you are using multiple processes and each prints warnings at the same time, total gibberish can result as the text gets mixed in. You could solve this by putting the errors into a Pipes.Concurrent mailbox and having a single thread print the errors; this sort of thing could be built into the library but so far I haven't been motivated to do it.

squelch :: Monad m => a -> m () Source #

Do not show or do anything with exceptions; useful to use as a handler.

Side effects: None.

procSpec Source #

Arguments

:: String

The name of the program to run, such as less.

-> [String]

Command-line arguments

-> CreateProcess 

Create a CreateProcess record with default settings. The default settings are:

MVar types

Lock

type Lock = MVar () Source #

Guarantees single-thread access

All MVar idioms thanks to Neil Mitchell: http://neilmitchell.blogspot.com/2012/06/flavours-of-mvar_04.html

withLock :: Lock -> IO a -> IO a Source #

Var

type Var a = MVar a Source #

Operates on mutable variables in thread-safe way.

newVar :: a -> IO (Var a) Source #

modifyVar :: Var a -> (a -> IO (a, b)) -> IO b Source #

modifyVar_ :: Var a -> (a -> IO a) -> IO () Source #

readVar :: Var a -> IO a Source #

Barrier

type Barrier a = MVar a Source #

Starts with no value, is written to once, and is read one or more times.

signalBarrier :: Barrier a -> a -> IO () Source #

MVar abstractions

once :: IO a -> IO (IO a) Source #

Takes an action and returns a new action. If the action is never called the argument action will never be executed, but if it is called more than once, it will only be executed once.

Side effects: creates a Var. Returns an IO action that modifies the contents of that Var.

Mailboxes

messageBox :: IO (a -> STM Bool, STM (Maybe a), STM ()) Source #

Creates a new mailbox. Returns an action to send to the mailbox; this action will return False if the mailbox is sealed, or True if the message was successfully placed in the mailbox. Also returns an action to retrieve from the mailbox, which returns Nothing if the mailbox is sealed, or Just if there is a value to be retrieved. Also returns an action to seal the mailbox.

sendBox :: TVar Bool -> TMVar a -> a -> STM Bool Source #

sendToBox :: MonadIO m => (a -> STM Bool) -> Consumer a m () Source #

Console

data Console Source #

Data that is computed once, after the process has been created. After computation, this data does not change.

Constructors

Console 

Fields

isStillRunning :: ProcessHandle -> IO Bool Source #

Is this process still running?

Side effects: examines the process handle to see if it has yet returned a value. Does not block; should return immediately.

data ProcessHandle Source #

Allows you to terminate the process, as well as to obtain some information about the process.

originalCreateProcess :: ProcessHandle -> CreateProcess Source #

Tells you the CreateProcess that was originally used to create the process associated with this ProcessHandle.

addReleaser :: ProcessHandle -> IO () -> IO () Source #

Add a finalizer to the ProcessHandle. When the finalizers are run, all exceptions are ignored, except asynchronous exceptions, which are masked.

terminateProcess :: ProcessHandle -> IO () Source #

Terminates a process. Sends the process a SIGTERM, which does not absolutely guarantee that it will exit. Closes any Handles that were created for the process through Cliff, and terminates any associated background threads that were moving data to and from the process. Use this function this with bracket to ensure proper cleanup of resources.

waitForProcess :: ProcessHandle -> IO ExitCode Source #

Gets the exit code of the process that belongs to the ProcessHandle. Often you can get the exit code through more idiomatic pipes functions, as the various Proxy return the ExitCode. Sometimes though it can be difficult to use the pipes idioms to get the exit code, so this function is here.

Side effects: may block if process has not yet exited.

newProcessHandle :: Maybe NonPipe -> Maybe NonPipe -> Maybe NonPipe -> CreateProcess -> IO ProcessHandle Source #

Creates a new ProcessHandle.

Side effects: Does not create the process right away; instead, creates an IO action that, when run, will create the process. This IO action contains another IO action that, when run, will return the process exit code.

In addition, the IO action will fork a simple thread that will immediately wait for the process. In effect, this means there is immediately a thread that will wait for the process to exit. Because this IO action was created with once, that means only one thread ever does the wait, which avoids a bug in System.Process.

Exception handling

handleException :: Activity -> HandleDesc -> CmdSpec -> (Oopsie -> IO ()) -> IOException -> IO () Source #

Sends an exception using the exception handler specified in the ErrSpec. Side effects: transmits the Oopsie to the right place; the recipient of the Oopsie might have additional side effects.

closeHandleNoThrow :: Handle -> HandleDesc -> CmdSpec -> (Oopsie -> IO ()) -> IO () Source #

Close a handle. Catches any exceptions and passes them to the handler.

Threads

conveyor :: Effect (SafeT IO) a -> IO (Async a) Source #

Runs in the background an effect, typically one that is moving data from one process to another. For examples of its usage, see Pipes.Cliff.Examples.

Effects

safeEffect :: Effect (SafeT IO) a -> IO a Source #

Runs in the foreground an effect in the SafeT monad.

Mailboxes

newMailbox :: (MonadSafe mi, MonadSafe mo) => IO (Consumer a mi (), Producer a mo (), STM ()) Source #

Creates a new mailbox and returns Proxy that stream values into and out of the mailbox. Each Proxy is equipped with a finalizer that will seal the mailbox immediately after production or consumption has completed, even if such completion is not due to an exhausted mailbox. This will signal to the other side of the mailbox that the mailbox is sealed.

Also returns an STM action to seal the box manually.

Exception safety

withProcess Source #

Arguments

:: IO (a, ProcessHandle)

Creates the process

-> (a -> IO b)

Uses the process

-> IO b 

Creates a process, uses it, and terminates it when the last computation ends. Don't try to use any of the process resources after the last computation ends, because the process will already have been terminated. For an example of its use, see standardOutputAndErrorBracketed.

withConveyor Source #

Arguments

:: Effect (SafeT IO) a

The Effect to run in another thread

-> IO b

The rest of the computation to run

-> IO b 

Runs an Effect in the backgroud (typically one that is moving data from one process to another). If the background thread is still running when the second computation ends, the background thread is terminated. For an example of its use, see standardOutputAndErrorBracketed.

Production from and consumption to Handles

bufSize :: Int Source #

I have no idea what this should be. I'll start with a simple small value and see how it works.

initHandle Source #

Arguments

:: MonadSafe mi 
=> HandleDesc

Used for error messages

-> (Console -> Handle)

Fetch the handle to close from the ProcessHandle.

-> ProcessHandle

Has the Handle that will be closed.

-> (Handle -> mi a)

The remainder of the computation.

-> mi a 

Initialize a handle. Returns a computation in the MonadSafe monad. That computation has a registered finalizer that will close a particular handle that is found in the ProcessHandle. As a side effect, the IO action creating the ProcessHandle is viewed, meaning that the process will launch if it hasn't already done so.

produceFromHandle :: (MonadSafe mi, MonadCatch (Base mi)) => Outbound -> ProcessHandle -> Producer ByteString mi () Source #

Produce values from a process standard output. Process is started if it isn't already.

finishProxy :: Async () -> ProcessHandle -> IO ExitCode Source #

Given an Async, waits for that thread to finish processing values. When it completes, wait for the process exit code.

runInputHandle Source #

Arguments

:: MonadSafe mi 
=> ProcessHandle 
-> Consumer ByteString mi ExitCode 

Takes all steps necessary to get a Consumer for standard input:

  • Creates a Consumer that will consume to the process standard input. This Consumer registers a MonadSafe releaser that will close the handle.
  • Creates a mailbox, with a Producer from the mailbox and a Consumer to the mailbox. Each of these Proxy has a MonadSafe releaser that will close the mailbox.
  • Spwans a thread to run an Effect that connects the Consumer that is connected to the handle to the Producer from the mailbox. In a typical UNIX pipeline situation (where the process keeps its stdin open as long as it is getting input) this Effect will stop running only when the mailbox is sealed.
  • Registers a releaser in the Panel (not in the MonadSafe computation) to destroy the thread; this is in case the user terminates the process.
  • Returns a Consumer. The Consumer consumes to the mailbox. This Consumer returns the exit code of this process (but remember that the ultimate result of the Proxy depends on which component terminates first).

Does not register in the MonadSafe an action to cancel the background thread. Data might still be moving to the process even if the Proxy has shut down. Let the thread terminate through mailbox closure or a broken pipe.

runOutputHandle Source #

Takes all steps necessary to get a Producer for standard input. Sets up a mailbox, runs a conveyor in the background. Then receives streaming data, and then gets the process exit code.

Creating Proxy

pipeInput Source #

Arguments

:: MonadSafe mi 
=> NonPipe

Standard output

-> NonPipe

Standard error

-> CreateProcess 
-> IO (Consumer ByteString mi ExitCode, ProcessHandle)

A Consumer for standard input

Create a Consumer for standard input.

pipeOutput Source #

Arguments

:: MonadSafe mo 
=> NonPipe

Standard input

-> NonPipe

Standard error

-> CreateProcess 
-> IO (Producer ByteString mo ExitCode, ProcessHandle)

A Producer for standard output

Create a Producer for standard output.

pipeError Source #

Arguments

:: MonadSafe me 
=> NonPipe

Standard input

-> NonPipe

Standard output

-> CreateProcess 
-> IO (Producer ByteString me ExitCode, ProcessHandle)

A Producer for standard error

Create a Producer for standard error.

pipeInputOutput Source #

Arguments

:: (MonadSafe mi, MonadSafe mo) 
=> NonPipe

Standard error

-> CreateProcess 
-> IO ((Consumer ByteString mi ExitCode, Producer ByteString mo ExitCode), ProcessHandle)

A Consumer for standard input, a Producer for standard output

Create a Consumer for standard input and a Producer for standard output.

pipeInputError Source #

Arguments

:: (MonadSafe mi, MonadSafe me) 
=> NonPipe

Standard output

-> CreateProcess 
-> IO ((Consumer ByteString mi ExitCode, Producer ByteString me ExitCode), ProcessHandle)

A Consumer for standard input, a Producer for standard error

Create a Consumer for standard input and a Producer for standard error.

pipeOutputError Source #

Arguments

:: (MonadSafe mo, MonadSafe me) 
=> NonPipe

Standard input

-> CreateProcess 
-> IO ((Producer ByteString mo ExitCode, Producer ByteString me ExitCode), ProcessHandle)

A Producer for standard output and a Producer for standard error

Create a Producer for standard output and a Producer for standard error.

pipeInputOutputError Source #

Arguments

:: (MonadSafe mi, MonadSafe mo, MonadSafe me) 
=> CreateProcess 
-> IO ((Consumer ByteString mi ExitCode, Producer ByteString mo ExitCode, Producer ByteString me ExitCode), ProcessHandle)

A Consumer for standard input, a Producer for standard output, and a Producer for standard error

Create a Consumer for standard input, a Producer for standard output, and a Producer for standard error.