Main module for defining Shake build systems. You may also want to include
Development.Shake.FilePath, for manipulating file paths. As a simple example,
let us build a result.tar
file from the contents of result.txt
:
import Development.Shake import Development.Shake.FilePath main =shake
shakeOptions
$ dowant
["result.tar"] "*.tar"*>
\out -> do contents <-readFileLines
$ replaceExtension out "txt"need
contentssystem'
"tar" $ ["-cf",out] ++ contents
For the background theory behind a previous version of Shake the online video: http://vimeo.com/15465133.
- shake :: ShakeOptions -> Rules () -> IO ()
- data ShakeOptions = ShakeOptions {}
- shakeOptions :: ShakeOptions
- 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 where
- validStored :: key -> value -> IO Bool
- data Rules a
- defaultRule :: Rule key value => (key -> Maybe (Action value)) -> Rules ()
- rule :: Rule key value => (key -> Maybe (Action value)) -> Rules ()
- action :: Action a -> Rules ()
- data Action a
- apply :: Rule key value => [key] -> Action [value]
- apply1 :: Rule key value => key -> Action value
- traced :: String -> IO a -> Action a
- data Verbosity
- = Silent
- | Quiet
- | Normal
- | Loud
- | Diagnostic
- getVerbosity :: Action Verbosity
- putLoud, putQuiet, putNormal :: String -> Action ()
- liftIO :: MonadIO m => forall a. IO a -> m a
- system' :: FilePath -> [String] -> Action ()
- systemOutput :: FilePath -> [String] -> Action (String, String)
- copyFile' :: FilePath -> FilePath -> Action ()
- readFile' :: FilePath -> Action String
- writeFile' :: FilePath -> String -> Action ()
- readFileLines :: FilePath -> Action [String]
- writeFileLines :: FilePath -> [String] -> Action ()
- writeFileChanged :: FilePath -> String -> Action ()
- need :: [FilePath] -> Action ()
- want :: [FilePath] -> Rules ()
- (*>) :: FilePattern -> (FilePath -> Action ()) -> Rules ()
- (**>) :: [FilePattern] -> (FilePath -> Action ()) -> Rules ()
- (?>) :: (FilePath -> Bool) -> (FilePath -> Action ()) -> Rules ()
- (*>>) :: [FilePattern] -> ([FilePath] -> Action ()) -> Rules ()
- type FilePattern = String
- (?==) :: FilePattern -> FilePath -> Bool
- doesFileExist :: FilePath -> Action Bool
- getDirectoryContents :: FilePath -> Action [FilePath]
- getDirectoryFiles :: FilePath -> FilePattern -> Action [FilePath]
- getDirectoryDirs :: FilePath -> Action [FilePath]
- addOracle :: [String] -> Action [String] -> Rules ()
- askOracle :: [String] -> Action [String]
- alwaysRerun :: Action ()
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,shakeDump
=True}
ShakeOptions | |
|
shakeOptions :: ShakeOptionsSource
The default set of ShakeOptions
.
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.
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
.
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.
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.
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
.
The verbosity data type, specified in shakeVerbosity
.
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 is appropriate. The output will not be interleaved with any other Shake messages (other than those generated by system commands).
Utility functions
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.
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
(*>>) :: [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" ?== "foor/bar.c" "*/*.c" ?== "foo/bar/baz.c"
Directory rules
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
, and
if the GHC version changes, the rule will rebuild. It is common for the value returned
by getOracle
[ghc]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,
there value will not be kept between runs. To get a similar behaviour using files, see
alwaysRerun
.
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"] writeFile' out stdout