Safe Haskell | None |
---|---|
Language | Haskell2010 |
Re-export all symbols and instances of the process-extras package. Adds the Chunk type with a ProcessOutput instance, and a collectOutput function to turn a list of chunks into any instance of ProcessOutput, such as (ExitCode, String, String). This means you can have readCreateProcess output a list of Chunk, operate on it to do progress reporting, and finally convert it to the type that readProcessWithExitCode woud have returned.
- class ListLikeIO text char => ListLikeProcessIO text char where
- class (IsString text, Monoid text, ListLike text char) => ProcessText text char
- class Monoid result => ProcessResult text result | result -> text where
- class ProcessMaker a where
- readCreateProcess :: (ProcessMaker maker, ProcessResult text result, ListLikeProcessIO text char) => maker -> text -> IO result
- readCreateProcessStrict :: (ProcessMaker maker, ProcessResult text result, ListLikeProcessIO text char) => maker -> text -> IO result
- readCreateProcessLazy :: (ProcessMaker maker, ProcessResult a b, ListLikeProcessIO a c) => maker -> a -> IO b
- readCreateProcessWithExitCode :: (ProcessMaker maker, ListLikeProcessIO text char) => maker -> text -> IO (ExitCode, text, text)
- readProcessWithExitCode :: ListLikeProcessIO text char => FilePath -> [String] -> text -> IO (ExitCode, text, text)
- showCreateProcessForUser :: CreateProcess -> String
- showCmdSpecForUser :: CmdSpec -> String
- data Chunk a
- collectOutput :: ProcessResult a b => [Chunk a] -> b
- foldOutput :: (ProcessHandle -> r) -> (a -> r) -> (a -> r) -> (SomeException -> r) -> (ExitCode -> r) -> Chunk a -> r
- writeOutput :: ListLikeIO a c => [Chunk a] -> IO [Chunk a]
- writeChunk :: ListLikeIO a c => Chunk a -> IO (Chunk a)
- data CmdSpec :: *
- data CreateProcess :: * = CreateProcess {
- cmdspec :: CmdSpec
- cwd :: Maybe FilePath
- env :: Maybe [(String, String)]
- std_in :: StdStream
- std_out :: StdStream
- std_err :: StdStream
- close_fds :: Bool
- create_group :: Bool
- delegate_ctlc :: Bool
- detach_console :: Bool
- create_new_console :: Bool
- new_session :: Bool
- child_group :: Maybe GroupID
- child_user :: Maybe UserID
- use_process_jobs :: Bool
- proc :: FilePath -> [String] -> CreateProcess
- shell :: String -> CreateProcess
- showCommandForUser :: FilePath -> [String] -> String
Classes for process IO monad, output type, and creation type
class ListLikeIO text char => ListLikeProcessIO text char where Source #
Process IO is based on the ListLikeIO
class from the ListLike
package
forceOutput :: text -> IO text Source #
class Monoid result => ProcessResult text result | result -> text where Source #
pidf :: ProcessHandle -> result Source #
outf :: text -> result Source #
errf :: text -> result Source #
intf :: SomeException -> result Source #
ListLikeProcessIO a c => ProcessResult a [Chunk a] Source # | |
ListLikeProcessIO a c => ProcessResult a (ExitCode, [Chunk a]) Source # | |
ListLikeProcessIO text char => ProcessResult text (ExitCode, text, text) Source # | |
class ProcessMaker a where Source #
process :: a -> IO (Handle, Handle, Handle, ProcessHandle) Source #
showProcessMakerForUser :: a -> String Source #
ProcessMaker CreateProcess Source # | This is the usual maker argument to |
ProcessMaker (CreateProcess, BufferMode, BufferMode) Source # | Passing this to |
The generalized process runners
readCreateProcess :: (ProcessMaker maker, ProcessResult text result, ListLikeProcessIO text char) => maker -> text -> IO result Source #
readCreateProcessStrict :: (ProcessMaker maker, ProcessResult text result, ListLikeProcessIO text char) => maker -> text -> IO result Source #
readCreateProcessLazy :: (ProcessMaker maker, ProcessResult a b, ListLikeProcessIO a c) => maker -> a -> IO b Source #
Like readCreateProcessStrict, but the output is read lazily.
readCreateProcessWithExitCode Source #
:: (ProcessMaker maker, ListLikeProcessIO text char) | |
=> maker | command and arguments to run |
-> text | standard input |
-> IO (ExitCode, text, text) | exitcode, stdout, stderr |
readProcessWithExitCode Source #
:: ListLikeProcessIO text char | |
=> FilePath | command to run |
-> [String] | any arguments |
-> text | standard input |
-> IO (ExitCode, text, text) | exitcode, stdout, stderr |
Like readProcessWithExitCode
, but with
generalized input and output type. Aside from the usual text-like
types, the output can be a list of Chunk a. This lets you process
the chunks received from stdout and stderr lazil, in the order they
are received, as well as the exit code. Utilities to handle Chunks
are provided in System.Process.ListLike.
Utility functions based on showCommandForUser
showCreateProcessForUser :: CreateProcess -> String Source #
System.Process utility functions.
showCmdSpecForUser :: CmdSpec -> String Source #
The Chunk type
This type is a concrete representation of the methods of class ProcessOutput. If you take your process output as this type you could, for example, echo all the output and then use collectOutput below to convert it to any other instance of ProcessOutput.
ProcessHandle ProcessHandle | This will always come first, before any output or exit code. |
Stdout a | |
Stderr a | |
Result ExitCode | |
Exception SomeException | Note that the instances below do not use this constructor. |
ListLikeProcessIO a c => ProcessResult a [Chunk a] Source # | |
ListLikeProcessIO a c => ProcessResult a (ExitCode, [Chunk a]) Source # | |
Show a => Show (Chunk a) Source # | |
collectOutput :: ProcessResult a b => [Chunk a] -> b Source #
Turn a [Chunk a]
into any other instance of ProcessOutput
. I
usually use this after processing the chunk list to turn it into
the (ExitCode, String, String) type returned by readProcessWithExitCode.
:: (ProcessHandle -> r) | called when the process handle becomes known |
-> (a -> r) | stdout handler |
-> (a -> r) | stderr handler |
-> (SomeException -> r) | exception handler |
-> (ExitCode -> r) | exit code handler |
-> Chunk a | |
-> r |
writeOutput :: ListLikeIO a c => [Chunk a] -> IO [Chunk a] Source #
Send Stdout chunks to stdout and Stderr chunks to stderr. Returns input list unmodified.
writeChunk :: ListLikeIO a c => Chunk a -> IO (Chunk a) Source #
Re-exports from process
ShellCommand String | A command line to execute using the shell |
RawCommand FilePath [String] | The name of an executable with a list of arguments The
|
data CreateProcess :: * #
CreateProcess | |
|
Eq CreateProcess | |
Show CreateProcess | |
ProcessMaker CreateProcess Source # | This is the usual maker argument to |
ProcessMaker (CreateProcess, BufferMode, BufferMode) Source # | Passing this to |
proc :: FilePath -> [String] -> CreateProcess #
Construct a CreateProcess
record for passing to createProcess
,
representing a raw command with arguments.
See RawCommand
for precise semantics of the specified FilePath
.
shell :: String -> CreateProcess #
Construct a CreateProcess
record for passing to createProcess
,
representing a command to be passed to the shell.
showCommandForUser :: FilePath -> [String] -> String #
Given a program p
and arguments args
,
showCommandForUser p args
returns a string suitable for pasting
into /bin/sh
(on Unix systems) or CMD.EXE
(on Windows).
Orphan instances
Show ProcessHandle Source # | |
ListLikeProcessIO String Char Source # | Like |
ProcessText String Char Source # | |