| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Development.Shake.Command
Description
This module provides functions for calling command line programs, primarily
   command and cmd. As a simple example:
command [] "gcc" ["-c",myfile]
The functions from this module are now available directly from Development.Shake.
   You should only need to import this module if you are using the cmd function in the IO monad.
- command :: CmdResult r => [CmdOption] -> String -> [String] -> Action r
- command_ :: [CmdOption] -> String -> [String] -> Action ()
- cmd :: CmdArguments args => args :-> Action r
- unit :: m () -> m ()
- class CmdArguments t
- type (:->) a t = a
- newtype Stdout a = Stdout {- fromStdout :: a
 
- newtype Stderr a = Stderr {- fromStderr :: a
 
- newtype Stdouterr a = Stdouterr {- fromStdouterr :: a
 
- newtype Exit = Exit {}
- newtype Process = Process {}
- newtype CmdTime = CmdTime {}
- newtype CmdLine = CmdLine {}
- class CmdResult a
- class CmdString a
- data CmdOption- = Cwd FilePath
- | Env [(String, String)]
- | AddEnv String String
- | RemEnv String
- | AddPath [String] [String]
- | Stdin String
- | StdinBS ByteString
- | FileStdin FilePath
- | Shell
- | BinaryPipes
- | Traced String
- | Timeout Double
- | WithStdout Bool
- | WithStderr Bool
- | EchoStdout Bool
- | EchoStderr Bool
- | FileStdout FilePath
- | FileStderr FilePath
- | AutoDeps
 
- addPath :: MonadIO m => [String] -> [String] -> m CmdOption
- addEnv :: MonadIO m => [(String, String)] -> m CmdOption
Documentation
command :: CmdResult r => [CmdOption] -> String -> [String] -> Action r Source #
Execute a system command. Before running command make sure you need any files
   that are used by the command.
This function takes a list of options (often just [], see CmdOption for the available
   options), the name of the executable (either a full name, or a program on the $PATH) and
   a list of arguments. The result is often (), but can be a tuple containg any of Stdout,
   Stderr and Exit. Some examples:
command_[] "gcc" ["-c","myfile.c"] -- compile a file, throwing an exception on failureExitc <-command[] "gcc" ["-c",myfile] -- run a command, recording the exit code (Exitc,Stderrerr) <-command[] "gcc" ["-c","myfile.c"] -- run a command, recording the exit code and error outputStdoutout <-command[] "gcc" ["-MM","myfile.c"] -- run a command, recording the outputcommand_[Cwd"generated"] "gcc" ["-c",myfile] -- run a command in a directory
Unless you retrieve the ExitCode using Exit, any ExitFailure will throw an error, including
   the Stderr in the exception message. If you capture the Stdout or Stderr, that stream will not be echoed to the console,
   unless you use the option EchoStdout or EchoStderr.
If you use command inside a do block and do not use the result, you may get a compile-time error about being
   unable to deduce CmdResult. To avoid this error, use command_.
By default the stderr stream will be captured for use in error messages, and also echoed. To only echo
   pass WithStderr Falsegcc)
   to detect they are running in a terminal.
cmd :: CmdArguments args => args :-> Action r Source #
Execute a system command. Before running cmd make sure you need any files
   that are used by the command.
- Stringarguments are treated as whitespace separated arguments.
- [String]arguments are treated as literal arguments.
- CmdOptionarguments are used as options.
As some examples, here are some calls, and the resulting command string:
unit$cmd"git log --pretty=" "oneline" -- git log --pretty= onelineunit$cmd"git log --pretty=" ["oneline"] -- git log --pretty= onelineunit$cmd"git log" ("--pretty=" ++ "oneline") -- git log --pretty=onelineunit$cmd"git log" ("--pretty=" ++ "one line") -- git log --pretty=one lineunit$cmd"git log" ["--pretty=" ++ "one line"] -- git log "--pretty=one line"
More examples, including return values, see this translation of the examples given for the command function:
() <-cmd"gcc -c myfile.c" -- compile a file, throwing an exception on failureunit$cmd"gcc -c myfile.c" -- alternative to () <- binding.Exitc <-cmd"gcc -c" [myfile] -- run a command, recording the exit code (Exitc,Stderrerr) <-cmd"gcc -c myfile.c" -- run a command, recording the exit code and error outputStdoutout <-cmd"gcc -MM myfile.c" -- run a command, recording the outputcmd(Cwd"generated") "gcc -c" [myfile] ::Action() -- run a command in a directory
When passing file arguments we use [myfile] so that if the myfile variable contains spaces they are properly escaped.
If you use cmd inside a do block and do not use the result, you may get a compile-time error about being
   unable to deduce CmdResult. To avoid this error, bind the result to (), or include a type signature, or use
   the unit function.
The cmd function can also be run in the IO monad, but then Traced is ignored and command lines are not echoed.
   As an example:
cmd(Cwd"generated")Shell"gcc -c myfile.c" :: IO ()
class CmdArguments t Source #
Minimal complete definition
cmdArguments
Instances
| CmdArguments [Either CmdOption String] Source # | |
| CmdResult r => CmdArguments (IO r) Source # | |
| CmdResult r => CmdArguments (Action r) Source # | |
| (Arg a, CmdArguments r) => CmdArguments (a -> r) Source # | |
A type annotation, equivalent to the first argument, but in variable argument contexts, gives a clue as to what return type is expected (not actually enforced).
Collect the stdout of the process.
   If used, the stdout will not be echoed to the terminal, unless you include EchoStdout.
   The value type may be either String, or either lazy or strict ByteString.
Constructors
| Stdout | |
| Fields 
 | |
Collect the stderr of the process.
   If used, the stderr will not be echoed to the terminal, unless you include EchoStderr.
   The value type may be either String, or either lazy or strict ByteString.
Constructors
| Stderr | |
| Fields 
 | |
Collect the stdout and stderr of the process.
   If used, the stderr and stdout will not be echoed to the terminal, unless you include EchoStdout and EchoStderr.
   The value type may be either String, or either lazy or strict ByteString.
Constructors
| Stdouterr | |
| Fields 
 | |
Collect the ExitCode of the process.
   If you do not collect the exit code, any ExitFailure will cause an exception.
Collect the ProcessHandle of the process.
   If you do collect the process handle, the command will run asyncronously and the call to 'cmd'/'command'
   will return as soon as the process is spawned. Any 'Stdout'\/'Stderr' captures will return empty strings.
Constructors
| Process | |
| Fields | |
Collect the time taken to execute the process. Can be used in conjunction with CmdLine to
   write helper functions that print out the time of a result.
timer :: (CmdResultr, MonadIO m) => (forall r .CmdResultr => m r) -> m r timer act = do (CmdTimet,CmdLinex, r) <- act liftIO $ putStrLn $ "Command " ++ x ++ " took " ++ show t ++ " seconds" return r run :: IO () run = timer $cmd"ghc --version"
Constructors
| CmdTime | |
| Fields | |
Collect the command line used for the process. This command line will be approximate - suitable for user diagnostics, but not for direct execution.
Constructors
| CmdLine | |
| Fields | |
A class for specifying what results you want to collect from a process.
   Values are formed of Stdout, Stderr, Exit and tuples of those.
Minimal complete definition
cmdResult
Instances
| CmdResult () Source # | |
| CmdResult ExitCode Source # | |
| CmdResult ProcessHandle Source # | |
| CmdResult CmdLine Source # | |
| CmdResult CmdTime Source # | |
| CmdResult Process Source # | |
| CmdResult Exit Source # | |
| CmdString a => CmdResult (Stdouterr a) Source # | |
| CmdString a => CmdResult (Stderr a) Source # | |
| CmdString a => CmdResult (Stdout a) Source # | |
| (CmdResult x1, CmdResult x2) => CmdResult (x1, x2) Source # | |
| (CmdResult x1, CmdResult x2, CmdResult x3) => CmdResult (x1, x2, x3) Source # | |
| (CmdResult x1, CmdResult x2, CmdResult x3, CmdResult x4) => CmdResult (x1, x2, x3, x4) Source # | |
| (CmdResult x1, CmdResult x2, CmdResult x3, CmdResult x4, CmdResult x5) => CmdResult (x1, x2, x3, x4, x5) Source # | |
The allowable String-like values that can be captured.
Minimal complete definition
cmdString
Options passed to command or cmd to control how processes are executed.
Constructors
| Cwd FilePath | Change the current directory in the spawned process. By default uses this processes current directory. | 
| Env [(String, String)] | Change the environment variables in the spawned process. By default uses this processes environment. | 
| AddEnv String String | Add an environment variable in the child process. | 
| RemEnv String | Remove an environment variable from the child process. | 
| AddPath [String] [String] | Add some items to the prefix and suffix of the  | 
| Stdin String | Given as the  | 
| StdinBS ByteString | Given as the  | 
| FileStdin FilePath | Take the  | 
| Shell | Pass the command to the shell without escaping - any arguments will be joined with spaces. By default arguments are escaped properly. | 
| BinaryPipes | Treat the  | 
| Traced String | Name to use with  | 
| Timeout Double | Abort the computation after N seconds, will raise a failure exit code. Calls  | 
| WithStdout Bool | Should I include the  | 
| WithStderr Bool | Should I include the  | 
| EchoStdout Bool | Should I echo the  | 
| EchoStderr Bool | Should I echo the  | 
| FileStdout FilePath | Should I put the  | 
| FileStderr FilePath | Should I put the  | 
| AutoDeps | Compute dependencies automatically. | 
addPath :: MonadIO m => [String] -> [String] -> m CmdOption Source #
Deprecated: Use AddPath. This function will be removed in a future version.
Add a prefix and suffix to the $PATH environment variable. For example:
opt <-addPath["/usr/special"] []cmdopt "userbinary --version"
Would prepend /usr/special to the current $PATH, and the command would pick
   /usr/special/userbinary, if it exists. To add other variables see addEnv.
addEnv :: MonadIO m => [(String, String)] -> m CmdOption Source #
Deprecated: Use AddEnv. This function will be removed in a future version.
Add a single variable to the environment. For example:
opt <-addEnv[("CFLAGS","-O2")]cmdopt "gcc -c main.c"
Would add the environment variable $CFLAGS with value -O2. If the variable $CFLAGS
   was already defined it would be overwritten. If you wish to modify $PATH see addPath.