shake-plus-0.3.3.1: Re-export of Shake using well-typed paths and ReaderT.
LicenseMIT
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Development.Shake.Plus.Command

Description

Utilities in Development.Shake.Command lifted to MonadAction.

Synopsis

Documentation

command :: (Partial, CmdResult r, MonadAction m) => [CmdOption] -> String -> [String] -> m r Source #

Lifted version of command.

command_ :: (Partial, MonadAction m) => [CmdOption] -> String -> [String] -> m () Source #

Lifted version of command_.

cmd :: (Partial, CmdArguments args) => args :-> Action r #

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.

  • 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.
  • CmdArgument arguments, which can be built by cmd itself, 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= oneline
cmd_ "git log --pretty=" ["oneline"]         -- git log --pretty= oneline
cmd_ "git log" ("--pretty=" ++ "oneline")    -- git log --pretty=oneline
cmd_ "git log" ("--pretty=" ++ "one line")   -- git log --pretty=one line
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
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

let gccCommand = cmd "gcc -c" :: CmdArgument                 -- build a sub-command. cmd can return CmdArgument values 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 ()

cmd_ :: (Partial, CmdArguments args, Unit args) => args :-> Action () #

See cmd. Same as cmd except with a unit result. cmd is to cmd_ as command is to command_.

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

newtype CmdArgument #

The arguments to cmd - see cmd for examples and semantics.

class CmdArguments t where #

The arguments to cmd - see cmd for examples and semantics.

Methods

cmdArguments :: CmdArgument -> t #

Arguments to cmd

Instances

Instances details
CmdArguments CmdArgument 
Instance details

Defined in Development.Shake.Command

CmdResult r => CmdArguments (IO r) 
Instance details

Defined in Development.Shake.Command

Methods

cmdArguments :: CmdArgument -> IO r #

CmdResult r => CmdArguments (Action r) 
Instance details

Defined in Development.Shake.Command

(IsCmdArgument a, CmdArguments r) => CmdArguments (a -> r) 
Instance details

Defined in Development.Shake.Command

Methods

cmdArguments :: CmdArgument -> a -> r #

class IsCmdArgument a where #

Class to convert an a to a CmdArgument

Methods

toCmdArgument :: a -> CmdArgument #

Conversion to a CmdArgument

Instances

Instances details
IsCmdArgument () 
Instance details

Defined in Development.Shake.Command

Methods

toCmdArgument :: () -> CmdArgument #

IsCmdArgument String 
Instance details

Defined in Development.Shake.Command

IsCmdArgument CmdArgument 
Instance details

Defined in Development.Shake.Command

IsCmdArgument CmdOption 
Instance details

Defined in Development.Shake.Command

IsCmdArgument [String] 
Instance details

Defined in Development.Shake.Command

IsCmdArgument [CmdOption] 
Instance details

Defined in Development.Shake.Command

IsCmdArgument a => IsCmdArgument (Maybe a) 
Instance details

Defined in Development.Shake.Command

IsCmdArgument (NonEmpty String) 
Instance details

Defined in Development.Shake.Command

type (:->) a t = a #

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).

newtype Stdout a #

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.

Constructors

Stdout 

Fields

Instances

Instances details
CmdString a => CmdResult (Stdout a) 
Instance details

Defined in Development.Shake.Command

Methods

cmdResult :: ([Result], [Result] -> Stdout a)

newtype StdoutTrim a #

Like Stdout but remove all leading and trailing whitespaces.

Constructors

StdoutTrim 

Fields

Instances

Instances details
CmdString a => CmdResult (StdoutTrim a) 
Instance details

Defined in Development.Shake.Command

Methods

cmdResult :: ([Result], [Result] -> StdoutTrim a)

newtype Stderr 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.

Constructors

Stderr 

Fields

Instances

Instances details
CmdString a => CmdResult (Stderr a) 
Instance details

Defined in Development.Shake.Command

Methods

