Copyright | 2015 Joey Hess <id@joeyh.name> |
---|---|
License | BSD-2-clause |
Safe Haskell | None |
Language | Haskell98 |
Concurrent output handling, internals.
May change at any time.
- data OutputHandle = OutputHandle {
- outputLock :: TMVar Lock
- outputBuffer :: TMVar OutputBuffer
- errorBuffer :: TMVar OutputBuffer
- outputThreads :: TMVar Integer
- processWaiters :: TMVar [Async ()]
- waitForProcessLock :: TMVar ()
- data Lock = Locked
- globalOutputHandle :: OutputHandle
- lockOutput :: (MonadIO m, MonadMask m) => m a -> m a
- takeOutputLock :: IO ()
- tryTakeOutputLock :: IO Bool
- withLock :: (TMVar Lock -> STM a) -> IO a
- takeOutputLock' :: Bool -> IO Bool
- dropOutputLock :: IO ()
- withConcurrentOutput :: (MonadIO m, MonadMask m) => m a -> m a
- flushConcurrentOutput :: IO ()
- class Outputable v where
- outputConcurrent :: Outputable v => v -> IO ()
- errorConcurrent :: Outputable v => v -> IO ()
- outputConcurrent' :: Outputable v => StdHandle -> v -> IO ()
- newtype ConcurrentProcessHandle = ConcurrentProcessHandle ProcessHandle
- toConcurrentProcessHandle :: (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> (Maybe Handle, Maybe Handle, Maybe Handle, ConcurrentProcessHandle)
- waitForProcessConcurrent :: ConcurrentProcessHandle -> IO ExitCode
- asyncProcessWaiter :: IO () -> IO ()
- createProcessConcurrent :: CreateProcess -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ConcurrentProcessHandle)
- createProcessForeground :: CreateProcess -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ConcurrentProcessHandle)
- fgProcess :: CreateProcess -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ConcurrentProcessHandle)
- bgProcess :: CreateProcess -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ConcurrentProcessHandle)
- willOutput :: StdStream -> Bool
- data OutputBuffer = OutputBuffer [OutputBufferedActivity]
- data StdHandle
- toHandle :: StdHandle -> Handle
- bufferFor :: StdHandle -> TMVar OutputBuffer
- data OutputBufferedActivity
- = Output Text
- | InTempFile { }
- data AtEnd = AtEnd
- data BufSig = BufSig
- setupOutputBuffer :: StdHandle -> Handle -> StdStream -> Handle -> IO (StdHandle, MVar OutputBuffer, TMVar BufSig, TMVar AtEnd)
- outputDrainer :: StdStream -> Handle -> MVar OutputBuffer -> TMVar BufSig -> TMVar AtEnd -> IO ()
- registerOutputThread :: IO ()
- unregisterOutputThread :: IO ()
- bufferWriter :: [(StdHandle, MVar OutputBuffer, TMVar BufSig, TMVar AtEnd)] -> IO ()
- addOutputBuffer :: OutputBufferedActivity -> OutputBuffer -> IO OutputBuffer
- bufferOutputSTM :: Outputable v => StdHandle -> v -> STM ()
- bufferOutputSTM' :: StdHandle -> OutputBuffer -> STM ()
- outputBufferWaiterSTM :: (OutputBuffer -> (OutputBuffer, OutputBuffer)) -> STM (StdHandle, OutputBuffer)
- waitAnyBuffer :: OutputBuffer -> (OutputBuffer, OutputBuffer)
- waitCompleteLines :: OutputBuffer -> (OutputBuffer, OutputBuffer)
- endsNewLine :: Text -> Bool
- emitOutputBuffer :: StdHandle -> OutputBuffer -> IO ()
Documentation
data OutputHandle Source
OutputHandle | |
|
globalOutputHandle :: OutputHandle Source
A shared global variable for the OutputHandle.
lockOutput :: (MonadIO m, MonadMask m) => m a -> m a Source
Holds a lock while performing an action. This allows the action to perform its own output to the console, without using functions from this module.
While this is running, other threads that try to lockOutput will block.
Any calls to outputConcurrent
and createProcessConcurrent
will not
block, but the output will be buffered and displayed only once the
action is done.
takeOutputLock :: IO () Source
Blocks until we have the output lock.
tryTakeOutputLock :: IO Bool Source
Tries to take the output lock, without blocking.
takeOutputLock' :: Bool -> IO Bool Source
dropOutputLock :: IO () Source
Only safe to call after taking the output lock.
withConcurrentOutput :: (MonadIO m, MonadMask m) => m a -> m a Source
Use this around any actions that use outputConcurrent
or createProcessConcurrent
This is necessary to ensure that buffered concurrent output actually gets displayed before the program exits.
flushConcurrentOutput :: IO () Source
Blocks until any processes started by createProcessConcurrent
have
finished, and any buffered output is displayed. Also blocks while
lockOutput
is is use.
withConcurrentOutput
calls this at the end, so you do not normally
need to use this.
class Outputable v where Source
Values that can be output.
outputConcurrent :: Outputable v => v -> IO () Source
Displays a value to stdout.
No newline is appended to the value, so if you want a newline, be sure to include it yourself.
Uses locking to ensure that the whole output occurs atomically even when other threads are concurrently generating output.
When something else is writing to the console at the same time, this does not block. It buffers the value, so it will be displayed once the other writer is done.
errorConcurrent :: Outputable v => v -> IO () Source
Like outputConcurrent
, but displays to stderr.
(Does not throw an exception.)
outputConcurrent' :: Outputable v => StdHandle -> v -> IO () Source
toConcurrentProcessHandle :: (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> (Maybe Handle, Maybe Handle, Maybe Handle, ConcurrentProcessHandle) Source
waitForProcessConcurrent :: ConcurrentProcessHandle -> IO ExitCode Source
Use this to wait for processes started with
createProcessConcurrent
and createProcessForeground
, and get their
exit status.
Note that such processes are actually automatically waited for
internally, so not calling this explicitly will not result
in zombie processes. This behavior differs from waitForProcess
asyncProcessWaiter :: IO () -> IO () Source
createProcessConcurrent :: CreateProcess -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ConcurrentProcessHandle) Source
Wrapper around createProcess
that prevents
multiple processes that are running concurrently from writing
to stdout/stderr at the same time.
If the process does not output to stdout or stderr, it's run by createProcess entirely as usual. Only processes that can generate output are handled specially:
A process is allowed to write to stdout and stderr in the usual way, assuming it can successfully take the output lock.
When the output lock is held (ie, by another concurrent process,
or because outputConcurrent
is being called at the same time),
the process is instead run with its stdout and stderr
redirected to a buffer. The buffered output will be displayed as soon
as the output lock becomes free.
Currently only available on Unix systems, not Windows.
createProcessForeground :: CreateProcess -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ConcurrentProcessHandle) Source
Wrapper around createProcess
that makes sure a process
is run in the foreground, with direct access to stdout and stderr.
Useful when eg, running an interactive process.
fgProcess :: CreateProcess -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ConcurrentProcessHandle) Source
bgProcess :: CreateProcess -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ConcurrentProcessHandle) Source
willOutput :: StdStream -> Bool Source
data OutputBuffer Source
Buffered output.
setupOutputBuffer :: StdHandle -> Handle -> StdStream -> Handle -> IO (StdHandle, MVar OutputBuffer, TMVar BufSig, TMVar AtEnd) Source
outputDrainer :: StdStream -> Handle -> MVar OutputBuffer -> TMVar BufSig -> TMVar AtEnd -> IO () Source
registerOutputThread :: IO () Source
unregisterOutputThread :: IO () Source
bufferWriter :: [(StdHandle, MVar OutputBuffer, TMVar BufSig, TMVar AtEnd)] -> IO () Source
bufferOutputSTM :: Outputable v => StdHandle -> v -> STM () Source
Adds a value to the output buffer for later display.
Note that buffering large quantities of data this way will keep it
resident in memory until it can be displayed. While outputConcurrent
uses temp files if the buffer gets too big, this STM function cannot do
so.
bufferOutputSTM' :: StdHandle -> OutputBuffer -> STM () Source
outputBufferWaiterSTM :: (OutputBuffer -> (OutputBuffer, OutputBuffer)) -> STM (StdHandle, OutputBuffer) Source
A STM action that waits for some buffered output to become available, and returns it.
The function can select a subset of output when only some is desired; the fst part is returned and the snd is left in the buffer.
This will prevent it from being displayed in the usual way, so you'll
need to use emitOutputBuffer
to display it yourself.
waitCompleteLines :: OutputBuffer -> (OutputBuffer, OutputBuffer) Source
Use with outputBufferWaiterSTM
to make it only return buffered
output that ends with a newline. Anything buffered without a newline
is left in the buffer.
endsNewLine :: Text -> Bool Source
emitOutputBuffer :: StdHandle -> OutputBuffer -> IO () Source
Emits the content of the OutputBuffer to the Handle
If you use this, you should use lockOutput
to ensure you're the only
thread writing to the console.