Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Synopsis
- shakeOptions :: ShakeOptions
- data Rules a
- data Action a
- action :: Action a -> Rules ()
- pattern Key :: () => (Typeable a, Hashable a, Show a) => a -> Key
- newKey :: (Typeable a, Hashable a, Show a) => a -> Key
- renderKey :: Key -> Text
- actionFinally :: Action a -> IO b -> Action a
- actionBracket :: IO a -> (a -> IO b) -> (a -> Action c) -> Action c
- actionCatch :: Exception e => Action a -> (e -> Action a) -> Action a
- actionFork :: Action a -> (Async a -> Action b) -> Action b
- data ShakeOptions
- getShakeExtra :: Typeable a => Action (Maybe a)
- getShakeExtraRules :: Typeable a => Rules (Maybe a)
- newShakeExtra :: Typeable a => a -> Maybe Dynamic
- parallel :: [Action a] -> Action [a]
- type ShakeValue a = (Show a, Typeable a, Eq a, Hashable a, NFData a)
- type family RuleResult key
- alwaysRerun :: Action ()
- getDirtySet :: Action [(Key, Int)]
- getKeysAndVisitedAge :: Action [(Key, Int)]
- module Development.IDE.Graph.KeyMap
- module Development.IDE.Graph.KeySet
Documentation
A computation that defines all the rules that form part of the computation graph.
Rules
has access to IO
through MonadIO
. Use of IO
is at your own risk: if
you write Rules
that throw exceptions, then you need to make sure to handle them
yourself when you run the resulting Rules
.
An action representing something that can be run as part of a Rule
.
Action
s can be pure functions but also have access to IO
via MonadIO
and 'MonadUnliftIO.
It should be assumed that actions throw exceptions, these can be caught with
actionCatch
. In particular, it is
permissible to use the MonadFail
instance, which will lead to an IOException
.
Instances
MonadFail Action Source # | |
Defined in Development.IDE.Graph.Internal.Types | |
MonadIO Action Source # | |
Defined in Development.IDE.Graph.Internal.Types | |
Applicative Action Source # | |
Functor Action Source # | |
Monad Action Source # | |
MonadCatch Action Source # | |
Defined in Development.IDE.Graph.Internal.Types | |
MonadMask Action Source # | |
Defined in Development.IDE.Graph.Internal.Types mask :: HasCallStack => ((forall a. Action a -> Action a) -> Action b) -> Action b # uninterruptibleMask :: HasCallStack => ((forall a. Action a -> Action a) -> Action b) -> Action b # generalBracket :: HasCallStack => Action a -> (a -> ExitCase b -> Action c) -> (a -> Action b) -> Action (b, c) # | |
MonadThrow Action Source # | |
Defined in Development.IDE.Graph.Internal.Types throwM :: (HasCallStack, Exception e) => e -> Action a # | |
MonadUnliftIO Action Source # | |
Defined in Development.IDE.Graph.Internal.Types |
Configuration
data ShakeOptions Source #
Explicit parallelism
Oracle rules
type family RuleResult key Source #
The type mapping between the key
or a rule and the resulting value
.
Special rules
alwaysRerun :: Action () Source #
Always rerun this rule when dirty, regardless of the dependencies.
Actions for inspecting the keys in the database
getDirtySet :: Action [(Key, Int)] Source #
Returns the set of dirty keys annotated with their age (in # of builds)
module Development.IDE.Graph.KeyMap
module Development.IDE.Graph.KeySet