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

Safe HaskellSafe-Infered

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 = shake shakeOptions $ do
    want ["result.tar"]
    "*.tar" *> \out -> do
        contents <- readFileLines $ replaceExtension out "txt"
        need contents
        system' "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.

When writing a Shake build system, start by defining what you want, then write rules with *> to produce the results. Before calling system' 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 CmdArgs package (http://hackage.haskell.org/package/cmdargs/) is well suited to providing command line parsing for build systems, often using flags to set fields in shakeOptions.
  • Put all result files in a distinguished directory, for example _make. You can implement a clean command by removing that directory, using removeDirectoryRecursive.
  • To obtain paralell builds set shakeThreads to a number greater than 1. You may also need to compile with -threaded.
  • Often the want commands will be determined by command line arguments, to mirror the behaviour of make targets.
  • 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.

The theory behind an old version of Shake is described in a video at http://vimeo.com/15465133.

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

Synopsis

Documentation

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.

Core of Shake

data ShakeOptions Source

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

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

Constructors

ShakeOptions 

Fields

shakeFiles :: FilePath

Where shall I store the database and journal files (defaults to .shake).

shakeThreads :: Int

What is the maximum number of rules I should run in parallel (defaults to 1). To enable parallelism you may need to compile with -threaded.

shakeVersion :: Int

What is the version of your build system, increment to force a complete rebuild (defaults to 1).

shakeVerbosity :: Verbosity

What messages to print out (defaults to Normal).

shakeStaunch :: Bool

Operate in staunch mode, where building continues even after errors (defaults to False).

shakeReport :: Maybe FilePath

Produce an HTML profiling report (defaults to Nothing).

shakeLint :: Bool

Perform basic sanity checks after building (defaults to False).

class (Show key, Typeable key, Eq key, Hashable key, Binary key, NFData key, Show value, Typeable value, Eq value, Hashable value, Binary value, NFData value) => Rule key value | key -> value whereSource

Define a pair of types that can be used by Shake rules.

Methods

validStored :: key -> value -> IO BoolSource

Given that the database contains key/value, does that still match the on-disk contents?

As an example for filenames/timestamps, if the file exists and had the same timestamp, you would return True, but otherwise return False. For rule values which are not also stored on disk, validStored should always return True.

Instances

Rule GetDir GetDir_ 
Rule Exist Bool 
Rule File FileTime 
Rule Question Answer 
Rule AlwaysRerun Dirty 
Rule Files FileTimes 

data Rules a Source

Define a set of rules. Rules can be created with calls to rule, defaultRule or action. Rules are combined with either the Monoid instance, or (more commonly) the Monad instance and do notation.

Instances

defaultRule :: Rule key value => (key -> Maybe (Action value)) -> Rules ()Source

Like rule, but lower priority, if no rule exists then defaultRule is checked. All default rules must be disjoint.

rule :: Rule key value => (key -> Maybe (Action value)) -> Rules ()Source

Add a rule to build a key, returning an appropriate Action. All rules must be disjoint. To define lower priority rules use defaultRule.

action :: Action a -> Rules ()Source

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

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.

apply :: Rule key value => [key] -> Action [value]Source

Execute a rule, returning the associated values. If possible, the rules will be run in parallel. This function requires that appropriate rules have been added with rule or defaultRule.

apply1 :: Rule key value => key -> Action valueSource

Apply a single rule, equivalent to calling apply with a singleton list. Where possible, use apply to allow parallelism.

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 system' command automatically calls traced. The trace list is used for profile reports (see shakeReport).

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 normal messages (typically errors and warnings).

Loud

Print lots of messages (typically errors, warnings and status updates).

Diagnostic

Print messages for virtually everything (for debugging a build system).

getVerbosity :: Action VerbositySource

Get the current verbosity level, as 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.

putLoud, putQuiet, 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).

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

Lift a computation from the IO monad.

Utility functions

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

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

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

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.

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

copyFile old new copies the existing file from old to new. The old file is has need called on it before copying the file.

readFile' :: FilePath -> Action StringSource

Read a file, after calling need.

