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

Safe HaskellNone
LanguageHaskell2010

Development.Shake.Rule

Contents

Description

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.

Synopsis

Documentation

class (ShakeValue key, ShakeValue value) => Rule key value where Source #

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:

  • How to identify individual artifacts, given by the key type, e.g. with file names.
  • How to describe the state of an artifact, given by the value type, e.g. the file modification time.
  • A way to compare two states of the same individual artifact, with equalValue returning either EqualCheap or NotEqual.
  • A way to query the current state of an artifact, with storedValue returning the current state, or Nothing if there is no current state (e.g. the file does not exist).

Checking if an artifact needs to be built consists of comparing two values of the same key with equalValue. The first value is obtained by applying storedValue to the key and the second is the value stored in the build database after the last successful build.

As an example, below is a simplified rule for building files, where files are identified by a FilePath and their state is identified by a hash of their contents (the builtin functions need and %> provide a similar rule).

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:

  • A value of type File uniquely identifies a generated file.
  • A value of type Modtime will be used to check if a file is up-to-date.

It is important to distinguish Rule instances from actual rules. Rule instances are one component required for the creation of rules. Actual rules are functions from a key to an Action; they are added to Rules using the rule function.

A rule can be created for the instance above with:

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

Minimal complete definition

storedValue

Methods

storedValue :: ShakeOptions -> key -> IO (Maybe value) Source #

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

equalValue :: ShakeOptions -> key -> value -> value -> EqualCost Source #

[Optional] Equality check, with a notion of how expensive the check was.

data EqualCost Source #

An equality check and a cost.

Constructors

EqualCheap

The equality check was cheap.

EqualExpensive

The equality check was expensive, as the results are not trivially equal.

NotEqual

The values are not equal.

Instances

Bounded EqualCost Source # 
Enum EqualCost Source # 
Eq EqualCost Source # 
Data EqualCost Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EqualCost -> c EqualCost #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EqualCost #

toConstr :: EqualCost -> Constr #

dataTypeOf :: EqualCost -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EqualCost) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EqualCost) #

gmapT :: (forall b. Data b => b -> b) -> EqualCost -> EqualCost #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EqualCost -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EqualCost -> r #

gmapQ :: (forall d. Data d => d -> u) -> EqualCost -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EqualCost -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EqualCost -> m EqualCost #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EqualCost -> m EqualCost #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EqualCost -> m EqualCost #

Ord EqualCost Source # 
Read EqualCost Source # 
Show EqualCost Source # 

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

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.

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

Execute a rule, returning the associated values. If possible, the rules will be run in parallel. This function requires that appropriate rules have been added with rule. All key values passed to apply become dependencies of the Action.

apply1 :: Rule key value => key -> Action value Source #

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

trackUse :: ShakeValue key => key -> Action () Source #

Track that a key has been used by the action preceeding it.

trackChange :: ShakeValue key => key -> Action () Source #

Track that a key has been changed by the action preceeding it.

trackAllow :: ShakeValue key => (key -> Bool) -> Action () Source #

Allow any matching key to violate the tracking rules.

Deprecated

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

Deprecated: Use rule with priority 0

A deprecated way of defining a low priority rule. Defined as:

defaultRule = priority 0 . rule