Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- command :: CmdResult r => [CmdOption] -> String -> [String] -> Action r
- command_ :: [CmdOption] -> String -> [String] -> Action ()
- cmd :: CmdArguments args => args :-> Action r
- cmd_ :: (CmdArguments args, Unit args) => args :-> Action ()
- unit :: m () -> m ()
- newtype CmdArgument = CmdArgument [Either CmdOption String]
- class CmdArguments t where
- cmdArguments :: CmdArgument -> t
- class IsCmdArgument a where
- toCmdArgument :: a -> CmdArgument
- type (:->) a t = a
- newtype Stdout a = Stdout {
- fromStdout :: a
- newtype StdoutTrim a = StdoutTrim {
- fromStdoutTrim :: 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 {}
- data FSATrace
- 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
- | UserCommand String
- | FSAOptions String
- 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 failureExit
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 outputStdout
out <-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
, which causes no streams to be captured by Shake, and certain programs (e.g. WithStderr
False
gcc
)
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.
String
arguments are treated as a list of whitespace separated arguments.[String]
arguments are treated as a list of literal arguments.CmdOption
arguments are used as options.
Typically only string literals should be passed as String
arguments. When using variables
prefer [myvar]
so that if myvar
contains spaces they are properly escaped.
As some examples, here are some calls, and the resulting command string:
cmd_
"git log --pretty=" "oneline" -- git log --pretty= onelinecmd_
"git log --pretty=" ["oneline"] -- git log --pretty= onelinecmd_
"git log" ("--pretty=" ++ "oneline") -- git log --pretty=onelinecmd_
"git log" ("--pretty=" ++ "one line") -- git log --pretty=one linecmd_
"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 failureExit
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 outputStdout
out <-cmd
"gcc -MM myfile.c" -- run a command, recording the outputcmd
(Cwd
"generated") "gcc -c" [myfile] ::Action
() -- run a command in a directory
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, use cmd_
. If you enable OverloadedStrings
or OverloadedLists
you may have to give type signatures to the arguments, or use the more constrained command
instead.
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 ()
The identity function which requires the inner argument to be ()
. Useful for functions
with overloaded return types.
\(x :: Maybe ()) -> unit x == x
newtype CmdArgument Source #
Instances
Eq CmdArgument Source # | |
Defined in Development.Shake.Command (==) :: CmdArgument -> CmdArgument -> Bool # (/=) :: CmdArgument -> CmdArgument -> Bool # | |
Show CmdArgument Source # | |
Defined in Development.Shake.Command showsPrec :: Int -> CmdArgument -> ShowS # show :: CmdArgument -> String # showList :: [CmdArgument] -> ShowS # | |
Semigroup CmdArgument Source # | |
Defined in Development.Shake.Command (<>) :: CmdArgument -> CmdArgument -> CmdArgument # sconcat :: NonEmpty CmdArgument -> CmdArgument # stimes :: Integral b => b -> CmdArgument -> CmdArgument # | |
Monoid CmdArgument Source # | |
Defined in Development.Shake.Command mempty :: CmdArgument # mappend :: CmdArgument -> CmdArgument -> CmdArgument # mconcat :: [CmdArgument] -> CmdArgument # | |
CmdArguments CmdArgument Source # | |
Defined in Development.Shake.Command |
class CmdArguments t where Source #
cmdArguments :: CmdArgument -> t Source #
Arguments to cmd
Instances
CmdArguments CmdArgument Source # | |
Defined in Development.Shake.Command | |
CmdResult r => CmdArguments (IO r) Source # | |
Defined in Development.Shake.Command cmdArguments :: CmdArgument -> IO r Source # | |
CmdResult r => CmdArguments (Action r) Source # | |
Defined in Development.Shake.Command cmdArguments :: CmdArgument -> Action r Source # | |
(IsCmdArgument a, CmdArguments r) => CmdArguments (a -> r) Source # | |
Defined in Development.Shake.Command cmdArguments :: CmdArgument -> a -> r Source # |
class IsCmdArgument a where Source #
Class to convert an a to a CmdArgument
toCmdArgument :: a -> CmdArgument Source #
Conversion to a CmdArgument
Instances
IsCmdArgument String Source # | |
Defined in Development.Shake.Command toCmdArgument :: String -> CmdArgument Source # | |
IsCmdArgument CmdOption Source # | |
Defined in Development.Shake.Command toCmdArgument :: CmdOption -> CmdArgument Source # | |
IsCmdArgument [String] Source # | |
Defined in Development.Shake.Command toCmdArgument :: [String] -> CmdArgument Source # | |
IsCmdArgument [CmdOption] Source # | |
Defined in Development.Shake.Command toCmdArgument :: [CmdOption] -> CmdArgument Source # | |
IsCmdArgument a => IsCmdArgument (Maybe a) Source # | |
Defined in Development.Shake.Command toCmdArgument :: Maybe a -> CmdArgument 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
.
Note that most programs end their output with a trailing newline, so calling
ghc --numeric-version
will result in Stdout
of "6.8.3\n"
. If you want to automatically
trim the resulting string, see StdoutTrim
.
Stdout | |
|
newtype StdoutTrim a Source #
Like Stdout
but remove all leading and trailing whitespaces.
StdoutTrim | |
|
Instances
CmdString a => CmdResult (StdoutTrim a) Source # | |
Defined in Development.Shake.Command cmdResult :: ([Result], [Result] -> StdoutTrim a) |
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
.
Stderr | |
|
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
.
Stdouterr | |
|
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.
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"
Collect the command line used for the process. This command line will be approximate - suitable for user diagnostics, but not for direct execution.
The results produced by fsatrace
. All files will be absolute paths.
You can get the results for a cmd
by requesting a value of type
[
.FSATrace
]
FSAWrite FilePath | Writing to a file |
FSARead FilePath | Reading from a file |
FSADelete FilePath | Deleting a file |
FSAMove FilePath FilePath | Moving, arguments destination, then source |
FSAQuery FilePath | Querying/stat on a file |
FSATouch FilePath | Touching a file |
Instances
Eq FSATrace Source # | |
Data FSATrace Source # | |
Defined in Development.Shake.Command gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FSATrace -> c FSATrace # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FSATrace # toConstr :: FSATrace -> Constr # dataTypeOf :: FSATrace -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FSATrace) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FSATrace) # gmapT :: (forall b. Data b => b -> b) -> FSATrace -> FSATrace # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FSATrace -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FSATrace -> r # gmapQ :: (forall d. Data d => d -> u) -> FSATrace -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FSATrace -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FSATrace -> m FSATrace # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FSATrace -> m FSATrace # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FSATrace -> m FSATrace # | |
Ord FSATrace Source # | |
Defined in Development.Shake.Command | |
Show FSATrace Source # | |
CmdResult [FSATrace] Source # | |
Defined in Development.Shake.Command |
A class for specifying what results you want to collect from a process.
Values are formed of Stdout
, Stderr
, Exit
and tuples of those.
cmdResult
Instances
The allowable String
-like values that can be captured.
cmdString
Instances
CmdString () Source # | |
Defined in Development.Shake.Command cmdString :: (Str, Str -> ()) | |
CmdString String Source # | |
Defined in Development.Shake.Command | |
CmdString ByteString Source # | |
Defined in Development.Shake.Command cmdString :: (Str, Str -> ByteString) | |
CmdString ByteString Source # | |
Defined in Development.Shake.Command cmdString :: (Str, Str -> ByteString) |
Options passed to command
or cmd
to control how processes are executed.
Cwd FilePath | Change the current directory in the spawned process. By default uses this processes current directory.
Successive |
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. |
UserCommand String | The command the user thinks about, before any munging. Defaults to the actual command. |
FSAOptions String | Options to |
Instances
Eq CmdOption Source # | |
Data CmdOption Source # | |
Defined in Development.Shake.Internal.CmdOption gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CmdOption -> c CmdOption # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CmdOption # toConstr :: CmdOption -> Constr # dataTypeOf :: CmdOption -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CmdOption) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CmdOption) # gmapT :: (forall b. Data b => b -> b) -> CmdOption -> CmdOption # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CmdOption -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CmdOption -> r # gmapQ :: (forall d. Data d => d -> u) -> CmdOption -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CmdOption -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CmdOption -> m CmdOption # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CmdOption -> m CmdOption # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CmdOption -> m CmdOption # | |
Ord CmdOption Source # | |
Defined in Development.Shake.Internal.CmdOption | |
Show CmdOption Source # | |
IsCmdArgument CmdOption Source # | |
Defined in Development.Shake.Command toCmdArgument :: CmdOption -> CmdArgument Source # | |
IsCmdArgument [CmdOption] Source # | |
Defined in Development.Shake.Command toCmdArgument :: [CmdOption] -> CmdArgument Source # |
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
.