Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Create and run child processes and retrieve results from them.
For example:
>>>
StdoutTrimmed stdout <- run $ cmd "echo" & addArgs ["Hello, World!"]
>>>
print stdout
"Hello, World!"
Outputs
run
is polymorphic in its output, the output type just has to implement
Output
. So for example you can get the exit code of a process like this:
>>>
run $ cmd "false" :: IO ExitCode
ExitFailure 1
If you don't want to retrieve any information from a child process, you can
use run_
(or make the output type ()
).
For more information on available output types, see Output
.
Process Configuration
To modify the setup of the child process -- e.g. to add arguments or modify
stdin or stdout, etc. -- you can use one of the functions that modify
ProcessConfiguration
, see here. Here's how you add
arguments, for example:
>>>
run_ $ cmd "echo" & addArgs ["foo", "bar"]
foo bar>>>
run_ $ cmd "echo"
No Shell, No Automatic Splitting of Strings
cradle
will never wrap your process in a shell process.
cradle
will not split any inputs by whitespace. So e.g. this doesn't work:
>>>
run_ $ cmd "echo foo bar"
*** Exception: echo foo bar: Cradle.run: posix_spawnp: does not exist (No such file or directory)
This is trying to run an executable with the file name "echo foo"
, which
doesn't exist. If you want to split up arguments automatically, you can do
that in haskell though:
>>>
run_ $ cmd "echo" & addArgs (words "foo bar")
foo bar
Synopsis
- run :: (Output output, MonadIO m) => ProcessConfiguration -> m output
- run_ :: MonadIO m => ProcessConfiguration -> m ()
- (&) :: a -> (a -> b) -> b
- data ProcessConfiguration
- cmd :: String -> ProcessConfiguration
- module Cradle.ProcessConfiguration.Helpers
- class Output output
- newtype StdoutUntrimmed = StdoutUntrimmed {}
- newtype StdoutTrimmed = StdoutTrimmed {}
- newtype StdoutRaw = StdoutRaw {}
- newtype StderrRaw = StderrRaw {}
- data ExitCode
Running Child Processes
run_ :: MonadIO m => ProcessConfiguration -> m () Source #
Same as run
, but always returns ()
.
>>>
run_ $ cmd "echo" & addArgs ["Hello, World!"]
Hello, World!
Process Configuration
Configuration on how to run a process. You can
- create one with
cmd
, - configure it with functions from
Helpers
, (which are re-exported from here for convenience) and - run the process with
run
orrun_
.
Usually it shouldn't be necessary to modify its fields directly, but you
*can* import the constructors and fields from
ProcessConfiguration
.
data ProcessConfiguration Source #
cmd :: String -> ProcessConfiguration Source #
Possible Outputs
Instances
newtype StdoutUntrimmed Source #
Instances
newtype StdoutTrimmed Source #
Instances
Instances
Generic StdoutRaw Source # | |
Show StdoutRaw Source # | |
Output StdoutRaw Source # | |
Defined in Cradle.Output | |
Eq StdoutRaw Source # | |
Ord StdoutRaw Source # | |
Defined in Cradle.Output | |
type Rep StdoutRaw Source # | |
Defined in Cradle.Output type Rep StdoutRaw = D1 ('MetaData "StdoutRaw" "Cradle.Output" "cradle-0.0.0.0-1xaj8uOykRu5O0ytQ7P3BP" 'True) (C1 ('MetaCons "StdoutRaw" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromStdoutRaw") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) |
Instances
Generic StderrRaw Source # | |
Show StderrRaw Source # | |
Output StderrRaw Source # | |
Defined in Cradle.Output | |
Eq StderrRaw Source # | |
Ord StderrRaw Source # | |
Defined in Cradle.Output | |
type Rep StderrRaw Source # | |
Defined in Cradle.Output type Rep StderrRaw = D1 ('MetaData "StderrRaw" "Cradle.Output" "cradle-0.0.0.0-1xaj8uOykRu5O0ytQ7P3BP" 'True) (C1 ('MetaCons "StderrRaw" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromStderr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) |
Defines the exit codes that a program can return.
ExitSuccess | indicates successful termination; |
ExitFailure Int | indicates program failure with an exit code. The exact interpretation of the code is operating-system dependent. In particular, some values may be prohibited (e.g. 0 on a POSIX-compliant system). |
Instances
Exception ExitCode | Since: base-4.1.0.0 |
Defined in GHC.IO.Exception toException :: ExitCode -> SomeException # fromException :: SomeException -> Maybe ExitCode # displayException :: ExitCode -> String # | |
Generic ExitCode | |
Read ExitCode | |
Show ExitCode | |
Output ExitCode Source # | |
Defined in Cradle.Output | |
NFData ExitCode | Since: deepseq-1.4.2.0 |
Defined in Control.DeepSeq | |
Eq ExitCode | |
Ord ExitCode | |
Defined in GHC.IO.Exception | |
type Rep ExitCode | |
Defined in GHC.IO.Exception type Rep ExitCode = D1 ('MetaData "ExitCode" "GHC.IO.Exception" "base" 'False) (C1 ('MetaCons "ExitSuccess" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExitFailure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) |