Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- createProcess :: (MonadIO m, TriggerEvent t m, PerformEvent t m, MonadIO (Performable m)) => CreateProcess -> ProcessConfig t (SendPipe ByteString) -> m (Process t ByteString ByteString)
- createProcessBufferingInput :: (MonadIO m, TriggerEvent t m, PerformEvent t m, MonadIO (Performable m)) => IO (SendPipe ByteString) -> (SendPipe ByteString -> IO ()) -> CreateProcess -> ProcessConfig t (SendPipe ByteString) -> m (Process t ByteString ByteString)
- defProcessConfig :: Reflex t => ProcessConfig t i
- unsafeCreateProcessWithHandles :: forall t m i o e. (MonadIO m, TriggerEvent t m, PerformEvent t m, MonadIO (Performable m)) => (Handle -> IO (i -> IO ())) -> (Handle -> (o -> IO ()) -> IO (IO ())) -> (Handle -> (e -> IO ()) -> IO (IO ())) -> CreateProcess -> ProcessConfig t i -> m (Process t o e)
- data Process t o e = Process {
- _process_handle :: ProcessHandle
- _process_stdout :: Event t o
- _process_stderr :: Event t e
- _process_exit :: Event t ExitCode
- _process_signal :: Event t Signal
- data ProcessConfig t i = ProcessConfig {
- _processConfig_stdin :: Event t i
- _processConfig_signal :: Event t Signal
- data SendPipe i
- createRedirectedProcess :: forall t m i o e. (MonadIO m, TriggerEvent t m, PerformEvent t m, MonadIO (Performable m)) => (Handle -> IO (i -> IO ())) -> (Handle -> (o -> IO ()) -> IO (IO ())) -> (Handle -> (e -> IO ()) -> IO (IO ())) -> CreateProcess -> ProcessConfig t i -> m (Process t o e)
Documentation
:: (MonadIO m, TriggerEvent t m, PerformEvent t m, MonadIO (Performable m)) | |
=> CreateProcess | Specification of process to create |
-> ProcessConfig t (SendPipe ByteString) | Reflex-level configuration for the process |
-> m (Process t ByteString ByteString) |
Create a process feeding it input using an Event
and exposing its output
Event
s representing the process exit code, stdout, and stderr.
The stdout
and stderr
Handle
s are line-buffered.
N.B. The process input is buffered with an unbounded channel! For more control of this,
use createProcessBufferingInput
directly.
N.B.: The std_in
, std_out
, and std_err
parameters of the
provided CreateProcess
are replaced with new pipes and all output is redirected
to those pipes.
createProcessBufferingInput Source #
:: (MonadIO m, TriggerEvent t m, PerformEvent t m, MonadIO (Performable m)) | |
=> IO (SendPipe ByteString) | An action that reads a value from the input stream buffer. This must block when the buffer is empty or not ready. |
-> (SendPipe ByteString -> IO ()) | An action that writes a value to the input stream buffer. |
-> CreateProcess | Specification of process to create |
-> ProcessConfig t (SendPipe ByteString) | Reflex-level configuration for the process |
-> m (Process t ByteString ByteString) |
Create a process feeding it input using an Event
and exposing its output with Event
s
for its exit code, stdout
, and stderr
. The input is fed via a buffer represented by a
reading action and a writing action.
The stdout
and stderr
Handle
s are line-buffered.
For example, you may use Chan
for an unbounded buffer (like createProcess
does) like this:
> channel <- liftIO newChan
> createProcessBufferingInput (readChan channel) (writeChan channel) myConfig
Similarly you could use TChan
.
Bounded buffers may cause the Reflex network to block when you trigger an Event
that would
cause more data to be sent to a process whose stdin
is blocked.
If an unbounded channel would lead to too much memory usage you will want to consider
* speeding up the consuming process.
* buffering with the file system or another persistent storage to reduce memory usage.
* if your usa case allows, dropping Event
s or messages that aren't important.
N.B.: The std_in
, std_out
, and std_err
parameters of the
provided CreateProcess
are replaced with new pipes and all output is redirected
to those pipes.
defProcessConfig :: Reflex t => ProcessConfig t i Source #
A default ProcessConfig
where stdin
and signals are never sent.
You can also use def
.
unsafeCreateProcessWithHandles Source #
:: forall t m i o e. (MonadIO m, TriggerEvent t m, PerformEvent t m, MonadIO (Performable m)) | |
=> (Handle -> IO (i -> IO ())) | Builder for the standard input handler. The |
-> (Handle -> (o -> IO ()) -> IO (IO ())) | Builder for the standard output handler. The |
-> (Handle -> (e -> IO ()) -> IO (IO ())) | Builder for the standard error handler. The |
-> CreateProcess | Specification of process to create |
-> ProcessConfig t i | Reflex-level configuration for the process |
-> m (Process t o e) |
Runs a process and uses the given input and output handler functions to
interact with the process via the standard streams. Used to implement
createProcess
.
N.B.: The std_in
, std_out
, and std_err
parameters of the
provided CreateProcess
are replaced with new pipes and all output is redirected
to those pipes.
The output of a process
Process | |
|
data ProcessConfig t i Source #
The inputs to a process
ProcessConfig | |
|
Instances
Reflex t => Default (ProcessConfig t i) Source # | |
Defined in Reflex.Process def :: ProcessConfig t i # |
SendPipe_Message i | A message that's sent to the underlying process |
SendPipe_EOF | Send an EOF to the underlying process |
SendPipe_LastMessage i | Send the last message (an EOF will be added). This option is offered for convenience, because it has the same effect of sending a Message and then the EOF signal |
createRedirectedProcess :: forall t m i o e. (MonadIO m, TriggerEvent t m, PerformEvent t m, MonadIO (Performable m)) => (Handle -> IO (i -> IO ())) -> (Handle -> (o -> IO ()) -> IO (IO ())) -> (Handle -> (e -> IO ()) -> IO (IO ())) -> CreateProcess -> ProcessConfig t i -> m (Process t o e) Source #
Deprecated: Use unsafeCreateProcessWithHandles instead.