cmdResult :: ([Result], [Result] -> Stderr a)

newtype Stdouterr a #

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

Instances

Instances details
CmdString a => CmdResult (Stdouterr a) 
Instance details

Defined in Development.Shake.Command

Methods

cmdResult :: ([Result], [Result] -> Stdouterr a)

newtype Exit #

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

Constructors

Exit 

Fields

Instances

Instances details
CmdResult Exit 
Instance details

Defined in Development.Shake.Command

Methods

cmdResult :: ([Result], [Result] -> Exit)

newtype Process #

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

Instances details
CmdResult Process 
Instance details

Defined in Development.Shake.Command

Methods

cmdResult :: ([Result], [Result] -> Process)

newtype CmdTime #

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"
    pure r

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

Constructors

CmdTime 

Fields

Instances

Instances details
CmdResult CmdTime 
Instance details

Defined in Development.Shake.Command

Methods

cmdResult :: ([Result], [Result] -> CmdTime)

newtype CmdLine #

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

Instances

Instances details
CmdResult CmdLine 
Instance details

Defined in Development.Shake.Command

Methods

cmdResult :: ([Result], [Result] -> CmdLine)

data FSATrace a #

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

FSAWrite a

Writing to a file

FSARead a

Reading from a file

FSADelete a

Deleting a file

FSAMove a a

Moving, arguments destination, then source

FSAQuery a

Querying/stat on a file

FSATouch a

Touching a file

Instances

Instances details
Functor FSATrace 
Instance details

Defined in Development.Shake.Command

Methods

fmap :: (a -> b) -> FSATrace a -> FSATrace b #

(<$) :: a -> FSATrace b -> FSATrace a #

Eq a => Eq (FSATrace a) 
Instance details

Defined in Development.Shake.Command

Methods

(==) :: FSATrace a -> FSATrace a -> Bool #

(/=) :: FSATrace a -> FSATrace a -> Bool #

Data a => Data (FSATrace a) 
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) #

Ord a => Ord (FSATrace a) 
Instance details

Defined in Development.Shake.Command

Methods

compare :: FSATrace a -> FSATrace a -> Ordering #

(<) :: FSATrace a -> FSATrace a -> Bool #

(<=) :: FSATrace a -> FSATrace a -> Bool #

(>) :: FSATrace a -> FSATrace a -> Bool #

(>=) :: FSATrace a -> FSATrace a -> Bool #

max :: FSATrace a -> FSATrace a -> FSATrace a #

min :: FSATrace a -> FSATrace a -> FSATrace a #

Show a => Show (FSATrace a) 
Instance details

Defined in Development.Shake.Command

Methods

showsPrec :: Int -> FSATrace a -> ShowS #

show :: FSATrace a -> String #

showList :: [FSATrace a] -> ShowS #

CmdResult [FSATrace ByteString] 
Instance details

Defined in Development.Shake.Command

Methods

cmdResult :: ([Result], [Result] -> [FSATrace ByteString])

CmdResult [FSATrace FilePath] 
Instance details

Defined in Development.Shake.Command

Methods

cmdResult :: ([Result], [Result] -> [FSATrace FilePath])

class CmdResult a #

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
CmdResult () 
Instance details

Defined in Development.Shake.Command

Methods

cmdResult :: ([Result], [Result] -> ())

CmdResult ExitCode 
Instance details

Defined in Development.Shake.Command

Methods

cmdResult :: ([Result], [Result] -> ExitCode)

CmdResult ProcessHandle 
Instance details

Defined in Development.Shake.Command

Methods

cmdResult :: ([Result], [Result] -> ProcessHandle)

CmdResult Exit 
Instance details

Defined in Development.Shake.Command

Methods

cmdResult :: ([Result], [Result] -> Exit)

CmdResult Process 
Instance details

Defined in Development.Shake.Command

Methods

cmdResult :: ([Result], [Result] -> Process)

CmdResult CmdTime 
Instance details

