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

Safe HaskellNone
LanguageHaskell2010

Development.Shake

Contents

Description

This module is used for defining Shake build systems. As a simple example of a Shake build system, let us build the file result.tar from the files listed by result.txt:

import Development.Shake
import Development.Shake.FilePath

main = shakeArgs shakeOptions $ do
    want ["result.tar"]
    "*.tar" %> \out -> do
        contents <- readFileLines $ out -<.> "txt"
        need contents
        cmd "tar -cf" [out] contents

We start by importing the modules defining both Shake and routines for manipulating FilePath values. We define main to call shake with the default shakeOptions. As the second argument to shake, we provide a set of rules. There are two common forms of rules, want to specify target files, and %> to define a rule which builds a FilePattern. We use want to require that after the build completes the file result.tar should be ready.

The *.tar rule describes how to build files with the extension .tar, including result.tar. We readFileLines on result.txt, after changing the .tar extension to .txt. We read each line into the variable contents -- being a list of the files that should go into result.tar. Next, we depend (need) all the files in contents. If any of these files change, the rule will be repeated. Finally we call the tar program. If either result.txt changes, or any of the files listed by result.txt change, then result.tar will be rebuilt.

To find out more:

Synopsis

Writing a build system

When writing a Shake build system, start by defining what you want, then write rules with %> to produce the results. Before calling cmd you should ensure that any files the command requires are demanded with calls to need. We offer the following advice to Shake users:

  • If ghc --make or cabal is capable of building your project, use that instead. Custom build systems are necessary for many complex projects, but many projects are not complex.
  • The shakeArgs function automatically handles command line arguments. To define non-file targets use phony.
  • Put all result files in a distinguished directory, for example _make. You can implement a clean command by removing that directory, using removeFilesAfter "_make" ["//*"].
  • To obtain parallel builds set shakeThreads to a number greater than 1.
  • Lots of compilers produce .o files. To avoid overlapping rules, use .c.o for C compilers, .hs.o for Haskell compilers etc.
  • Do not be afraid to mix Shake rules, system commands and other Haskell libraries -- use each for what it does best.
  • The more accurate the dependencies are, the better. Use additional rules like doesFileExist and getDirectoryFiles to track information other than just the contents of files. For information in the environment that you suspect will change regularly (perhaps ghc version number), either write the information to a file with alwaysRerun and writeFileChanged, or use addOracle.

GHC build flags

For large build systems the choice of GHC flags can have a significant impact. We recommend:

ghc --make MyBuildSystem -threaded -rtsopts "-with-rtsopts=-I0 -qg -qb"
  • -rtsopts: Allow the setting of further GHC options at runtime.
  • -I0: Disable idle garbage collection, to avoid frequent unnecessary garbage collection, see a full explanation.
  • With GHC 7.6 and before, omit -threaded: GHC bug 7646 can cause a race condition in build systems that write files then read them. Omitting -threaded will still allow your cmd actions to run in parallel, so most build systems will still run in parallel.
  • With GHC 7.8 and later you may add -threaded, and pass the options -qg -qb to -with-rtsopts to disable parallel garbage collection. Parallel garbage collection in Shake programs typically goes slower than sequential garbage collection, while occupying many cores that could be used for running system commands.

Core

shake :: ShakeOptions -> Rules () -> IO () Source #

Main entry point for running Shake build systems. For an example see the top of the module Development.Shake. Use ShakeOptions to specify how the system runs, and Rules to specify what to build. The function will throw an exception if the build fails.

To use command line flags to modify ShakeOptions see shakeArgs.

data Rules a Source #

Define a set of rules. Rules can be created with calls to functions such as %> or action. Rules are combined with either the Monoid instance, or (more commonly) the Monad instance and do notation. To define your own custom types of rule, see Development.Shake.Rule.

Instances

Monad Rules Source # 

Methods

(>>=) :: Rules a -> (a -> Rules b) -> Rules b #

(>>) :: Rules a -> Rules b -> Rules b #

return :: a -> Rules a #

fail :: String -> Rules a #

Functor Rules Source # 

Methods

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

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

MonadFix Rules Source # 

Methods

mfix :: (a -> Rules a) -> Rules a #

Applicative Rules Source # 

Methods

pure :: a -> Rules a #

(<*>) :: Rules (a -> b) -> Rules a -> Rules b #

liftA2 :: (a -> b -> c) -> Rules a -> Rules b -> Rules c #

(*>) :: Rules a -> Rules b -> Rules b #

(<*) :: Rules a -> Rules b -> Rules a #

MonadIO Rules Source # 

Methods

liftIO :: IO a -> Rules a #

Semigroup a => Semigroup (Rules a) Source # 

Methods

(<>) :: Rules a -> Rules a -> Rules a #

sconcat :: NonEmpty (Rules a) -> Rules a #

stimes :: Integral b => b -> Rules a -> Rules a #

(Semigroup a, Monoid a) => Monoid (Rules a) Source # 

Methods

mempty :: Rules a #

mappend :: Rules a -> Rules a -> Rules a #

mconcat :: [Rules a] -> Rules a #

action :: Action a -> Rules () Source #

Run an action, usually used for specifying top-level requirements.

main = shake shakeOptions $ do
   action $ do
       b <- doesFileExist "file.src"
       when b $ need ["file.out"]

This action builds file.out, but only if file.src exists. The action will be run in every build execution (unless withoutActions is used), so only cheap operations should be performed. All arguments to action may be run in parallel, in any order.

For the standard requirement of only needing a fixed list of files in the action, see want.

withoutActions :: Rules () -> Rules () Source #

Remove all actions specified in a set of rules, usually used for implementing command line specification of what to build.

alternatives :: Rules () -> Rules () Source #

Change the matching behaviour of rules so rules do not have to be disjoint, but are instead matched in order. Only recommended for small blocks containing a handful of rules.

alternatives $ do
    "hello.*" %> \out -> writeFile' out "hello.*"
    "*.txt" %> \out -> writeFile' out "*.txt"

In this example hello.txt will match the first rule, instead of raising an error about ambiguity. Inside alternatives the priority of each rule is not used to determine which rule matches, but the resulting match uses that priority compared to the rules outside the alternatives block.

priority :: Double -> Rules () -> Rules () Source #

Change the priority of a given set of rules, where higher priorities take precedence. All matching rules at a given priority must be disjoint, or an error is raised. All builtin Shake rules have priority between 0 and 1. Excessive use of priority is discouraged. As an example:

priority 4 $ "hello.*" %> \out -> writeFile' out "hello.*"
priority 8 $ "*.txt" %> \out -> writeFile' out "*.txt"

In this example hello.txt will match the second rule, instead of raising an error about ambiguity.

The priority function obeys the invariants:

priority p1 (priority p2 r1) === priority p1 r1
priority p1 (r1 >> r2) === priority p1 r1 >> priority p1 r2

data Action a Source #

The Action monad, use liftIO to raise IO actions into it, and need to execute files. Action values are used by addUserRule and action. The Action monad tracks the dependencies of a rule. To raise an exception call error, fail or liftIO . throwIO.

Instances

Monad Action Source # 

Methods

(>>=) :: Action a -> (a -> Action b) -> Action b #

(>>) :: Action a -> Action b -> Action b #

return :: a -> Action a #

fail :: String -> Action a #

Functor Action Source # 

Methods

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

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

MonadFail Action Source # 

Methods

fail :: String -> Action a #

Applicative Action Source # 

Methods

pure :: a -> Action a #

(<*>) :: Action (a -> b) -> Action a -> Action b #

