Safe Haskell | None |
---|---|
Language | Haskell2010 |
Internal module that defines fine-grained rules for setup hooks.
Users should import SetupHooks
instead.
Synopsis
- type Rule = RuleData 'User
- data RuleData (scope :: Scope) = Rule {
- ruleCommands :: !(RuleCmds scope)
- staticDependencies :: ![Dependency]
- results :: !(NonEmpty Location)
- data RuleId = RuleId {
- ruleNameSpace :: !RulesNameSpace
- ruleName :: !ShortText
- staticRule :: Typeable arg => Command arg (IO ()) -> [Dependency] -> NonEmpty Location -> Rule
- dynamicRule :: (Typeable depsArg, Typeable depsRes, Typeable arg) => StaticPtr (Dict (Binary depsRes, Show depsRes, Eq depsRes)) -> Command depsArg (IO ([Dependency], depsRes)) -> Command arg (depsRes -> IO ()) -> [Dependency] -> NonEmpty Location -> Rule
- data RuleCommands (scope :: Scope) (deps :: Scope -> Type -> Type -> Type) (ruleCmd :: Scope -> Type -> Type -> Type) where
- StaticRuleCommand :: forall arg (deps :: Scope -> Type -> Type -> Type) (ruleCmd :: Scope -> Type -> Type -> Type) (scope :: Scope). If (scope == 'System) (arg ~ ByteString) () => {..} -> RuleCommands scope deps ruleCmd
- DynamicRuleCommands :: forall depsArg depsRes arg (deps :: Scope -> Type -> Type -> Type) (ruleCmd :: Scope -> Type -> Type -> Type) (scope :: Scope). If (scope == 'System) (depsArg ~ ByteString, depsRes ~ ByteString, arg ~ ByteString) () => {..} -> RuleCommands scope deps ruleCmd
- type Command = CommandData 'User
- data CommandData (scope :: Scope) arg res = Command {}
- runCommand :: Command args res -> res
- mkCommand :: StaticPtr (Dict (Binary arg, Show arg)) -> StaticPtr (arg -> res) -> arg -> Command arg res
- data Dict c where
- type RuleCmds (scope :: Scope) = RuleCommands scope DynDepsCmd CommandData
- type RuleDynDepsCmd (scope :: Scope) = RuleCommands scope DynDepsCmd (NoCmd :: Scope -> Type -> Type -> Type)
- type RuleExecCmd (scope :: Scope) = RuleCommands scope (DepsRes :: Scope -> Type -> Type -> Type) CommandData
- newtype DynDepsCmd (scope :: Scope) depsArg depsRes = DynDepsCmd {
- dynDepsCmd :: CommandData scope depsArg (IO ([Dependency], depsRes))
- newtype DepsRes (scope :: Scope) (depsArg :: k) depsRes = DepsRes {
- depsRes :: ScopedArgument scope depsRes
- ruleDepsCmd :: forall (scope :: Scope). RuleCmds scope -> RuleDynDepsCmd scope
- runRuleDynDepsCmd :: RuleDynDepsCmd 'User -> Maybe (IO ([Dependency], ByteString))
- ruleExecCmd :: forall (scope :: Scope). SScope scope -> RuleCmds scope -> Maybe ByteString -> RuleExecCmd scope
- runRuleExecCmd :: RuleExecCmd 'User -> IO ()
- newtype Rules env = Rules {}
- data Dependency
- data RuleOutput = RuleOutput {
- outputOfRule :: !RuleId
- outputIndex :: !Word
- rules :: StaticPtr label -> (env -> RulesM ()) -> Rules env
- noRules :: RulesM ()
- data Location where
- location :: Location -> SymbolicPath Pkg 'File
- data MonitorFilePath
- data MonitorKindFile
- data MonitorKindDir
- type RulesM a = RulesT IO a
- newtype RulesT (m :: Type -> Type) a = RulesT {}
- data RulesEnv = RulesEnv {
- rulesEnvVerbosity :: !Verbosity
- rulesEnvNameSpace :: !RulesNameSpace
- computeRules :: Verbosity -> env -> Rules env -> IO (Map RuleId Rule, [MonitorFilePath])
- data Scope
- data SScope (scope :: Scope) where
- data family Static (scope :: Scope) :: Type -> Type
- type RuleBinary = RuleData 'System
- ruleBinary :: Rule -> RuleBinary
Rules
Rule
data RuleData (scope :: Scope) Source #
A rule consists of:
- an action to run to execute the rule,
- a description of the rule inputs and outputs.
Use staticRule
or dynamicRule
to construct a rule, overriding specific
fields, rather than directly using the Rule
constructor.
Rule | Please use the |
|
Instances
A unique identifier for a Rule
.
RuleId | |
|
staticRule :: Typeable arg => Command arg (IO ()) -> [Dependency] -> NonEmpty Location -> Rule Source #
A rule with static dependencies.
Prefer using this smart constructor instead of Rule
whenever possible.
dynamicRule :: (Typeable depsArg, Typeable depsRes, Typeable arg) => StaticPtr (Dict (Binary depsRes, Show depsRes, Eq depsRes)) -> Command depsArg (IO ([Dependency], depsRes)) -> Command arg (depsRes -> IO ()) -> [Dependency] -> NonEmpty Location -> Rule Source #
A rule with dynamic dependencies.
Prefer using this smart constructor instead of Rule
whenever possible.
Commands
data RuleCommands (scope :: Scope) (deps :: Scope -> Type -> Type -> Type) (ruleCmd :: Scope -> Type -> Type -> Type) where Source #
Commands to execute a rule:
- for a rule with static dependencies, a single command,
- for a rule with dynamic dependencies, a command for computing dynamic dependencies, and a command for executing the rule.
StaticRuleCommand | A rule with statically-known dependencies. |
| |
DynamicRuleCommands | |
|
Instances
(forall res. Binary (ruleCmd 'System ByteString res), Binary (deps 'System ByteString ByteString)) => Binary (RuleCommands 'System deps ruleCmd) Source # | |
Defined in Distribution.Simple.SetupHooks.Rule put :: RuleCommands 'System deps ruleCmd -> Put # get :: Get (RuleCommands 'System deps ruleCmd) # putList :: [RuleCommands 'System deps ruleCmd] -> Put # | |
(forall arg res. Binary (ruleCmd 'User arg res), forall depsArg depsRes. Binary depsRes => Binary (deps 'User depsArg depsRes)) => Binary (RuleCommands 'User deps ruleCmd) Source # | |
Defined in Distribution.Simple.SetupHooks.Rule put :: RuleCommands 'User deps ruleCmd -> Put # get :: Get (RuleCommands 'User deps ruleCmd) # putList :: [RuleCommands 'User deps ruleCmd] -> Put # | |
(forall arg res. Show (ruleCmd 'User arg res), forall depsArg depsRes. Show depsRes => Show (deps 'User depsArg depsRes)) => Show (RuleCommands 'User deps ruleCmd) Source # | |
Defined in Distribution.Simple.SetupHooks.Rule | |
(forall res. Eq (ruleCmd 'System ByteString res), Eq (deps 'System ByteString ByteString)) => Eq (RuleCommands 'System deps ruleCmd) Source # | |
Defined in Distribution.Simple.SetupHooks.Rule (==) :: RuleCommands 'System deps ruleCmd -> RuleCommands 'System deps ruleCmd -> Bool # (/=) :: RuleCommands 'System deps ruleCmd -> RuleCommands 'System deps ruleCmd -> Bool # | |
(forall arg res. Eq (ruleCmd 'User arg res), forall depsArg depsRes. Eq depsRes => Eq (deps 'User depsArg depsRes)) => Eq (RuleCommands 'User deps ruleCmd) Source # | |
Defined in Distribution.Simple.SetupHooks.Rule (==) :: RuleCommands 'User deps ruleCmd -> RuleCommands 'User deps ruleCmd -> Bool # (/=) :: RuleCommands 'User deps ruleCmd -> RuleCommands 'User deps ruleCmd -> Bool # |
type Command = CommandData 'User Source #
A command consists of a statically-known action together with a (possibly dynamic) argument to that action.
For example, the action can consist of running an executable
(such as happy
or c2hs
), while the argument consists of the variable
component of the command, e.g. the specific file to run happy
on.
data CommandData (scope :: Scope) arg res Source #
Internal datatype used for commands, both for the Hooks API (Command
)
and for the build system.
Command | |
|
Instances
arg ~ ByteString => Binary (CommandData 'System arg res) Source # | |
Defined in Distribution.Simple.SetupHooks.Rule put :: CommandData 'System arg res -> Put # get :: Get (CommandData 'System arg res) # putList :: [CommandData 'System arg res] -> Put # | |
Binary (CommandData 'User arg res) Source # | |
Defined in Distribution.Simple.SetupHooks.Rule put :: CommandData 'User arg res -> Put # get :: Get (CommandData 'User arg res) # putList :: [CommandData 'User arg res] -> Put # | |
Show (CommandData 'User arg res) Source # | |
Defined in Distribution.Simple.SetupHooks.Rule | |
arg ~ ByteString => Eq (CommandData 'System arg res) Source # | |
Defined in Distribution.Simple.SetupHooks.Rule (==) :: CommandData 'System arg res -> CommandData 'System arg res -> Bool # (/=) :: CommandData 'System arg res -> CommandData 'System arg res -> Bool # | |
Eq (CommandData 'User arg res) Source # | |
Defined in Distribution.Simple.SetupHooks.Rule (==) :: CommandData 'User arg res -> CommandData 'User arg res -> Bool # (/=) :: CommandData 'User arg res -> CommandData 'User arg res -> Bool # |
runCommand :: Command args res -> res Source #
Run a Command
.
mkCommand :: StaticPtr (Dict (Binary arg, Show arg)) -> StaticPtr (arg -> res) -> arg -> Command arg res Source #
Construct a command.
Prefer using this smart constructor instead of Command
whenever possible.
A wrapper used to pass evidence of a constraint as an explicit value.
Helpers for executing commands
type RuleCmds (scope :: Scope) = RuleCommands scope DynDepsCmd CommandData Source #
Both the rule command and the (optional) dynamic dependency command.
type RuleDynDepsCmd (scope :: Scope) = RuleCommands scope DynDepsCmd (NoCmd :: Scope -> Type -> Type -> Type) Source #
Only the (optional) dynamic dependency command.
type RuleExecCmd (scope :: Scope) = RuleCommands scope (DepsRes :: Scope -> Type -> Type -> Type) CommandData Source #
The rule command together with the result of the (optional) dynamic dependency computation.
newtype DynDepsCmd (scope :: Scope) depsArg depsRes Source #
A dynamic dependency command.
DynDepsCmd | |
|
Instances
(arg ~ ByteString, depsRes ~ ByteString) => Binary (DynDepsCmd 'System arg depsRes) Source # | |
Defined in Distribution.Simple.SetupHooks.Rule put :: DynDepsCmd 'System arg depsRes -> Put # get :: Get (DynDepsCmd 'System arg depsRes) # putList :: [DynDepsCmd 'System arg depsRes] -> Put # | |
Binary (DynDepsCmd 'User depsArg depsRes) Source # | |
Defined in Distribution.Simple.SetupHooks.Rule put :: DynDepsCmd 'User depsArg depsRes -> Put # get :: Get (DynDepsCmd 'User depsArg depsRes) # putList :: [DynDepsCmd 'User depsArg depsRes] -> Put # | |
Show (DynDepsCmd 'User depsArg depsRes) Source # | |
Defined in Distribution.Simple.SetupHooks.Rule | |
(arg ~ ByteString, depsRes ~ ByteString) => Eq (DynDepsCmd 'System arg depsRes) Source # | |
Defined in Distribution.Simple.SetupHooks.Rule (==) :: DynDepsCmd 'System arg depsRes -> DynDepsCmd 'System arg depsRes -> Bool # (/=) :: DynDepsCmd 'System arg depsRes -> DynDepsCmd 'System arg depsRes -> Bool # | |
Eq (DynDepsCmd 'User depsArg depsRes) Source # | |
Defined in Distribution.Simple.SetupHooks.Rule (==) :: DynDepsCmd 'User depsArg depsRes -> DynDepsCmd 'User depsArg depsRes -> Bool # (/=) :: DynDepsCmd 'User depsArg depsRes -> DynDepsCmd 'User depsArg depsRes -> Bool # |
newtype DepsRes (scope :: Scope) (depsArg :: k) depsRes Source #
The result of a dynamic dependency computation.
Instances
Binary (ScopedArgument scope depsRes) => Binary (DepsRes scope depsArg depsRes) Source # | |
Show depsRes => Show (DepsRes scope depsArg depsRes) Source # | |
Eq depsRes => Eq (DepsRes scope depsArg depsRes) Source # | |
Ord depsRes => Ord (DepsRes scope depsArg depsRes) Source # | |
Defined in Distribution.Simple.SetupHooks.Rule compare :: DepsRes scope depsArg depsRes -> DepsRes scope depsArg depsRes -> Ordering # (<) :: DepsRes scope depsArg depsRes -> DepsRes scope depsArg depsRes -> Bool # (<=) :: DepsRes scope depsArg depsRes -> DepsRes scope depsArg depsRes -> Bool # (>) :: DepsRes scope depsArg depsRes -> DepsRes scope depsArg depsRes -> Bool # (>=) :: DepsRes scope depsArg depsRes -> DepsRes scope depsArg depsRes -> Bool # max :: DepsRes scope depsArg depsRes -> DepsRes scope depsArg depsRes -> DepsRes scope depsArg depsRes # min :: DepsRes scope depsArg depsRes -> DepsRes scope depsArg depsRes -> DepsRes scope depsArg depsRes # |
ruleDepsCmd :: forall (scope :: Scope). RuleCmds scope -> RuleDynDepsCmd scope Source #
Project out the (optional) dependency computation command, so that it can be serialised without serialising anything else.
runRuleDynDepsCmd :: RuleDynDepsCmd 'User -> Maybe (IO ([Dependency], ByteString)) Source #
Obtain the (optional) IO
action that computes dynamic dependencies.
ruleExecCmd :: forall (scope :: Scope). SScope scope -> RuleCmds scope -> Maybe ByteString -> RuleExecCmd scope Source #
Project out the command for running the rule, passing in the result of the dependency computation if there was one.
runRuleExecCmd :: RuleExecCmd 'User -> IO () Source #
Obtain the IO
action that executes a rule.
Collections of rules
A collection of Rule
s.
Use the rules
smart constructor instead of directly using the Rules
constructor.
- Rules are registered using
registerRule
, - Monitored files or directories are declared using
addRuleMonitors
; a change in these will trigger the recomputation of all rules.
The env
type parameter represents an extra argument, which usually
consists of information known to Cabal such as LocalBuildInfo
and
ComponentLocalBuildInfo
.
data Dependency Source #
A dependency of a rule.
RuleDependency !RuleOutput | A dependency on an output of another rule. |
FileDependency !Location | A direct dependency on a file at a particular location on disk. This should not be used for files that are generated by other rules;
use |
Instances
Structured Dependency Source # | |||||
Defined in Distribution.Simple.SetupHooks.Rule structure :: Proxy Dependency -> Structure Source # structureHash' :: Tagged Dependency MD5 | |||||
Binary Dependency Source # | |||||
Defined in Distribution.Simple.SetupHooks.Rule | |||||
Generic Dependency Source # | |||||
Defined in Distribution.Simple.SetupHooks.Rule
from :: Dependency -> Rep Dependency x # to :: Rep Dependency x -> Dependency # | |||||
Show Dependency Source # | |||||
Defined in Distribution.Simple.SetupHooks.Rule showsPrec :: Int -> Dependency -> ShowS # show :: Dependency -> String # showList :: [Dependency] -> ShowS # | |||||
Eq Dependency Source # | |||||
Defined in Distribution.Simple.SetupHooks.Rule (==) :: Dependency -> Dependency -> Bool # (/=) :: Dependency -> Dependency -> Bool # | |||||
Ord Dependency Source # | |||||
Defined in Distribution.Simple.SetupHooks.Rule compare :: Dependency -> Dependency -> Ordering # (<) :: Dependency -> Dependency -> Bool # (<=) :: Dependency -> Dependency -> Bool # (>) :: Dependency -> Dependency -> Bool # (>=) :: Dependency -> Dependency -> Bool # max :: Dependency -> Dependency -> Dependency # min :: Dependency -> Dependency -> Dependency # | |||||
type Rep Dependency Source # | |||||
Defined in Distribution.Simple.SetupHooks.Rule type Rep Dependency = D1 ('MetaData "Dependency" "Distribution.Simple.SetupHooks.Rule" "Cabal-3.14.0.0-be97" 'False) (C1 ('MetaCons "RuleDependency" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RuleOutput)) :+: C1 ('MetaCons "FileDependency" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Location))) |
data RuleOutput Source #
A reference to an output of another rule.
RuleOutput | |
|
Instances
Structured RuleOutput Source # | |||||
Defined in Distribution.Simple.SetupHooks.Rule structure :: Proxy RuleOutput -> Structure Source # structureHash' :: Tagged RuleOutput MD5 | |||||
Binary RuleOutput Source # | |||||
Defined in Distribution.Simple.SetupHooks.Rule | |||||
Generic RuleOutput Source # | |||||
Defined in Distribution.Simple.SetupHooks.Rule
from :: RuleOutput -> Rep RuleOutput x # to :: Rep RuleOutput x -> RuleOutput # | |||||
Show RuleOutput Source # | |||||
Defined in Distribution.Simple.SetupHooks.Rule showsPrec :: Int -> RuleOutput -> ShowS # show :: RuleOutput -> String # showList :: [RuleOutput] -> ShowS # | |||||
Eq RuleOutput Source # | |||||
Defined in Distribution.Simple.SetupHooks.Rule (==) :: RuleOutput -> RuleOutput -> Bool # (/=) :: RuleOutput -> RuleOutput -> Bool # | |||||
Ord RuleOutput Source # | |||||
Defined in Distribution.Simple.SetupHooks.Rule compare :: RuleOutput -> RuleOutput -> Ordering # (<) :: RuleOutput -> RuleOutput -> Bool # (<=) :: RuleOutput -> RuleOutput -> Bool # (>) :: RuleOutput -> RuleOutput -> Bool # (>=) :: RuleOutput -> RuleOutput -> Bool # max :: RuleOutput -> RuleOutput -> RuleOutput # min :: RuleOutput -> RuleOutput -> RuleOutput # | |||||
type Rep RuleOutput Source # | |||||
Defined in Distribution.Simple.SetupHooks.Rule type Rep RuleOutput = D1 ('MetaData "RuleOutput" "Distribution.Simple.SetupHooks.Rule" "Cabal-3.14.0.0-be97" 'False) (C1 ('MetaCons "RuleOutput" 'PrefixI 'True) (S1 ('MetaSel ('Just "outputOfRule") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RuleId) :*: S1 ('MetaSel ('Just "outputIndex") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word))) |
:: StaticPtr label | unique label for this collection of rules |
-> (env -> RulesM ()) | the computation of rules |
-> Rules env |
Construct a collection of rules with a given label.
A label for the rules can be constructed using the static
keyword,
using the StaticPointers
extension.
NB: separate calls to rules
should have different labels.
Example usage:
myRules :: Rules env myRules = rules (static ()) $ \ env -> do { .. } -- use the monadic API here
Rule inputs/outputs
A (fully resolved) location of a dependency or result of a rule, consisting of a base directory and of a file path relative to that base directory path.
In practice, this will be something like
,
where:Location
dir (moduleNameSymbolicPath
mod . "hs")
- for a file dependency,
dir
is one of the Cabal search directories, - for an output,
dir
is a directory such asautogenComponentModulesDir
orcomponentBuildDir
.
Location | |
|
location :: Location -> SymbolicPath Pkg 'File Source #
Get a (relative or absolute) un-interpreted path to a Location
.
File/directory monitoring
data MonitorFilePath Source #
A description of a file (or set of files) to monitor for changes.
Where file paths are relative they are relative to a common directory (e.g. project root), not necessarily the process current directory.
Instances
Structured MonitorFilePath Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types structure :: Proxy MonitorFilePath -> Structure Source # structureHash' :: Tagged MonitorFilePath MD5 | |||||
Binary MonitorFilePath Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types | |||||
Generic MonitorFilePath Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types
from :: MonitorFilePath -> Rep MonitorFilePath x # to :: Rep MonitorFilePath x -> MonitorFilePath # | |||||
Show MonitorFilePath Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types showsPrec :: Int -> MonitorFilePath -> ShowS # show :: MonitorFilePath -> String # showList :: [MonitorFilePath] -> ShowS # | |||||
Eq MonitorFilePath Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types (==) :: MonitorFilePath -> MonitorFilePath -> Bool # (/=) :: MonitorFilePath -> MonitorFilePath -> Bool # | |||||
type Rep MonitorFilePath Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types type Rep MonitorFilePath = D1 ('MetaData "MonitorFilePath" "Distribution.Simple.FileMonitor.Types" "Cabal-3.14.0.0-be97" 'False) (C1 ('MetaCons "MonitorFile" 'PrefixI 'True) (S1 ('MetaSel ('Just "monitorKindFile") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MonitorKindFile) :*: (S1 ('MetaSel ('Just "monitorKindDir") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MonitorKindDir) :*: S1 ('MetaSel ('Just "monitorPath") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 FilePath))) :+: C1 ('MetaCons "MonitorFileGlob" 'PrefixI 'True) (S1 ('MetaSel ('Just "monitorKindFile") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MonitorKindFile) :*: (S1 ('MetaSel ('Just "monitorKindDir") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MonitorKindDir) :*: S1 ('MetaSel ('Just "monitorPathGlob") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RootedGlob)))) |
data MonitorKindFile Source #
Instances
Structured MonitorKindFile Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types structure :: Proxy MonitorKindFile -> Structure Source # structureHash' :: Tagged MonitorKindFile MD5 | |||||
Binary MonitorKindFile Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types | |||||
Generic MonitorKindFile Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types
from :: MonitorKindFile -> Rep MonitorKindFile x # to :: Rep MonitorKindFile x -> MonitorKindFile # | |||||
Show MonitorKindFile Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types showsPrec :: Int -> MonitorKindFile -> ShowS # show :: MonitorKindFile -> String # showList :: [MonitorKindFile] -> ShowS # | |||||
Eq MonitorKindFile Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types (==) :: MonitorKindFile -> MonitorKindFile -> Bool # (/=) :: MonitorKindFile -> MonitorKindFile -> Bool # | |||||
type Rep MonitorKindFile Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types type Rep MonitorKindFile = D1 ('MetaData "MonitorKindFile" "Distribution.Simple.FileMonitor.Types" "Cabal-3.14.0.0-be97" 'False) ((C1 ('MetaCons "FileExists" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FileModTime" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "FileHashed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FileNotExists" 'PrefixI 'False) (U1 :: Type -> Type))) |
data MonitorKindDir Source #
Instances
Structured MonitorKindDir Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types structure :: Proxy MonitorKindDir -> Structure Source # structureHash' :: Tagged MonitorKindDir MD5 | |||||
Binary MonitorKindDir Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types | |||||
Generic MonitorKindDir Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types
from :: MonitorKindDir -> Rep MonitorKindDir x # to :: Rep MonitorKindDir x -> MonitorKindDir # | |||||
Show MonitorKindDir Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types showsPrec :: Int -> MonitorKindDir -> ShowS # show :: MonitorKindDir -> String # showList :: [MonitorKindDir] -> ShowS # | |||||
Eq MonitorKindDir Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types (==) :: MonitorKindDir -> MonitorKindDir -> Bool # (/=) :: MonitorKindDir -> MonitorKindDir -> Bool # | |||||
type Rep MonitorKindDir Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types type Rep MonitorKindDir = D1 ('MetaData "MonitorKindDir" "Distribution.Simple.FileMonitor.Types" "Cabal-3.14.0.0-be97" 'False) (C1 ('MetaCons "DirExists" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DirModTime" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DirNotExists" 'PrefixI 'False) (U1 :: Type -> Type))) |
Monadic API for generation of ActionId
newtype RulesT (m :: Type -> Type) a Source #
Monad transformer for defining rules. Usually wraps the IO
monad,
allowing IO
actions to be performed using liftIO
.
Instances
MonadTrans RulesT Source # | |
Monad m => Applicative (RulesT m) Source # | |
Functor m => Functor (RulesT m) Source # | |
Monad m => Monad (RulesT m) Source # | |
MonadFix m => MonadFix (RulesT m) Source # | |
Defined in Distribution.Simple.SetupHooks.Rule | |
MonadIO m => MonadIO (RulesT m) Source # | |
Defined in Distribution.Simple.SetupHooks.Rule |
The environment within the monadic API.
RulesEnv | |
|
computeRules :: Verbosity -> env -> Rules env -> IO (Map RuleId Rule, [MonitorFilePath]) Source #
Internals
data family Static (scope :: Scope) :: Type -> Type Source #
A static pointer (in user scope) or its key (in system scope).
Instances
Binary (Static 'System fnTy) Source # | |
Binary (Static 'User fnTy) Source # | |
Show (Static 'System fnTy) Source # | |
Show (Static 'User fnTy) Source # | |
Eq (Static 'System fnTy) Source # | |
Eq (Static 'User fnTy) Source # | |
Ord (Static 'System fnTy) Source # | |
Defined in Distribution.Simple.SetupHooks.Rule compare :: Static 'System fnTy -> Static 'System fnTy -> Ordering # (<) :: Static 'System fnTy -> Static 'System fnTy -> Bool # (<=) :: Static 'System fnTy -> Static 'System fnTy -> Bool # (>) :: Static 'System fnTy -> Static 'System fnTy -> Bool # (>=) :: Static 'System fnTy -> Static 'System fnTy -> Bool # max :: Static 'System fnTy -> Static 'System fnTy -> Static 'System fnTy # min :: Static 'System fnTy -> Static 'System fnTy -> Static 'System fnTy # | |
Ord (Static 'User fnTy) Source # | |
Defined in Distribution.Simple.SetupHooks.Rule compare :: Static 'User fnTy -> Static 'User fnTy -> Ordering # (<) :: Static 'User fnTy -> Static 'User fnTy -> Bool # (<=) :: Static 'User fnTy -> Static 'User fnTy -> Bool # (>) :: Static 'User fnTy -> Static 'User fnTy -> Bool # (>=) :: Static 'User fnTy -> Static 'User fnTy -> Bool # max :: Static 'User fnTy -> Static 'User fnTy -> Static 'User fnTy # min :: Static 'User fnTy -> Static 'User fnTy -> Static 'User fnTy # | |
newtype Static 'System fnTy Source # | |
Defined in Distribution.Simple.SetupHooks.Rule | |
newtype Static 'User fnTy Source # | |
Defined in Distribution.Simple.SetupHooks.Rule |
type RuleBinary = RuleData 'System Source #
ruleBinary :: Rule -> RuleBinary Source #