cradle-0.0.0.0: A simpler process library
Safe HaskellSafe-Inferred
LanguageHaskell2010

Cradle

Description

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

Running Child Processes

run :: (Output output, MonadIO m) => ProcessConfiguration -> m output Source #

run_ :: MonadIO m => ProcessConfiguration -> m () Source #

Same as run, but always returns ().

>>> run_ $ cmd "echo" & addArgs ["Hello, World!"]
Hello, World!

(&) :: a -> (a -> b) -> b infixl 1 #

& is a reverse application operator. This provides notational convenience. Its precedence is one higher than that of the forward application operator $, which allows & to be nested in $.

>>> 5 & (+1) & show
"6"

Since: base-4.8.0.0

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 or run_.

Usually it shouldn't be necessary to modify its fields directly, but you *can* import the constructors and fields from ProcessConfiguration.

Possible Outputs

class Output output Source #

Minimal complete definition

configure, extractOutput

Instances

Instances details
Output ExitCode Source # 
Instance details

Defined in Cradle.Output

Output StderrRaw Source # 
Instance details

Defined in Cradle.Output

Output StdoutRaw Source # 
Instance details

Defined in Cradle.Output

Output StdoutTrimmed Source # 
Instance details

Defined in Cradle.Output

Output StdoutUntrimmed Source # 
Instance details

Defined in Cradle.Output

Output () Source # 
Instance details

Defined in Cradle.Output

(Output a, Output b) => Output (a, b) Source # 
Instance details

Defined in Cradle.Output

(Output a, Output b, Output c) => Output (a, b, c) Source # 
Instance details

Defined in Cradle.Output

(Output a, Output b, Output c, Output d) => Output (a, b, c, d) Source # 
Instance details

Defined in Cradle.Output

(Output a, Output b, Output c, Output d, Output e) => Output (a, b, c, d, e) Source # 
Instance details

Defined in Cradle.Output

(Output a, Output b, Output c, Output d, Output e, Output f) => Output (a, b, c, d, e, f) Source # 
Instance details

Defined in Cradle.Output

Methods

configure :: Proxy (a, b, c, d, e, f) -> ProcessConfiguration -> ProcessConfiguration Source #

extractOutput :: ProcessResult -> (a, b, c, d, e, f) Source #

newtype StdoutUntrimmed Source #

Constructors

StdoutUntrimmed 

Instances

Instances details
Generic StdoutUntrimmed Source # 
Instance details

Defined in Cradle.Output

Associated Types

type Rep StdoutUntrimmed :: Type -> Type #

Show StdoutUntrimmed Source # 
Instance details

Defined in Cradle.Output

Output StdoutUntrimmed Source # 
Instance details

Defined in Cradle.Output

Eq StdoutUntrimmed Source # 
Instance details

Defined in Cradle.Output

Ord StdoutUntrimmed Source # 
Instance details

Defined in Cradle.Output

type Rep StdoutUntrimmed Source # 
Instance details

Defined in Cradle.Output

type Rep StdoutUntrimmed = D1 ('MetaData "StdoutUntrimmed" "Cradle.Output" "cradle-0.0.0.0-1xaj8uOykRu5O0ytQ7P3BP" 'True) (C1 ('MetaCons "StdoutUntrimmed" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromStdoutUntrimmed") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

newtype StdoutTrimmed Source #

Constructors

StdoutTrimmed 

Instances

Instances details
Generic StdoutTrimmed Source # 
Instance details

Defined in Cradle.Output

Associated Types

type Rep StdoutTrimmed :: Type -> Type #

Show StdoutTrimmed Source # 
Instance details

Defined in Cradle.Output

Output StdoutTrimmed Source # 
Instance details

Defined in Cradle.Output

Eq StdoutTrimmed Source # 
Instance details

Defined in Cradle.Output

Ord StdoutTrimmed Source # 
Instance details

Defined in Cradle.Output

type Rep StdoutTrimmed Source # 
Instance details

Defined in Cradle.Output

type Rep StdoutTrimmed = D1 ('MetaData "StdoutTrimmed" "Cradle.Output" "cradle-0.0.0.0-1xaj8uOykRu5O0ytQ7P3BP" 'True) (C1 ('MetaCons "StdoutTrimmed" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromStdoutTrimmed") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

newtype StdoutRaw Source #

Constructors

StdoutRaw 

Instances

Instances details
Generic StdoutRaw Source # 
Instance details

Defined in Cradle.Output

Associated Types

type Rep StdoutRaw :: Type -> Type #

Show StdoutRaw Source # 
Instance details

Defined in Cradle.Output

Output StdoutRaw Source # 
Instance details

Defined in Cradle.Output

Eq StdoutRaw Source # 
Instance details

Defined in Cradle.Output

Ord StdoutRaw Source # 
Instance details

Defined in Cradle.Output

type Rep StdoutRaw Source # 
Instance details

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)))

newtype StderrRaw Source #

Constructors

StderrRaw 

Instances

Instances details
Generic StderrRaw Source # 
Instance details

Defined in Cradle.Output

Associated Types

type Rep StderrRaw :: Type -> Type #

Show StderrRaw Source # 
Instance details

Defined in Cradle.Output

Output StderrRaw Source # 
Instance details

Defined in Cradle.Output

Eq StderrRaw Source # 
Instance details

Defined in Cradle.Output

Ord StderrRaw Source # 
Instance details

Defined in Cradle.Output

type Rep StderrRaw Source # 
Instance details

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)))

data ExitCode #

Defines the exit codes that a program can return.

Constructors

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

Instances details
Exception ExitCode

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Generic ExitCode 
Instance details

Defined in GHC.IO.Exception

Associated Types

type Rep ExitCode :: Type -> Type #

Methods

from :: ExitCode -> Rep ExitCode x #

to :: Rep ExitCode x -> ExitCode #

Read ExitCode 
Instance details

Defined in GHC.IO.Exception

Show ExitCode 
Instance details

Defined in GHC.IO.Exception

Output ExitCode Source # 
Instance details

Defined in Cradle.Output

NFData ExitCode

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: ExitCode -> () #

Eq ExitCode 
Instance details

Defined in GHC.IO.Exception

Ord ExitCode 
Instance details

Defined in GHC.IO.Exception

type Rep ExitCode 
Instance details

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)))