liftA2 :: (a -> b -> c) -> Action a -> Action b -> Action c #

(*>) :: Action a -> Action b -> Action b #

(<*) :: Action a -> Action b -> Action a #

MonadIO Action Source # 

Methods

liftIO :: IO a -> Action a #

CmdResult r => CmdArguments (Action r) Source # 

traced :: String -> IO a -> Action a Source #

Write an action to the trace list, along with the start/end time of running the IO action. The cmd and command functions automatically call traced. The trace list is used for profile reports (see shakeReport).

By default traced prints some useful extra context about what Shake is building, e.g.:

# traced message (for myobject.o)

To suppress the output of traced (for example you want more control over the message using putNormal), use the quietly combinator.

liftIO :: MonadIO m => forall a. IO a -> m a #

Lift a computation from the IO monad.

actionOnException :: Action a -> IO b -> Action a Source #

If an exception is raised by the Action, perform some IO.

actionFinally :: Action a -> IO b -> Action a Source #

After an Action, perform some IO, even if there is an exception.

runAfter :: IO () -> Action () Source #

Specify an action to be run after the database has been closed, if building completes successfully.

data ShakeException Source #

Error representing all expected exceptions thrown by Shake. Problems when executing rules will be raising using this exception type.

Constructors

ShakeException 

Fields

Configuration

data ShakeOptions Source #

Options to control the execution of Shake, usually specified by overriding fields in shakeOptions:

 shakeOptions{shakeThreads=4, shakeReport=["report.html"]}

The Data instance for this type reports the shakeProgress and shakeOutput fields as having the abstract type Hidden, because Data cannot be defined for functions or TypeReps.

Constructors

ShakeOptions 

Fields

  • shakeFiles :: FilePath

    Defaults to .shake. The directory used for storing Shake metadata files. All metadata files will be named shakeFiles/.shake.file-name, for some file-name. If the shakeFiles directory does not exist it will be created.

  • shakeThreads :: Int

    Defaults to 1. Maximum number of rules to run in parallel, similar to make --jobs=N. For many build systems, a number equal to or slightly less than the number of physical processors works well. Use 0 to match the detected number of processors (when 0, getShakeOptions will return the number of threads used).

  • shakeVersion :: String

    Defaults to "1". The version number of your build rules. Change the version number to force a complete rebuild, such as when making significant changes to the rules that require a wipe. The version number should be set in the source code, and not passed on the command line.

  • shakeVerbosity :: Verbosity

    Defaults to Normal. What level of messages should be printed out.

  • shakeStaunch :: Bool

    Defaults to False. Operate in staunch mode, where building continues even after errors, similar to make --keep-going.

  • shakeReport :: [FilePath]

    Defaults to []. Write a profiling report to a file, showing which rules rebuilt, why, and how much time they took. Useful for improving the speed of your build systems. If the file extension is .json it will write JSON data; if .js it will write Javascript; if .trace it will write trace events (load into about://tracing in Chrome); otherwise it will write HTML.

  • shakeLint :: Maybe Lint

    Defaults to Nothing. Perform sanity checks during building, see Lint for details.

  • shakeLintInside :: [FilePath]

    Directories in which the files will be tracked by the linter.

  • shakeLintIgnore :: [FilePattern]

    File patterns which are ignored from linter tracking, a bit like calling trackAllow in every rule.

  • shakeCommandOptions :: [CmdOption]

    Defaults to []. Additional options to be passed to all command invocations.

  • shakeFlush :: Maybe Double

    Defaults to Just 10. How often to flush Shake metadata files in seconds, or Nothing to never flush explicitly. It is possible that on abnormal termination (not Haskell exceptions) any rules that completed in the last shakeFlush seconds will be lost.

  • shakeRebuild :: [(Rebuild, FilePattern)]

    What to rebuild

  • shakeAbbreviations :: [(String, String)]

    Defaults to []. A list of substrings that should be abbreviated in status messages, and their corresponding abbreviation. Commonly used to replace the long paths (e.g. .make/i586-linux-gcc/output) with an abbreviation (e.g. $OUT).

  • shakeStorageLog :: Bool

    Defaults to False. Write a message to shakeFiles/.shake.storage.log whenever a storage event happens which may impact on the current stored progress. Examples include database version number changes, database compaction or corrupt files.

  • shakeLineBuffering :: Bool

    Defaults to True. Change stdout and stderr to line buffering while running Shake.

  • shakeTimings :: Bool

    Defaults to False. Print timing information for each stage at the end.

  • shakeRunCommands :: Bool

    Default to True. Should you run command line actions, set to False to skip actions whose output streams and exit code are not used. Useful for profiling the non-command portion of the build system.

  • shakeChange :: Change

    Default to ChangeModtime. How to check if a file has changed, see Change for details.

  • shakeCreationCheck :: Bool

    Default to True. After running a rule to create a file, is it an error if the file does not exist. Provided for compatibility with make and ninja (which have ugly file creation semantics).

  • shakeLiveFiles :: [FilePath]

    Default to []. After the build system completes, write a list of all files which were live in that run, i.e. those which Shake checked were valid or rebuilt. Produces best answers if nothing rebuilds.

  • shakeVersionIgnore :: Bool

    Defaults to False. Ignore any differences in shakeVersion.

  • shakeColor :: Bool

    Defaults to False. Whether to colorize the output.

  • shakeProgress :: IO Progress -> IO ()

    Defaults to no action. A function called when the build starts, allowing progress to be reported. The function is called on a separate thread, and that thread is killed when the build completes. For applications that want to display progress messages, progressSimple is often sufficient, but more advanced users should look at the Progress data type.

  • shakeOutput :: Verbosity -> String -> IO ()

    Defaults to writing using putStrLn. A function called to output messages from Shake, along with the Verbosity at which that message should be printed. This function will be called atomically from all other shakeOutput functions. The Verbosity will always be greater than or higher than shakeVerbosity.

  • shakeExtra :: HashMap TypeRep Dynamic

    This a map which can be used to store arbitrary extra information that a user may need when writing rules. The key of each entry must be the dynTypeRep of the value. Insert values using addShakeExtra and retrieve them using getShakeExtra. The correct way to use this field is to define a hidden newtype for the key, so that conflicts cannot occur.

Instances

Data ShakeOptions Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ShakeOptions -> c ShakeOptions #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ShakeOptions #

toConstr :: ShakeOptions -> Constr #

dataTypeOf :: ShakeOptions -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ShakeOptions) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ShakeOptions) #

gmapT :: (forall b. Data b => b -> b) -> ShakeOptions -> ShakeOptions #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ShakeOptions -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ShakeOptions -> r #

gmapQ :: (forall d. Data d => d -> u) -> ShakeOptions -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ShakeOptions -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ShakeOptions -> m ShakeOptions #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ShakeOptions -> m ShakeOptions #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ShakeOptions -> m ShakeOptions #

Show ShakeOptions Source # 

data Rebuild Source #

The current assumptions made by the build system, used by shakeRebuild. These options allow the end user to specify that any rules run are either to be treated as clean, or as dirty, regardless of what the build system thinks.

These assumptions only operate on files reached by the current action commands. Any other files in the database are left unchanged.

Constructors

RebuildNow

Assume these files are dirty and require rebuilding. for benchmarking rebuild speed and for rebuilding if untracked dependencies have changed. This flag is safe, but may cause more rebuilding than necessary.

RebuildNormal

Useful to reset the rebuild status to how it was before, equivalent to passing no Rebuild flags.

RebuildLater

This assumption is unsafe, and may lead to incorrect build results in this run. Assume these files are clean in this run, but test them normally in future runs.

