| Safe Haskell | Safe-Inferred |
|---|---|
| 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.
Synopsis
- command :: (Partial, CmdResult r) => [CmdOption] -> String -> [String] -> Action r
- command_ :: Partial => [CmdOption] -> String -> [String] -> Action ()
- cmd :: (Partial, CmdArguments args) => args :-> Action r
- cmd_ :: (Partial, CmdArguments args, Unit args) => args :-> Action ()
- unit :: m () -> m ()
- newtype CmdArgument = CmdArgument [Either CmdOption String]
- class CmdArguments t where
- cmdArguments :: Partial => 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 a
- 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
- | CloseFileHandles
- | NoProcessGroup
- | InheritStdin
- addPath :: MonadIO m => [String] -> [String] -> m CmdOption
- addEnv :: MonadIO m => [(String, String)] -> m CmdOption
Documentation
command :: (Partial, 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 , 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 :: (Partial, CmdArguments args) => args :-> Action r Source #
Build or execute a system command. Before using cmd to run a command, make sure you need any files
that are used by the command.
Stringarguments are treated as a list of whitespace separated arguments.[String]arguments are treated as a list of literal arguments.CmdOptionarguments are used as options.CmdArgumentarguments, which can be built bycmditself, are spliced into the containing command.
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 failureExitc <-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 let gccCommand =cmd"gcc -c" ::CmdArgument-- build a sub-command.cmdcan returnCmdArgumentvalues as well as execute commands cmd (Cwd"generated") gccCommand [myfile] -- splice that command into a greater command
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 #
Constructors
Instances
Instances details
Instance details
Defined in Development.Shake.Command
Methods
mempty :: CmdArgument #
mappend :: CmdArgument -> CmdArgument -> CmdArgument #
mconcat :: [CmdArgument] -> CmdArgument #
Instance details
Defined in Development.Shake.Command
Methods
(<>) :: CmdArgument -> CmdArgument -> CmdArgument #
sconcat :: NonEmpty CmdArgument -> CmdArgument #
stimes :: Integral b => b -> CmdArgument -> CmdArgument #
Instance details
Defined in Development.Shake.Command
Methods
showsPrec :: Int -> CmdArgument -> ShowS #
show :: CmdArgument -> String #
showList :: [CmdArgument] -> ShowS #
Instance details
Defined in Development.Shake.Command
class CmdArguments t where Source #
Instances
Instances details
Instance details
Defined in Development.Shake.Command
Methods
cmdArguments :: CmdArgument -> IO r Source #
Instance details
Defined in Development.Shake.Command
Methods
cmdArguments :: CmdArgument -> Action r Source #
Instance details
Defined in Development.Shake.Command
Methods
cmdArguments :: CmdArgument -> a -> r Source #
class IsCmdArgument a where Source #
Class to convert an a to a CmdArgument
Instances
Instances details
Instance details
Defined in Development.Shake.Command
Methods
toCmdArgument :: CmdOption -> CmdArgument Source #
Instance details
Defined in Development.Shake.Command
Methods
toCmdArgument :: String -> CmdArgument Source #
Instance details
Defined in Development.Shake.Command
Methods
toCmdArgument :: () -> CmdArgument Source #
Instance details
Defined in Development.Shake.Command
Methods
toCmdArgument :: Maybe a -> CmdArgument Source #
Instance details
Defined in Development.Shake.Command
Methods
toCmdArgument :: [CmdOption] -> CmdArgument Source #
Instance details
Defined in Development.Shake.Command
Methods
toCmdArgument :: [String] -> 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 .
newtype StdoutTrim a Source #
Like Stdout but remove all leading and trailing whitespaces.
Instances
Instances details
Instance details
Defined in Development.Shake.Command
Methods
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.
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.
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 :: (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" pure 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 ]
Constructors
Writing to a file
Reading from a file
Deleting a file
Moving, arguments destination, then source
Querying/stat on a file
Touching a file
Instances
Instances details
Instance details
Defined in Development.Shake.Command
Methods
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FSATrace a -> c (FSATrace a) #
gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FSATrace a) #
toConstr :: FSATrace a -> Constr #
dataTypeOf :: FSATrace a -> DataType #
dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FSATrace a)) #
dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FSATrace a)) #
gmapT :: (forall b. Data b => b -> b) -> FSATrace a -> FSATrace a #
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FSATrace a -> r #
gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FSATrace a -> r #
gmapQ :: (forall d. Data d => d -> u) -> FSATrace a -> [u] #
gmapQi :: Int -> (forall d. Data d => d -> u) -> FSATrace a -> u #
gmapM :: Monad m => (forall d. Data d => d -> m d) -> FSATrace a -> m (FSATrace a) #
gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FSATrace a -> m (FSATrace a) #
gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FSATrace a -> m (FSATrace a) #
Instance details
Defined in Development.Shake.Command
Instance details
Defined in Development.Shake.Command
Instance details
Defined in Development.Shake.Command
Methods
cmdResult :: ([Result], [Result] -> [FSATrace ByteString])
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
Instances details
Instance details
Defined in Development.Shake.Command
Instance details
Defined in Development.Shake.Command
Methods
cmdResult :: ([Result], [Result] -> ProcessHandle)
Instance details
Defined in Development.Shake.Command
Instance details
Defined in Development.Shake.Command
Instance details
Defined in Development.Shake.Command
Instance details
Defined in Development.Shake.Command
Instance details
Defined in Development.Shake.Command
Instance details
Defined in Development.Shake.Command
Instance details
Defined in Development.Shake.Command
Methods
cmdResult :: ([Result], [Result] -> StdoutTrim a)
Instance details
Defined in Development.Shake.Command
Instance details
Defined in Development.Shake.Command
Instance details
Defined in Development.Shake.Command
Methods
cmdResult :: ([Result], [Result] -> [FSATrace ByteString])
Instance details
Defined in Development.Shake.Command
Methods
cmdResult :: ([Result], [Result] -> (x1, x2))
Instance details
Defined in Development.Shake.Command
Methods
cmdResult :: ([Result], [Result] -> (x1, x2, x3))
Instance details
Defined in Development.Shake.Command
Methods
cmdResult :: ([Result], [Result] -> (x1, x2, x3, x4))
Instance details
Defined in Development.Shake.Command
Methods
cmdResult :: ([Result], [Result] -> (x1, x2, x3, x4, x5))
The allowable String -like values that can be captured.
Minimal complete definition
cmdString
Instances
Instances details
Options passed to command or cmd to control how processes are executed.
Constructors
Change the current directory in the spawned process. By default uses this processes current directory.
Successive Cwd options are joined together, to change into nested directories.
Change the environment variables in the spawned process. By default uses this processes environment.
Pass the command to the shell without escaping - any arguments will be joined with spaces. By default arguments are escaped properly.
Treat the stdin/stdout/stderr messages as binary. By default String results use text encoding and ByteString results use binary encoding.
Name to use with traced, or "" for no tracing. By default traces using the name of the executable.
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.
Should I include the stdout in the exception if the command fails? Defaults to False .
Should I include the stderr in the exception if the command fails? Defaults to True .
Should I echo the stdout? Defaults to True unless a Stdout result is required or you use FileStdout .
Should I echo the stderr? Defaults to True unless a Stderr result is required or you use FileStderr .
Compute dependencies automatically. Only works if shakeLintInside has been set to the files where autodeps might live.
The command the user thinks about, before any munging. Defaults to the actual command.
Options to fsatrace, a list of strings with characters such as "r" (reads) "w" (writes). Defaults to "rwmdqt" if the output of fsatrace is required.
Before starting the command in the child process, close all file handles except stdin, stdout, stderr in the child process. Uses close_fds from package process and comes with the same caveats, i.e. runtime is linear with the maximum number of open file handles (RLIMIT_NOFILE, see man 2 getrlimit on Linux).
Don't run the process in its own group. Required when running docker. Will mean that process timeouts and asyncronous exceptions may not properly clean up child processes.
Cause the stdin from the parent to be inherited. Might also require NoProcessGroup on Linux. Ignored if you explicitly pass a stdin.
Instances
Instances details
Instance details
Defined in Development.Shake.Internal.CmdOption
Methods
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 :: forall r r'. (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 #
Instance details
Defined in Development.Shake.Internal.CmdOption
Instance details
Defined in Development.Shake.Command
Methods
toCmdArgument :: CmdOption -> CmdArgument Source #
Instance details
Defined in Development.Shake.Command
Methods
toCmdArgument :: [CmdOption] -> CmdArgument Source #
addPath :: 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 .