-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Build system library, like Make, but more accurate dependencies. -- -- Shake is a Haskell library for writing build systems - designed as a -- replacement for make. See Development.Shake for an -- introduction, including an example. Further examples are included in -- the Cabal tarball, under the Examples directory. -- -- To use Shake the user writes a Haskell program that imports -- Development.Shake, defines some build rules, and calls the -- Development.Shake.shake function. Thanks to do notation and -- infix operators, a simple Shake build system is not too dissimilar -- from a simple Makefile. However, as build systems get more complex, -- Shake is able to take advantage of the excellent abstraction -- facilities offered by Haskell and easily support much larger projects. -- -- The Shake library provides all the standard features available in -- other build systems, including automatic parallelism and minimal -- rebuilds. Shake provides highly accurate dependency tracking, -- including seamless support for generated files, and dependencies on -- system information (i.e. compiler version). Shake can produce profile -- reports, indicating which files and take longest to build, and -- providing an analysis of the parallelism. -- -- The theory behind Shake is described in an ICFP 2012 paper, Shake -- Before Building -- Replacing Make with Haskell -- http://community.haskell.org/~ndm/downloads/paper-shake_before_building-10_sep_2012.pdf. -- The associated talk forms a short overview of Shake -- http://www.youtube.com/watch?v=xYCPpXVlqFM. @package shake @version 0.10.6 -- | A module for FilePath operations, to be used instead of -- System.FilePath when writing build systems. In build systems, -- when using the file name as a key for indexing rules, it is important -- that two different strings do not refer to the same on-disk file. We -- therefore follow the conventions: -- -- module Development.Shake.FilePath -- | Drop the first directory from a FilePath. Should only be used -- on relative paths. -- --
--   dropDirectory1 "aaa/bbb" == "bbb"
--   dropDirectory1 "aaa/" == ""
--   dropDirectory1 "aaa" == ""
--   dropDirectory1 "" == ""
--   
dropDirectory1 :: FilePath -> FilePath -- | Take the first component of a FilePath. Should only be used on -- relative paths. -- --
--   takeDirectory1 "aaa/bbb" == "aaa"
--   takeDirectory1 "aaa/" == "aaa"
--   takeDirectory1 "aaa" == "aaa"
--   
takeDirectory1 :: FilePath -> FilePath -- | Normalise a FilePath, applying the standard FilePath -- normalisation, plus translating any path separators to / and -- removing foo/.. components where possible. normalise :: FilePath -> FilePath -- | Remove the current extension and add another, an alias for -- replaceExtension. (-<.>) :: FilePath -> String -> FilePath -- | Convert to native path separators, namely \ on Windows. toNative :: FilePath -> FilePath -- | Combine two file paths, an alias for combine. () :: FilePath -> FilePath -> FilePath -- | Combine two file paths. Any leading ./ or ../ -- components in the right file are eliminated. -- --
--   combine "aaa/bbb" "ccc" == "aaa/bbb/ccc"
--   combine "aaa/bbb" "./ccc" == "aaa/bbb/ccc"
--   combine "aaa/bbb" "../ccc" == "aaa/ccc"
--   
combine :: FilePath -> FilePath -> FilePath -- | The extension of executables, "exe" on Windows and -- "" otherwise. exe :: String -- | This module reexports the six necessary type classes that every -- Rule type must support. You can use this module to define new -- rules without depending on the binary, deepseq and -- hashable packages. module Development.Shake.Classes -- | Conversion of values to readable Strings. -- -- Minimal complete definition: showsPrec or show. -- -- Derived instances of Show have the following properties, which -- are compatible with derived instances of Read: -- -- -- -- For example, given the declarations -- --
--   infixr 5 :^:
--   data Tree a =  Leaf a  |  Tree a :^: Tree a
--   
-- -- the derived instance of Show is equivalent to -- --
--   instance (Show a) => Show (Tree a) where
--   
--          showsPrec d (Leaf m) = showParen (d > app_prec) $
--               showString "Leaf " . showsPrec (app_prec+1) m
--            where app_prec = 10
--   
--          showsPrec d (u :^: v) = showParen (d > up_prec) $
--               showsPrec (up_prec+1) u .
--               showString " :^: "      .
--               showsPrec (up_prec+1) v
--            where up_prec = 5
--   
-- -- Note that right-associativity of :^: is ignored. For example, -- -- class Show a showsPrec :: Show a => Int -> a -> ShowS show :: Show a => a -> String showList :: Show a => [a] -> ShowS -- | The class Typeable allows a concrete representation of a type -- to be calculated. class Typeable a typeOf :: Typeable a => a -> TypeRep -- | The Eq class defines equality (==) and inequality -- (/=). All the basic datatypes exported by the Prelude -- are instances of Eq, and Eq may be derived for any -- datatype whose constituents are also instances of Eq. -- -- Minimal complete definition: either == or /=. class Eq a (==) :: Eq a => a -> a -> Bool (/=) :: Eq a => a -> a -> Bool -- | The class of types that can be converted to a hash value. class Hashable a hashWithSalt :: Hashable a => Int -> a -> Int -- | The Binary class provides put and get, methods -- to encode and decode a Haskell value to a lazy ByteString. It mirrors -- the Read and Show classes for textual representation of Haskell types, -- and is suitable for serialising Haskell values to disk, over the -- network. -- -- For parsing and generating simple external binary formats (e.g. C -- structures), Binary may be used, but in general is not suitable for -- complex protocols. Instead use the Put and Get primitives directly. -- -- Instances of Binary should satisfy the following property: -- --
--   decode . encode == id
--   
-- -- That is, the get and put methods should be the inverse -- of each other. A range of instances are provided for basic Haskell -- types. class Binary t put :: Binary t => t -> Put get :: Binary t => Get t -- | A class of types that can be fully evaluated. class NFData a rnf :: NFData a => a -> () -- | Deprecated: This module should no longer be imported as all the -- functions are available directly from Development.Shake. In -- future versions this module will be removed. module Development.Shake.Command -- | Execute a system command. Before running command make sure you -- need any files that are required 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 :: CmdResult r => [CmdOption] -> String -> [String] -> Action r -- | A version of command where you do not require any results, used -- to avoid errors about being unable to deduce CmdResult. command_ :: [CmdOption] -> String -> [String] -> Action () -- | A variable arity version of command. -- -- -- -- 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. cmd :: CmdArguments args => args :-> Action r -- | Collect the stdout of the process. If you are collecting the -- stdout, it will not be echoed to the terminal, unless you -- include EchoStdout. newtype Stdout Stdout :: String -> Stdout fromStdout :: Stdout -> String -- | Collect the stderr of the process. If you are collecting the -- stderr, it will not be echoed to the terminal, unless you -- include EchoStderr. newtype Stderr Stderr :: String -> Stderr fromStderr :: Stderr -> String -- | Collect the ExitCode of the process. If you do not collect the -- exit code, any ExitFailure will cause an exception. newtype Exit Exit :: ExitCode -> Exit fromExit :: Exit -> ExitCode -- | A class for specifying what results you want to collect from a -- process. Values are formed of Stdout, Stderr, -- Exit and tuples of those. class CmdResult a -- | Options passed to command or cmd to control how -- processes are executed. data CmdOption -- | Change the current directory in the spawned process. By default uses -- this processes current directory. Cwd :: FilePath -> CmdOption -- | Change the environment variables in the spawned process. By default -- uses this processes environment. Env :: [(String, String)] -> CmdOption -- | Given as the stdin of the spawned process. By default no -- stdin is given. Stdin :: String -> CmdOption -- | Pass the command to the shell without escaping - any arguments will be -- joined with spaces. By default arguments are escaped properly. Shell :: CmdOption -- | Treat the stdin/stdout/stderr messages as -- binary. By default streams use text encoding. BinaryPipes :: CmdOption -- | Name to use with traced, or "" for no tracing. By -- default traces using the name of the executable. Traced :: String -> CmdOption -- | Should I include the stderr in the exception if the command -- fails? Defaults to True. WithStderr :: Bool -> CmdOption -- | Should I echo the stdout? Defaults to True unless a -- Stdout result is required. EchoStdout :: Bool -> CmdOption -- | Should I echo the stderr? Defaults to True unless a -- Stderr result is required. EchoStderr :: Bool -> CmdOption instance Eq CmdOption instance Ord CmdOption instance Show CmdOption instance Eq Result instance Arg [CmdOption] instance Arg CmdOption instance Arg [String] instance Arg String instance CmdResult r => CmdArguments (Action r) instance (Arg a, CmdArguments r) => CmdArguments (a -> r) instance (CmdResult x1, CmdResult x2, CmdResult x3) => CmdResult (x1, x2, x3) instance (CmdResult x1, CmdResult x2) => CmdResult (x1, x2) instance CmdResult () instance CmdResult Stderr instance CmdResult Stdout instance CmdResult ExitCode instance CmdResult Exit -- | Warning: I intend to remove this module. Please use 'command' or -- 'cmd' instead. -- -- This module provides versions of the system' family of -- functions which take a variable number of arguments. -- -- All these functions take a variable number of arguments. -- -- -- -- As an example, to run ghc --make -O2 inputs -o output: -- --
--   sys "ghc --make -O2" inputs "-o" [output]
--   
-- -- Note that we enclose output as a list so that if the output -- name contains spaces they are appropriately escaped. module Development.Shake.Sys -- | A variable arity version of system'. sys :: SysArguments v => String -> v :-> Action () -- | A variable arity version of systemCwd. sysCwd :: SysCwdArguments v => FilePath -> String -> v :-> Action () -- | A variable arity version of systemOutput. sysOutput :: SysOutputArguments v => String -> v :-> Action (String, String) -- | A variable arity function to accumulate a list of arguments. args :: ArgsArguments v => v :-> [String] instance Arg [String] instance Arg String instance ArgsArguments [String] instance (Arg a, ArgsArguments r) => ArgsArguments (a -> r) instance SysOutputArguments (Action (String, String)) instance (Arg a, SysOutputArguments r) => SysOutputArguments (a -> r) instance SysCwdArguments (Action ()) instance (Arg a, SysCwdArguments r) => SysCwdArguments (a -> r) instance SysArguments (Action ()) instance (Arg a, SysArguments r) => SysArguments (a -> r) -- | 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. -- -- 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: -- -- -- -- The theory behind Shake is described in an ICFP 2012 paper, Shake -- Before Building -- Replacing Make with Haskell -- http://community.haskell.org/~ndm/downloads/paper-shake_before_building-10_sep_2012.pdf. -- The associated talk forms a short overview of Shake -- http://www.youtube.com/watch?v=xYCPpXVlqFM. -- -- Acknowledgements: Thanks to Austin Seipp for properly -- integrating the profiling code. module Development.Shake -- | 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. shake :: ShakeOptions -> Rules () -> IO () -- | The default set of ShakeOptions. shakeOptions :: ShakeOptions -- | Define an alias for the six type classes required for things involved -- in Shake Rules. This alias is only available in GHC 7.4 and -- above, and 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)
--   
type ShakeValue a = (Show a, Typeable a, Eq a, Hashable a, Binary a, NFData a) -- | Define a pair of types that can be used by Shake rules. To import all -- the type classes required see Development.Shake.Classes. class (ShakeValue key, ShakeValue value) => Rule key value storedValue :: Rule key value => key -> IO (Maybe value) -- | 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. data Rules a -- | Like rule, but lower priority, if no rule exists then -- defaultRule is checked. All default rules must be disjoint. defaultRule :: Rule key value => (key -> Maybe (Action value)) -> Rules () -- | Add a rule to build a key, returning an appropriate Action. All -- rules must be disjoint. To define lower priority rules use -- defaultRule. rule :: Rule key value => (key -> Maybe (Action value)) -> Rules () -- | Run an action, usually used for specifying top-level requirements. action :: Action a -> Rules () -- | Remove all actions specified in a set of rules, usually used for -- implementing command line specification of what to build. withoutActions :: Rules () -> Rules () -- | The Action monad, use liftIO to raise IO actions -- into it, and need to execute files. Action values are used by -- rule and action. data Action a -- | 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. apply :: Rule key value => [key] -> Action [value] -- | Apply a single rule, equivalent to calling apply with a -- singleton list. Where possible, use apply to allow parallelism. apply1 :: Rule key value => key -> Action value -- | 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). traced :: String -> IO a -> Action a -- | Lift a computation from the IO monad. liftIO :: MonadIO m => forall a. IO a -> m a -- | If an exception is raised by the Action, perform some -- IO. actionOnException :: Action a -> IO b -> Action a -- | After an Action, perform some IO, even if there is an -- exception. actionFinally :: Action a -> IO b -> Action a -- | Error representing all expected exceptions thrown by Shake. Problems -- when executing rules will be raising using this exception type. data ShakeException ShakeException :: String -> [String] -> SomeException -> ShakeException -- | The target that was being built when the exception occured. shakeExceptionTarget :: ShakeException -> String -- | The stack of targets, where the shakeExceptionTarget is last. shakeExceptionStack :: ShakeException -> [String] -- | The underlying exception that was raised. shakeExceptionInner :: ShakeException -> SomeException -- | Options to control the execution of Shake, usually specified by -- overriding fields in shakeOptions: -- --
--   shakeOptions{shakeThreads=4, shakeReport=Just "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. data ShakeOptions ShakeOptions :: FilePath -> Int -> String -> Verbosity -> Bool -> Maybe FilePath -> Bool -> Maybe Double -> Maybe Assume -> [(String, String)] -> Bool -> Bool -> Bool -> (IO Progress -> IO ()) -> (Verbosity -> String -> IO ()) -> ShakeOptions -- | 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. shakeFiles :: ShakeOptions -> FilePath -- | Defaults to 1. Maximum number of rules to run in parallel, -- similar to make --jobs=N. To enable parallelism you -- may need to compile with -threaded. For many build systems, a -- number equal to or slightly less than the number of physical -- processors works well. shakeThreads :: ShakeOptions -> Int -- | 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. shakeVersion :: ShakeOptions -> String -- | Defaults to Normal. What level of messages should be printed -- out. shakeVerbosity :: ShakeOptions -> Verbosity -- | Defaults to False. Operate in staunch mode, where building -- continues even after errors, similar to make --keep-going. shakeStaunch :: ShakeOptions -> Bool -- | Defaults to Nothing. Write an HTML 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. shakeReport :: ShakeOptions -> Maybe FilePath -- | Defaults to False. Perform basic sanity checks during building, -- checking the current directory is not modified and that output files -- are not modified by multiple rules. These sanity checks do not check -- for missing or redundant dependencies. shakeLint :: ShakeOptions -> Bool -- | 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. shakeFlush :: ShakeOptions -> Maybe Double -- | Defaults to Nothing. Assume all build objects are clean/dirty, -- see Assume for details. Can be used to implement make -- --touch. shakeAssume :: ShakeOptions -> Maybe Assume -- | 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). shakeAbbreviations :: ShakeOptions -> [(String, String)] -- | 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. shakeStorageLog :: ShakeOptions -> Bool -- | Defaults to True. Change stdout and stderr to -- line buffering while running Shake. shakeLineBuffering :: ShakeOptions -> Bool -- | Default to False. Print timing information for each stage at -- the end. shakeTimings :: ShakeOptions -> Bool -- | Defaults to no action. A function called on a separate thread when the -- build starts, allowing progress to be reported. For applications that -- want to display progress messages, progressSimple is often -- sufficient, but more advanced users should look at the Progress -- data type. shakeProgress :: ShakeOptions -> IO Progress -> 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. shakeOutput :: ShakeOptions -> Verbosity -> String -> IO () -- | 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. data Assume -- | 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. AssumeDirty :: Assume -- | 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. AssumeClean :: Assume -- | 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. AssumeSkip :: Assume -- | 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: -- -- shakeArgs :: ShakeOptions -> Rules () -> IO () -- | 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)
--   
-- -- -- -- 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. shakeArgsWith :: ShakeOptions -> [OptDescr (Either String a)] -> ([a] -> [String] -> IO (Maybe (Rules ()))) -> IO () -- | 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. shakeOptDescrs :: [OptDescr (Either String (ShakeOptions -> ShakeOptions))] -- | 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. data Progress Progress :: !Bool -> !(Maybe String) -> {-# UNPACK #-} !Int -> {-# UNPACK #-} !Int -> {-# UNPACK #-} !Int -> {-# UNPACK #-} !Int -> {-# UNPACK #-} !Double -> {-# UNPACK #-} !Double -> {-# UNPACK #-} !Double -> {-# UNPACK #-} !(Double, Int) -> Progress -- | Starts out True, becomes False once the build has -- completed. isRunning :: Progress -> !Bool -- | Starts out Nothing, becomes Just if a rule fails. isFailure :: Progress -> !(Maybe String) -- | Number of rules which were required, but were already in a valid -- state. countSkipped :: Progress -> {-# UNPACK #-} !Int -- | Number of rules which were have been built in this run. countBuilt :: Progress -> {-# UNPACK #-} !Int -- | Number of rules which have been built previously, but are not yet -- known to be required. countUnknown :: Progress -> {-# UNPACK #-} !Int -- | Number of rules which are currently required (ignoring dependencies -- that do not change), but not built. countTodo :: Progress -> {-# UNPACK #-} !Int -- | Time spent building countSkipped rules in previous runs. timeSkipped :: Progress -> {-# UNPACK #-} !Double -- | Time spent building countBuilt rules. timeBuilt :: Progress -> {-# UNPACK #-} !Double -- | Time spent building countUnknown rules in previous runs. timeUnknown :: Progress -> {-# UNPACK #-} !Double -- | Time spent building countTodo rules in previous runs, plus the -- number which have no known time (have never been built before). timeTodo :: Progress -> {-# UNPACK #-} !(Double, Int) -- | A simple method for displaying progress messages, suitable for using -- as shakeProgress. This function writes the current progress to -- the titlebar every five seconds. The function is defined as: -- --
--   progressSimple = progressDisplay 5 progressTitlebar
--   
progressSimple :: IO Progress -> IO () -- | 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. progressDisplay :: Double -> (String -> IO ()) -> IO Progress -> IO () -- | 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. progressTitlebar :: String -> IO () -- | The verbosity data type, used by shakeVerbosity. data Verbosity -- | Don't print any messages. Silent :: Verbosity -- | Only print essential messages, typically errors. Quiet :: Verbosity -- | Print errors and # command-name file-name when -- running a traced command. Normal :: Verbosity -- | Print errors and full command lines when running a system' -- command. Loud :: Verbosity -- | Print errors, full command line and status messages when starting a -- rule. Chatty :: Verbosity -- | Print messages for virtually everything (mostly for debugging). Diagnostic :: Verbosity -- | 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. getVerbosity :: Action Verbosity -- | 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). putLoud :: String -> Action () -- | 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 () -- | 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 () -- | Run an action with Quiet verbosity, in particular messages -- produced by traced (including from cmd or -- command) will not be printed to the screen. quietly :: Action a -> Action a -- | Execute a system command. Before running command make sure you -- need any files that are required 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 :: CmdResult r => [CmdOption] -> String -> [String] -> Action r -- | A version of command where you do not require any results, used -- to avoid errors about being unable to deduce CmdResult. command_ :: [CmdOption] -> String -> [String] -> Action () -- | A variable arity version of command. -- -- -- -- 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. cmd :: CmdArguments args => args :-> Action r -- | Collect the stdout of the process. If you are collecting the -- stdout, it will not be echoed to the terminal, unless you -- include EchoStdout. newtype Stdout Stdout :: String -> Stdout fromStdout :: Stdout -> String -- | Collect the stderr of the process. If you are collecting the -- stderr, it will not be echoed to the terminal, unless you -- include EchoStderr. newtype Stderr Stderr :: String -> Stderr fromStderr :: Stderr -> String -- | Collect the ExitCode of the process. If you do not collect the -- exit code, any ExitFailure will cause an exception. newtype Exit Exit :: ExitCode -> Exit fromExit :: Exit -> ExitCode -- | A class for specifying what results you want to collect from a -- process. Values are formed of Stdout, Stderr, -- Exit and tuples of those. class CmdResult a -- | Options passed to command or cmd to control how -- processes are executed. data CmdOption -- | Change the current directory in the spawned process. By default uses -- this processes current directory. Cwd :: FilePath -> CmdOption -- | Change the environment variables in the spawned process. By default -- uses this processes environment. Env :: [(String, String)] -> CmdOption -- | Given as the stdin of the spawned process. By default no -- stdin is given. Stdin :: String -> CmdOption -- | Pass the command to the shell without escaping - any arguments will be -- joined with spaces. By default arguments are escaped properly. Shell :: CmdOption -- | Treat the stdin/stdout/stderr messages as -- binary. By default streams use text encoding. BinaryPipes :: CmdOption -- | Name to use with traced, or "" for no tracing. By -- default traces using the name of the executable. Traced :: String -> CmdOption -- | Should I include the stderr in the exception if the command -- fails? Defaults to True. WithStderr :: Bool -> CmdOption -- | Should I echo the stdout? Defaults to True unless a -- Stdout result is required. EchoStdout :: Bool -> CmdOption -- | Should I echo the stderr? Defaults to True unless a -- Stderr result is required. EchoStderr :: Bool -> CmdOption -- | 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. system' :: FilePath -> [String] -> Action () -- | 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" []
--   
systemCwd :: FilePath -> FilePath -> [String] -> Action () -- | 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. systemOutput :: FilePath -> [String] -> Action (String, String) -- | copyFile' old new copies the existing file from old -- to new. The old file is has need called on it -- before copying the file. copyFile' :: FilePath -> FilePath -> Action () -- | Read a file, after calling need. readFile' :: FilePath -> Action String -- | A version of readFile' which also splits the result into lines. readFileLines :: FilePath -> Action [String] -- | Write a file, lifted to the Action monad. writeFile' :: FilePath -> String -> Action () -- | A version of writeFile' which writes out a list of lines. writeFileLines :: FilePath -> [String] -> Action () -- | Write a file, but only if the contents would change. writeFileChanged :: FilePath -> String -> Action () -- | Remove all empty directories and files that match any of the patterns -- beneath a directory. Some examples: -- --
--   removeFiles "output" ["//*"]
--   removeFiles "." ["//*.hi","//*.o"]
--   
-- -- This function is often useful when writing a clean action for -- your build system, often as a phony rule. removeFiles :: FilePath -> [FilePattern] -> IO () -- | 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. removeFilesAfter :: FilePath -> [FilePattern] -> Action () -- | Require that the following files are built before continuing. -- Particularly necessary when calling cmd or command. As -- an example: -- --
--   "//*.rot13" *> \out -> do
--       let src = dropExtension out
--       need [src]
--       cmd "rot13" [src] "-o" [out]
--   
need :: [FilePath] -> Action () -- | 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. want :: [FilePath] -> Rules () -- | 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]
--       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 () -- | Define a set of patterns, and if any of them match, run the associated -- rule. See *>. (**>) :: [FilePattern] -> (FilePath -> Action ()) -> Rules () -- | 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' out . map toUpper =<< readFile' src
--   
(?>) :: (FilePath -> Bool) -> (FilePath -> Action ()) -> Rules () -- | Declare a phony action, this is 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 intended to define command-line abbreviations. You -- should not need phony actions as dependencies of rules, as that -- will cause excessive rebuilding. phony :: String -> Action () -> Rules () -- | 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: -- --
--   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]. (?>>) :: (FilePath -> Maybe [FilePath]) -> ([FilePath] -> Action ()) -> Rules () -- | 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 = 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. (*>>) :: [FilePattern] -> ([FilePath] -> Action ()) -> Rules () -- | A type synonym for file patterns, containing // and -- *. For the syntax and semantics of FilePattern see -- ?==. type FilePattern = String -- | Match a FilePattern against a FilePath, There are only -- two special forms: -- -- -- -- 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"
--   
(?==) :: FilePattern -> FilePath -> Bool -- | Returns True if the file exists. doesFileExist :: FilePath -> Action Bool -- | Returns True if the directory exists. doesDirectoryExist :: FilePath -> Action Bool -- | 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. -- -- It is usually simpler to call either getDirectoryFiles or -- getDirectoryDirs. getDirectoryContents :: FilePath -> Action [FilePath] -- | 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. 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"]
--   
getDirectoryFiles :: FilePath -> [FilePattern] -> Action [FilePath] -- | Get the directories in a directory, not including . or -- ... All directories are relative to the argument directory. -- --
--   getDirectoryDirs "/Users"
--      -- Return all directories in the /Users directory
--      -- e.g. ["Emily","Henry","Neil"]
--   
getDirectoryDirs :: FilePath -> Action [FilePath] -- | Return Just the value of the environment variable, or -- Nothing if the variable is not set. getEnv :: String -> Action (Maybe String) -- | 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 (last . words . fromStdout) $ cmd "ghc --version"
--       ... rules ...
--   
-- -- If a rule calls askOracle (GhcVersion ()), that rule -- will be rerun whenever the GHC version changes. Some notes: -- -- -- -- 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. addOracle :: (ShakeValue q, ShakeValue a) => (q -> Action a) -> Rules (q -> Action a) -- | Get information previously added with addOracle. The -- question/answer types must match those provided to addOracle. askOracle :: (ShakeValue q, ShakeValue a) => q -> Action a -- | 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. askOracleWith :: (ShakeValue q, ShakeValue a) => q -> a -> Action a -- | Always rerun the associated action. Useful for defining rules that -- query the environment. For example: -- --
--   "ghcVersion.txt" *> \out -> do
--       alwaysRerun
--       Stdout stdout <- cmd "ghc --version"
--       writeFileChanged out stdout
--   
alwaysRerun :: Action () -- | A type representing a finite resource, which multiple build actions -- should respect. Created with newResource and used with -- withResource 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: -- --
--   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. 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 -- cmd) should be run inside withResource, not commands -- such as need. If an action requires multiple resources, use -- withResources to avoid deadlock. -- -- 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] ...
--   
data Resource -- | Create a new finite resource, given a name (for error messages) and a -- quantity of the resource that exists. For an example see -- Resource. newResource :: String -> Int -> Rules Resource -- | A version of newResource that runs in IO, and can be called -- before calling shake. Most people should use newResource -- instead. newResourceIO :: String -> Int -> IO Resource -- | Run an action which uses part of a finite resource. For an example see -- Resource. withResource :: Resource -> Int -> Action a -> Action a -- | 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. withResources :: [(Resource, Int)] -> Action a -> Action a -- | Given a way of loading information from a file, produce a cached -- version that will load each file at most once. Using the cached -- function will still result in a dependency on the original file. The -- argument function should not access any files other than the one -- passed as its argument. 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. newCache :: (FilePath -> IO a) -> Rules (FilePath -> Action a) -- | A version of newCache that runs in IO, and can be called before -- calling shake. Most people should use newCache instead. newCacheIO :: (FilePath -> IO a) -> IO (FilePath -> Action a)