Instances

Bounded Rebuild Source # 
Enum Rebuild Source # 
Eq Rebuild Source # 

Methods

(==) :: Rebuild -> Rebuild -> Bool #

(/=) :: Rebuild -> Rebuild -> Bool #

Data Rebuild Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Rebuild -> c Rebuild #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Rebuild #

toConstr :: Rebuild -> Constr #

dataTypeOf :: Rebuild -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Rebuild) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Rebuild) #

gmapT :: (forall b. Data b => b -> b) -> Rebuild -> Rebuild #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Rebuild -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Rebuild -> r #

gmapQ :: (forall d. Data d => d -> u) -> Rebuild -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Rebuild -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Rebuild -> m Rebuild #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Rebuild -> m Rebuild #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Rebuild -> m Rebuild #

Ord Rebuild Source # 
Read Rebuild Source # 
Show Rebuild Source # 

data Lint Source #

Which lint checks to perform, used by shakeLint.

Constructors

LintBasic

The most basic form of linting. Checks that the current directory does not change and that results do not change after they are first written. Any calls to needed will assert that they do not cause a rule to be rebuilt.

LintFSATrace

Track which files are accessed by command line programs using fsatrace.

Instances

Bounded Lint Source # 
Enum Lint Source # 

Methods

succ :: Lint -> Lint #

pred :: Lint -> Lint #

toEnum :: Int -> Lint #

fromEnum :: Lint -> Int #

enumFrom :: Lint -> [Lint] #

enumFromThen :: Lint -> Lint -> [Lint] #

enumFromTo :: Lint -> Lint -> [Lint] #

enumFromThenTo :: Lint -> Lint -> Lint -> [Lint] #

Eq Lint Source # 

Methods

(==) :: Lint -> Lint -> Bool #

(/=) :: Lint -> Lint -> Bool #

Data Lint Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Lint -> c Lint #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Lint #

toConstr :: Lint -> Constr #

dataTypeOf :: Lint -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Lint) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Lint) #

gmapT :: (forall b. Data b => b -> b) -> Lint -> Lint #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Lint -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Lint -> r #

gmapQ :: (forall d. Data d => d -> u) -> Lint -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Lint -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Lint -> m Lint #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Lint -> m Lint #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Lint -> m Lint #

Ord Lint Source # 

Methods

compare :: Lint -> Lint -> Ordering #

(<) :: Lint -> Lint -> Bool #

(<=) :: Lint -> Lint -> Bool #

(>) :: Lint -> Lint -> Bool #

(>=) :: Lint -> Lint -> Bool #

max :: Lint -> Lint -> Lint #

min :: Lint -> Lint -> Lint #

Read Lint Source # 
Show Lint Source # 

Methods

showsPrec :: Int -> Lint -> ShowS #

show :: Lint -> String #

showList :: [Lint] -> ShowS #

data Change Source #

How should you determine if a file has changed, used by shakeChange. The most common values are ChangeModtime (the default, very fast, touch causes files to rebuild) and ChangeModtimeAndDigestInput (slightly slower, touch and switching git branches does not cause input files to rebuild).

Constructors

ChangeModtime

Compare equality of modification timestamps, a file has changed if its last modified time changes. A touch will force a rebuild. This mode is fast and usually sufficiently accurate, so is the default.

ChangeDigest

Compare equality of file contents digests, a file has changed if its digest changes. A touch will not force a rebuild. Use this mode if modification times on your file system are unreliable.

ChangeModtimeAndDigest

A file is rebuilt if both its modification time and digest have changed. For efficiency reasons, the modification time is checked first, and if that has changed, the digest is checked.

ChangeModtimeAndDigestInput

Use ChangeModtimeAndDigest for input/source files and ChangeModtime for output files. An input file is one which is a dependency but is not built by Shake as it has no matching rule and already exists on the file system.

ChangeModtimeOrDigest

A file is rebuilt if either its modification time or its digest has changed. A touch will force a rebuild, but even if a files modification time is reset afterwards, changes will also cause a rebuild.

Instances

Bounded Change Source # 
Enum Change Source # 
Eq Change Source # 

Methods

(==) :: Change -> Change -> Bool #

(/=) :: Change -> Change -> Bool #

Data Change Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Change -> c Change #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Change #

toConstr :: Change -> Constr #

dataTypeOf :: Change -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Change) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Change) #

gmapT :: (forall b. Data b => b -> b) -> Change -> Change #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Change -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Change -> r #

gmapQ :: (forall d. Data d => d -> u) -> Change -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Change -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Change -> m Change #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Change -> m Change #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Change -> m Change #

Ord Change Source # 
Read Change Source # 
Show Change Source # 

getShakeOptions :: Action ShakeOptions Source #

Get the initial ShakeOptions, these will not change during the build process.

getHashedShakeVersion :: [FilePath] -> IO String Source #

Get a checksum of a list of files, suitable for using as shakeVersion. This will trigger a rebuild when the Shake rules defined in any of the files are changed. For example:

main = do
    ver <- getHashedShakeVersion ["Shakefile.hs"]
    shakeArgs shakeOptions{shakeVersion = ver} ...

To automatically detect the name of the current file, turn on the TemplateHaskell extension and write $(LitE . StringL . loc_filename <$> location).

This feature can be turned off during development by passing the flag --no-rule-version or setting shakeVersionIgnore to True.

getShakeExtra :: Typeable a => Action (Maybe a) Source #

Get an item from shakeExtra, using the requested type as the key. Fails if the value found at this key does not match the requested type.

addShakeExtra :: Typeable a => a -> HashMap TypeRep Dynamic -> HashMap TypeRep Dynamic Source #

Add a properly structued value to shakeExtra which can be retrieved with getShakeExtra.

Command line

shakeArgs :: ShakeOptions -> Rules () -> IO () Source #

Run a build system using command line arguments for configuration. The available flags are those from shakeOptDescrs, along with a few additional make compatible flags that are not represented in ShakeOptions, such as --print-directory. If there are no file arguments then the Rules are used directly, otherwise the file arguments are wanted (after calling withoutActions). As an example:

main = shakeArgs shakeOptions{shakeFiles = "_make", shakeProgress = progressSimple} $ do
    phony "clean" $ removeFilesAfter "_make" ["//*"]
    want ["_make/neil.txt","_make/emily.txt"]
    "_make/*.txt" %> \out ->
        ... build action here ...

This build system will default to building neil.txt and emily.txt, while showing progress messages, and putting the Shake files in locations such as _make/.database. Some example command line flags:

  • main --no-progress will turn off progress messages.
  • main -j6 will build on 6 threads.
  • main --help will display a list of supported flags.
  • main clean will not build anything, but will remove the _make directory, including the any shakeFiles.
  • main _make/henry.txt will not build neil.txt or emily.txt, but will instead build henry.txt.

shakeArgsWith :: ShakeOptions -> [OptDescr (Either String a)] -> ([a] -> [String] -> IO (Maybe (Rules ()))) -> IO () Source #

A version of shakeArgs with more flexible handling of command line arguments. The caller of shakeArgsWith can add additional flags (the second argument) and chose how to convert the flags/arguments into rules (the third argument). Given:

shakeArgsWith opts flags (\flagValues argValues -> result)
  • opts is the initial ShakeOptions value, which may have some fields overriden by command line flags. This argument is usually shakeOptions, perhaps with a few fields overriden.
  • flags is a list of flag descriptions, which either produce a String containing an error message (typically for flags with invalid arguments, .e.g. Left "could not parse as int"), or a value that is passed as flagValues. If you have no custom flags, pass [].
  • flagValues is a list of custom flags that the user supplied. If flags == [] then this list will be [].
  • argValues is a list of non-flag arguments, which are often treated as files and passed to want.
  • result should produce a Nothing to indicate that no building needs to take place, or a Just providing the rules that should be used.

