• Home
  • History
  • Annotate
Name Date Size #Lines LOC

..03-May-2022-

src/System/Process/H19-Mar-2018-1,1681,016

test/H19-Mar-2018-171121

ChangeLog.mdH A D02-Jul-20191.2 KiB5330

LICENSEH A D19-Mar-20181.1 KiB2117

README.mdH A D28-Feb-201914.5 KiB496393

Setup.hsH A D19-Mar-201846 32

typed-process.cabalH A D02-Jul-20192.1 KiB9386

README.md

1## typed-process
2
3[![Build Status](https://travis-ci.org/fpco/typed-process.svg?branch=master)](https://travis-ci.org/fpco/typed-process) [![Build status](https://ci.appveyor.com/api/projects/status/bhh7aekbgeqp7g5j/branch/master?svg=true)](https://ci.appveyor.com/project/snoyberg/typed-process/branch/master)
4
5API level documentation (Haddocks) may be [found on
6Stackage](https://www.stackage.org/package/typed-process).
7
8This library provides the ability to launch and interact with external
9processes. It wraps around the
10[process library](https://haskell-lang.org/library/process), and
11intends to improve upon it by:
12
131. Using type variables to represent the standard streams, making them
14   easier to manipulate
152. Use proper concurrency (e.g., the async library) in place of the
16   weird lazy I/O tricks for such things as consuming output streams
173. Allow for more complex concurrency by providing STM-based functions
184. Using binary I/O correctly
195. Providing a more composable API, designed to be easy to use for
20   both simple and complex use cases
21
22__NOTE__ It's highly recommended that you compile any program using this
23library with the multi-threaded runtime, usually by adding `ghc-options:
24-threaded` to your executable stanza in your cabal or `package.yaml` file. The
25single-threaded runtime necessitates some inefficient polling to be used under
26the surface.
27
28## Synopsis
29
30```haskell
31#!/usr/bin/env stack
32-- stack --resolver lts-12.21 script
33{-# LANGUAGE OverloadedStrings #-}
34import System.IO (hPutStr, hClose)
35import System.Process.Typed
36import qualified Data.ByteString.Lazy as L
37import qualified Data.ByteString.Lazy.Char8 as L8
38import Control.Concurrent.STM (atomically)
39import Control.Exception (throwIO)
40
41main :: IO ()
42main = do
43    -- Run a process, print its exit code
44    runProcess "true" >>= print
45    runProcess "false" >>= print
46
47    -- Check that the exit code is a success
48    runProcess_ "true"
49    -- This will throw an exception: runProcess_ "false"
50
51    -- Capture output and error
52    (dateOut, dateErr) <- readProcess_ "date"
53    print (dateOut, dateErr)
54
55    -- Use shell commands
56    (dateOut2, dateErr2) <- readProcess_ "date >&2"
57    print (dateOut2, dateErr2)
58
59    -- Interact with a process
60    let catConfig = setStdin createPipe
61                  $ setStdout byteStringOutput
62                  $ proc "cat" ["/etc/hosts", "-", "/etc/group"]
63    withProcess_ catConfig $ \p -> do
64        hPutStr (getStdin p) "\n\nHELLO\n"
65        hPutStr (getStdin p) "WORLD\n\n\n"
66        hClose (getStdin p)
67
68        atomically (getStdout p) >>= L8.putStr
69```
70
71## Types
72
73The two primary types in this package are `ProcessConfig` and
74`Process`. `ProcessConfig` gives a specification for how to run a
75process (e.g., the command to run, working directory, environment
76variables) and how to deal with the three standard streams: input,
77output, and error. You use one of the functions in this package for
78launching a process to turn a `ProcessConfig` into a `Process`, which
79represents an actual running system process.
80
81The easiest way to create a `ProcessConfig` is using the `IsString`
82instance and `OverloadedStrings`. For example, to run the `date`
83command, we can do the following. (NOTE: The type signatures used here
84are simply to spell things out, they are not needed.)
85
86```haskell
87#!/usr/bin/env stack
88-- stack --resolver lts-12.21 script
89{-# LANGUAGE OverloadedStrings #-}
90import System.Process.Typed
91
92main :: IO ()
93main = do
94    let dateConfig :: ProcessConfig () () ()
95        dateConfig = "date"
96
97    process <- startProcess dateConfig
98    exitCode <- waitExitCode (process :: Process () () ())
99    print exitCode
100
101    stopProcess process
102```
103
104This shows the general workflow: use `startProcess` to launch a
105`Process` from a `ProcessConfig`, interact with it (such as
106`waitExitCode` to wait for the process to exit), and then clean up
107resources with `stopProcess`. (We'll get to those `() () ()` type
108parameters in the next section.)
109
110Instead of explicitly dealing with `startProcess` and `stopProcess`,
111it's recommended to instead use `withProcess`, which uses the bracket
112pattern and is exception safe:
113
114```haskell
115#!/usr/bin/env stack
116-- stack --resolver lts-12.21 script
117{-# LANGUAGE OverloadedStrings #-}
118import System.Process.Typed
119
120main :: IO ()
121main = withProcess "date" $ \process -> do
122    exitCode <- waitExitCode (process :: Process () () ())
123    print exitCode
124```
125
126But this pattern of running a process, waiting for it to exit, and
127getting its exit code is very common, so it has a helper function of
128its own:
129
130```haskell
131#!/usr/bin/env stack
132-- stack --resolver lts-12.21 script
133{-# LANGUAGE OverloadedStrings #-}
134import System.Process.Typed
135
136main :: IO ()
137main = do
138    exitCode <- runProcess "date"
139    print exitCode
140```
141
142We'll discuss some functions which automatically check the exit code
143below.
144
145## Type parameters
146
147Both `ProcessConfig` and `Process` take three type parameters:
148the types of the standard input, output, and error streams for the
149process. As you saw above, our default is `()` for each, and our
150default behavior is to inherit the streams from the parent
151process. This is why, when you run the previous programs, the `date`
152program's output goes directly to your console.
153
154We can override these defaults in a number of ways. Perhaps the
155easiest is to simply close the stream for the child so it cannot use
156it at all.
157
158```haskell
159#!/usr/bin/env stack
160-- stack --resolver lts-12.21 script
161{-# LANGUAGE OverloadedStrings #-}
162import System.Process.Typed
163
164main :: IO ()
165main = do
166    let dateConfig :: ProcessConfig () () ()
167        dateConfig = setStdin closed
168                   $ setStdout closed
169                   $ setStderr closed
170                     "date"
171    exitCode <- runProcess dateConfig
172    print exitCode
173```
174
175A few things to note:
176
177* The type parameter is still `()`, since there's no data to
178  return. We'll see some more interesting cases later.
179* This process now returns an `ExitFailure 1`, since it tries to write
180  to a closed `stdout` file descriptor.
181
182## Using `proc` and `shell`
183
184Using the `OverloadedStrings` approach works nicely for some cases,
185but we'll often want more control over things. There are two smart
186constructors available: `proc` takes a command and list of arguments,
187and `shell` takes a single string which will be passed directly to the
188system's shell.
189
190```haskell
191#!/usr/bin/env stack
192-- stack --resolver lts-12.21 script
193{-# LANGUAGE OverloadedStrings #-}
194import System.Process.Typed
195
196main :: IO ()
197main = do
198    -- Command and arguments
199    runProcess (proc "cat" ["/etc/hosts"]) >>= print
200
201    -- Shell
202    runProcess (shell "cat /etc/hosts >&2 && false") >>= print
203```
204
205The behavior of the `OverloadedStrings` approach we've used until now
206is actually based on these two smart constructors. If you provide it a
207string without any spaces (like `"date"`), it will use `proc` without
208any arguments, e.g. `fromString "date" = proc "date" []`. If there are
209any spaces in the string, it will use `shell`.
210
211__EXERCISE__: Rewrite the previous example to not use the `shell`
212constructor.
213
214## Checking the exit code
215
216We've done a lot of printing of exit codes. In many cases, we don't
217actually want to look at the exit code, but instead just throw an
218exception if the process failed. Fortunately, we have such an
219exit-code-checking function.
220
221```haskell
222#!/usr/bin/env stack
223-- stack --resolver lts-12.21 script
224{-# LANGUAGE OverloadedStrings #-}
225import System.Process.Typed
226
227main :: IO ()
228main = runProcess_ "date"
229```
230
231By adding the `_` at the end of `runProcess`, we're now automatically
232checking the exit code and throwing an exception if it returns
233anything but success. Want to see it in action?
234
235```haskell
236#!/usr/bin/env stack
237-- stack --resolver lts-12.21 script
238{-# LANGUAGE OverloadedStrings #-}
239import System.Process.Typed
240
241main :: IO ()
242main = runProcess_ "false"
243```
244
245Under the surface, this function is using the `checkExitCode`
246function. We can do this more explicitly if desired:
247
248```haskell
249#!/usr/bin/env stack
250-- stack --resolver lts-12.21 script
251{-# LANGUAGE OverloadedStrings #-}
252import System.Process.Typed
253
254main :: IO ()
255main = withProcess "false" checkExitCode
256```
257
258## Reading from a process
259
260Sending all output to the parent process's handles is sometimes
261desired, but often we'd rather just capture that output. The easiest
262way to do that is to capture it in memory as a lazy
263`ByteString`. Fortunately, we have a helper `readProcess` function for
264that:
265
266```haskell
267#!/usr/bin/env stack
268-- stack --resolver lts-12.21 script
269{-# LANGUAGE OverloadedStrings #-}
270import System.Process.Typed
271import System.Exit (ExitCode)
272import Data.ByteString.Lazy (ByteString)
273
274main :: IO ()
275main = do
276    (exitCode, out, err) <- readProcess "date"
277    print (exitCode :: ExitCode)
278    print (out :: ByteString)
279    print (err :: ByteString)
280```
281
282One thing to point out is that, even though this is a lazy
283`ByteString`, it is not using any lazy I/O. When `readProcess` exits,
284the output has been fully generated, and is resident in memory. We
285only use a lazy `ByteString` instead of a strict one for better memory
286configuration (chunking into multiple smaller bits instead of one
287massive chunk of data).
288
289Like `runProcess`, there's an exit-code-checking variant of
290`readProcess`:
291
292```haskell
293#!/usr/bin/env stack
294-- stack --resolver lts-12.21 script
295{-# LANGUAGE OverloadedStrings #-}
296import System.Process.Typed
297import Data.ByteString.Lazy (ByteString)
298
299main :: IO ()
300main = do
301    (out, err) <- readProcess_ "date"
302    print (out :: ByteString)
303    print (err :: ByteString)
304```
305
306__EXERCISE__: Use shell redirection to move the output from standard
307output to standard error.
308
309## Redirecting to a file
310
311Another technique we'll commonly want to employ is to redirect output
312from a process to a file. This is superior to the memory approach as
313it does not have the risk of using large amounts of memory, though it
314is more inconvenient. Together with the
315[`UnliftIO.Temporary`](https://www.stackage.org/haddock/lts/unliftio/UnliftIO-Temporary.html), we
316can do some nice things:
317
318```haskell
319#!/usr/bin/env stack
320-- stack --resolver lts-12.21 script
321{-# LANGUAGE OverloadedStrings #-}
322import System.Process.Typed
323import UnliftIO.Temporary (withSystemTempFile)
324
325main :: IO ()
326main = withSystemTempFile "date" $ \fp h -> do
327    let dateConfig = setStdin closed
328                   $ setStdout (useHandleClose h)
329                   $ setStderr closed
330                     "date"
331
332    runProcess_ dateConfig
333
334    readFile fp >>= print
335```
336
337The `useHandleClose` function lets us provide an already existing
338`Handle`, and will close it when done. If you want to write the output
339of multiple processes to a single file, you can instead use
340`useHandleOpen`:
341
342```haskell
343#!/usr/bin/env stack
344-- stack --resolver lts-12.21 script
345{-# LANGUAGE OverloadedStrings #-}
346import System.Process.Typed
347import System.IO (hClose)
348import UnliftIO.Temporary (withSystemTempFile)
349import Control.Monad (replicateM_)
350
351main :: IO ()
352main = withSystemTempFile "date" $ \fp h -> do
353    let dateConfig = setStdin closed
354                   $ setStdout (useHandleOpen h)
355                   $ setStderr closed
356                     "date"
357
358    replicateM_ 10 $ runProcess_ dateConfig
359    hClose h
360
361    readFile fp >>= putStrLn
362```
363
364__EXERCISE__ Create a separate file for error output and capture that
365as well.
366
367## Providing input
368
369Using `OverloadedStrings`, it's trivial to provide some input to a
370process:
371
372```haskell
373#!/usr/bin/env stack
374-- stack --resolver lts-12.21 script
375{-# LANGUAGE OverloadedStrings #-}
376import System.Process.Typed
377
378main :: IO ()
379main = runProcess_ $ setStdin "Hello World!\n" "cat"
380```
381
382This is just a shortcut for using the `byteStringInput` function:
383
384```haskell
385#!/usr/bin/env stack
386-- stack --resolver lts-12.21 script
387{-# LANGUAGE OverloadedStrings #-}
388import System.Process.Typed
389
390main :: IO ()
391main = runProcess_ $ setStdin (byteStringInput "Hello World!\n") "cat"
392```
393
394But like output and error, we can also use a `Handle` or a temporary
395file:
396
397```haskell
398#!/usr/bin/env stack
399-- stack --resolver lts-12.21 script
400{-# LANGUAGE OverloadedStrings #-}
401import System.Process.Typed
402import System.IO
403import UnliftIO.Temporary (withSystemTempFile)
404
405main :: IO ()
406main = withSystemTempFile "input" $ \fp h -> do
407    hPutStrLn h "Hello World!"
408    hClose h
409
410    withBinaryFile fp ReadMode $ \h' ->
411        runProcess_ $ setStdin (useHandleClose h') "cat"
412```
413
414## Interacting with a process
415
416So far, everything we've done has been _running_ processes: spawning a
417child with some settings, then waiting for it to exit. We will often
418want to _interact_ with a process: spawn it, and then send it input or
419receive output from it while it is still running.
420
421For this, using `createPipe` makes a lot of sense:
422
423```haskell
424#!/usr/bin/env stack
425-- stack --resolver lts-12.21 script
426{-# LANGUAGE OverloadedStrings #-}
427import System.Process.Typed
428import System.IO
429
430main :: IO ()
431main = do
432    let catConfig = setStdin createPipe
433                  $ setStdout createPipe
434                  $ setStderr closed
435                    "cat"
436
437    withProcess_ catConfig $ \p -> do
438        hPutStrLn (getStdin p) "Hello!"
439        hFlush (getStdin p)
440        hGetLine (getStdout p) >>= print
441
442        hClose (getStdin p)
443```
444
445__EXERCISE__: What happens if you remove the `hClose` line, and why?
446Hint: what happens if you both remove `hClose` _and_ replace
447`withProcess_` with `withProcess`?
448
449## Other settings
450
451We've so far only played with modifying streams, but there are a
452number of other settings you can tweak. It's best to just
453[look at the API docs](https://www.stackage.org/package/typed-process)
454for all available functions. We'll give examples of the two most
455common settings: the working directory and environment variables.
456
457```haskell
458#!/usr/bin/env stack
459-- stack --resolver lts-12.21 script
460{-# LANGUAGE OverloadedStrings #-}
461import System.Process.Typed
462
463main :: IO ()
464main = do
465    putStrLn "1:"
466    runProcess_ "pwd"
467    putStrLn "\n2:"
468    runProcess_ $ setWorkingDir "/tmp" "pwd"
469
470    putStrLn "\n3:"
471    runProcess_ "env"
472    putStrLn "\n4:"
473    runProcess_ $ setEnv [("HELLO", "WORLD")] "env"
474```
475
476## Async and STM
477
478When interacting with a process on multiple streams, you'll often want
479to use some kind of concurrency. The strong recommendation is to use
480the
481[async library](https://haskell-lang.org/library/async). Additionally,
482this library provides a number of functions that use STM, which also
483plays very nicely with concurrency and the async package. For some
484examples, check out:
485
486* `waitExitCodeSTM`
487* `getExitCodeSTM`
488* `checkExitCodeSTM`
489* `byteStringOutput`
490
491__EXERCISE__ Reimplement the `readProcess` function using
492`byteStringOutput` and `waitExitCodeSTM`.
493
494__EXERCISE__ Reimplement the `readProcess_` function using
495`byteStringOutput` and `checkExitCodeSTM`.
496