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

Safe HaskellNone

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:

== 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 -rtsopts -with-rtsopts=-I0
  • -rtsopts: Allow the setting of further GHC options at runtime.
  • -I0: Disable idle garbage collection. In a build system regularly running many system commands the program appears "idle" very often, triggering regular unnecessary garbage collection, stealing resources from the program doing actual work.
  • Omit -threaded: In GHC 7.6 and earlier bug 7646 http://ghc.haskell.org/trac/ghc/ticket/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.
  • If you do compile with -threaded, 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.

Acknowledgements: Thanks to Austin Seipp for properly integrating the profiling code.

Synopsis

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.

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.

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.

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 rule and action. The Action monad tracks the dependencies of a Rule.

traced :: String -> IO a -> Action aSource

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

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

actionOnException :: Action a -> IO b -> Action aSource

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

actionFinally :: Action a -> IO b -> Action aSource

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

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

shakeExceptionTarget :: String

The target that was being built when the exception occured.

shakeExceptionStack :: [String]

The stack of targets, where the shakeExceptionTarget is last.

shakeExceptionInner :: SomeException

The underlying exception that was raised.

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 Function, because Data cannot be defined for functions.

Constructors

ShakeOptions 

Fields

shakeFiles :: FilePath

Defaults to .shake. The prefix of the filename used for storing Shake metadata files. All metadata files will be named shakeFiles.extension, for some extension. 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.

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.

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.

shakeAssume :: Maybe Assume

Defaults to Nothing. Assume all build objects are clean/dirty, see Assume for details. Can be used to implement make --touch.

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

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.

data Assume Source

The current assumptions made by the build system, used by shakeAssume. 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

AssumeDirty

Assume that all rules reached are dirty and require rebuilding, equivalent to storedValue always returning Nothing. Useful to undo the results of AssumeClean, for benchmarking rebuild speed and for rebuilding if untracked dependencies have changed. This assumption is safe, but may cause more rebuilding than necessary.

AssumeClean

This assumption is unsafe, and may lead to incorrect build results in this run, and in future runs. Assume and record that all rules reached are clean and do not require rebuilding, provided the rule has a storedValue and has been built before. Useful if you have modified a file in some inconsequential way, such as only the comments or whitespace, and wish to avoid a rebuild.

AssumeSkip

This assumption is unsafe, and may lead to incorrect build results in this run. Assume that all rules reached are clean in this run. Only useful for benchmarking, to remove any overhead from running storedValue operations.

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.

LintTracker

Track which files are accessed by command line programs run by command or cmd, using tracker.exe as supplied with the Microsoft .NET 4.5 SDK (Windows only). Also performs all checks from LintBasic. Note that some programs are not tracked properly, particularly cygwin programs (it seems).

data Change Source