As an example of a build system that can use either gcc or distcc for compiling:

import System.Console.GetOpt

data Flags = DistCC deriving Eq
flags = [Option "" ["distcc"] (NoArg $ Right DistCC) "Run distributed."]

main = shakeArgsWith shakeOptions flags $ \flags targets -> return $ Just $ do
    if null targets then want ["result.exe"] else want targets
    let compiler = if DistCC `elem` flags then "distcc" else "gcc"
    "*.o" %> \out -> do
        need ...
        cmd compiler ...
    ...

Now you can pass --distcc to use the distcc compiler.

shakeArgsOptionsWith :: ShakeOptions -> [OptDescr (Either String a)] -> (ShakeOptions -> [a] -> [String] -> IO (Maybe (ShakeOptions, Rules ()))) -> IO () Source #

Like shakeArgsWith, but also lets you manipulate the ShakeOptions.

shakeOptDescrs :: [OptDescr (Either String (ShakeOptions -> ShakeOptions))] Source #

A list of command line options that can be used to modify ShakeOptions. Each option returns either an error message (invalid argument to the flag) or a function that changes some fields in ShakeOptions. The command line flags are make compatible where possbile, but additional flags have been added for the extra options Shake supports.

Progress reporting

data Progress Source #

Information about the current state of the build, obtained by either passing a callback function to shakeProgress (asynchronous output) or getProgress (synchronous output). Typically a build system will pass progressDisplay to shakeProgress, which will poll this value and produce status messages.

Constructors

Progress 

Fields

Instances

Eq Progress Source # 
Data Progress Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Progress -> c Progress #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Progress #

toConstr :: Progress -> Constr #

dataTypeOf :: Progress -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Progress) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Progress) #

gmapT :: (forall b. Data b => b -> b) -> Progress -> Progress #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Progress -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Progress -> r #

gmapQ :: (forall d. Data d => d -> u) -> Progress -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Progress -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Progress -> m Progress #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Progress -> m Progress #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Progress -> m Progress #

Ord Progress Source # 
Read Progress Source # 
Show Progress Source # 
Semigroup Progress Source # 
Monoid Progress Source # 

progressSimple :: IO Progress -> IO () Source #

A simple method for displaying progress messages, suitable for using as shakeProgress. This function writes the current progress to the titlebar every five seconds using progressTitlebar, and calls any shake-progress program on the $PATH using progressProgram.

progressDisplay :: Double -> (String -> IO ()) -> IO Progress -> IO () Source #

Given a sampling interval (in seconds) and a way to display the status message, produce a function suitable for using as shakeProgress. This function polls the progress information every n seconds, produces a status message and displays it using the display function.

Typical status messages will take the form of 1m25s (15%), indicating that the build is predicted to complete in 1 minute 25 seconds (85 seconds total), and 15% of the necessary build time has elapsed. This function uses past observations to predict future behaviour, and as such, is only guessing. The time is likely to go up as well as down, and will be less accurate from a clean build (as the system has fewer past observations).

The current implementation is to predict the time remaining (based on timeTodo) and the work already done (timeBuilt). The percentage is then calculated as remaining / (done + remaining), while time left is calculated by scaling remaining by the observed work rate in this build, roughly done / time_elapsed.

progressTitlebar :: String -> IO () Source #

Set the title of the current console window to the given text. If the environment variable $TERM is set to xterm this uses xterm escape sequences. On Windows, if not detected as an xterm, this function uses the SetConsoleTitle API.

progressProgram :: IO (String -> IO ()) Source #

Call the program shake-progress if it is on the $PATH. The program is called with the following arguments:

  • --title=string - the string passed to progressProgram.
  • --state=Normal, or one of NoProgress, Normal, or Error to indicate what state the progress bar should be in.
  • --value=25 - the percent of the build that has completed, if not in NoProgress state.

The program will not be called consecutively with the same --state and --value options.

Windows 7 or higher users can get taskbar progress notifications by placing the following program in their $PATH: https://github.com/ndmitchell/shake/releases.

getProgress :: Action Progress Source #

Get the current Progress structure, as would be returned by shakeProgress.

Verbosity

data Verbosity Source #

The verbosity data type, used by shakeVerbosity.

Constructors

Silent

Don't print any messages.

Quiet

Only print essential messages, typically errors.

Normal

Print errors and # command-name (for file-name) when running a traced command.

Loud

Print errors and full command lines when running a command or cmd command.

Chatty

Print errors, full command line and status messages when starting a rule.

Diagnostic

Print messages for virtually everything (mostly for debugging).

Instances

Bounded Verbosity Source # 
Enum Verbosity Source # 
Eq Verbosity Source # 
Data Verbosity Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Verbosity -> c Verbosity #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Verbosity #

toConstr :: Verbosity -> Constr #

dataTypeOf :: Verbosity -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Verbosity) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Verbosity) #

gmapT :: (forall b. Data b => b -> b) -> Verbosity -> Verbosity #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Verbosity -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Verbosity -> r #

gmapQ :: (forall d. Data d => d -> u) -> Verbosity -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Verbosity -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Verbosity -> m Verbosity #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Verbosity -> m Verbosity #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Verbosity -> m Verbosity #

Ord Verbosity Source # 
Read Verbosity Source # 
Show Verbosity Source # 

getVerbosity :: Action Verbosity Source #

Get the current verbosity level, originally set by shakeVerbosity. If you want to output information to the console, you are recommended to use putLoud / putNormal / putQuiet, which ensures multiple messages are not interleaved. The verbosity can be modified locally by withVerbosity.

putLoud :: String -> Action () Source #

Write an unimportant message to the output, only shown when shakeVerbosity is higher than normal (Loud or above). The output will not be interleaved with any other Shake messages (other than those generated by system commands).

putNormal :: String -> Action () Source #

Write a normal priority message to the output, only supressed when shakeVerbosity is Quiet or Silent. The output will not be interleaved with any other Shake messages (other than those generated by system commands).

putQuiet :: String -> Action () Source #

Write an important message to the output, only supressed when shakeVerbosity is Silent. The output will not be interleaved with any other Shake messages (other than those generated by system commands).

withVerbosity :: Verbosity -> Action a -> Action a Source #

Run an action with a particular verbosity level. Will not update the shakeVerbosity returned by getShakeOptions and will not have any impact on Diagnostic tracing.

quietly :: Action a -> Action a Source #

Run an action with Quiet verbosity, in particular messages produced by traced (including from cmd or command) will not be printed to the screen. Will not update the shakeVerbosity returned by getShakeOptions and will not turn off any Diagnostic tracing.

Running commands

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:

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

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, use cmd_.

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_ :: (CmdArguments args, Unit args) => args :-> Action () Source #

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

Instances

CmdString a => CmdResult (Stdout a) Source # 

Methods

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

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

Instances

CmdString a => CmdResult (Stderr a) Source # 

Methods

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

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

Instances

CmdString a => CmdResult (Stdouterr a) Source # 

Methods

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

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

Instances

CmdResult Exit Source # 

Methods

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

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

CmdResult Process Source # 

Methods

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

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

Instances

CmdResult CmdTime Source # 

Methods

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

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

Instances

CmdResult CmdLine Source # 

Methods

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

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

Instances

CmdResult () Source # 

Methods

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

CmdResult ExitCode Source # 

Methods

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

CmdResult ProcessHandle Source # 

