Cabal-3.14.0.0: A framework for packaging Haskell software
Safe HaskellNone
LanguageHaskell2010

Distribution.Simple.SetupHooks.Rule

Description

Internal module that defines fine-grained rules for setup hooks. Users should import SetupHooks instead.

Synopsis

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.

Constructors

Rule

Please use the staticRule or dynamicRule smart constructors instead of this constructor, in order to avoid relying on internal implementation details.

Fields

Instances

Instances details
Show RuleBinary Source #

Trimmed down Show instance, mostly for error messages.

Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Binary (RuleData 'System) Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

put :: RuleData 'System -> Put #

get :: Get (RuleData 'System) #

putList :: [RuleData 'System] -> Put #

Binary (RuleData 'User) Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

put :: RuleData 'User -> Put #

get :: Get (RuleData 'User) #

putList :: [RuleData 'User] -> Put #

Generic (RuleData scope) Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Associated Types

type Rep (RuleData scope) 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

type Rep (RuleData scope) = D1 ('MetaData "RuleData" "Distribution.Simple.SetupHooks.Rule" "Cabal-3.14.0.0-7eed" 'False) (C1 ('MetaCons "Rule" 'PrefixI 'True) (S1 ('MetaSel ('Just "ruleCommands") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (RuleCmds scope)) :*: (S1 ('MetaSel ('Just "staticDependencies") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Dependency]) :*: S1 ('MetaSel ('Just "results") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty Location)))))

Methods

from :: RuleData scope -> Rep (RuleData scope) x #

to :: Rep (RuleData scope) x -> RuleData scope #

Show (RuleData 'User) Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Eq (RuleData 'System) Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Eq (RuleData 'User) Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

type Rep (RuleData scope) Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

type Rep (RuleData scope) = D1 ('MetaData "RuleData" "Distribution.Simple.SetupHooks.Rule" "Cabal-3.14.0.0-7eed" 'False) (C1 ('MetaCons "Rule" 'PrefixI 'True) (S1 ('MetaSel ('Just "ruleCommands") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (RuleCmds scope)) :*: (S1 ('MetaSel ('Just "staticDependencies") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Dependency]) :*: S1 ('MetaSel ('Just "results") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty Location)))))

data RuleId Source #

A unique identifier for a Rule.

Constructors

RuleId 

Fields

Instances

Instances details
Structured RuleId Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Binary RuleId Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

put :: RuleId -> Put #

get :: Get RuleId #

putList :: [RuleId] -> Put #

Generic RuleId Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Associated Types

type Rep RuleId 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

type Rep RuleId

Methods

from :: RuleId -> Rep RuleId x #

to :: Rep RuleId x -> RuleId #

Show RuleId Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Eq RuleId Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

(==) :: RuleId -> RuleId -> Bool #

(/=) :: RuleId -> RuleId -> Bool #

Ord RuleId Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

type Rep RuleId Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

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

Constructors

StaticRuleCommand

A rule with statically-known dependencies.

Fields

DynamicRuleCommands 

Fields

  • :: 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) ()
     
  • => { dynamicRuleInstances :: !(Static scope (Dict (Binary depsRes, Show depsRes, Eq depsRes)))

    A rule with dynamic dependencies, which consists of two parts:

    • a dynamic dependency computation, that returns additional edges to be added to the build graph together with an additional piece of data,
    • the command to execute the rule itself, which receives the additional piece of data returned by the dependency computation.
  •    , dynamicDeps :: !(deps scope depsArg depsRes)

    A dynamic dependency computation. The resulting dependencies will be injected into the build graph, and the result of the computation will be passed on to the command that executes the rule.

  •    , dynamicRuleCommand :: !(ruleCmd scope arg (depsRes -> IO ()))

    The command to execute the rule. It will receive the result of the dynamic dependency computation.

  •    , dynamicRuleTypeRep :: !(If (scope == 'System) SomeTypeRep (TypeRep (depsArg, depsRes, arg)))

    A TypeRep for the triple (depsArg,depsRes,arg).

  •    } -> RuleCommands scope deps ruleCmd
     

Instances

Instances details
(forall res. Binary (ruleCmd 'System ByteString res), Binary (deps 'System ByteString ByteString)) => Binary (RuleCommands 'System deps ruleCmd) Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

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 # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

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 # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

showsPrec :: Int -> RuleCommands 'User deps ruleCmd -> ShowS #

show :: RuleCommands 'User deps ruleCmd -> String #

showList :: [RuleCommands 'User deps ruleCmd] -> ShowS #

(forall res. Eq (ruleCmd 'System ByteString res), Eq (deps 'System ByteString ByteString)) => Eq (RuleCommands 'System deps ruleCmd) Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

(==) :: 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 # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

(==) :: 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.

Constructors

Command 

Fields

  • actionPtr :: !(Static scope (arg -> res))

    The (statically-known) action to execute.

  • actionArg :: !(ScopedArgument scope arg)

    The (possibly dynamic) argument to pass to the action.

  • cmdInstances :: !(Static scope (Dict (Binary arg, Show arg)))

    Static evidence that the argument can be serialised and deserialised.

Instances

Instances details
arg ~ ByteString => Binary (CommandData 'System arg res) Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

put :: CommandData 'System arg res -> Put #

get :: Get (CommandData 'System arg res) #

putList :: [CommandData 'System arg res] -> Put #

Binary (CommandData 'User arg res) Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

put :: CommandData 'User arg res -> Put #

get :: Get (CommandData 'User arg res) #

putList :: [CommandData 'User arg res] -> Put #

Show (CommandData 'User arg res) Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

showsPrec :: Int -> CommandData 'User arg res -> ShowS #

show :: CommandData 'User arg res -> String #

showList :: [CommandData 'User arg res] -> ShowS #

arg ~ ByteString => Eq (CommandData 'System arg res) Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

(==) :: CommandData 'System arg res -> CommandData 'System arg res -> Bool #

(/=) :: CommandData 'System arg res -> CommandData 'System arg res -> Bool #

Eq (CommandData 'User arg res) Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

(==) :: 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.

data Dict c where Source #

A wrapper used to pass evidence of a constraint as an explicit value.

Constructors

Dict :: forall c. c => Dict c 

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.

Constructors

DynDepsCmd 

Fields

Instances

Instances details
(arg ~ ByteString, depsRes ~ ByteString) => Binary (DynDepsCmd 'System arg depsRes) Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

put :: DynDepsCmd 'System arg depsRes -> Put #

get :: Get (DynDepsCmd 'System arg depsRes) #

putList :: [DynDepsCmd 'System arg depsRes] -> Put #

Binary (DynDepsCmd 'User depsArg depsRes) Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

put :: DynDepsCmd 'User depsArg depsRes -> Put #

get :: Get (DynDepsCmd 'User depsArg depsRes) #

putList :: [DynDepsCmd 'User depsArg depsRes] -> Put #

Show (DynDepsCmd 'User depsArg depsRes) Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

showsPrec :: Int -> DynDepsCmd 'User depsArg depsRes -> ShowS #

show :: DynDepsCmd 'User depsArg depsRes -> String #

showList :: [DynDepsCmd 'User depsArg depsRes] -> ShowS #

(arg ~ ByteString, depsRes ~ ByteString) => Eq (DynDepsCmd 'System arg depsRes) Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

(==) :: DynDepsCmd 'System arg depsRes -> DynDepsCmd 'System arg depsRes -> Bool #

(/=) :: DynDepsCmd 'System arg depsRes -> DynDepsCmd 'System arg depsRes -> Bool #

Eq (DynDepsCmd 'User depsArg depsRes) Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

(==) :: 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.

Constructors

DepsRes 

Fields

  • depsRes :: ScopedArgument scope depsRes
     

Instances

Instances details
Binary (ScopedArgument scope depsRes) => Binary (DepsRes scope depsArg depsRes) Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

put :: DepsRes scope depsArg depsRes -> Put #

get :: Get (DepsRes scope depsArg depsRes) #

putList :: [DepsRes scope depsArg depsRes] -> Put #

Show depsRes => Show (DepsRes scope depsArg depsRes) Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

showsPrec :: Int -> DepsRes scope depsArg depsRes -> ShowS #

show :: DepsRes scope depsArg depsRes -> String #

showList :: [DepsRes scope depsArg depsRes] -> ShowS #

Eq depsRes => Eq (DepsRes scope depsArg depsRes) Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

(==) :: DepsRes scope depsArg depsRes -> DepsRes scope depsArg depsRes -> Bool #

(/=) :: DepsRes scope depsArg depsRes -> DepsRes scope depsArg depsRes -> Bool #

Ord depsRes => Ord (DepsRes scope depsArg depsRes) Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

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

newtype Rules env Source #

A collection of Rules.

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.

Constructors

Rules 

Fields

Instances

Instances details
Monoid (Rules env) Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

mempty :: Rules env #

mappend :: Rules env -> Rules env -> Rules env #

mconcat :: [Rules env] -> Rules env #

Semigroup (Rules env) Source #

Warning: this Semigroup instance is not commutative.

Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

(<>) :: Rules env -> Rules env -> Rules env #

sconcat :: NonEmpty (Rules env) -> Rules env #

stimes :: Integral b => b -> Rules env -> Rules env #

data Dependency Source #

A dependency of a rule.

Constructors

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

Instances

Instances details
Structured Dependency Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Binary Dependency Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

put :: Dependency -> Put #

get :: Get Dependency #

putList :: [Dependency] -> Put #

Generic Dependency Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Associated Types

type Rep Dependency 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

type Rep Dependency = D1 ('MetaData "Dependency" "Distribution.Simple.SetupHooks.Rule" "Cabal-3.14.0.0-7eed" '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)))
Show Dependency Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Eq Dependency Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Ord Dependency Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

type Rep Dependency Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

type Rep Dependency = D1 ('MetaData "Dependency" "Distribution.Simple.SetupHooks.Rule" "Cabal-3.14.0.0-7eed" '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.

Constructors

RuleOutput 

Fields

Instances

Instances details
Structured RuleOutput Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Binary RuleOutput Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

put :: RuleOutput -> Put #

get :: Get RuleOutput #

putList :: [RuleOutput] -> Put #

Generic RuleOutput Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Associated Types

type Rep RuleOutput 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

type Rep RuleOutput = D1 ('MetaData "RuleOutput" "Distribution.Simple.SetupHooks.Rule" "Cabal-3.14.0.0-7eed" 'False) (C1 ('MetaCons "RuleOutput" 'PrefixI 'True) (S1 ('MetaSel ('Just "outputOfRule") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RuleId) :*: S1 ('MetaSel ('Just "outputIndex") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word)))
Show RuleOutput Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Eq RuleOutput Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Ord RuleOutput Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

type Rep RuleOutput Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

type Rep RuleOutput = D1 ('MetaData "RuleOutput" "Distribution.Simple.SetupHooks.Rule" "Cabal-3.14.0.0-7eed" 'False) (C1 ('MetaCons "RuleOutput" 'PrefixI 'True) (S1 ('MetaSel ('Just "outputOfRule") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RuleId) :*: S1 ('MetaSel ('Just "outputIndex") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word)))

rules Source #

Arguments

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

noRules :: RulesM () Source #

An empty collection of rules.

Rule inputs/outputs

data Location where Source #

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 Location dir (moduleNameSymbolicPath mod . "hs"), where:

  • for a file dependency, dir is one of the Cabal search directories,
  • for an output, dir is a directory such as autogenComponentModulesDir or componentBuildDir.

Constructors

Location 

Fields

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

Instances details
Structured MonitorFilePath Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

Binary MonitorFilePath Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

Methods

put :: MonitorFilePath -> Put #

get :: Get MonitorFilePath #

putList :: [MonitorFilePath] -> Put #

Generic MonitorFilePath Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

Associated Types

type Rep MonitorFilePath 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

type Rep MonitorFilePath = D1 ('MetaData "MonitorFilePath" "Distribution.Simple.FileMonitor.Types" "Cabal-3.14.0.0-7eed" '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))))
Show MonitorFilePath Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

Eq MonitorFilePath Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

type Rep MonitorFilePath Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

type Rep MonitorFilePath = D1 ('MetaData "MonitorFilePath" "Distribution.Simple.FileMonitor.Types" "Cabal-3.14.0.0-7eed" '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

Instances details
Structured MonitorKindFile Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

Binary MonitorKindFile Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

Methods

put :: MonitorKindFile -> Put #

get :: Get MonitorKindFile #

putList :: [MonitorKindFile] -> Put #

Generic MonitorKindFile Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

Associated Types

type Rep MonitorKindFile 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

type Rep MonitorKindFile = D1 ('MetaData "MonitorKindFile" "Distribution.Simple.FileMonitor.Types" "Cabal-3.14.0.0-7eed" '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)))
Show MonitorKindFile Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

Eq MonitorKindFile Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

type Rep MonitorKindFile Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

type Rep MonitorKindFile = D1 ('MetaData "MonitorKindFile" "Distribution.Simple.FileMonitor.Types" "Cabal-3.14.0.0-7eed" '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

Instances details
Structured MonitorKindDir Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

Binary MonitorKindDir Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

Methods

put :: MonitorKindDir -> Put #

get :: Get MonitorKindDir #

putList :: [MonitorKindDir] -> Put #

Generic MonitorKindDir Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

Associated Types

type Rep MonitorKindDir 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

type Rep MonitorKindDir = D1 ('MetaData "MonitorKindDir" "Distribution.Simple.FileMonitor.Types" "Cabal-3.14.0.0-7eed" '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)))
Show MonitorKindDir Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

Eq MonitorKindDir Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

type Rep MonitorKindDir Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

type Rep MonitorKindDir = D1 ('MetaData "MonitorKindDir" "Distribution.Simple.FileMonitor.Types" "Cabal-3.14.0.0-7eed" '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

type RulesM a = RulesT IO a Source #

Monad for constructing rules.

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

Instances details
MonadTrans RulesT Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

lift :: Monad m => m a -> RulesT m a Source #

Monad m => Applicative (RulesT m) Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

pure :: a -> RulesT m a #

(<*>) :: RulesT m (a -> b) -> RulesT m a -> RulesT m b #

liftA2 :: (a -> b -> c) -> RulesT m a -> RulesT m b -> RulesT m c #

(*>) :: RulesT m a -> RulesT m b -> RulesT m b #

(<*) :: RulesT m a -> RulesT m b -> RulesT m a #

Functor m => Functor (RulesT m) Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

fmap :: (a -> b) -> RulesT m a -> RulesT m b #

(<$) :: a -> RulesT m b -> RulesT m a #

Monad m => Monad (RulesT m) Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

(>>=) :: RulesT m a -> (a -> RulesT m b) -> RulesT m b #

(>>) :: RulesT m a -> RulesT m b -> RulesT m b #

return :: a -> RulesT m a #

MonadFix m => MonadFix (RulesT m) Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

mfix :: (a -> RulesT m a) -> RulesT m a #

MonadIO m => MonadIO (RulesT m) Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

liftIO :: IO a -> RulesT m a #

data RulesEnv Source #

The environment within the monadic API.

Constructors

RulesEnv 

Fields

computeRules :: Verbosity -> env -> Rules env -> IO (Map RuleId Rule, [MonitorFilePath]) Source #

Internal function: run the monadic Rules computations in order to obtain all the Rules with their RuleIds.

Internals

data Scope Source #

Rules are defined with rich types by the package.

The build system only has a limited view of these; most data consists of opaque ByteStrings.

The Scope data-type describes which side of this divide we are on.

Constructors

User

User space (with rich types).

System

Build-system space (manipulation of raw data).

data SScope (scope :: Scope) where Source #

Constructors

SUser :: SScope 'User 
SSystem :: SScope 'System 

data family Static (scope :: Scope) :: Type -> Type Source #

A static pointer (in user scope) or its key (in system scope).

Instances

Instances details
Binary (Static 'System fnTy) Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

put :: Static 'System fnTy -> Put #

get :: Get (Static 'System fnTy) #

putList :: [Static 'System fnTy] -> Put #

Binary (Static 'User fnTy) Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

put :: Static 'User fnTy -> Put #

get :: Get (Static 'User fnTy) #

putList :: [Static 'User fnTy] -> Put #

Show (Static 'System fnTy) Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

showsPrec :: Int -> Static 'System fnTy -> ShowS #

show :: Static 'System fnTy -> String #

showList :: [Static 'System fnTy] -> ShowS #

Show (Static 'User fnTy) Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

showsPrec :: Int -> Static 'User fnTy -> ShowS #

show :: Static 'User fnTy -> String #

showList :: [Static 'User fnTy] -> ShowS #

Eq (Static 'System fnTy) Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

(==) :: Static 'System fnTy -> Static 'System fnTy -> Bool #

(/=) :: Static 'System fnTy -> Static 'System fnTy -> Bool #

Eq (Static 'User fnTy) Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

(==) :: Static 'User fnTy -> Static 'User fnTy -> Bool #

(/=) :: Static 'User fnTy -> Static 'User fnTy -> Bool #

Ord (Static 'System fnTy) Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

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 # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

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 # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

newtype Static 'User fnTy Source # 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

newtype Static 'User fnTy = UserStatic {}