shake-0.15.5: Build system library, like Make, but more accurate dependencies.

Safe HaskellNone
LanguageHaskell2010

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.

Synopsis

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 failure
Exit c <- command [] "gcc" ["-c",myfile]                     -- run a command, recording the exit code
(Exit c, Stderr err) <- command [] "gcc" ["-c","myfile.c"]   -- run a command, recording the exit code and error output
Stdout out <- command [] "gcc" ["-MM","myfile.c"]            -- run a command, recording the output
command_ [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 False, which causes no streams to be captured by Shake, and certain programs (e.g. gcc) to detect they are running in a terminal.

command_ :: [CmdOption] -> String -> [String] -> Action () Source

A version of command where you do not require any results, used to avoid errors about being unable to deduce CmdResult.

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.

  • String arguments are treated as whitespace separated arguments.
  • [String] arguments are treated as literal arguments.
  • CmdOption arguments 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= oneline
unit $ cmd "git log --pretty=" ["oneline"]         -- git log --pretty= oneline
unit $ cmd "git log" ("--pretty=" ++ "oneline")    -- git log --pretty=oneline
unit $ cmd "git log" ("--pretty=" ++ "one line")   -- git log --pretty=one line
unit $ 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 failure
unit $ cmd "gcc -c myfile.c"                                 -- alternative to () <- binding.
Exit c <- cmd "gcc -c" [myfile]                              -- run a command, recording the exit code
(Exit c, Stderr err) <- cmd "gcc -c myfile.c"                -- run a command, recording the exit code and error output
Stdout out <- cmd "gcc -MM myfile.c"                         -- run a command, recording the output
cmd (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 ()

unit :: m () -> m ()

The identity function which requires the inner argument to be (). Useful for functions with overloaded return types.

\(x :: Maybe ()) -> unit x == x

class CmdArguments t Source

Minimal complete definition

cmdArguments

Instances

CmdResult r => CmdArguments (IO r) 
CmdResult r => CmdArguments (Action r) 
(Arg a, CmdArguments r) => CmdArguments (a -> r) 

newtype Stdout a Source

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

fromStdout :: a
 

Instances

newtype Stderr a Source

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

fromStderr :: a
 

Instances

newtype Stdouterr a Source

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

fromStdouterr :: a
 

Instances

newtype Exit Source

Collect the ExitCode of the process. If you do not collect the exit code, any ExitFailure will cause an exception.

Constructors

Exit 

Fields

fromExit :: ExitCode
 

Instances

newtype Process Source

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 

Instances

newtype CmdTime Source

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 :: (CmdResult r, MonadIO m) => (forall r . CmdResult r => m r) -> m r
timer act = do
    (CmdTime t, CmdLine x, r) <- act
    liftIO $ putStrLn $ "Command " ++ x ++ " took " ++ show t ++ " seconds"
    return r

run :: IO ()
run = timer $ cmd "ghc --version"
 

Constructors

CmdTime 

Fields

fromCmdTime :: Double
 

Instances

newtype CmdLine Source

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

fromCmdLine :: String
 

Instances

class CmdResult a Source

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

class CmdString a Source

Minimal complete definition

cmdString

data CmdOption Source

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.

AddPath [String] [String]

Add some items to the prefix and suffix of the $PATH variable.

Stdin String

Given as the stdin of the spawned process. By default the stdin is inherited.

StdinBS ByteString

Given as the stdin of the spawned process.

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 stdin/stdout/stderr messages as binary. By default String results use text encoding and ByteString results use binary encoding.

Traced String

Name to use with traced, or "" for no tracing. By default traces using the name of the executable.

Timeout Double

Abort the computation after N seconds, will raise a failure exit code. Calls interruptProcessGroupOf and terminateProcess, but may sometimes fail to abort the process and not timeout.

WithStdout Bool

Should I include the stdout in the exception if the command fails? Defaults to False.

WithStderr Bool

Should I include the stderr in the exception if the command fails? Defaults to True.

EchoStdout Bool

Should I echo the stdout? Defaults to True unless a Stdout result is required or you use FileStdout.

EchoStderr Bool

Should I echo the stderr? Defaults to True unless a Stderr result is required or you use FileStderr.

FileStdout FilePath

Should I put the stdout to a file.

FileStderr FilePath

Should I put the stderr to a file.

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"] []
cmd opt "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")]
cmd opt "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.