Methods

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

CmdResult CmdLine Source # 

Methods

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

CmdResult CmdTime Source # 

Methods

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

CmdResult Process Source # 

Methods

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

CmdResult Exit Source # 

Methods

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

CmdString a => CmdResult (Stdouterr a) Source # 

Methods

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

CmdString a => CmdResult (Stderr a) Source # 

Methods

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

CmdString a => CmdResult (Stdout a) Source # 

Methods

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

(CmdResult x1, CmdResult x2) => CmdResult (x1, x2) Source # 

Methods

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

(CmdResult x1, CmdResult x2, CmdResult x3) => CmdResult (x1, x2, x3) Source # 

Methods

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

(CmdResult x1, CmdResult x2, CmdResult x3, CmdResult x4) => CmdResult (x1, x2, x3, x4) Source # 

Methods

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

(CmdResult x1, CmdResult x2, CmdResult x3, CmdResult x4, CmdResult x5) => CmdResult (x1, x2, x3, x4, x5) Source # 

Methods

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

class CmdString a Source #

The allowable String-like values that can be captured.

Minimal complete definition

cmdString

Instances

CmdString () Source # 

Methods

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

CmdString String Source # 

Methods

cmdString :: (Str, Str -> String)

CmdString ByteString Source # 

Methods

cmdString :: (Str, Str -> ByteString)

CmdString ByteString Source # 

Methods

cmdString :: (Str, Str -> ByteString)

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.

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.

Instances