writeFile' :: FilePath -> String -> Action ()Source

Write a file, lifted to the Action monad.

readFileLines :: FilePath -> Action [String]Source

A version of readFile' which also splits the result into lines.

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.

File rules

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

Require that the following files are built before continuing. Particularly necessary when calling system'. As an example:

 "*.rot13" *> \out -> do
     let src = dropExtension out
     need [src]
     system' ["rot13",src,"-o",out]

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

Require that the following 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.

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

Define a rule that matches a FilePattern. No file required by the system must be matched by more than one pattern. For the pattern rules, see ?==.

 "*.asm.o" *> \out -> do
     let src = dropExtension out
     need [src]
     system' ["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. See *>.

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

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

(?>>) :: (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 *>>.

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:

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

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

Define a rule for building multiple files at the same time. As an example, a single invokation of GHC produces both .hi and .o files:

 ["*.o","*.hi"] *>> \[o,hi] -> do
     let hs = replaceExtension o "hs"
     need ... -- all files the .hs import
     system' "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.

type FilePattern = StringSource

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

(?==) :: 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 componenets.

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"

Directory rules

doesFileExist :: FilePath -> Action BoolSource

Returns True if the file exists.

getDirectoryContents :: FilePath -> Action [FilePath]Source

Get the contents of a directory. The result will be sorted, and will not contain the files . or .. (unlike the standard Haskell version). It is usually better to call either getDirectoryFiles or getDirectoryDirs. The resulting paths will be relative to the first argument.

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

Get the files in a directory that match a particular pattern. For the interpretation of the pattern see ?==.

getDirectoryDirs :: FilePath -> Action [FilePath]Source

Get the directories contained by a directory, does not include . or ...

Additional rules

addOracle :: [String] -> Action [String] -> Rules ()Source

Add extra information which your build should depend on. For example:

 addOracle ["ghc"] $ return ["7.2.1"]
 addOracle ["ghc-pkg","shake"] $ return ["1.0"]

If a rule depends on the GHC version, it can then use askOracle ["ghc"], and if the GHC version changes, the rule will rebuild. It is common for the value returned by askOracle to be ignored.

The Oracle maps questions of [String] and answers of [String]. This type is a compromise. Questions will often be the singleton list, but allowing a list of strings there is more flexibility for heirarchical schemes and grouping - i.e. to have ghc-pkg shake, ghc-pkg base etc. The answers are often singleton lists, but sometimes are used as sets - for example the list of packages returned by ghc-pkg.

Actions passed to addOracle will be run in every Shake execution they are required, their value will not be kept between runs. To get a similar behaviour using files, see alwaysRerun.

askOracle :: [String] -> Action [String]Source

Get information previously added with addOracle.

alwaysRerun :: Action ()Source

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

 "ghcVersion.txt" *> \out -> do
     alwaysRerun
     (stdout,_) <- systemOutput "ghc" ["--version"]
     writeFileChanged out stdout

Finite resources

data Resource Source

The type representing a finite resource, which multiple build actions should respect. Created with newResource in the IO monad before calling shake, and used with withResource in the Action monad when defining rules.

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:

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

Now the two calls to excel will not happen in parallel. Using Resource is better than MVar as it will not block any other threads from executing. Be careful that the actions run within withResource do not themselves require further quantities of this resource, or you may get a "thread blocked indefinitely in an MVar operation" exception. Typically only system commands (such as system') will be run inside withResource, not commands such as need.

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:

 do disk <- newResource "Disk" 4
    shake shakeOptions{shakeThreads=8} $ do
        want [show i <.> "exe" | i <- [1..100]]
        "*.exe" *> \out ->
            withResource disk 1 $
                system' "ld" ["-o",out,...]
        "*.o" *> \out ->
            system' "cl" ["-o",out,...]

Instances

newResource :: String -> Int -> IO ResourceSource

Create a new finite resource, given a name (for error messages) and a quantity of the resource that exists. For an example see Resource.

withResource :: Resource -> Int -> Action a -> Action aSource

Run an action which uses part of a finite resource. For an example see Resource.