Defined in Development.Shake.Command

Methods

cmdResult :: ([Result], [Result] -> CmdTime)

CmdResult CmdLine 
Instance details

Defined in Development.Shake.Command

Methods

cmdResult :: ([Result], [Result] -> CmdLine)

CmdResult [FSATrace ByteString] 
Instance details

Defined in Development.Shake.Command

Methods

cmdResult :: ([Result], [Result] -> [FSATrace ByteString])

CmdResult [FSATrace FilePath] 
Instance details

Defined in Development.Shake.Command

Methods

cmdResult :: ([Result], [Result] -> [FSATrace FilePath])

CmdString a => CmdResult (Stdout a) 
Instance details

Defined in Development.Shake.Command

Methods

cmdResult :: ([Result], [Result] -> Stdout a)

CmdString a => CmdResult (StdoutTrim a) 
Instance details

Defined in Development.Shake.Command

Methods

cmdResult :: ([Result], [Result] -> StdoutTrim a)

CmdString a => CmdResult (Stderr a) 
Instance details

Defined in Development.Shake.Command

Methods

cmdResult :: ([Result], [Result] -> Stderr a)

CmdString a => CmdResult (Stdouterr a) 
Instance details

Defined in Development.Shake.Command

Methods

cmdResult :: ([Result], [Result] -> Stdouterr a)

(CmdResult x1, CmdResult x2) => CmdResult (x1, x2) 
Instance details

Defined in Development.Shake.Command

Methods

cmdResult :: ([Result], [Result] -> (x1, x2))

(CmdResult x1, CmdResult x2, CmdResult x3) => CmdResult (x1, x2, x3) 
Instance details

Defined in Development.Shake.Command

Methods

cmdResult :: ([Result], [Result] -> (x1, x2, x3))

(CmdResult x1, CmdResult x2, CmdResult x3, CmdResult x4) => CmdResult (x1, x2, x3, x4) 
Instance details

Defined in Development.Shake.Command

Methods

cmdResult :: ([Result], [Result] -> (x1, x2, x3, x4))

(CmdResult x1, CmdResult x2, CmdResult x3, CmdResult x4, CmdResult x5) => CmdResult (x1, x2, x3, x4, x5) 
Instance details

Defined in Development.Shake.Command

Methods

cmdResult :: ([Result], [Result] -> (x1, x2, x3, x4, x5))

class CmdString a #

The allowable String-like values that can be captured.

Minimal complete definition

cmdString

Instances

Instances details
CmdString () 
Instance details

Defined in Development.Shake.Command

Methods

cmdString :: (Str, Str -> ())

CmdString ByteString 
Instance details

Defined in Development.Shake.Command

Methods

cmdString :: (Str, Str -> ByteString)

CmdString ByteString 
Instance details

Defined in Development.Shake.Command

Methods

cmdString :: (Str, Str -> ByteString)

CmdString String 
Instance details

Defined in Development.Shake.Command

Methods

cmdString :: (Str, Str -> String)

data CmdOption #

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. Successive Cwd options are joined together, to change into nested directories.

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 $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.

FileStdin FilePath

Take the stdin from a file.

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.

AutoDeps

Compute dependencies automatically. Only works if shakeLintInside has been set to the files where autodeps might live.

UserCommand String

The command the user thinks about, before any munging. Defaults to the actual command.

FSAOptions String

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.

CloseFileHandles

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).

NoProcessGroup

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.

InheritStdin

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
Eq CmdOption 
Instance details

Defined in Development.Shake.Internal.CmdOption

Data CmdOption 
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 #

Ord CmdOption 
Instance details

Defined in Development.Shake.Internal.CmdOption

Show CmdOption 
Instance details

Defined in Development.Shake.Internal.CmdOption

IsCmdArgument CmdOption 
Instance details

Defined in Development.Shake.Command

IsCmdArgument [CmdOption] 
Instance details

Defined in Development.Shake.Command