How should you determine if a file has changed, used by shakeChange. The most common values are ChangeModtime (very fast, touch causes files to rebuild) and ChangeModtimeAndDigestInput (a bit slower, touch 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.

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.

getShakeOptions :: Action ShakeOptionsSource

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

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.

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 passing a callback function to shakeProgress. Typically a program will use progressDisplay to poll this value and produce status messages, which is implemented using this data type.

Constructors

Progress 

Fields

isFailure :: !(Maybe String)

Starts out Nothing, becomes Just a target name if a rule fails.

countSkipped :: !Int

Number of rules which were required, but were already in a valid state.

countBuilt :: !Int

Number of rules which were have been built in this run.

countUnknown :: !Int

Number of rules which have been built previously, but are not yet known to be required.

countTodo :: !Int

Number of rules which are currently required (ignoring dependencies that do not change), but not built.

timeSkipped :: !Double

Time spent building countSkipped rules in previous runs.

timeBuilt :: !Double

Time spent building countBuilt rules.

timeUnknown :: !Double

Time spent building countUnknown rules in previous runs.

timeTodo :: !(Double, Int)

Time spent building countTodo rules in previous runs, plus the number which have no known time (have never been built before).

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.

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

getVerbosity :: Action VerbositySource

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 a message to the output when the verbosity (shakeVerbosity) is appropriate. The output will not be interleaved with any other Shake messages (other than those generated by system commands).

putNormal :: String -> Action ()Source

Write a message to the output when the verbosity (shakeVerbosity) is appropriate. The output will not be interleaved with any other Shake messages (other than those generated by system commands).

putQuiet :: String -> Action ()Source

Write a message to the output when the verbosity (shakeVerbosity) is appropriate. The output will not be interleaved with any other Shake messages (other than those generated by system commands).

withVerbosity :: Verbosity -> Action a -> Action aSource

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 aSource

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 rSource

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

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 rSource

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.

To take the examples from command:

 () <- 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, bind the result to (), or include a type signature.

The cmd command can also be run in the IO monad, but then Traced is ignored and command lines are not echoed.

newtype Stdout Source

Collect the stdout of the process. If you are collecting the stdout, it will not be echoed to the terminal, unless you include EchoStdout.

Constructors

Stdout 

Fields

fromStdout :: String
 

Instances

newtype Stderr Source

Collect the stderr of the process. If you are collecting the stderr, it will not be echoed to the terminal, unless you include EchoStderr.

Constructors

Stderr 

Fields

fromStderr :: String
 

Instances

newtype Exit Source

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

Constructors

Exit 

Fields

fromExit :: ExitCode
 

Instances

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.

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. Use addPath to modify the $PATH variable, or addEnv to modify other variables.

Stdin String

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

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 streams use text encoding.

Traced String

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

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.

EchoStderr Bool

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

addPath :: MonadIO m => [String] -> [String] -> m CmdOptionSource

Produce a CmdOption of value Env that is the current environment, plus 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 CmdOptionSource

Produce a CmdOption of value Env that is the current environment, plus the argument environment variables. 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.

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.

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

copyFile' old new copies the existing file from old to new, if the contents have changed. The old file will be tracked as a dependency.

readFile' :: FilePath -> Action StringSource

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' :: FilePath -> String -> Action ()Source

Write a file, lifted to the Action monad.

writeFileLines :: FilePath -> [String] -> Action ()Source

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

writeFileChanged :: FilePath -> String -> Action ()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" ["//*"]
 removeFiles "." ["//*.hi","//*.o"]

Any directories that become empty after deleting items from within them will themselves be deleted, up to (and including) the containing directory. 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.

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.

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

(|*>) :: [FilePattern] -> (FilePath -> Action ()) -> Rules ()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 ()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

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

Declare a phony action -- an action that does not produce a file, and will be rerun in every execution that requires it. You can demand phony rules using want / need. Phony actions are never executed more than once in a single build run.

Phony actions are intended to define command-line abbreviations. 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.

(~>) :: String -> Action () -> Rules ()Source

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

(&*>) :: [FilePattern] -> ([FilePath] -> Action ()) -> Rules ()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. Think of it as the OR (||) equivalent of *>.

(&?>) :: (FilePath -> Maybe [FilePath]) -> ([FilePath] -> Action ()) -> Rules ()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, and you will have lost some opportunity for parallelism.

type FilePattern = StringSource

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

Most FilePath values are suitable as FilePattern values which match only that specific file.

(?==) :: FilePattern -> FilePath -> BoolSource

Match a FilePattern against a FilePath, There are only two special forms:

  • * matches an entire path component, excluding any separators.
  • // matches an arbitrary number of path components.

Some examples that match:

 "//*.c" ?== "foo/bar/baz.c"
 "*.c" ?== "baz.c"
 "//*.c" ?== "baz.c"
 "test.c" ?== "test.c"

Examples that don't match:

 "*.c" ?== "foo/bar.c"
 "*/*.c" ?== "foo/bar/baz.c"

An example that only matches on Windows:

 "foo/bar" ?== "foo\\bar"

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

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

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 BoolSource

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 FilePath 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 FilePath argument, for example the following two expressions are equivalent:

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

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.

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

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.

getEnvWithDefault :: String -> String -> Action StringSource

Return the value of the environment variable, or the default value if it not set. Similar to getEnv.

Oracle rules

addOracle :: (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)
 rules = do
     addOracle $ \(GhcVersion _) -> fmap fromStdout $ cmd "ghc --numeric-version"
     ... 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.
  • Each call to addOracle must use a different type of question.
  • Actions passed to addOracle will be run in every build they are required, but if their value does not change they will not invalidate any rules depending on them. To get a similar behaviour using data stored in files, 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)
newtype GhcPkgVersion = GhcPkgVersion String deriving (Show,Typeable,Eq,Hashable,Binary,NFData)

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 :: (ShakeValue q, ShakeValue a) => q -> Action aSource

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

askOracleWith :: (ShakeValue q, ShakeValue a) => q -> a -> Action aSource

Get information previously added with addOracle. The second argument is not used, but can be useful to fix the answer type, avoiding ambiguous type error messages.

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

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 ResourceSource

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 ResourceSource

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 aSource

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 aSource

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 ResourceSource

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 ResourceSource

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 aSource

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.

Deprecated

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

Deprecated: Alias for |*>.

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

Deprecated: Alias for &*>.

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

Deprecated: Alias for &?>.

system' :: FilePath -> [String] -> Action ()Source

Deprecated: Use command or cmd

Deprecated: Please use command or cmd instead. This function will be removed in a future version.

Execute a system command. This function will raise an error if the exit code is non-zero. Before running system' make sure you need any required files.

systemCwd :: FilePath -> FilePath -> [String] -> Action ()Source

Deprecated: Use command or cmd with Cwd

Deprecated: Please use command or cmd instead, with Cwd. This function will be removed in a future version.

Execute a system command with a specified current working directory (first argument). This function will raise an error if the exit code is non-zero. Before running systemCwd make sure you need any required files.

 systemCwd "/usr/MyDirectory" "pwd" []

systemOutput :: FilePath -> [String] -> Action (String, String)Source

Deprecated: Use command or cmd with Stdout or Stderr

Deprecated: Please use command or cmd instead, with Stdout or Stderr. This function will be removed in a future version.

Execute a system command, returning (stdout,stderr). This function will raise an error if the exit code is non-zero. Before running systemOutput make sure you need any required files.