Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module is used for defining new types of rules for Shake build systems, e.g. to support values stored in a database.
Most users will find the built-in set of rules sufficient. The functions in this module are designed for high-performance,
not ease of use or abstraction. As a result, they are difficult to work with and change more often than the other parts of Shake.
Before writing a builtin rule you are encouraged to use addOracle
or addOracleCache
if possible.
With all those warnings out the way, read on for the grungy details.
Synopsis
- addBuiltinRule :: (RuleResult key ~ value, ShakeValue key, Typeable value, NFData value, Show value, Partial) => BuiltinLint key value -> BuiltinIdentity key value -> BuiltinRun key value -> Rules ()
- type BuiltinLint key value = key -> value -> IO (Maybe String)
- noLint :: BuiltinLint key value
- type BuiltinIdentity key value = key -> value -> Maybe ByteString
- noIdentity :: BuiltinIdentity key value
- type BuiltinRun key value = key -> Maybe ByteString -> RunMode -> Action (RunResult value)
- data RunMode
- data RunChanged
- data RunResult value = RunResult {
- runChanged :: RunChanged
- runStore :: ByteString
- runValue :: value
- apply :: (Partial, RuleResult key ~ value, ShakeValue key, Typeable value) => [key] -> Action [value]
- apply1 :: (Partial, RuleResult key ~ value, ShakeValue key, Typeable value) => key -> Action value
- addUserRule :: Typeable a => a -> Rules ()
- getUserRuleList :: Typeable a => (a -> Maybe b) -> Action [(Int, b)]
- getUserRuleMaybe :: (ShakeValue key, Typeable a) => key -> (a -> Maybe String) -> (a -> Maybe b) -> Action (Maybe (Int, b))
- getUserRuleOne :: (ShakeValue key, Typeable a) => key -> (a -> Maybe String) -> (a -> Maybe b) -> Action (Int, b)
- lintTrackRead :: ShakeValue key => [key] -> Action ()
- lintTrackWrite :: ShakeValue key => [key] -> Action ()
- lintTrackAllow :: ShakeValue key => (key -> Bool) -> Action ()
- historyIsEnabled :: Action Bool
- historySave :: Int -> ByteString -> Action ()
- historyLoad :: Int -> Action (Maybe ByteString)
Builtin rules
Shake "Builtin" rules are ones map keys to values - e.g. files to file contents. For each builtin rule you need to think:
- What is the
key
type, which uniquely identifies each location, e.g. a filename. - What is the
value
type. Thevalue
is not necessarily the full value, but is the result people can get if they ask for the value associated with thekey
. As an example, for files when youneed
a file you don't get any value back from the file, so a simple file rule could have()
as its value. - What information is stored between runs. This information should be sufficient to check if the value has changed since last time, e.g. the modification time for files.
Typically a custom rule will define a wrapper of type Rules
that calls addBuiltinRule
, along with a type-safe wrapper over
apply
so users can introduce dependencies.
Extensions
Once you have implemented the basic functionality there is more scope for embracing additional features of Shake, e.g.:
- You can integrate with cached history by providing a working
BuiltinIdentity
and usinghistorySave
andhistoryLoad
. - You can let users provide their own rules which you interpret with
addUserRule
. - You can integrate with linting by specifying a richer
BuiltinLint
and options likelintTrackRead
.
There are lots of rules defined in the Shake repo at https://github.com/ndmitchell/shake/tree/master/src/Development/Shake/Internal/Rules. You are encouraged to read those for inspiration.
Worked example
Shake provides a very comprehensive file rule which currently runs to over 500 lines of code, and supports lots of features and optimisations. However, let's imagine we want to define a simpler rule type for files. As mentioned earlier, we have to make some decisions.
- A
key
will just be the file name. - A
value
will be()
- when the user depends on a file they don't expect any information in return. - The stored information will be the contents of the file, in it's entirety. Alternative choices would be the modtime or a hash of the contents,
but Shake doesn't require that. The stored information in Shake must be stored in a
ByteString
, so wepack
andunpack
to convert. - We will allow user rules to be defined saying how to build any individual file.
First we define the type of key and value, deriving all the necessary type classes. We define a newtype
over FilePath
so we can
guarantee not to conflict with anyone else. Typically you wouldn't export the File
type, providing only sugar functions over it.
newtype File = File FilePath deriving (Show,Eq,Hashable,Binary,NFData) type instance RuleResult File = ()
Since we have decided we are also going to have user rules, we need to define a new type to capture the information stored by the rules. We need to store at least the file it is producing and the action, which we do with:
data FileRule = FileRule File (Action ())
With the definitions above users could call apply
and addUserRule
directly, but that's tedious and not very type safe. To make it easier
we introduce some helpers:
fileRule :: FilePath -> Action () -> Rules () fileRule file act = addUserRule $ FileRule (File file) act fileNeed :: FilePath -> Action () fileNeed = apply1 . File
These helpers just add our type names, providing a more pleasant interface for the user. Using these function we can exercise our build system with:
example = do fileRule "a.txt" $ pure () fileRule "b.txt" $ do fileNeed "a.txt" liftIO $ writeFile "b.txt" . reverse =<< readFile "a.txt" action $ fileNeed "b.txt"
This example defines rules for a.txt
(a source file) and b.txt
(the reverse
of a.txt
). At runtime this example will
complain about not having a builtin rule for File
, so the only thing left is to provide one.
addBuiltinFileRule :: Rules () addBuiltinFileRule = addBuiltinRule noLint noIdentity run where fileContents (File x) = do b <- IO.doesFileExist x; if b then IO.readFile' x else pure "" run :: BuiltinRun File () run key old mode = do now <- liftIO $ fileContents key if mode == RunDependenciesSame && fmap BS.unpack old == Just now then pure $ RunResult ChangedNothing (BS.pack now) () else do (_, act) <- getUserRuleOne key (const Nothing) $ \(FileRule k act) -> if k == key then Just act else Nothing act now <- liftIO $ fileContents key pure $ RunResult ChangedRecomputeDiff (BS.pack now) ()
We define a wrapper addBuiltinFileRule
that calls addBuiltinRule
, opting out of linting and cached storage.
The only thing we provide is a BuiltinRun
function which gets the previous state, and whether any dependency has changed,
and decides whether to rebuild. If something has changed we call getUserRuleOne
to find the users rule and rerun it.
The RunResult
says what changed (either ChangedNothing
or ChangedRecomputeDiff
in our cases), gives us a new stored value
(just packing the contents) and the value
which is ()
.
To execute our example we need to also call addBuiltinFileRule
, and now everything works.
Defining builtin rules
Functions and types for defining new types of Shake rules.
addBuiltinRule :: (RuleResult key ~ value, ShakeValue key, Typeable value, NFData value, Show value, Partial) => BuiltinLint key value -> BuiltinIdentity key value -> BuiltinRun key value -> Rules () Source #
Before looking at this function, you should read the warnings at the top of this module. This function is not often necessary in build systems.
Define a builtin rule, passing the functions to run in the right circumstances.
The key
and value
types will be what is used by apply
.
As a start, you can use noLint
and noIdentity
as the first two functions,
but are required to supply a suitable BuiltinRun
.
Raises an error if any other rule exists at this type.
For a worked example of writing a rule see https://tech-blog.capital-match.com/posts/5-upgrading-shake.html.
type BuiltinLint key value = key -> value -> IO (Maybe String) Source #
The action performed by --lint
for a given key
/value
pair.
At the end of the build the lint action will be called for each key
that was built this run,
passing the value
it produced. Return Nothing
to indicate the value has not changed and
is acceptable, or Just
an error message to indicate failure.
For builtin rules where the value is expected to change, or has no useful checks to perform.
use noLint
.
noLint :: BuiltinLint key value Source #
A suitable BuiltinLint
that always succeeds.
type BuiltinIdentity key value = key -> value -> Maybe ByteString Source #
Produce an identity for a value
that can be used to do direct equality. If you have a custom
notion of equality then the result should return only one member from each equivalence class,
as values will be compared for literal equality.
The result of the identity should be reasonably short (if it is excessively long, hash it).
For rules where the value is never compatible use noIdentity
, which
returns Nothing
. This will disable shared caches of anything that depends on it.
noIdentity :: BuiltinIdentity key value Source #
A suitable BuiltinIdentity
that always fails with a runtime error, incompatible with shakeShare
.
Use this function if you don't care about shakeShare
, or if your rule provides a dependency that can
never be cached (in which case you should also call historyDisable
).
type BuiltinRun key value = key -> Maybe ByteString -> RunMode -> Action (RunResult value) Source #
Define a rule between key
and value
. As an example, a typical BuiltinRun
will look like:
run key oldStore mode = do ... pure $ RunResult change newStore newValue
Where you have:
key
, how to identify individual artifacts, e.g. with file names.oldStore
, the value stored in the database previously, e.g. the file modification time.mode
, eitherRunDependenciesSame
(none of your dependencies changed, you can probably not rebuild) orRunDependenciesChanged
(your dependencies changed, probably rebuild).change
, usually one of eitherChangedNothing
(no work was required) orChangedRecomputeDiff
(I reran the rule and it should be considered different).newStore
, the new value to store in the database, which will be passed in next time asoldStore
.newValue
, the result thatapply
will return when asked for the givenkey
.
What mode a rule is running in, passed as an argument to BuiltinRun
.
RunDependenciesSame | My dependencies have not changed. |
RunDependenciesChanged | At least one of my dependencies from last time have changed, or I have no recorded dependencies. |
data RunChanged Source #
How the output of a rule has changed.
ChangedNothing | Nothing has changed. |
ChangedStore | The stored value has changed, but in a way that should be considered identical (used rarely). |
ChangedRecomputeSame | I recomputed the value and it was the same. |
ChangedRecomputeDiff | I recomputed the value and it was different. |
Instances
Eq RunChanged Source # | |
Defined in Development.Shake.Internal.Core.Types (==) :: RunChanged -> RunChanged -> Bool # (/=) :: RunChanged -> RunChanged -> Bool # | |
Show RunChanged Source # | |
Defined in Development.Shake.Internal.Core.Types showsPrec :: Int -> RunChanged -> ShowS # show :: RunChanged -> String # showList :: [RunChanged] -> ShowS # | |
NFData RunChanged Source # | |
Defined in Development.Shake.Internal.Core.Types rnf :: RunChanged -> () # |
The result of BuiltinRun
.
RunResult | |
|
Calling builtin rules
Wrappers around calling Shake rules. In general these should be specialised to a builtin rule.
apply :: (Partial, RuleResult key ~ value, ShakeValue key, Typeable 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 addBuiltinRule
.
All key
values passed to apply
become dependencies of the Action
.
apply1 :: (Partial, RuleResult key ~ value, ShakeValue key, Typeable value) => key -> Action value Source #
User rules
Define user rules that can be used by builtin rules. Absent any builtin rule making use of a user rule at a given type, a user rule will have on effect - they have no inherent effect or interpretation on their own.
addUserRule :: Typeable a => a -> Rules () Source #
Add a user rule. In general these should be specialised to the type expected by a builtin rule.
The user rules can be retrieved by getUserRuleList
.
getUserRuleList :: Typeable a => (a -> Maybe b) -> Action [(Int, b)] Source #
Get the user rules that were added at a particular type which return Just
on a given function.
Return all equally applicable rules, paired with the version of the rule
(set by versioned
). Where rules are specified with alternatives
or priority
the less-applicable rules will not be returned.
If you can only deal with zero/one results, call getUserRuleMaybe
or getUserRuleOne
,
which raise informative errors.
getUserRuleMaybe :: (ShakeValue key, Typeable a) => key -> (a -> Maybe String) -> (a -> Maybe b) -> Action (Maybe (Int, b)) Source #
A version of getUserRuleList
that fails if there is more than one result
Requires a key
for better error messages.
getUserRuleOne :: (ShakeValue key, Typeable a) => key -> (a -> Maybe String) -> (a -> Maybe b) -> Action (Int, b) Source #
A version of getUserRuleList
that fails if there is not exactly one result
Requires a key
for better error messages.
Lint integration
Provide lint warnings when running code.
lintTrackRead :: ShakeValue key => [key] -> Action () Source #
Track that a key has been used/read by the action preceding it when shakeLint
is active.
lintTrackWrite :: ShakeValue key => [key] -> Action () Source #
Track that a key has been changed/written by the action preceding it when shakeLint
is active.
lintTrackAllow :: ShakeValue key => (key -> Bool) -> Action () Source #
Allow any matching key recorded with lintTrackRead
or lintTrackWrite
in this action,
after this call, to violate the tracking rules.
History caching
Interact with the non-local cache. When using the cache it is important that all
rules have accurate BuiltinIdentity
functions.
historyIsEnabled :: Action Bool Source #
Is the history enabled, returns True
if you have a shakeShare
or shakeCloud
,
and haven't called historyDisable
so far in this rule.
historySave :: Int -> ByteString -> Action () Source #
Save a value to the history. Record the version of any user rule
(or 0
), and a payload. Must be run at the end of the rule, after
any dependencies have been captured. If history is enabled, stores the information
in a cache.
This function relies on produces
to have been called correctly to describe
which files were written during the execution of this rule.
historyLoad :: Int -> Action (Maybe ByteString) Source #
Load a value from the history. Given a version from any user rule
(or 0
), return the payload that was stored by historySave
.
If this function returns Just
it will also have restored any files that
were saved by historySave
.