-- 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. The homepage -- contains links to a user manual, an academic paper and further -- information: http://shakebuild.com -- -- To use Shake the user writes a Haskell program that imports -- Development.Shake, defines some build rules, and calls the -- Development.Shake.shakeArgs 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 also provides more accurate dependency tracking, -- including seamless support for generated files, and dependencies on -- system information (e.g. compiler version). @package shake @version 0.15.11 -- | A module for FilePath operations exposing -- System.FilePath plus some additional operations. -- -- Windows note: The extension methods (<.>, -- takeExtension etc) use the Posix variants since on Windows -- "//*" <.> "txt" produces "//*\\.txt" -- (which is bad for FilePattern values). 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 rules: -- --
-- 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, -- --
-- showsPrec d x r ++ s == showsPrec d x (r ++ s) ---- -- Derived instances of Read and Show satisfy the -- following: -- -- -- -- That is, readsPrec parses the string produced by -- showsPrec, and delivers the value that showsPrec started -- with. showsPrec :: Show a => Int -> a -> ShowS -- | A specialised variant of showsPrec, using precedence context -- zero, and returning an ordinary String. show :: Show a => a -> String -- | The method showList is provided to allow the programmer to give -- a specialised way of showing lists of values. For example, this is -- used by the predefined Show instance of the Char type, -- where values of type String should be shown in double quotes, -- rather than between square brackets. showList :: Show a => [a] -> ShowS -- | The class Typeable allows a concrete representation of a type -- to be calculated. class Typeable (a :: k) -- | 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. -- -- Minimal implementation: hashWithSalt. class Hashable a -- | Return a hash value for the argument, using the given salt. -- -- The general contract of hashWithSalt is: -- --
-- 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 -- | Encode a value in the Put monad. put :: Binary t => t -> Put -- | Decode a value in the Get monad get :: Binary t => Get t -- | A class of types that can be fully evaluated. -- -- Since: 1.1.0.0 class NFData a -- | rnf should reduce its argument to normal form (that is, fully -- evaluate all sub-components), and then return '()'. -- --
-- {-# LANGUAGE DeriveGeneric #-} -- -- import GHC.Generics (Generic) -- import Control.DeepSeq -- -- data Foo a = Foo a String -- deriving (Eq, Generic) -- -- instance NFData a => NFData (Foo a) -- -- data Colour = Red | Green | Blue -- deriving Generic -- -- instance NFData Colour ---- -- Starting with GHC 7.10, the example above can be written more -- concisely by enabling the new DeriveAnyClass extension: -- --
-- {-# LANGUAGE DeriveGeneric, DeriveAnyClass #-} -- -- import GHC.Generics (Generic) -- import Control.DeepSeq -- -- data Foo a = Foo a String -- deriving (Eq, Generic, NFData) -- -- data Colour = Red | Green | Blue -- deriving (Generic, NFData) ---- --
-- rnf a = seq a () ---- -- However, starting with deepseq-1.4.0.0, the default -- implementation is based on DefaultSignatures allowing for -- more accurate auto-derived NFData instances. If you need the -- previously used exact default rnf method implementation -- semantics, use -- --
-- instance NFData Colour where rnf x = seq x () ---- -- or alternatively -- --
-- {-# LANGUAGE BangPatterns #-} -- instance NFData Colour where rnf !_ = () --rnf :: NFData a => a -> () -- | This module provides functions for calling command line programs, -- primarily command and cmd. As a simple example: -- --
-- command [] "gcc" ["-c",myfile] ---- -- The functions from this module are now available directly from -- Development.Shake. You should only need to import this module -- if you are using the cmd function in the IO monad. module Development.Shake.Command -- | Execute a system command. Before running command make sure you -- need any files that are used by the command. -- -- This function takes a list of options (often just [], see -- CmdOption for the available options), the name of the -- executable (either a full name, or a program on the $PATH) -- and a list of arguments. The result is often (), but can be a -- tuple containg any of Stdout, Stderr and Exit. -- Some examples: -- --
-- command_ [] "gcc" ["-c","myfile.c"] -- compile a file, throwing an exception on failure -- Exit c <- command [] "gcc" ["-c",myfile] -- run a command, recording the exit code -- (Exit c, Stderr err) <- command [] "gcc" ["-c","myfile.c"] -- run a command, recording the exit code and error output -- Stdout out <- command [] "gcc" ["-MM","myfile.c"] -- run a command, recording the output -- command_ [Cwd "generated"] "gcc" ["-c",myfile] -- run a command in a directory ---- -- Unless you retrieve the ExitCode using Exit, any -- ExitFailure will throw an error, including the Stderr in -- the exception message. If you capture the Stdout or -- Stderr, that stream will not be echoed to the console, unless -- you use the option EchoStdout or EchoStderr. -- -- If you use command inside a do block and do not use -- the result, you may get a compile-time error about being unable to -- deduce CmdResult. To avoid this error, use command_. -- -- By default the stderr stream will be captured for use in -- error messages, and also echoed. To only echo pass -- WithStderr False, which causes no streams to be -- captured by Shake, and certain programs (e.g. gcc) to detect -- they are running in a terminal. command :: 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 () -- | Execute a system command. Before running cmd make sure you -- need any files that are used by the command. -- --
-- unit $ cmd "git log --pretty=" "oneline" -- git log --pretty= oneline -- unit $ cmd "git log --pretty=" ["oneline"] -- git log --pretty= oneline -- unit $ cmd "git log" ("--pretty=" ++ "oneline") -- git log --pretty=oneline -- unit $ cmd "git log" ("--pretty=" ++ "one line") -- git log --pretty=one line -- unit $ cmd "git log" ["--pretty=" ++ "one line"] -- git log "--pretty=one line" ---- -- More examples, including return values, see this translation of the -- examples given for the command function: -- --
-- () <- cmd "gcc -c myfile.c" -- compile a file, throwing an exception on failure -- unit $ cmd "gcc -c myfile.c" -- alternative to () <- binding. -- 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, or use the unit function. -- -- The cmd function can also be run in the IO monad, but -- then Traced is ignored and command lines are not echoed. As an -- example: -- --
-- cmd (Cwd "generated") Shell "gcc -c myfile.c" :: IO () --cmd :: CmdArguments args => args :-> Action r -- | The identity function which requires the inner argument to be -- (). Useful for functions with overloaded return types. -- --
-- \(x :: Maybe ()) -> unit x == x --unit :: m () -> m () -- | The arguments to cmd - see cmd for examples and -- semantics. class CmdArguments t -- | A type annotation, equivalent to the first argument, but in variable -- argument contexts, gives a clue as to what return type is expected -- (not actually enforced). type (:->) a t = a -- | Collect the stdout of the process. If used, the -- stdout will not be echoed to the terminal, unless you include -- EchoStdout. The value type may be either String, or -- either lazy or strict ByteString. newtype Stdout a Stdout :: a -> Stdout a [fromStdout] :: Stdout a -> a -- | Collect the stderr of the process. If used, the -- stderr will not be echoed to the terminal, unless you include -- EchoStderr. The value type may be either String, or -- either lazy or strict ByteString. newtype Stderr a Stderr :: a -> Stderr a [fromStderr] :: Stderr a -> a -- | Collect the stdout and stderr of the process. If -- used, the stderr and stdout will not be echoed to -- the terminal, unless you include EchoStdout and -- EchoStderr. The value type may be either String, or -- either lazy or strict ByteString. newtype Stdouterr a Stdouterr :: a -> Stdouterr a [fromStdouterr] :: Stdouterr a -> a -- | 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 -- | Collect the ProcessHandle of the process. If you do collect the -- process handle, the command will run asyncronously and the call to -- 'cmd'/'command' will return as soon as the process is spawned. Any -- 'Stdout'\/'Stderr' captures will return empty strings. newtype Process Process :: ProcessHandle -> Process [fromProcess] :: Process -> ProcessHandle -- | Collect the time taken to execute the process. Can be used in -- conjunction with CmdLine to write helper functions that print -- out the time of a result. -- --
-- timer :: (CmdResult r, MonadIO m) => (forall r . CmdResult r => m r) -> m r -- timer act = do -- (CmdTime t, CmdLine x, r) <- act -- liftIO $ putStrLn $ "Command " ++ x ++ " took " ++ show t ++ " seconds" -- return r -- -- run :: IO () -- run = timer $ cmd "ghc --version" --newtype CmdTime CmdTime :: Double -> CmdTime [fromCmdTime] :: CmdTime -> Double -- | Collect the command line used for the process. This command line will -- be approximate - suitable for user diagnostics, but not for direct -- execution. newtype CmdLine CmdLine :: String -> CmdLine [fromCmdLine] :: CmdLine -> String -- | 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 -- | The allowable String-like values that can be captured. class CmdString 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 -- | Add an environment variable in the child process. AddEnv :: String -> String -> CmdOption -- | Remove an environment variable from the child process. RemEnv :: String -> CmdOption -- | Add some items to the prefix and suffix of the $PATH -- variable. AddPath :: [String] -> [String] -> CmdOption -- | Given as the stdin of the spawned process. By default the -- stdin is inherited. Stdin :: String -> CmdOption -- | Given as the stdin of the spawned process. StdinBS :: ByteString -> CmdOption -- | Take the stdin from a file. FileStdin :: FilePath -> 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 String results use text encoding and -- ByteString results use binary encoding. BinaryPipes :: CmdOption -- | Name to use with traced, or "" for no tracing. By -- default traces using the name of the executable. Traced :: String -> CmdOption -- | Abort the computation after N seconds, will raise a failure exit code. -- Calls interruptProcessGroupOf and terminateProcess, -- but may sometimes fail to abort the process and not timeout. Timeout :: Double -> CmdOption -- | Should I include the stdout in the exception if the command -- fails? Defaults to False. WithStdout :: Bool -> 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 or you use FileStdout. EchoStdout :: Bool -> CmdOption -- | Should I echo the stderr? Defaults to True unless a -- Stderr result is required or you use FileStderr. EchoStderr :: Bool -> CmdOption -- | Should I put the stdout to a file. FileStdout :: FilePath -> CmdOption -- | Should I put the stderr to a file. FileStderr :: FilePath -> CmdOption -- | Compute dependencies automatically. AutoDeps :: CmdOption -- | Deprecated: Use AddPath. This function will be removed -- in a future version. -- -- Add a prefix and suffix to the $PATH environment variable. -- For example: -- --
-- opt <- addPath ["/usr/special"] [] -- cmd opt "userbinary --version" ---- -- Would prepend /usr/special to the current $PATH, and -- the command would pick /usr/special/userbinary, if it exists. -- To add other variables see addEnv. addPath :: MonadIO m => [String] -> [String] -> m CmdOption -- | Deprecated: Use AddEnv. This function will be removed in -- a future version. -- -- Add a single variable to the environment. For example: -- --
-- opt <- addEnv [("CFLAGS","-O2")] -- cmd opt "gcc -c main.c" ---- -- Would add the environment variable $CFLAGS with value -- -O2. If the variable $CFLAGS was already defined it -- would be overwritten. If you wish to modify $PATH see -- addPath. addEnv :: MonadIO m => [(String, String)] -> m CmdOption instance GHC.Classes.Eq Development.Shake.Command.Result instance GHC.Classes.Eq Development.Shake.Command.Str instance GHC.Classes.Eq Development.Shake.Command.Pid instance Development.Shake.Command.CmdString () instance Development.Shake.Command.CmdString GHC.Base.String instance Development.Shake.Command.CmdString Data.ByteString.Internal.ByteString instance Development.Shake.Command.CmdString Data.ByteString.Lazy.Internal.ByteString instance Development.Shake.Command.CmdResult Development.Shake.Command.Exit instance Development.Shake.Command.CmdResult GHC.IO.Exception.ExitCode instance Development.Shake.Command.CmdResult Development.Shake.Command.Process instance Development.Shake.Command.CmdResult System.Process.Internals.ProcessHandle instance Development.Shake.Command.CmdResult Development.Shake.Command.CmdLine instance Development.Shake.Command.CmdResult Development.Shake.Command.CmdTime instance Development.Shake.Command.CmdString a => Development.Shake.Command.CmdResult (Development.Shake.Command.Stdout a) instance Development.Shake.Command.CmdString a => Development.Shake.Command.CmdResult (Development.Shake.Command.Stderr a) instance Development.Shake.Command.CmdString a => Development.Shake.Command.CmdResult (Development.Shake.Command.Stdouterr a) instance Development.Shake.Command.CmdResult () instance (Development.Shake.Command.CmdResult x1, Development.Shake.Command.CmdResult x2) => Development.Shake.Command.CmdResult (x1, x2) instance (Development.Shake.Command.CmdResult x1, Development.Shake.Command.CmdResult x2, Development.Shake.Command.CmdResult x3) => Development.Shake.Command.CmdResult (x1, x2, x3) instance (Development.Shake.Command.CmdResult x1, Development.Shake.Command.CmdResult x2, Development.Shake.Command.CmdResult x3, Development.Shake.Command.CmdResult x4) => Development.Shake.Command.CmdResult (x1, x2, x3, x4) instance (Development.Shake.Command.CmdResult x1, Development.Shake.Command.CmdResult x2, Development.Shake.Command.CmdResult x3, Development.Shake.Command.CmdResult x4, Development.Shake.Command.CmdResult x5) => Development.Shake.Command.CmdResult (x1, x2, x3, x4, x5) instance (Development.Shake.Command.Arg a, Development.Shake.Command.CmdArguments r) => Development.Shake.Command.CmdArguments (a -> r) instance Development.Shake.Command.CmdResult r => Development.Shake.Command.CmdArguments (Development.Shake.Core.Action r) instance Development.Shake.Command.CmdResult r => Development.Shake.Command.CmdArguments (GHC.Types.IO r) instance Development.Shake.Command.CmdArguments [Data.Either.Either Development.Shake.CmdOption.CmdOption GHC.Base.String] instance Development.Shake.Command.Arg GHC.Base.String instance Development.Shake.Command.Arg [GHC.Base.String] instance Development.Shake.Command.Arg Development.Shake.CmdOption.CmdOption instance Development.Shake.Command.Arg [Development.Shake.CmdOption.CmdOption] instance Development.Shake.Command.Arg a => Development.Shake.Command.Arg (GHC.Base.Maybe a) -- | This module is used for defining new types of rules for Shake build -- systems. Most users will find the built-in set of rules sufficient. module Development.Shake.Rule -- | Define a pair of types that can be used by Shake rules. To import all -- the type classes required see Development.Shake.Classes. -- -- A Rule instance for a class of artifacts (e.g. files) -- provides: -- --
-- newtype File = File FilePath deriving (Show, Typeable, Eq, Hashable, Binary, NFData) -- newtype Modtime = Modtime Double deriving (Show, Typeable, Eq, Hashable, Binary, NFData) -- getFileModtime file = ... -- -- instance Rule File Modtime where -- storedValue _ (File x) = do -- exists <- System.Directory.doesFileExist x -- if exists then Just <$> getFileModtime x else return Nothing -- equalValue _ _ t1 t2 = -- if t1 == t2 then EqualCheap else NotEqual ---- -- This example instance means: -- --
-- -- Compile foo files; for every foo output file there must be a -- -- single input file named "filename.foo". -- compileFoo :: Rules () -- compileFoo = rule (Just . compile) -- where -- compile :: File -> Action Modtime -- compile (File outputFile) = do -- -- figure out the name of the input file -- let inputFile = outputFile <.> "foo" -- unit $ cmd "fooCC" inputFile outputFile -- -- return the (new) file modtime of the output file: -- getFileModtime outputFile ---- -- Note: In this example, the timestamps of the input files are -- never used, let alone compared to the timestamps of the ouput files. -- Dependencies between output and input files are not expressed -- by Rule instances. Dependencies are created automatically by -- apply. -- -- For rules whose values are not stored externally, storedValue -- should return Just with a sentinel value and equalValue -- should always return EqualCheap for that sentinel. class (ShakeValue key, ShakeValue value) => Rule key value where equalValue _ _ v1 v2 = if v1 == v2 then EqualCheap else NotEqual -- | [Required] Retrieve the value associated with a -- key, if available. -- -- As an example for filenames/timestamps, if the file exists you should -- return Just the timestamp, but otherwise return Nothing. storedValue :: Rule key value => ShakeOptions -> key -> IO (Maybe value) -- | [Optional] Equality check, with a notion of how expensive the -- check was. equalValue :: Rule key value => ShakeOptions -> key -> value -> value -> EqualCost -- | An equality check and a cost. data EqualCost -- | The equality check was cheap. EqualCheap :: EqualCost -- | The equality check was expensive, as the results are not trivially -- equal. EqualExpensive :: EqualCost -- | The values are not equal. NotEqual :: EqualCost -- | Add a rule to build a key, returning an appropriate Action if -- the key matches, or Nothing otherwise. All rules at a -- given priority must be disjoint on all used key values, with -- at most one match. Rules have priority 1 by default, which can be -- modified with priority. rule :: Rule key value => (key -> Maybe (Action value)) -> Rules () -- | 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. All key values passed -- to apply become dependencies of the Action. 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 -- | Track that a key has been used by the action preceeding it. trackUse :: ShakeValue key => key -> Action () -- | Track that a key has been changed by the action preceeding it. trackChange :: ShakeValue key => key -> Action () -- | Allow any matching key to violate the tracking rules. trackAllow :: ShakeValue key => (key -> Bool) -> Action () -- | A deprecated way of defining a low priority rule. Defined as: -- --
-- defaultRule = priority 0 . rule ---- | Deprecated: Use rule with priority 0 defaultRule :: Rule key value => (key -> Maybe (Action value)) -> Rules () -- | 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: -- --
-- ghc --make MyBuildSystem -rtsopts -with-rtsopts=-I0 ---- --
-- 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. 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 () -- | Change the matching behaviour of rules so rules do not have to be -- disjoint, but are instead matched in order. Only recommended for small -- blocks containing a handful of rules. -- --
-- alternatives $ do -- "hello.*" %> \out -> writeFile' out "hello.*" -- "*.txt" %> \out -> writeFile' out "*.txt" ---- -- In this example hello.txt will match the first rule, instead -- of raising an error about ambiguity. Inside alternatives the -- priority of each rule is not used to determine which rule -- matches, but the resulting match uses that priority compared to the -- rules outside the alternatives block. alternatives :: Rules () -> Rules () -- | Change the priority of a given set of rules, where higher priorities -- take precedence. All matching rules at a given priority must be -- disjoint, or an error is raised. All builtin Shake rules have priority -- between 0 and 1. Excessive use of priority is discouraged. As -- an example: -- --
-- priority 4 $ "hello.*" %> \out -> writeFile' out "hello.*" -- priority 8 $ "*.txt" %> \out -> writeFile' out "*.txt" ---- -- In this example hello.txt will match the second rule, instead -- of raising an error about ambiguity. -- -- The priority function obeys the invariants: -- --
-- priority p1 (priority p2 r1) === priority p1 r1 -- priority p1 (r1 >> r2) === priority p1 r1 >> priority p1 r2 --priority :: Double -> 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. The Action monad tracks the -- dependencies of a Rule. data Action a -- | Write an action to the trace list, along with the start/end time of -- running the IO action. The cmd and command functions -- automatically call traced. The trace list is used for profile -- reports (see shakeReport). -- -- By default traced prints some useful extra context about what -- Shake is building, e.g.: -- --
-- # traced message (for myobject.o) ---- -- To suppress the output of traced (for example you want more -- control over the message using putNormal), use the -- quietly combinator. 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=["report.html"]} ---- -- The Data instance for this type reports the -- shakeProgress and shakeOutput fields as having the -- abstract type Hidden, because Data cannot be defined for -- functions or TypeReps. data ShakeOptions ShakeOptions :: FilePath -> Int -> String -> Verbosity -> Bool -> [FilePath] -> Maybe Lint -> [FilePath] -> [FilePattern] -> [CmdOption] -> Maybe Double -> Maybe Assume -> [(String, String)] -> Bool -> Bool -> Bool -> Bool -> Change -> Bool -> [FilePath] -> Bool -> (IO Progress -> IO ()) -> (Verbosity -> String -> IO ()) -> HashMap TypeRep Dynamic -> ShakeOptions -- | Defaults to .shake. The directory used for storing Shake -- metadata files. All metadata files will be named -- shakeFiles/.shake.file-name, for some -- file-name. If the shakeFiles directory does not -- exist it will be created. [shakeFiles] :: ShakeOptions -> FilePath -- | Defaults to 1. Maximum number of rules to run in parallel, -- similar to make --jobs=N. For many build systems, a -- number equal to or slightly less than the number of physical -- processors works well. Use 0 to match the detected number of -- processors (when 0, getShakeOptions will return the -- number of threads used). [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 []. 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. [shakeReport] :: ShakeOptions -> [FilePath] -- | Defaults to Nothing. Perform sanity checks during building, see -- Lint for details. [shakeLint] :: ShakeOptions -> Maybe Lint -- | Directories in which the files will be tracked by the linter. [shakeLintInside] :: ShakeOptions -> [FilePath] -- | File patterns which are ignored from linter tracking, a bit like -- calling trackAllow in every rule. [shakeLintIgnore] :: ShakeOptions -> [FilePattern] -- | Defaults to []. Additional options to be passed to all -- command invocations. [shakeCommandOptions] :: ShakeOptions -> [CmdOption] -- | 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/.shake.storage.log whenever a storage event -- happens which may impact on the current stored progress. Examples -- include database version number changes, database compaction or -- corrupt files. [shakeStorageLog] :: ShakeOptions -> Bool -- | Defaults to True. Change stdout and stderr to -- line buffering while running Shake. [shakeLineBuffering] :: ShakeOptions -> Bool -- | Defaults to False. Print timing information for each stage at -- the end. [shakeTimings] :: ShakeOptions -> 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. [shakeRunCommands] :: ShakeOptions -> Bool -- | Default to ChangeModtime. How to check if a file has changed, -- see Change for details. [shakeChange] :: ShakeOptions -> Change -- | 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). [shakeCreationCheck] :: ShakeOptions -> Bool -- | 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. [shakeLiveFiles] :: ShakeOptions -> [FilePath] -- | Defaults to False. Ignore any differences in -- shakeVersion. [shakeVersionIgnore] :: ShakeOptions -> Bool -- | 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. [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 () -- | This a map which can be used to store arbitrary extra information that -- a user may need when writing Rules. The correct way to use -- this is to define a (hidden) newtype to use as a key, so that -- conflicts cannot occur. [shakeExtra] :: ShakeOptions -> HashMap TypeRep Dynamic -- | 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 -- | Which lint checks to perform, used by shakeLint. data Lint -- | 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. LintBasic :: Lint -- | Track which files are accessed by command line programs using -- fsatrace. LintFSATrace :: Lint -- | 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). data Change -- | 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. ChangeModtime :: Change -- | 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. ChangeDigest :: Change -- | 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. ChangeModtimeAndDigest :: Change -- | Use ChangeModtimeAndDigest for input/source files and -- ChangeModtime for output files. ChangeModtimeAndDigestInput :: Change -- | 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. ChangeModtimeOrDigest :: Change -- | Get the initial ShakeOptions, these will not change during the -- build process. getShakeOptions :: Action ShakeOptions -- | Get a checksum of a list of files, suitable for using as -- shakeVersion. This will trigger a rebuild when the Shake rules -- defined in any of the files are changed. For example: -- --
-- main = do -- ver <- getHashedShakeVersion ["Shakefile.hs"] -- shakeArgs shakeOptions{shakeVersion = ver} ... ---- -- To automatically detect the name of the current file, turn on the -- TemplateHaskell extension and write $(LitE . StringL . -- loc_filename <$> location). -- -- This feature can be turned off during development by passing the flag -- --no-rule-version or setting shakeVersionIgnore to -- True. getHashedShakeVersion :: [FilePath] -> IO String -- | 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: -- --
-- shakeArgsWith opts flags (\flagValues argValues -> result) ---- --
-- 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 either -- passing a callback function to shakeProgress (asynchronous -- output) or getProgress (synchronous output). Typically a build -- system will pass progressDisplay to shakeProgress, which -- will poll this value and produce status messages. data Progress Progress :: !(Maybe String) -> {-# UNPACK #-} !Int -> {-# UNPACK #-} !Int -> {-# UNPACK #-} !Int -> {-# UNPACK #-} !Int -> {-# UNPACK #-} !Double -> {-# UNPACK #-} !Double -> {-# UNPACK #-} !Double -> {-# UNPACK #-} !(Double, Int) -> Progress -- | Starts out Nothing, becomes Just a target name 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 using progressTitlebar, and -- calls any shake-progress program on the $PATH using -- progressProgram. 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 () -- | Call the program shake-progress if it is on the -- $PATH. The program is called with the following arguments: -- --
-- command_ [] "gcc" ["-c","myfile.c"] -- compile a file, throwing an exception on failure -- Exit c <- command [] "gcc" ["-c",myfile] -- run a command, recording the exit code -- (Exit c, Stderr err) <- command [] "gcc" ["-c","myfile.c"] -- run a command, recording the exit code and error output -- Stdout out <- command [] "gcc" ["-MM","myfile.c"] -- run a command, recording the output -- command_ [Cwd "generated"] "gcc" ["-c",myfile] -- run a command in a directory ---- -- Unless you retrieve the ExitCode using Exit, any -- ExitFailure will throw an error, including the Stderr in -- the exception message. If you capture the Stdout or -- Stderr, that stream will not be echoed to the console, unless -- you use the option EchoStdout or EchoStderr. -- -- If you use command inside a do block and do not use -- the result, you may get a compile-time error about being unable to -- deduce CmdResult. To avoid this error, use command_. -- -- By default the stderr stream will be captured for use in -- error messages, and also echoed. To only echo pass -- WithStderr False, which causes no streams to be -- captured by Shake, and certain programs (e.g. gcc) to detect -- they are running in a terminal. command :: 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 () -- | Execute a system command. Before running cmd make sure you -- need any files that are used by the command. -- --
-- unit $ cmd "git log --pretty=" "oneline" -- git log --pretty= oneline -- unit $ cmd "git log --pretty=" ["oneline"] -- git log --pretty= oneline -- unit $ cmd "git log" ("--pretty=" ++ "oneline") -- git log --pretty=oneline -- unit $ cmd "git log" ("--pretty=" ++ "one line") -- git log --pretty=one line -- unit $ cmd "git log" ["--pretty=" ++ "one line"] -- git log "--pretty=one line" ---- -- More examples, including return values, see this translation of the -- examples given for the command function: -- --
-- () <- cmd "gcc -c myfile.c" -- compile a file, throwing an exception on failure -- unit $ cmd "gcc -c myfile.c" -- alternative to () <- binding. -- 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, or use the unit function. -- -- The cmd function can also be run in the IO monad, but -- then Traced is ignored and command lines are not echoed. As an -- example: -- --
-- cmd (Cwd "generated") Shell "gcc -c myfile.c" :: IO () --cmd :: CmdArguments args => args :-> Action r -- | The identity function which requires the inner argument to be -- (). Useful for functions with overloaded return types. -- --
-- \(x :: Maybe ()) -> unit x == x --unit :: m () -> m () -- | Collect the stdout of the process. If used, the -- stdout will not be echoed to the terminal, unless you include -- EchoStdout. The value type may be either String, or -- either lazy or strict ByteString. newtype Stdout a Stdout :: a -> Stdout a [fromStdout] :: Stdout a -> a -- | Collect the stderr of the process. If used, the -- stderr will not be echoed to the terminal, unless you include -- EchoStderr. The value type may be either String, or -- either lazy or strict ByteString. newtype Stderr a Stderr :: a -> Stderr a [fromStderr] :: Stderr a -> a -- | Collect the stdout and stderr of the process. If -- used, the stderr and stdout will not be echoed to -- the terminal, unless you include EchoStdout and -- EchoStderr. The value type may be either String, or -- either lazy or strict ByteString. newtype Stdouterr a Stdouterr :: a -> Stdouterr a [fromStdouterr] :: Stdouterr a -> a -- | 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 -- | Collect the time taken to execute the process. Can be used in -- conjunction with CmdLine to write helper functions that print -- out the time of a result. -- --
-- timer :: (CmdResult r, MonadIO m) => (forall r . CmdResult r => m r) -> m r -- timer act = do -- (CmdTime t, CmdLine x, r) <- act -- liftIO $ putStrLn $ "Command " ++ x ++ " took " ++ show t ++ " seconds" -- return r -- -- run :: IO () -- run = timer $ cmd "ghc --version" --newtype CmdTime CmdTime :: Double -> CmdTime [fromCmdTime] :: CmdTime -> Double -- | Collect the command line used for the process. This command line will -- be approximate - suitable for user diagnostics, but not for direct -- execution. newtype CmdLine CmdLine :: String -> CmdLine [fromCmdLine] :: CmdLine -> String -- | 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 -- | The allowable String-like values that can be captured. class CmdString 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 -- | Add an environment variable in the child process. AddEnv :: String -> String -> CmdOption -- | Remove an environment variable from the child process. RemEnv :: String -> CmdOption -- | Add some items to the prefix and suffix of the $PATH -- variable. AddPath :: [String] -> [String] -> CmdOption -- | Given as the stdin of the spawned process. By default the -- stdin is inherited. Stdin :: String -> CmdOption -- | Given as the stdin of the spawned process. StdinBS :: ByteString -> CmdOption -- | Take the stdin from a file. FileStdin :: FilePath -> 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 String results use text encoding and -- ByteString results use binary encoding. BinaryPipes :: CmdOption -- | Name to use with traced, or "" for no tracing. By -- default traces using the name of the executable. Traced :: String -> CmdOption -- | Abort the computation after N seconds, will raise a failure exit code. -- Calls interruptProcessGroupOf and terminateProcess, -- but may sometimes fail to abort the process and not timeout. Timeout :: Double -> CmdOption -- | Should I include the stdout in the exception if the command -- fails? Defaults to False. WithStdout :: Bool -> 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 or you use FileStdout. EchoStdout :: Bool -> CmdOption -- | Should I echo the stderr? Defaults to True unless a -- Stderr result is required or you use FileStderr. EchoStderr :: Bool -> CmdOption -- | Should I put the stdout to a file. FileStdout :: FilePath -> CmdOption -- | Should I put the stderr to a file. FileStderr :: FilePath -> CmdOption -- | Compute dependencies automatically. AutoDeps :: CmdOption -- | Deprecated: Use AddPath. This function will be removed -- in a future version. -- -- Add a prefix and suffix to the $PATH environment variable. -- For example: -- --
-- opt <- addPath ["/usr/special"] [] -- cmd opt "userbinary --version" ---- -- Would prepend /usr/special to the current $PATH, and -- the command would pick /usr/special/userbinary, if it exists. -- To add other variables see addEnv. addPath :: MonadIO m => [String] -> [String] -> m CmdOption -- | Deprecated: Use AddEnv. This function will be removed in -- a future version. -- -- Add a single variable to the environment. For example: -- --
-- opt <- addEnv [("CFLAGS","-O2")] -- cmd opt "gcc -c main.c" ---- -- Would add the environment variable $CFLAGS with value -- -O2. If the variable $CFLAGS was already defined it -- would be overwritten. If you wish to modify $PATH see -- addPath. addEnv :: MonadIO m => [(String, String)] -> m CmdOption -- | Execute a list of actions in parallel. In most cases need -- will be more appropriate to benefit from parallelism. parallel :: [Action a] -> Action [a] -- | A parallel version of forM. forP :: [a] -> (a -> Action b) -> Action [b] -- | Execute two operations in parallel, based on parallel. par :: Action a -> Action b -> Action (a, b) -- | copyFile' old new copies the existing file from old -- to new. The old file will be tracked as a -- dependency. copyFile' :: FilePath -> FilePath -> Action () -- | copyFileChanged old new copies the existing file from -- old to new, if the contents have changed. The -- old file will be tracked as a dependency. copyFileChanged :: FilePath -> FilePath -> Action () -- | Read a file, after calling need. The argument file will be -- tracked as a dependency. readFile' :: FilePath -> Action String -- | A version of readFile' which also splits the result into lines. -- The argument file will be tracked as a dependency. readFileLines :: FilePath -> Action [String] -- | Write a file, lifted to the Action monad. writeFile' :: MonadIO m => FilePath -> String -> m () -- | A version of writeFile' which writes out a list of lines. writeFileLines :: MonadIO m => FilePath -> [String] -> m () -- | Write a file, but only if the contents would change. writeFileChanged :: MonadIO m => FilePath -> String -> m () -- | Remove all files and directories that match any of the patterns within -- a directory. Some examples: -- --
-- removeFiles "output" ["//*"] -- delete everything inside 'output' -- removeFiles "output" ["//"] -- delete 'output' itself -- removeFiles "." ["//*.hi","//*.o"] -- delete all '.hi' and '.o' files ---- -- If the argument directory is missing no error is raised. This function -- will follow symlinks, so should be used with care. -- -- This function is often useful when writing a clean action for -- your build system, often as a phony rule. 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 () -- | Create a temporary file in the temporary directory. The file will be -- deleted after the action completes (provided the file is not still -- open). The FilePath will not have any file extension, will -- exist, and will be zero bytes long. If you require a file with a -- specific name, use withTempDir. withTempFile :: (FilePath -> Action a) -> Action a -- | Create a temporary directory inside the system temporary directory. -- The directory will be deleted after the action completes. withTempDir :: (FilePath -> Action a) -> Action a -- | Add a dependency on the file arguments, ensuring they are built before -- continuing. The file arguments may be built in parallel, in any order. -- This function is particularly necessary when calling cmd or -- command. As an example: -- --
-- "//*.rot13" %> \out -> do -- let src = dropExtension out -- need [src] -- cmd "rot13" [src] "-o" [out] ---- -- Usually need [foo,bar] is preferable to need [foo] -- >> need [bar] as the former allows greater parallelism, -- while the latter requires foo to finish building before -- starting to build bar. -- -- This function should not be called with wildcards (e.g. *.txt -- - use getDirectoryFiles to expand them), environment -- variables (e.g. $HOME - use getEnv to expand them) -- or directories (directories cannot be tracked directly - track files -- within the directory instead). need :: [FilePath] -> Action () -- | 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. want :: [FilePath] -> Rules () -- | Define a rule that matches a FilePattern, see ?== for -- the pattern rules. Patterns with no wildcards have higher priority -- than those with wildcards, and no file required by the system may be -- matched by more than one pattern at the same priority (see -- priority and alternatives to modify this behaviour). -- This function will create the directory for the result file, if -- necessary. -- --
-- "*.asm.o" %> \out -> do -- let src = dropExtension out -- need [src] -- cmd "as" [src] "-o" [out] ---- -- To define a build system for multiple compiled languages, we recommend -- using .asm.o, .cpp.o, .hs.o, to indicate -- which language produces an object file. I.e., the file -- foo.cpp produces object file foo.cpp.o. -- -- Note that matching is case-sensitive, even on Windows. -- -- If the Action completes successfully the file is considered -- up-to-date, even if the file has not changed. (%>) :: FilePattern -> (FilePath -> Action ()) -> Rules () -- | 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 %>. (|%>) :: [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. This function will create the directory for -- the result file, if necessary. -- --
-- (all isUpper . takeBaseName) ?> \out -> do -- let src = replaceBaseName out $ map toLower $ takeBaseName out -- writeFile' out . map toUpper =<< readFile' src ---- -- If the Action completes successfully the file is considered -- up-to-date, even if the file has not changed. (?>) :: (FilePath -> Bool) -> (FilePath -> Action ()) -> Rules () -- | Declare a Make-style phony action. A phony target does not name a file -- (despite living in the same namespace as file rules); rather, it names -- some action to be executed when explicitly requested. You can demand -- phony rules using want. (And need, although -- that's not recommended.) -- -- Phony actions are intended to define recipes that can be executed by -- the user. If you need a phony action in a rule then every -- execution where that rule is required will rerun both the rule and the -- phony action. However, note that phony actions are never executed more -- than once in a single build run. -- -- In make, the .PHONY attribute on non-file-producing rules has -- a similar effect. However, while in make it is acceptable to omit the -- .PHONY attribute as long as you don't create the file in -- question, a Shake rule which behaves this way will fail lint. Use a -- phony rule! For file-producing rules which should be rerun every -- execution of Shake, see alwaysRerun. phony :: String -> Action () -> Rules () -- | Infix operator alias for phony, for sake of consistency with -- normal rules. (~>) :: String -> Action () -> Rules () -- | A predicate version of phony, return Just with the -- Action for the matching rules. phonys :: (String -> Maybe (Action ())) -> Rules () -- | 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. (&%>) :: [FilePattern] -> ([FilePath] -> Action ()) -> Rules () -- | 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]. (&?>) :: (FilePath -> Maybe [FilePath]) -> ([FilePath] -> Action ()) -> Rules () -- | 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. orderOnly :: [FilePath] -> Action () -- | Run an action but do not depend on anything the action uses. A more -- general version of orderOnly. orderOnlyAction :: Action a -> Action a -- | A type synonym for file patterns, containing // and -- *. For the syntax and semantics of FilePattern see -- ?==. -- -- Most normaliseExd FilePath values are suitable as -- FilePattern values which match only that specific file. On -- Windows \ is treated as equivalent to /. -- -- You can write FilePattern values as a literal string, or build -- them up using the operators <.>, </> and -- <//>. However, beware that: -- --
-- "dir" <//> "*" == "dir//*" --(/>) :: FilePattern -> FilePattern -> FilePattern -- | 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. needed :: [FilePath] -> Action () -- | Track that a file was read by the action preceeding it. If -- shakeLint is activated then these files must be dependencies of -- this rule. Calls to trackRead are automatically inserted in -- LintFSATrace mode. trackRead :: [FilePath] -> Action () -- | Track that a file was written by the action preceeding it. If -- shakeLint is activated then these files must either be the -- target of this rule, or never referred to by the build system. Calls -- to trackWrite are automatically inserted in LintFSATrace -- mode. trackWrite :: [FilePath] -> Action () -- | Allow accessing a file in this rule, ignoring any -- 'trackRead'\/'trackWrite' calls matching the pattern. trackAllow :: [FilePattern] -> Action () -- | 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. doesFileExist :: FilePath -> Action Bool -- | 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. 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. 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. 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 directory argument. The result is -- tracked as a dependency, and if it changes the rule will rerun in -- subsequent builds. Some examples: -- --
-- getDirectoryFiles "Config" ["//*.xml"] -- -- All .xml files anywhere under the Config directory -- -- If Config/foo/bar.xml exists it will return ["foo/bar.xml"] -- getDirectoryFiles "Modules" ["*.hs","*.lhs"] -- -- All .hs or .lhs in the Modules directory -- -- If Modules/foo.hs and Modules/foo.lhs exist, it will return ["foo.hs","foo.lhs"] ---- -- If you require a qualified file name it is often easier to use -- "" as the FilePath argument, for example the following -- two expressions are equivalent: -- --
-- fmap (map ("Config" </>)) (getDirectoryFiles "Config" ["//*.xml"]) -- getDirectoryFiles "" ["Config//*.xml"] ---- -- If the first argument directory does not exist it will raise an error. -- If foo does not exist, then the first of these error, but the -- second will not. -- --
-- getDirectoryFiles "foo" ["//*"] -- error -- getDirectoryFiles "" ["foo//*"] -- returns [] ---- -- This function is tracked and serves as a dependency. If a rule calls -- getDirectoryFiles "" ["*.c"] and someone adds foo.c -- to the directory, that rule will rebuild. If someone changes one of -- the .c files, but the list of .c files -- doesn't change, then it will not rebuild. As a consequence of being -- tracked, if the contents change during the build (e.g. you are -- generating .c files in this directory) then the build not -- reach a stable point, which is an error - detected by running with -- --lint. You should only call this function returning source -- files. -- -- For an untracked variant see getDirectoryFilesIO. getDirectoryFiles :: FilePath -> [FilePattern] -> Action [FilePath] -- | Get the directories in a directory, not including . or -- ... All directories are relative to the argument directory. -- The result is tracked as a dependency, and if it changes the rule will -- rerun in subsequent builds. The rules about creating entries described -- in getDirectoryFiles also apply here. -- --
-- getDirectoryDirs "/Users" -- -- Return all directories in the /Users directory -- -- e.g. ["Emily","Henry","Neil"] --getDirectoryDirs :: FilePath -> Action [FilePath] -- | A version of getDirectoryFiles that is in IO, and thus -- untracked. getDirectoryFilesIO :: FilePath -> [FilePattern] -> IO [FilePath] -- | Return Just the value of the environment variable, or -- Nothing if the variable is not set. The environment variable is -- tracked as a dependency, and if it changes the rule will rerun in -- subsequent builds. This function is a tracked version of -- 'getEnv'/'lookupEnv' from the base library. -- --
-- flags <- getEnv "CFLAGS" -- cmd "gcc -c" [out] (maybe [] words flags) --getEnv :: String -> Action (Maybe String) -- | Return the value of the environment variable (second argument), or the -- default value (first argument) if it is not set. Similar to -- getEnv. -- --
-- flags <- getEnvWithDefault "-Wall" "CFLAGS" -- cmd "gcc -c" [out] flags --getEnvWithDefault :: String -> String -> Action String -- | Define an alias for the six type classes required for things involved -- in Shake Rules. Using this alias requires the -- ConstraintKinds extension. -- -- To define your own values meeting the necessary constraints it is -- convenient to use the extensions GeneralizedNewtypeDeriving -- and DeriveDataTypeable to write: -- --
-- newtype MyType = MyType (String, Bool) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) ---- -- Shake needs these instances on keys and values. They are used for: -- --
-- newtype GhcVersion = GhcVersion () deriving (Show,Typeable,Eq,Hashable,Binary,NFData) -- rules = do -- addOracle $ \(GhcVersion _) -> fmap fromStdout $ cmd "ghc --numeric-version" :: Action String -- ... rules ... ---- -- If a rule calls askOracle (GhcVersion ()), that rule -- will be rerun whenever the GHC version changes. Some notes: -- --
-- 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 --numeric-version" -- writeFileChanged out stdout ---- -- In make, the .PHONY attribute on file-producing rules has a -- similar effect. -- -- Note that alwaysRerun is applied when a rule is executed. -- Modifying an existing rule to insert alwaysRerun will -- not cause that rule to rerun next time. alwaysRerun :: Action () -- | A type representing an external resource which the build system should -- respect. There are two ways to create Resources in Shake: -- --
-- 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] ... --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 more details -- see Resource. You cannot depend on a rule (e.g. need) -- while a resource is held. 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 -- | 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. newThrottle :: String -> Int -> Double -> Rules Resource -- | A version of newThrottle that runs in IO, and can be called -- before calling shake. Most people should use newThrottle -- instead. newThrottleIO :: String -> Int -> Double -> IO Resource -- | 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'. unsafeExtraThread :: Action a -> Action a -- | 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. newCache :: (Eq k, Hashable k) => (k -> Action v) -> Rules (k -> Action v) -- | A version of newCache that runs in IO, and can be called before -- calling shake. Most people should use newCache instead. newCacheIO :: (Eq k, Hashable k) => (k -> Action v) -> IO (k -> Action v) -- | Deprecated: Alias for %>. Note that *> -- clashes with a Prelude operator in GHC 7.10. (*>) :: FilePattern -> (FilePath -> Action ()) -> Rules () -- | Deprecated: Alias for |%>. (|*>) :: [FilePattern] -> (FilePath -> Action ()) -> Rules () -- | Deprecated: Alias for &%>. (&*>) :: [FilePattern] -> ([FilePath] -> Action ()) -> Rules () -- | Deprecated: Alias for |%>. (**>) :: [FilePattern] -> (FilePath -> Action ()) -> Rules () -- | Deprecated: Alias for &%>. (*>>) :: [FilePattern] -> ([FilePath] -> Action ()) -> Rules () -- | Deprecated: Alias for &?>. (?>>) :: (FilePath -> Maybe [FilePath]) -> ([FilePath] -> Action ()) -> Rules () -- | 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. -- | Deprecated: Use command or cmd 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" [] ---- | Deprecated: Use command or cmd with -- Cwd 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. -- | Deprecated: Use command or cmd with -- Stdout or Stderr systemOutput :: FilePath -> [String] -> Action (String, String) -- | A module for parsing and using config files in a Shake build system. -- Config files consist of variable bindings, for example: -- --
-- # This is my Config file -- HEADERS_DIR = /path/to/dir -- CFLAGS = -g -I${HEADERS_DIR} -- CFLAGS = $CFLAGS -O2 -- include extra/file.cfg ---- -- This defines the variable HEADERS_DIR (equal to -- /path/to/dir), and CFLAGS (equal to -g -- -I/path/to/dir -O2), and also includes the configuration -- statements in the file extra/file.cfg. The full lexical -- syntax for configuration files is defined here: -- https://ninja-build.org/manual.html#_lexical_syntax. -- -- To use the configuration file either use readConfigFile to -- parse the configuration file and use the values directly, or -- usingConfigFile and getConfig to track the configuration -- values, so they become build dependencies. module Development.Shake.Config -- | Read a config file, returning a list of the variables and their -- bindings. Config files use the Ninja lexical syntax: -- https://ninja-build.org/manual.html#_lexical_syntax readConfigFile :: FilePath -> IO (HashMap String String) -- | Read a config file with an initial environment, returning a list of -- the variables and their bindings. Config files use the Ninja lexical -- syntax: https://ninja-build.org/manual.html#_lexical_syntax readConfigFileWithEnv :: [(String, String)] -> FilePath -> IO (HashMap String String) -- | Specify the file to use with getConfig. usingConfigFile :: FilePath -> Rules () -- | Specify the values to use with getConfig, generally prefer -- usingConfigFile unless you also need access to the values of -- variables outside Action. usingConfig :: HashMap String String -> Rules () -- | Obtain the value of a configuration variable, returns Nothing -- to indicate the variable has no binding. Any build system using -- getConfig must call either usingConfigFile or -- usingConfig. The getConfig function will introduce a -- dependency on the configuration variable (but not the whole -- configuration file), and if the configuration variable changes, the -- rule will be rerun. As an example: -- --
-- usingConfigFile "myconfiguration.cfg" -- "*.o" %> \out -> do -- cflags <- getConfig "CFLAGS" -- cmd "gcc" [out -<.> "c"] (fromMaybe "" cflags) --getConfig :: String -> Action (Maybe String) -- | Obtain the configuration keys. Any build system using -- getConfigKeys must call either usingConfigFile or -- usingConfig. The getConfigKeys function will introduce a -- dependency on the configuration keys (but not the whole configuration -- file), and if the configuration keys change, the rule will be rerun. -- Usually use as part of an action. As an example: -- --
-- usingConfigFile "myconfiguration.cfg" -- action $ need =<< getConfigKeys --getConfigKeys :: Action [String] instance Control.DeepSeq.NFData Development.Shake.Config.ConfigKeys instance Data.Binary.Class.Binary Development.Shake.Config.ConfigKeys instance Data.Hashable.Class.Hashable Development.Shake.Config.ConfigKeys instance GHC.Classes.Eq Development.Shake.Config.ConfigKeys instance GHC.Show.Show Development.Shake.Config.ConfigKeys instance Control.DeepSeq.NFData Development.Shake.Config.Config instance Data.Binary.Class.Binary Development.Shake.Config.Config instance Data.Hashable.Class.Hashable Development.Shake.Config.Config instance GHC.Classes.Eq Development.Shake.Config.Config instance GHC.Show.Show Development.Shake.Config.Config -- | A module for producing forward-defined build systems, in contrast to -- standard backwards-defined build systems such as shake. Based around -- ideas from fabricate. As an example: -- --
-- import Development.Shake -- import Development.Shake.Forward -- import Development.Shake.FilePath -- -- main = shakeArgsForward shakeOptions $ do -- contents <- readFileLines "result.txt" -- cache $ cmd "tar -cf result.tar" contents ---- -- Compared to backward-defined build systems (such as normal Shake), -- forward-defined build systems tend to be simpler for simple systems -- (less boilerplate, more direct style), but more complex for larger -- build systems (requires explicit parallelism, explicit sharing of -- build products, no automatic command line targets). As a general -- approach for writing forward-defined systems: -- --
-- parseMakefile "a: b c\nd : e" == [("a",["b","c"]),("d",["e"])] --parseMakefile :: String -> [(FilePath, [FilePath])] -- | Depend on the dependencies listed in a Makefile. Does not depend on -- the Makefile itself. -- --
-- needMakefileDependencies file = need . concatMap snd . parseMakefile =<< liftIO (readFile file) --needMakefileDependencies :: FilePath -> Action () -- | Depend on the dependencies listed in a Makefile. Does not depend on -- the Makefile itself. Use this function to indicate that you have -- already used the files in question. -- --
-- neededMakefileDependencies file = needed . concatMap snd . parseMakefile =<< liftIO (readFile file) --neededMakefileDependencies :: FilePath -> Action () -- | Like shakeArgsWith, but instead of accumulating a list of -- flags, apply functions to a default value. Usually used to populate a -- record structure. As an example of a build system that can use either -- gcc or distcc for compiling: -- --
-- import System.Console.GetOpt -- -- data Flags = Flags {distCC :: Bool} deriving Eq -- flags = [Option "" ["distcc"] (NoArg $ Right $ \x -> x{distCC=True}) "Run distributed."] -- -- main = shakeArgsAccumulate shakeOptions flags (Flags False) $ \flags targets -> return $ Just $ do -- if null targets then want ["result.exe"] else want targets -- let compiler = if distCC flags then "distcc" else "gcc" -- "*.o" %> \out -> do -- need ... -- cmd compiler ... -- ... ---- -- Now you can pass --distcc to use the distcc -- compiler. shakeArgsAccumulate :: ShakeOptions -> [OptDescr (Either String (a -> a))] -> a -> (a -> [String] -> IO (Maybe (Rules ()))) -> IO () -- | Like shakeArgs but also takes a pruning function. If -- --prune is passed, then after the build has completed, the -- second argument is called with a list of the files that the build -- checked were up-to-date. shakeArgsPrune :: ShakeOptions -> ([FilePath] -> IO ()) -> Rules () -> IO () -- | A version of shakeArgsPrune that also takes a list of extra -- options to use. shakeArgsPruneWith :: ShakeOptions -> ([FilePath] -> IO ()) -> [OptDescr (Either String a)] -> ([a] -> [String] -> IO (Maybe (Rules ()))) -> IO ()