Eq CmdOption Source # 
Data CmdOption Source # 

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 :: (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 # 
Show CmdOption Source # 
IsCmdArgument CmdOption Source # 
IsCmdArgument [CmdOption] 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.

Explicit parallelism

parallel :: [Action a] -> Action [a] Source #

Execute a list of actions in parallel. In most cases need will be more appropriate to benefit from parallelism.

forP :: [a] -> (a -> Action b) -> Action [b] Source #

A parallel version of forM.

par :: Action a -> Action b -> Action (a, b) Source #

Execute two operations in parallel, based on parallel.

Utility functions

copyFile' :: FilePath -> FilePath -> Action () Source #

copyFile' old new copies the existing file from old to new. The old file will be tracked as a dependency. Also creates the new directory if necessary.

copyFileChanged :: FilePath -> FilePath -> Action () Source #

copyFileChanged old new copies the existing file from old to new, if the contents have changed. The old file will be tracked as a dependency. Also creates the new directory if necessary.

readFile' :: FilePath -> Action String Source #

Read a file, after calling need. The argument file will be tracked as a dependency.

readFileLines :: FilePath -> Action [String] Source #

A version of readFile' which also splits the result into lines. The argument file will be tracked as a dependency.

writeFile' :: MonadIO m => FilePath -> String -> m () Source #

Write a file, lifted to the Action monad.

writeFileLines :: MonadIO m => FilePath -> [String] -> m () Source #

A version of writeFile' which writes out a list of lines.

writeFileChanged :: MonadIO m => FilePath -> String -> m () Source #

Write a file, but only if the contents would change.

removeFiles :: FilePath -> [FilePattern] -> IO () Source #

Remove all files and directories that match any of the patterns within a directory. Some examples:

removeFiles "output" ["//*"]        -- delete everything inside 'output'
removeFiles "output" ["//"]         -- delete 'output' itself
removeFiles "." ["//*.hi","//*.o"] -- delete all '.hi' and '.o' files

If the argument directory is missing no error is raised. This function will follow symlinks, so should be used with care.

This function is often useful when writing a clean action for your build system, often as a phony rule.

removeFilesAfter :: FilePath -> [FilePattern] -> Action () Source #

Remove files, like removeFiles, but executed after the build completes successfully. Useful for implementing clean actions that delete files Shake may have open for building.

withTempFile :: (FilePath -> Action a) -> Action a Source #

Create a temporary file in the temporary directory. The file will be deleted after the action completes (provided the file is not still open). The FilePath will not have any file extension, will exist, and will be zero bytes long. If you require a file with a specific name, use withTempDir.

withTempDir :: (FilePath -> Action a) -> Action a Source #

Create a temporary directory inside the system temporary directory. The directory will be deleted after the action completes. As an example:

withTempDir $ \mydir -> do
   putNormal $ "Temp directory is " ++ mydir
   writeFile' (mydir </> "test.txt") "writing out a temp file"

withTempFileWithin :: FilePath -> (FilePath -> Action a) -> Action a Source #

Like withTempFile but using a custom temporary directory.

withTempDirWithin :: FilePath -> (FilePath -> Action a) -> Action a Source #

Like withTempDir but using a custom temporary directory.

File rules

need :: [FilePath] -> Action () Source #

Add a dependency on the file arguments, ensuring they are built before continuing. The file arguments may be built in parallel, in any order. This function is particularly necessary when calling cmd or command. As an example:

"//*.rot13" %> \out -> do
    let src = dropExtension out
    need [src]
    cmd "rot13" [src] "-o" [out]

Usually need [foo,bar] is preferable to need [foo] >> need [bar] as the former allows greater parallelism, while the latter requires foo to finish building before starting to build bar.

This function should not be called with wildcards (e.g. *.txt - use getDirectoryFiles to expand them), environment variables (e.g. $HOME - use getEnv to expand them) or directories (directories cannot be tracked directly - track files within the directory instead).

want :: [FilePath] -> Rules () Source #

Require that the argument files are built by the rules, used to specify the target.

main = shake shakeOptions $ do
   want ["Main.exe"]
   ...

This program will build Main.exe, given sufficient rules. All arguments to all want calls may be built in parallel, in any order.

This function is defined in terms of action and need, use action if you need more complex targets than want allows.

(%>) :: FilePattern -> (FilePath -> Action ()) -> Rules () infix 1 Source #

Define a rule that matches a FilePattern, see ?== for the pattern rules. Patterns with no wildcards have higher priority than those with wildcards, and no file required by the system may be matched by more than one pattern at the same priority (see priority and alternatives to modify this behaviour). This function will create the directory for the result file, if necessary.

"*.asm.o" %> \out -> do
    let src = dropExtension out
    need [src]
    cmd "as" [src] "-o" [out]

To define a build system for multiple compiled languages, we recommend using .asm.o, .cpp.o, .hs.o, to indicate which language produces an object file. I.e., the file foo.cpp produces object file foo.cpp.o.

Note that matching is case-sensitive, even on Windows.

If the Action completes successfully the file is considered up-to-date, even if the file has not changed.

(|%>) :: [FilePattern] -> (FilePath -> Action ()) -> Rules () infix 1 Source #

Define a set of patterns, and if any of them match, run the associated rule. Defined in terms of %>. Think of it as the OR (||) equivalent of %>.

(?>) :: (FilePath -> Bool) -> (FilePath -> Action ()) -> Rules () infix 1 Source #

Define a rule to build files. If the first argument returns True for a given file, the second argument will be used to build it. Usually %> is sufficient, but ?> gives additional power. For any file used by the build system, only one rule should return True. This function will create the directory for the result file, if necessary.

(all isUpper . takeBaseName) ?> \out -> do
    let src = replaceBaseName out $ map toLower $ takeBaseName out
    writeFile' out . map toUpper =<< readFile' src

If the Action completes successfully the file is considered up-to-date, even if the file has not changed.

phony :: String -> Action () -> Rules () Source #

Declare a Make-style phony action. A phony target does not name a file (despite living in the same namespace as file rules); rather, it names some action to be executed when explicitly requested. You can demand phony rules using want. (And need, although that's not recommended.)

Phony actions are intended to define recipes that can be executed by the user. If you need a phony action in a rule then every execution where that rule is required will rerun both the rule and the phony action. However, note that phony actions are never executed more than once in a single build run.

In make, the .PHONY attribute on non-file-producing rules has a similar effect. However, while in make it is acceptable to omit the .PHONY attribute as long as you don't create the file in question, a Shake rule which behaves this way will fail lint. Use a phony rule! For file-producing rules which should be rerun every execution of Shake, see alwaysRerun.

(~>) :: String -> Action () -> Rules () infix 1 Source #

Infix operator alias for phony, for sake of consistency with normal rules.

phonys :: (String -> Maybe (Action ())) -> Rules () Source #

A predicate version of phony, return Just with the Action for the matching rules.

(&%>) :: [FilePattern] -> ([FilePath] -> Action ()) -> Rules () infix 1 Source #

Define a rule for building multiple files at the same time. Think of it as the AND (&&) equivalent of %>. As an example, a single invocation of GHC produces both .hi and .o files:

["*.o","*.hi"] &%> \[o,hi] -> do
    let hs = o -<.> "hs"
    need ... -- all files the .hs import
    cmd "ghc -c" [hs]

However, in practice, it's usually easier to define rules with %> and make the .hi depend on the .o. When defining rules that build multiple files, all the FilePattern values must have the same sequence of // and * wildcards in the same order. This function will create directories for the result files, if necessary.

(&?>) :: (FilePath -> Maybe [FilePath]) -> ([FilePath] -> Action ()) -> Rules () infix 1 Source #

Define a rule for building multiple files at the same time, a more powerful and more dangerous version of &%>. Think of it as the AND (&&) equivalent of ?>.

Given an application test &?> ..., test should return Just if the rule applies, and should return the list of files that will be produced. This list must include the file passed as an argument and should obey the invariant:

forAll $ \x ys -> test x == Just ys ==> x `elem` ys && all ((== Just ys) . test) ys

As an example of a function satisfying the invariaint:

test x | takeExtension x `elem` [".hi",".o"]
       = Just [dropExtension x <.> "hi", dropExtension x <.> "o"]
test _ = Nothing

Regardless of whether Foo.hi or Foo.o is passed, the function always returns [Foo.hi, Foo.o].

orderOnly :: [FilePath] -> Action () Source #

Define order-only dependencies, these are dependencies that will always be built before continuing, but which aren't dependencies of this action. Mostly useful for defining generated dependencies you think might be real dependencies. If they turn out to be real dependencies, you should add an explicit dependency afterwards.

"source.o" %> \out -> do
    orderOnly ["header.h"]
    cmd_ "gcc -c source.c -o source.o -MMD -MF source.m"
    neededMakefileDependencies "source.m"

If header.h is included by source.c then the call to needMakefileDependencies will cause it to be added as a real dependency. If it isn't, then the rule won't rebuild if it changes.

orderOnlyAction :: Action a -> Action a Source #

Run an action but do not depend on anything the action uses. A more general version of orderOnly.

type FilePattern = String Source #

A type synonym for file patterns, containing // and *. For the syntax and semantics of FilePattern see ?==.

Most normaliseExd FilePath values are suitable as FilePattern values which match only that specific file. On Windows \ is treated as equivalent to /.

You can write FilePattern values as a literal string, or build them up using the operators <.>, </> and <//>. However, beware that:

  • On Windows, use <.> from Development.Shake.FilePath instead of from System.FilePath - otherwise "//*" <.> exe results in "//*\\.exe".
  • If the second argument of </> has a leading path separator (namely /) then the second argument will be returned.

(?==) :: FilePattern -> FilePath -> Bool Source #

Match a FilePattern against a FilePath, There are three special forms:

  • * matches an entire path component, excluding any separators.
  • // matches an arbitrary number of path components, including absolute path prefixes.
  • ** as a path component matches an arbitrary number of path components, but not absolute path prefixes. Currently considered experimental.

Some examples:

  • test.c matches test.c and nothing else.
  • *.c matches all .c files in the current directory, so file.c matches, but file.h and dir/file.c don't.
  • //*.c matches all .c files anywhere on the filesystem, so file.c, dir/file.c, dir1/dir2/file.c and /path/to/file.c all match, but file.h and dir/file.h don't.
  • dir/*/* matches all files one level below dir, so dir/one/file.c and dir/two/file.h match, but file.c, one/dir/file.c, dir/file.h and dir/one/two/file.c don't.

Patterns with constructs such as foo/../bar will never match normalised FilePath values, so are unlikely to be correct.

(<//>) :: FilePattern -> FilePattern -> FilePattern infixr 5 Source #

Join two FilePattern values by inserting two / characters between them. Will first remove any trailing path separators on the first argument, and any leading separators on the second.

"dir" <//> "*" == "dir//*"

filePattern :: FilePattern -> FilePath -> Maybe [String] Source #

Like ?==, but returns Nothing on if there is no match, otherwise Just with the list of fragments matching each wildcard. For example:

filePattern "**/*.c" "test.txt" == Nothing
filePattern "**/*.c" "foo.c" == Just ["","foo"]
filePattern "**/*.c" "bar/baz/foo.c" == Just ["bar/baz/","foo"]

Note that the ** will often contain a trailing /, and even on Windows any \ separators will be replaced by /.

needed :: [FilePath] -> Action () Source #

Like need, but if shakeLint is set, check that the file does not rebuild. Used for adding dependencies on files that have already been used in this rule.

trackRead :: [FilePath] -> Action () Source #

Track that a file was read by the action preceeding it. If shakeLint is activated then these files must be dependencies of this rule. Calls to trackRead are automatically inserted in LintFSATrace mode.

trackWrite :: [FilePath] -> Action () Source #

Track that a file was written by the action preceeding it. If shakeLint is activated then these files must either be the target of this rule, or never referred to by the build system. Calls to trackWrite are automatically inserted in LintFSATrace mode.

trackAllow :: [FilePattern] -> Action () Source #

Allow accessing a file in this rule, ignoring any trackRead / trackWrite calls matching the pattern.

Directory rules

doesFileExist :: FilePath -> Action Bool Source #

Returns True if the file exists. The existence of the file is tracked as a dependency, and if the file is created or deleted the rule will rerun in subsequent builds.

You should not call doesFileExist on files which can be created by the build system.

doesDirectoryExist :: FilePath -> Action Bool Source #

Returns True if the directory exists. The existence of the directory is tracked as a dependency, and if the directory is created or delete the rule will rerun in subsequent builds.

You should not call doesDirectoryExist on directories which can be created by the build system.

getDirectoryContents :: FilePath -> Action [FilePath] Source #

Get the contents of a directory. The result will be sorted, and will not contain the entries . or .. (unlike the standard Haskell version). The resulting paths will be relative to the first argument. The result is tracked as a dependency, and if it changes the rule will rerun in subsequent builds.

It is usually simpler to call either getDirectoryFiles or getDirectoryDirs.

getDirectoryFiles :: FilePath -> [FilePattern] -> Action [FilePath] Source #

Get the files anywhere under a directory that match any of a set of patterns. For the interpretation of the patterns see ?==. All results will be relative to the directory argument. The result is tracked as a dependency, and if it changes the rule will rerun in subsequent builds. Some examples:

getDirectoryFiles "Config" ["//*.xml"]
    -- All .xml files anywhere under the Config directory
    -- If Config/foo/bar.xml exists it will return ["foo/bar.xml"]
getDirectoryFiles "Modules" ["*.hs","*.lhs"]
    -- All .hs or .lhs in the Modules directory
    -- If Modules/foo.hs and Modules/foo.lhs exist, it will return ["foo.hs","foo.lhs"]

If you require a qualified file name it is often easier to use "" as the FilePath argument, for example the following two expressions are equivalent:

fmap (map ("Config" </>)) (getDirectoryFiles "Config" ["//*.xml"])
getDirectoryFiles "" ["Config//*.xml"]

If the first argument directory does not exist it will raise an error. If foo does not exist, then the first of these error, but the second will not.

getDirectoryFiles "foo" ["//*"] -- error
getDirectoryFiles "" ["foo//*"] -- returns []

This function is tracked and serves as a dependency. If a rule calls getDirectoryFiles "" ["*.c"] and someone adds foo.c to the directory, that rule will rebuild. If someone changes one of the .c files, but the list of .c files doesn't change, then it will not rebuild. As a consequence of being tracked, if the contents change during the build (e.g. you are generating .c files in this directory) then the build not reach a stable point, which is an error - detected by running with --lint. You should normally only call this function returning source files.

For an untracked variant see getDirectoryFilesIO.

getDirectoryDirs :: FilePath -> Action [FilePath] Source #

Get the directories in a directory, not including . or ... All directories are relative to the argument directory. The result is tracked as a dependency, and if it changes the rule will rerun in subsequent builds. The rules about creating entries described in getDirectoryFiles also apply here.

getDirectoryDirs "/Users"
   -- Return all directories in the /Users directory
   -- e.g. ["Emily","Henry","Neil"]

getDirectoryFilesIO :: FilePath -> [FilePattern] -> IO [FilePath] Source #

A version of getDirectoryFiles that is in IO, and thus untracked.

Environment rules

getEnv :: String -> Action (Maybe String) Source #

Return Just the value of the environment variable, or Nothing if the variable is not set. The environment variable is tracked as a dependency, and if it changes the rule will rerun in subsequent builds. This function is a tracked version of getEnv / lookupEnv from the base library.

flags <- getEnv "CFLAGS"
cmd "gcc -c" [out] (maybe [] words flags)

getEnvWithDefault :: String -> String -> Action String Source #

getEnvWithDefault def var returns the value of the environment variable var, or the default value def if it is not set. Similar to getEnv.

flags <- getEnvWithDefault "-Wall" "CFLAGS"
cmd "gcc -c" [out] flags

Oracle rules

type ShakeValue a = (Show a, Typeable a, Eq a, Hashable a, Binary a, NFData a) Source #

Define an alias for the six type classes required for things involved in Shake rules. Using this alias requires the ConstraintKinds extension.

To define your own values meeting the necessary constraints it is convenient to use the extensions GeneralizedNewtypeDeriving and DeriveDataTypeable to write:

newtype MyType = MyType (String, Bool) deriving (Show, Typeable, Eq, Hashable, Binary, NFData)

Shake needs these instances on keys and values. They are used for:

  • Show is used to print out keys in errors, profiling, progress messages and diagnostics.
  • Typeable is used because Shake indexes its database by the type of the key and value involved in the rule (overlap is not allowed for type classes and not allowed in Shake either).
  • Eq and Hashable are used on keys in order to build hash maps from keys to values. Eq is used on values to test if the value has changed or not (this is used to support unchanging rebuilds, where Shake can avoid rerunning rules if it runs a dependency, but it turns out that no changes occurred.) The Hashable instances are only use at runtime (never serialised to disk), so they do not have to be stable across runs. Hashable on values is not used, and only required for a consistent interface.
  • Binary is used to serialize keys and values into Shake's build database; this lets Shake cache values across runs and implement unchanging rebuilds.
  • NFData is used to avoid space and thunk leaks, especially when Shake is parallelized.

type family RuleResult key Source #

addOracle :: (RuleResult q ~ a, ShakeValue q, ShakeValue a) => (q -> Action a) -> Rules (q -> Action a) Source #

Add extra information which rules can depend on. An oracle is a function from a question type q, to an answer type a. As an example, we can define an oracle allowing you to depend on the current version of GHC:

newtype GhcVersion = GhcVersion () deriving (Show,Typeable,Eq,Hashable,Binary,NFData)
type instance RuleResult GhcVersion = String
rules = do
    addOracle $ \(GhcVersion _) -> fmap fromStdout $ cmd "ghc --numeric-version" :: Action String
    ... rules ...

If a rule calls askOracle (GhcVersion ()), that rule will be rerun whenever the GHC version changes. Some notes:

  • We define GhcVersion with a newtype around (), allowing the use of GeneralizedNewtypeDeriving. All the necessary type classes are exported from Development.Shake.Classes.
  • The type instance requires the extension TypeFamilies.
  • Each call to addOracle must use a different type of question.
  • Actions passed to addOracle will be run in every build they are required, even if nothing else changes, so be careful of slow actions. If the result of an oracle does not change it will not invalidate any rules depending on it. To always rerun files rules see alwaysRerun.
  • If the value returned by askOracle is ignored then askOracleWith may help avoid ambiguous type messages. Alternatively, use the result of addOracle, which is askOracle restricted to the correct type.

As a more complex example, consider tracking Haskell package versions:

newtype GhcPkgList = GhcPkgList () deriving (Show,Typeable,Eq,Hashable,Binary,NFData)
type instance RuleResult GhcPkgList = [(String, String)]
newtype GhcPkgVersion = GhcPkgVersion String deriving (Show,Typeable,Eq,Hashable,Binary,NFData)
type instance RuleResult GhcPkgVersion = Maybe String

rules = do
    getPkgList <- addOracle $ \GhcPkgList{} -> do
        Stdout out <- cmd "ghc-pkg list --simple-output"
        return [(reverse b, reverse a) | x <- words out, let (a,_:b) = break (== '-') $ reverse x]

    getPkgVersion <- addOracle $ \(GhcPkgVersion pkg) -> do
        pkgs <- getPkgList $ GhcPkgList ()
        return $ lookup pkg pkgs

    "myrule" %> \_ -> do
        getPkgVersion $ GhcPkgVersion "shake"
        ... rule using the shake version ...

Using these definitions, any rule depending on the version of shake should call getPkgVersion $ GhcPkgVersion "shake" to rebuild when shake is upgraded.

askOracle :: (RuleResult q ~ a, ShakeValue q, ShakeValue a) => q -> Action a Source #

Get information previously added with addOracle. The question/answer types must match those provided to addOracle.

Special rules

alwaysRerun :: Action () Source #

Always rerun the associated action. Useful for defining rules that query the environment. For example:

"ghcVersion.txt" %> \out -> do
    alwaysRerun
    Stdout stdout <- cmd "ghc --numeric-version"
    writeFileChanged out stdout

In make, the .PHONY attribute on file-producing rules has a similar effect.

Note that alwaysRerun is applied when a rule is executed. Modifying an existing rule to insert alwaysRerun will not cause that rule to rerun next time.

Resources

data Resource Source #

A type representing an external resource which the build system should respect. There are two ways to create Resources in Shake:

  • newResource creates a finite resource, stopping too many actions running simultaneously.
  • newThrottle creates a throttled resource, stopping too many actions running over a short time period.

These resources are used with withResource when defining rules. Typically only system commands (such as cmd) should be run inside withResource, not commands such as need.

Be careful that the actions run within withResource do not themselves require further resources, or you may get a "thread blocked indefinitely in an MVar operation" exception. If an action requires multiple resources, use withResources to avoid deadlock.

newResource :: String -> Int -> Rules Resource Source #

Create a finite resource, given a name (for error messages) and a quantity of the resource that exists. Shake will ensure that actions using the same finite resource do not execute in parallel. As an example, only one set of calls to the Excel API can occur at one time, therefore Excel is a finite resource of quantity 1. You can write:

shake shakeOptions{shakeThreads=2} $ do
   want ["a.xls","b.xls"]
   excel <- newResource "Excel" 1
   "*.xls" %> \out ->
       withResource excel 1 $
           cmd "excel" out ...

Now the two calls to excel will not happen in parallel.

As another example, calls to compilers are usually CPU bound but calls to linkers are usually disk bound. Running 8 linkers will often cause an 8 CPU system to grid to a halt. We can limit ourselves to 4 linkers with:

disk <- newResource "Disk" 4
want [show i <.> "exe" | i <- [1..100]]
"*.exe" %> \out ->
    withResource disk 1 $
        cmd "ld -o" [out] ...
"*.o" %> \out ->
    cmd "cl -o" [out] ...

newResourceIO :: String -> Int -> IO Resource Source #

A version of newResource that runs in IO, and can be called before calling shake. Most people should use newResource instead.

withResource :: Resource -> Int -> Action a -> Action a Source #

Run an action which uses part of a finite resource. For more details see Resource. You cannot depend on a rule (e.g. need) while a resource is held.

withResources :: [(Resource, Int)] -> Action a -> Action a Source #

Run an action which uses part of several finite resources. Acquires the resources in a stable order, to prevent deadlock. If all rules requiring more than one resource acquire those resources with a single call to withResources, resources will not deadlock.

newThrottle :: String -> Int -> Double -> Rules Resource Source #

Create a throttled resource, given a name (for error messages) and a number of resources (the Int) that can be used per time period (the Double in seconds). Shake will ensure that actions using the same throttled resource do not exceed the limits. As an example, let us assume that making more than 1 request every 5 seconds to Google results in our client being blacklisted, we can write:

google <- newThrottle "Google" 1 5
"*.url" %> \out -> do
    withResource google 1 $
        cmd "wget" ["http://google.com?q=" ++ takeBaseName out] "-O" [out]

Now we will wait at least 5 seconds after querying Google before performing another query. If Google change the rules to allow 12 requests per minute we can instead use newThrottle "Google" 12 60, which would allow greater parallelisation, and avoid throttling entirely if only a small number of requests are necessary.

In the original example we never make a fresh request until 5 seconds after the previous request has completed. If we instead want to throttle requests since the previous request started we can write:

google <- newThrottle "Google" 1 5
"*.url" %> \out -> do
    withResource google 1 $ return ()
    cmd "wget" ["http://google.com?q=" ++ takeBaseName out] "-O" [out]

However, the rule may not continue running immediately after withResource completes, so while we will never exceed an average of 1 request every 5 seconds, we may end up running an unbounded number of requests simultaneously. If this limitation causes a problem in practice it can be fixed.

newThrottleIO :: String -> Int -> Double -> IO Resource Source #

A version of newThrottle that runs in IO, and can be called before calling shake. Most people should use newThrottle instead.

unsafeExtraThread :: Action a -> Action a Source #

Run an action without counting to the thread limit, typically used for actions that execute on remote machines using barely any local CPU resources. Unsafe as it allows the shakeThreads limit to be exceeded. You cannot depend on a rule (e.g. need) while the extra thread is executing. If the rule blocks (e.g. calls withResource) then the extra thread may be used by some other action. Only really suitable for calling cmd / command.

Cache

newCache :: (Eq k, Hashable k) => (k -> Action v) -> Rules (k -> Action v) Source #

Given an action on a key, produce a cached version that will execute the action at most once per key. Using the cached result will still result include any dependencies that the action requires. Each call to newCache creates a separate cache that is independent of all other calls to newCache.

This function is useful when creating files that store intermediate values, to avoid the overhead of repeatedly reading from disk, particularly if the file requires expensive parsing. As an example:

digits <- newCache $ \file -> do
    src <- readFile' file
    return $ length $ filter isDigit src
"*.digits" %> \x -> do
    v1 <- digits (dropExtension x)
    v2 <- digits (dropExtension x)
    writeFile' x $ show (v1,v2)

To create the result MyFile.txt.digits the file MyFile.txt will be read and counted, but only at most once per execution.

newCacheIO :: (Eq k, Hashable k) => (k -> Action v) -> IO (k -> Action v) Source #

A version of newCache that runs in IO, and can be called before calling shake. Most people should use newCache instead.

Batching

needHasChanged :: [FilePath] -> Action [FilePath] Source #

Like need but returns a list of rebuild dependencies this build.

The following example writes a list of changed dependencies to a file as its action.

"target" %> \out -> do
      let sourceList = ["source1", "source2"]
      rebuildList <- needHasChanged sourceList
      writeFileLines out rebuildList

This function can be used to alter the action depending on which dependency needed to be rebuild.

Note that a rule can be run even if no dependency has changed, for example because of shakeRebuild or because the target has changed or been deleted. To detect the latter case you may wish to use resultHasChanged.

resultHasChanged :: FilePath -> Action Bool Source #

Has a file changed. This function will only give the correct answer if called in the rule producing the file, before the rule has modified the file in question. Best avoided, but sometimes necessary in conjunction with needHasChanged to cause rebuilds to happen if the result is deleted or modified.

batch :: Int -> ((a -> Action ()) -> Rules ()) -> (a -> Action b) -> ([b] -> Action ()) -> Rules () Source #

Batch different outputs into a single Action, typically useful when a command has a high startup cost - e.g. apt-get install foo bar baz is a lot cheaper than three separate calls to apt-get install. As an example, if we have a standard build rule:

"*.out" %> \out -> do
    need [out -<.> "in"]
    cmd "build-multiple" [out -<.> "in"]

Assuming that build-multiple can compile multiple files in a single run, and that the cost of doing so is a lot less than running each individually, we can write:

batch 3 ("*.out" %>)
    (\out -> do need [out -<.> "in"]; return out)
    (\outs -> cmd "build-multiple" [out -<.> "in" | out <- outs])

In constrast to the normal call, we have specified a maximum batch size of 3, an action to run on each output individually (typically all the need dependencies), and an action that runs on multiple files at once. If we were to require lots of *.out files, they would typically be built in batches of 3.

If Shake ever has nothing else to do it will run batches before they are at the maximum, so you may see much smaller batches, especially at high parallelism settings.

Deprecated

(*>) :: FilePattern -> (FilePath -> Action ()) -> Rules () infix 1 Source #

Deprecated: Alias for %>. Note that *> clashes with a Prelude operator in GHC 7.10.

(|*>) :: [FilePattern] -> (FilePath -> Action ()) -> Rules () infix 1 Source #

Deprecated: Alias for |%>.

(&*>) :: [FilePattern] -> ([FilePath] -> Action ()) -> Rules () infix 1 Source #

Deprecated: Alias for &%>.

(**>) :: [FilePattern] -> (FilePath -> Action ()) -> Rules () infix 1 Source #

Deprecated: Alias for |%>.

(*>>) :: [FilePattern] -> ([FilePath] -> Action ()) -> Rules () infix 1 Source #

Deprecated: Alias for &%>.

(?>>) :: (FilePath -> Maybe [FilePath]) -> ([FilePath] -> Action ()) -> Rules () infix 1 Source #

Deprecated: Alias for &?>.

askOracleWith :: (RuleResult q ~ a, ShakeValue q, ShakeValue a) => q -> a -> Action a Source #

Depreciated: Replace askOracleWith q a by askOracle q since the RuleResult type family now fixes the result type.