Cabal-hooks-3.14: API for the Hooks build-type
Safe HaskellSafe-Inferred
LanguageHaskell2010

Distribution.Simple.SetupHooks

Description

This module defines the interface for the Hooks build-type.

To write a package that implements build-type: Hooks, you should define a module SetupHooks.hs which exports a value setupHooks :: SetupHooks. This is a record that declares actions that should be hooked into the cabal build process.

See SetupHooks for more details.

Synopsis

Hooks

A Cabal package with Hooks build-type must define the Haskell module SetupHooks which defines a value setupHooks :: SetupHooks.

These *setup hooks* allow package authors to customise the configuration and building of a package by providing certain hooks that get folded into the general package configuration and building logic within Cabal.

This mechanism replaces the Custom build-type, providing better integration with the rest of the Haskell ecosystem.

Usage example:

-- In your .cabal file
build-type: Hooks

custom-setup
  setup-depends:
    base        >= 4.18 && < 5,
    Cabal-hooks >= 3.14 && < 3.15

The declared Cabal version should also be at least 3.14.
-- In SetupHooks.hs, next to your .cabal file
module SetupHooks where
import Distribution.Simple.SetupHooks ( SetupHooks, noSetupHooks )

setupHooks :: SetupHooks
setupHooks =
 noSetupHooks
   { configureHooks = myConfigureHooks
   , buildHooks = myBuildHooks }

Note that SetupHooks can be monoidally combined, e.g.:

module SetupHooks where
import Distribution.Simple.SetupHooks
import qualified SomeOtherLibrary ( setupHooks )

setupHooks :: SetupHooks
setupHooks = SomeOtherLibrary.setupHooks <> mySetupHooks

mySetupHooks :: SetupHooks
mySetupHooks = ...

data SetupHooks #

Hooks into the cabal build phases.

Usage:

  • In your .cabal file, declare build-type: Hooks (with a cabal-version greater than or equal to 3.14),
  • In your .cabal file, include a custom-setup stanza which declares the dependencies of your SetupHooks module; this will usually contain a dependency on the Cabal-hooks package.
  • Provide a SetupHooks.hs module next to your .cabal file; it must export setupHooks :: SetupHooks.

Constructors

SetupHooks 

Fields

Instances

Instances details
Monoid SetupHooks 
Instance details

Defined in Distribution.Simple.SetupHooks.Internal

Semigroup SetupHooks

SetupHooks can be combined monoidally. This is useful to combine setup hooks defined by another package with your own package-specific hooks.

Warning: this Semigroup instance is not commutative.

Instance details

Defined in Distribution.Simple.SetupHooks.Internal

noSetupHooks :: SetupHooks #

Empty hooks.

Configure hooks

Configure hooks can be used to augment the Cabal configure logic with package-specific logic. The main principle is that the configure hooks can feed into updating the PackageDescription of a cabal package. From then on, this package configuration is set in stone, and later hooks (e.g. hooks into the build phase) can no longer modify this configuration; instead they will receive this configuration in their inputs, and must honour it.

Configuration happens at two levels:

  • global configuration covers the entire package,
  • local configuration covers a single component.

Once the global package configuration is done, all hooks work on a per-component level. The configuration hooks thus follow a simple philosophy:

For example, to generate modules inside a given component, you should:

  • In the per-component configure hook, declare the modules you are going to generate by adding them to the autogenModules field for that component (unless you know them ahead of time, in which case they can be listed textually in the .cabal file of the project).
  • In the build hooks, describe the actions that will generate these modules.

noConfigureHooks :: ConfigureHooks #

Empty configure phase hooks.

Per-package configure hooks

data PreConfPackageInputs #

Inputs to the package-wide pre-configure step.

Constructors

PreConfPackageInputs 

Fields

Instances

Instances details
Structured PreConfPackageInputs 
Instance details

Defined in Distribution.Simple.SetupHooks.Internal

Generic PreConfPackageInputs 
Instance details

Defined in Distribution.Simple.SetupHooks.Internal

Associated Types

type Rep PreConfPackageInputs :: Type -> Type #

Show PreConfPackageInputs 
Instance details

Defined in Distribution.Simple.SetupHooks.Internal

Binary PreConfPackageInputs 
Instance details

Defined in Distribution.Simple.SetupHooks.Internal

type Rep PreConfPackageInputs 
Instance details

Defined in Distribution.Simple.SetupHooks.Internal

type Rep PreConfPackageInputs = D1 ('MetaData "PreConfPackageInputs" "Distribution.Simple.SetupHooks.Internal" "Cabal-3.14.1.1-KNG8xgahazw32ECV34zzCb" 'False) (C1 ('MetaCons "PreConfPackageInputs" 'PrefixI 'True) ((S1 ('MetaSel ('Just "configFlags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ConfigFlags) :*: S1 ('MetaSel ('Just "localBuildConfig") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LocalBuildConfig)) :*: (S1 ('MetaSel ('Just "compiler") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Compiler) :*: S1 ('MetaSel ('Just "platform") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Platform))))

data PreConfPackageOutputs #

Outputs of the package-wide pre-configure step.

Prefer using noPreConfPackageOutputs and overriding the fields you care about, to avoid depending on implementation details of this datatype.

Instances

Instances details
Structured PreConfPackageOutputs 
Instance details

Defined in Distribution.Simple.SetupHooks.Internal

Generic PreConfPackageOutputs 
Instance details

Defined in Distribution.Simple.SetupHooks.Internal

Associated Types

type Rep PreConfPackageOutputs :: Type -> Type #

Show PreConfPackageOutputs 
Instance details

Defined in Distribution.Simple.SetupHooks.Internal

Binary PreConfPackageOutputs 
Instance details

Defined in Distribution.Simple.SetupHooks.Internal

type Rep PreConfPackageOutputs 
Instance details

Defined in Distribution.Simple.SetupHooks.Internal

type Rep PreConfPackageOutputs = D1 ('MetaData "PreConfPackageOutputs" "Distribution.Simple.SetupHooks.Internal" "Cabal-3.14.1.1-KNG8xgahazw32ECV34zzCb" 'False) (C1 ('MetaCons "PreConfPackageOutputs" 'PrefixI 'True) (S1 ('MetaSel ('Just "buildOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuildOptions) :*: S1 ('MetaSel ('Just "extraConfiguredProgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ConfiguredProgs)))

noPreConfPackageOutputs :: PreConfPackageInputs -> PreConfPackageOutputs #

Use this smart constructor to declare an empty set of changes by the package-wide pre-configure hook, and override the fields you care about.

Use this rather than PreConfPackageOutputs to avoid relying on internal implementation details of the latter.

data PostConfPackageInputs #

Inputs to the package-wide post-configure step.

Instances

Instances details
Structured PostConfPackageInputs 
Instance details

Defined in Distribution.Simple.SetupHooks.Internal

Generic PostConfPackageInputs 
Instance details

Defined in Distribution.Simple.SetupHooks.Internal

Associated Types

type Rep PostConfPackageInputs :: Type -> Type #

Show PostConfPackageInputs 
Instance details

Defined in Distribution.Simple.SetupHooks.Internal

Binary PostConfPackageInputs 
Instance details

Defined in Distribution.Simple.SetupHooks.Internal

type Rep PostConfPackageInputs 
Instance details

Defined in Distribution.Simple.SetupHooks.Internal

type Rep PostConfPackageInputs = D1 ('MetaData "PostConfPackageInputs" "Distribution.Simple.SetupHooks.Internal" "Cabal-3.14.1.1-KNG8xgahazw32ECV34zzCb" 'False) (C1 ('MetaCons "PostConfPackageInputs" 'PrefixI 'True) (S1 ('MetaSel ('Just "localBuildConfig") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LocalBuildConfig) :*: S1 ('MetaSel ('Just "packageBuildDescr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PackageBuildDescr)))

type PostConfPackageHook = PostConfPackageInputs -> IO () #

Package-wide post-configure step.

Perform side effects. Last opportunity for any package-wide logic; any subsequent hooks work per-component.

Per-component configure hooks

data PreConfComponentInputs #

Inputs to the per-component pre-configure step.

Instances

Instances details
Structured PreConfComponentInputs 
Instance details

Defined in Distribution.Simple.SetupHooks.Internal

Generic PreConfComponentInputs 
Instance details

Defined in Distribution.Simple.SetupHooks.Internal

Associated Types

type Rep PreConfComponentInputs :: Type -> Type #

Show PreConfComponentInputs 
Instance details

Defined in Distribution.Simple.SetupHooks.Internal

Binary PreConfComponentInputs 
Instance details

Defined in Distribution.Simple.SetupHooks.Internal

type Rep PreConfComponentInputs 
Instance details

Defined in Distribution.Simple.SetupHooks.Internal

type Rep PreConfComponentInputs = D1 ('MetaData "PreConfComponentInputs" "Distribution.Simple.SetupHooks.Internal" "Cabal-3.14.1.1-KNG8xgahazw32ECV34zzCb" 'False) (C1 ('MetaCons "PreConfComponentInputs" 'PrefixI 'True) (S1 ('MetaSel ('Just "localBuildConfig") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LocalBuildConfig) :*: (S1 ('MetaSel ('Just "packageBuildDescr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PackageBuildDescr) :*: S1 ('MetaSel ('Just "component") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Component))))

data PreConfComponentOutputs #

Outputs of the per-component pre-configure step.

Prefer using noPreComponentOutputs and overriding the fields you care about, to avoid depending on implementation details of this datatype.

noPreConfComponentOutputs :: PreConfComponentInputs -> PreConfComponentOutputs #

Use this smart constructor to declare an empty set of changes by a per-component pre-configure hook, and override the fields you care about.

Use this rather than PreConfComponentOutputs to avoid relying on internal implementation details of the latter.

type PreConfComponentHook = PreConfComponentInputs -> IO PreConfComponentOutputs #

Per-component pre-configure step.

For each component of the package, this hook can perform side effects, and return a diff to the passed in component, e.g. to declare additional autogenerated modules.

Build hooks

data BuildHooks #

Build-time hooks.

Constructors

BuildHooks 

Fields

noBuildHooks :: BuildHooks #

Empty build hooks.

data BuildingWhat #

What kind of build phase are we doing/hooking into?

Is this a normal build, or is it perhaps for running an interactive session or Haddock?

Constructors

BuildNormal BuildFlags

A normal build.

BuildRepl ReplFlags

Build steps for an interactive session.

BuildHaddock HaddockFlags

Build steps for generating documentation.

BuildHscolour HscolourFlags

Build steps for Hscolour.

Instances

Instances details
Structured BuildingWhat 
Instance details

Defined in Distribution.Simple.Setup

Generic BuildingWhat 
Instance details

Defined in Distribution.Simple.Setup

Associated Types

type Rep BuildingWhat :: Type -> Type #

Show BuildingWhat 
Instance details

Defined in Distribution.Simple.Setup

Binary BuildingWhat 
Instance details

Defined in Distribution.Simple.Setup

type Rep BuildingWhat 
Instance details

Defined in Distribution.Simple.Setup

Pre-build rules

Pre-build hooks are specified as a collection of pre-build Rules. Each Rule consists of:

  • a specification of its static dependencies and outputs,
  • the commands that execute the rule.

Rules are constructed using either one of the staticRule or dynamicRule smart constructors. Directly constructing a Rule using the constructors of that data type is not advised, as this relies on internal implementation details which are subject to change in between versions of the `Cabal-hooks` library.

Note that:

  • To declare the dependency on the output of a rule, one must refer to the rule directly, and not to the path to the output executing that rule will eventually produce. To do so, registering a Rule with the API returns a unique identifier for that rule, in the form of a RuleId.
  • File dependencies and outputs are not specified directly by FilePath, but rather use the Location type (which is more convenient when working with preprocessors).
  • Rules refer to the actions that execute them using static pointers, in order to enable serialisation/deserialisation of rules.
  • Rules can additionally monitor files or directories, which determines when to re-compute the entire set of rules.

data PreBuildComponentInputs #

Constructors

PreBuildComponentInputs 

Fields

Instances

Instances details
Structured PreBuildComponentInputs 
Instance details

Defined in Distribution.Simple.SetupHooks.Internal

Generic PreBuildComponentInputs 
Instance details

Defined in Distribution.Simple.SetupHooks.Internal

Associated Types

type Rep PreBuildComponentInputs :: Type -> Type #

Show PreBuildComponentInputs 
Instance details

Defined in Distribution.Simple.SetupHooks.Internal

Binary PreBuildComponentInputs 
Instance details

Defined in Distribution.Simple.SetupHooks.Internal

type Rep PreBuildComponentInputs 
Instance details

Defined in Distribution.Simple.SetupHooks.Internal

type Rep PreBuildComponentInputs = D1 ('MetaData "PreBuildComponentInputs" "Distribution.Simple.SetupHooks.Internal" "Cabal-3.14.1.1-KNG8xgahazw32ECV34zzCb" 'False) (C1 ('MetaCons "PreBuildComponentInputs" 'PrefixI 'True) (S1 ('MetaSel ('Just "buildingWhat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuildingWhat) :*: (S1 ('MetaSel ('Just "localBuildInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LocalBuildInfo) :*: S1 ('MetaSel ('Just "targetInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TargetInfo))))

Post-build hooks

data PostBuildComponentInputs #

Instances

Instances details
Structured PostBuildComponentInputs 
Instance details

Defined in Distribution.Simple.SetupHooks.Internal

Generic PostBuildComponentInputs 
Instance details

Defined in Distribution.Simple.SetupHooks.Internal

Associated Types

type Rep PostBuildComponentInputs :: Type -> Type #

Show PostBuildComponentInputs 
Instance details

Defined in Distribution.Simple.SetupHooks.Internal

Binary PostBuildComponentInputs 
Instance details

Defined in Distribution.Simple.SetupHooks.Internal

type Rep PostBuildComponentInputs 
Instance details

Defined in Distribution.Simple.SetupHooks.Internal

type Rep PostBuildComponentInputs = D1 ('MetaData "PostBuildComponentInputs" "Distribution.Simple.SetupHooks.Internal" "Cabal-3.14.1.1-KNG8xgahazw32ECV34zzCb" 'False) (C1 ('MetaCons "PostBuildComponentInputs" 'PrefixI 'True) (S1 ('MetaSel ('Just "buildFlags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuildFlags) :*: (S1 ('MetaSel ('Just "localBuildInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LocalBuildInfo) :*: S1 ('MetaSel ('Just "targetInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TargetInfo))))

Rules

data Rules env #

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.

Instances

Instances details
Monoid (Rules env) 
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)

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 #

rules #

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 () #

An empty collection of rules.

data Dependency #

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

Defined in Distribution.Simple.SetupHooks.Rule

Generic Dependency 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Associated Types

type Rep Dependency :: Type -> Type #

Show Dependency 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Binary Dependency 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Eq Dependency 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Ord Dependency 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

type Rep Dependency 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

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

A reference to an output of another rule.

Constructors

RuleOutput 

Fields

Instances

Instances details
Structured RuleOutput 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Generic RuleOutput 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Associated Types

type Rep RuleOutput :: Type -> Type #

Show RuleOutput 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Binary RuleOutput 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Eq RuleOutput 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Ord RuleOutput 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

type Rep RuleOutput 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

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

data RuleId #

A unique identifier for a Rule.

Instances

Instances details
Structured RuleId 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Generic RuleId 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Associated Types

type Rep RuleId :: Type -> Type #

Methods

from :: RuleId -> Rep RuleId x #

to :: Rep RuleId x -> RuleId #

Show RuleId 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Binary RuleId 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

put :: RuleId -> Put #

get :: Get RuleId #

putList :: [RuleId] -> Put #

Eq RuleId 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

Methods

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

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

Ord RuleId 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

type Rep RuleId 
Instance details

Defined in Distribution.Simple.SetupHooks.Rule

type Rep RuleId = D1 ('MetaData "RuleId" "Distribution.Simple.SetupHooks.Rule" "Cabal-3.14.1.1-KNG8xgahazw32ECV34zzCb" 'False) (C1 ('MetaCons "RuleId" 'PrefixI 'True) (S1 ('MetaSel ('Just "ruleNameSpace") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RulesNameSpace) :*: S1 ('MetaSel ('Just "ruleName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ShortText)))

staticRule :: Typeable arg => Command arg (IO ()) -> [Dependency] -> NonEmpty Location -> Rule #

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 #

A rule with dynamic dependencies.

Prefer using this smart constructor instead of Rule whenever possible.

Rule inputs/outputs

Rules can declare various kinds of dependencies:

Rules are considered out-of-date precisely when any of the following conditions apply:

O1
there has been a (relevant) change in the files and directories monitored by the rules,
O2
the environment passed to the computation of rules has changed.

If the rules are out-of-date, the build system is expected to re-run the computation that computes all rules.

After this re-computation of the set of all rules, we match up new rules with old rules, by RuleId. A rule is then considered stale if any of following conditions apply:

N
the rule is new, or
S
the rule matches with an old rule, and either:
S1
a file dependency of the rule has been modifiedcreateddeleted, or a (transitive) rule dependency of the rule is itself stale, or
S2
the rule is different from the old rule, e.g. the argument stored in the rule command has changed, or the pointer to the action to run the rule has changed. (This is determined using the Eq Rule instance.)

A stale rule becomes no longer stale once we run its associated action. The build system is responsible for re-running the actions associated with each stale rule, in dependency order. This means the build system is expected to behave as follows:

  1. Any time the rules are out-of-date, query the rules to obtain up-to-date rules.
  2. Re-run stale rules.

data Location where #

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 #

Get a (relative or absolute) un-interpreted path to a Location.

autogenComponentModulesDir :: LocalBuildInfo -> ComponentLocalBuildInfo -> SymbolicPath Pkg ('Dir Source) #

The directory in which we put auto-generated modules for a particular component.

Actions

data RuleCommands (scope :: Scope) (deps :: Scope -> Type -> Type -> Type) (ruleCmd :: Scope -> Type -> Type -> Type) where #

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 arg res. Show (ruleCmd 'User arg res), forall depsArg depsRes. Show depsRes => Show (deps 'User depsArg depsRes)) => Show (RuleCommands 'User deps ruleCmd) 
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. Binary (ruleCmd 'System ByteString res), Binary (deps 'System ByteString ByteString)) => Binary (RuleCommands 'System deps ruleCmd) 
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) 
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 res. Eq (ruleCmd 'System ByteString res), Eq (deps 'System ByteString ByteString)) => Eq (RuleCommands 'System deps ruleCmd) 
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) 
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 #

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.

mkCommand :: StaticPtr (Dict (Binary arg, Show arg)) -> StaticPtr (arg -> res) -> arg -> Command arg res #

Construct a command.

Prefer using this smart constructor instead of Command whenever possible.

data Dict c where #

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

Constructors

Dict :: forall c. c => Dict c 

Rules API

Defining pre-build rules can be done in the following style:

{-# LANGUAGE BlockArguments, StaticPointers #-}
myPreBuildRules :: PreBuildComponentRules
myPreBuildRules = rules (static ()) $ \ preBuildEnvironment -> do
  let cmd1 = mkCommand (static Dict) $ static \ arg -> do { .. }
      cmd2 = mkCommand (static Dict) $ static \ arg -> do { .. }
  myData <- liftIO someIOAction
  addRuleMonitors [ monitorDirectory "someSearchDir" ]
  registerRule_ "rule_1_1" $ staticRule (cmd1 arg1) deps1 outs1
  registerRule_ "rule_1_2" $ staticRule (cmd1 arg2) deps2 outs2
  registerRule_ "rule_1_3" $ staticRule (cmd1 arg3) deps3 outs3
  registerRule_ "rule_2_4" $ staticRule (cmd2 arg4) deps4 outs4

Here we use the rules, staticRule and mkCommand smart constructors, rather than directly using the Rules, Rule and Command constructors, which insulates us from internal changes to the Rules, Rule and Command datatypes, respectively.

We use addRuleMonitors to declare a monitored directory that the collection of rules as a whole depends on. In this case, we declare that they depend on the contents of the "searchDir" directory. This means that the rules will be computed anew whenever the contents of this directory change.

type RulesM a = RulesT IO a #

Monad for constructing rules.

registerRule Source #

Arguments

:: ShortText

user-given rule name; these should be unique on a per-package level

-> Rule

the rule to register

-> RulesM RuleId 

Register a rule. Returns an identifier for that rule.

registerRule_ Source #

Arguments

:: ShortText

user-given rule name; these should be unique on a per-package level

-> Rule

the rule to register

-> RulesT IO () 

Register a rule, discarding the produced RuleId.

Using this function means that you don't expect any other rules to ever depend on any outputs of this rule. Use registerRule to retain the RuleId instead.

File/directory monitoring

addRuleMonitors :: Monad m => [MonitorFilePath] -> RulesT m () Source #

Declare additional monitored objects for the collection of all rules.

When these monitored objects change, the rules are re-computed.

Install hooks

noInstallHooks :: InstallHooks #

Empty copy/install hooks.

data InstallComponentInputs #

Instances

Instances details
Structured InstallComponentInputs 
Instance details

Defined in Distribution.Simple.SetupHooks.Internal

Generic InstallComponentInputs 
Instance details

Defined in Distribution.Simple.SetupHooks.Internal

Associated Types

type Rep InstallComponentInputs :: Type -> Type #

Show InstallComponentInputs 
Instance details

Defined in Distribution.Simple.SetupHooks.Internal

Binary InstallComponentInputs 
Instance details

Defined in Distribution.Simple.SetupHooks.Internal

type Rep InstallComponentInputs 
Instance details

Defined in Distribution.Simple.SetupHooks.Internal

type Rep InstallComponentInputs = D1 ('MetaData "InstallComponentInputs" "Distribution.Simple.SetupHooks.Internal" "Cabal-3.14.1.1-KNG8xgahazw32ECV34zzCb" 'False) (C1 ('MetaCons "InstallComponentInputs" 'PrefixI 'True) (S1 ('MetaSel ('Just "copyFlags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CopyFlags) :*: (S1 ('MetaSel ('Just "localBuildInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LocalBuildInfo) :*: S1 ('MetaSel ('Just "targetInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TargetInfo))))

type InstallComponentHook = InstallComponentInputs -> IO () #

A per-component install hook, which can only perform side effects (e.g. copying files).

Re-exports

Hooks

Configure hooks

data ConfigFlags #

Flags to configure command.

IMPORTANT: every time a new flag is added, filterConfigureFlags should be updated. IMPORTANT: every time a new flag is added, it should be added to the Eq instance

Constructors

ConfigFlags 

Fields

Instances

Instances details
Structured ConfigFlags 
Instance details

Defined in Distribution.Simple.Setup.Config

Monoid ConfigFlags 
Instance details

Defined in Distribution.Simple.Setup.Config

Semigroup ConfigFlags 
Instance details

Defined in Distribution.Simple.Setup.Config

Generic ConfigFlags 
Instance details

Defined in Distribution.Simple.Setup.Config

Associated Types

type Rep ConfigFlags :: Type -> Type #

Read ConfigFlags 
Instance details

Defined in Distribution.Simple.Setup.Config

Show ConfigFlags 
Instance details

Defined in Distribution.Simple.Setup.Config

Binary ConfigFlags 
Instance details

Defined in Distribution.Simple.Setup.Config

Eq ConfigFlags 
Instance details

Defined in Distribution.Simple.Setup.Config

type Rep ConfigFlags 
Instance details

Defined in Distribution.Simple.Setup.Config

type Rep ConfigFlags = D1 ('MetaData "ConfigFlags" "Distribution.Simple.Setup.Config" "Cabal-3.14.1.1-KNG8xgahazw32ECV34zzCb" 'False) (C1 ('MetaCons "ConfigFlags" 'PrefixI 'True) (((((S1 ('MetaSel ('Just "configCommonFlags") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CommonSetupFlags) :*: (S1 ('MetaSel ('Just "configPrograms_") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Option' (Last' ProgramDb))) :*: S1 ('MetaSel ('Just "configProgramPaths") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(String, FilePath)]))) :*: ((S1 ('MetaSel ('Just "configProgramArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(String, [String])]) :*: S1 ('MetaSel ('Just "configProgramPathExtra") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NubList FilePath))) :*: (S1 ('MetaSel ('Just "configHcFlavor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag CompilerFlavor)) :*: S1 ('MetaSel ('Just "configHcPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath))))) :*: ((S1 ('MetaSel ('Just "configHcPkg") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)) :*: (S1 ('MetaSel ('Just "configVanillaLib") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "configProfLib") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)))) :*: ((S1 ('MetaSel ('Just "configSharedLib") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "configStaticLib") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))) :*: (S1 ('MetaSel ('Just "configDynExe") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "configFullyStaticExe") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)))))) :*: (((S1 ('MetaSel ('Just "configProfExe") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: (S1 ('MetaSel ('Just "configProf") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "configProfShared") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)))) :*: ((S1 ('MetaSel ('Just "configProfDetail") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag ProfDetailLevel)) :*: S1 ('MetaSel ('Just "configProfLibDetail") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag ProfDetailLevel))) :*: (S1 ('MetaSel ('Just "configConfigureArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "configOptimization") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag OptimisationLevel))))) :*: ((S1 ('MetaSel ('Just "configProgPrefix") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag PathTemplate)) :*: (S1 ('MetaSel ('Just "configProgSuffix") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag PathTemplate)) :*: S1 ('MetaSel ('Just "configInstallDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (InstallDirs (Flag PathTemplate))))) :*: ((S1 ('MetaSel ('Just "configScratchDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)) :*: S1 ('MetaSel ('Just "configExtraLibDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SymbolicPath Pkg ('Dir Lib)])) :*: (S1 ('MetaSel ('Just "configExtraLibDirsStatic") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SymbolicPath Pkg ('Dir Lib)]) :*: S1 ('MetaSel ('Just "configExtraFrameworkDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SymbolicPath Pkg ('Dir Framework)])))))) :*: ((((S1 ('MetaSel ('Just "configExtraIncludeDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SymbolicPath Pkg ('Dir Include)]) :*: (S1 ('MetaSel ('Just "configIPID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag String)) :*: S1 ('MetaSel ('Just "configCID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag ComponentId)))) :*: ((S1 ('MetaSel ('Just "configDeterministic") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "configUserInstall") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))) :*: (S1 ('MetaSel ('Just "configPackageDBs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Maybe PackageDB]) :*: S1 ('MetaSel ('Just "configGHCiLib") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))))) :*: ((S1 ('MetaSel ('Just "configSplitSections") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: (S1 ('MetaSel ('Just "configSplitObjs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "configStripExes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)))) :*: ((S1 ('MetaSel ('Just "configStripLibs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "configConstraints") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PackageVersionConstraint])) :*: (S1 ('MetaSel ('Just "configDependencies") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [GivenComponent]) :*: S1 ('MetaSel ('Just "configPromisedDependencies") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PromisedComponent]))))) :*: (((S1 ('MetaSel ('Just "configInstantiateWith") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(ModuleName, Module)]) :*: (S1 ('MetaSel ('Just "configConfigurationsFlags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FlagAssignment) :*: S1 ('MetaSel ('Just "configTests") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)))) :*: ((S1 ('MetaSel ('Just "configBenchmarks") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "configCoverage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))) :*: (S1 ('MetaSel ('Just "configLibCoverage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "configExactConfiguration") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))))) :*: (((S1 ('MetaSel ('Just "configFlagError") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag String)) :*: S1 ('MetaSel ('Just "configRelocatable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))) :*: (S1 ('MetaSel ('Just "configDebugInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag DebugInfoLevel)) :*: S1 ('MetaSel ('Just "configDumpBuildInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag DumpBuildInfo)))) :*: ((S1 ('MetaSel ('Just "configUseResponseFiles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "configAllowDependingOnPrivateLibs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))) :*: (S1 ('MetaSel ('Just "configCoverageFor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag [UnitId])) :*: S1 ('MetaSel ('Just "configIgnoreBuildTools") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)))))))))

Build hooks

data BuildFlags #

Instances

Instances details
Structured BuildFlags 
Instance details

Defined in Distribution.Simple.Setup.Build

Monoid BuildFlags 
Instance details

Defined in Distribution.Simple.Setup.Build

Semigroup BuildFlags 
Instance details

Defined in Distribution.Simple.Setup.Build

Generic BuildFlags 
Instance details

Defined in Distribution.Simple.Setup.Build

Associated Types

type Rep BuildFlags :: Type -> Type #

Read BuildFlags 
Instance details

Defined in Distribution.Simple.Setup.Build

Show BuildFlags 
Instance details

Defined in Distribution.Simple.Setup.Build

Binary BuildFlags 
Instance details

Defined in Distribution.Simple.Setup.Build

type Rep BuildFlags 
Instance details

Defined in Distribution.Simple.Setup.Build

type Rep BuildFlags = D1 ('MetaData "BuildFlags" "Distribution.Simple.Setup.Build" "Cabal-3.14.1.1-KNG8xgahazw32ECV34zzCb" 'False) (C1 ('MetaCons "BuildFlags" 'PrefixI 'True) ((S1 ('MetaSel ('Just "buildCommonFlags") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CommonSetupFlags) :*: S1 ('MetaSel ('Just "buildProgramPaths") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(String, FilePath)])) :*: (S1 ('MetaSel ('Just "buildProgramArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(String, [String])]) :*: (S1 ('MetaSel ('Just "buildNumJobs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag (Maybe Int))) :*: S1 ('MetaSel ('Just "buildUseSemaphore") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag String))))))

data ReplFlags #

Instances

Instances details
Structured ReplFlags 
Instance details

Defined in Distribution.Simple.Setup.Repl

Monoid ReplFlags 
Instance details

Defined in Distribution.Simple.Setup.Repl

Semigroup ReplFlags 
Instance details

Defined in Distribution.Simple.Setup.Repl

Generic ReplFlags 
Instance details

Defined in Distribution.Simple.Setup.Repl

Associated Types

type Rep ReplFlags :: Type -> Type #

Show ReplFlags 
Instance details

Defined in Distribution.Simple.Setup.Repl

Binary ReplFlags 
Instance details

Defined in Distribution.Simple.Setup.Repl

type Rep ReplFlags 
Instance details

Defined in Distribution.Simple.Setup.Repl

type Rep ReplFlags = D1 ('MetaData "ReplFlags" "Distribution.Simple.Setup.Repl" "Cabal-3.14.1.1-KNG8xgahazw32ECV34zzCb" 'False) (C1 ('MetaCons "ReplFlags" 'PrefixI 'True) ((S1 ('MetaSel ('Just "replCommonFlags") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CommonSetupFlags) :*: S1 ('MetaSel ('Just "replProgramPaths") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(String, FilePath)])) :*: (S1 ('MetaSel ('Just "replProgramArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(String, [String])]) :*: (S1 ('MetaSel ('Just "replReload") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "replReplOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ReplOptions)))))

data HaddockFlags #

Instances

Instances details
Structured HaddockFlags 
Instance details

Defined in Distribution.Simple.Setup.Haddock

Monoid HaddockFlags 
Instance details

Defined in Distribution.Simple.Setup.Haddock

Semigroup HaddockFlags 
Instance details

Defined in Distribution.Simple.Setup.Haddock

Generic HaddockFlags 
Instance details

Defined in Distribution.Simple.Setup.Haddock

Associated Types

type Rep HaddockFlags :: Type -> Type #

Show HaddockFlags 
Instance details

Defined in Distribution.Simple.Setup.Haddock

Binary HaddockFlags 
Instance details

Defined in Distribution.Simple.Setup.Haddock

type Rep HaddockFlags 
Instance details

Defined in Distribution.Simple.Setup.Haddock

type Rep HaddockFlags = D1 ('MetaData "HaddockFlags" "Distribution.Simple.Setup.Haddock" "Cabal-3.14.1.1-KNG8xgahazw32ECV34zzCb" 'False) (C1 ('MetaCons "HaddockFlags" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "haddockCommonFlags") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CommonSetupFlags) :*: S1 ('MetaSel ('Just "haddockProgramPaths") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(String, FilePath)])) :*: (S1 ('MetaSel ('Just "haddockProgramArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(String, [String])]) :*: (S1 ('MetaSel ('Just "haddockHoogle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "haddockHtml") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))))) :*: ((S1 ('MetaSel ('Just "haddockHtmlLocation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag String)) :*: (S1 ('MetaSel ('Just "haddockForHackage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag HaddockTarget)) :*: S1 ('MetaSel ('Just "haddockExecutables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)))) :*: (S1 ('MetaSel ('Just "haddockTestSuites") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: (S1 ('MetaSel ('Just "haddockBenchmarks") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "haddockForeignLibs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)))))) :*: (((S1 ('MetaSel ('Just "haddockInternal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: (S1 ('MetaSel ('Just "haddockCss") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)) :*: S1 ('MetaSel ('Just "haddockLinkedSource") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)))) :*: (S1 ('MetaSel ('Just "haddockQuickJump") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: (S1 ('MetaSel ('Just "haddockHscolourCss") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)) :*: S1 ('MetaSel ('Just "haddockContents") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag PathTemplate))))) :*: ((S1 ('MetaSel ('Just "haddockIndex") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag PathTemplate)) :*: (S1 ('MetaSel ('Just "haddockKeepTempFiles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "haddockBaseUrl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag String)))) :*: (S1 ('MetaSel ('Just "haddockResourcesDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag String)) :*: (S1 ('MetaSel ('Just "haddockOutputDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)) :*: S1 ('MetaSel ('Just "haddockUseUnicode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))))))))

data HscolourFlags #

Instances

Instances details
Structured HscolourFlags 
Instance details

Defined in Distribution.Simple.Setup.Hscolour

Monoid HscolourFlags 
Instance details

Defined in Distribution.Simple.Setup.Hscolour

Semigroup HscolourFlags 
Instance details

Defined in Distribution.Simple.Setup.Hscolour

Generic HscolourFlags 
Instance details

Defined in Distribution.Simple.Setup.Hscolour

Associated Types

type Rep HscolourFlags :: Type -> Type #

Show HscolourFlags 
Instance details

Defined in Distribution.Simple.Setup.Hscolour

Binary HscolourFlags 
Instance details

Defined in Distribution.Simple.Setup.Hscolour

type Rep HscolourFlags 
Instance details

Defined in Distribution.Simple.Setup.Hscolour

type Rep HscolourFlags = D1 ('MetaData "HscolourFlags" "Distribution.Simple.Setup.Hscolour" "Cabal-3.14.1.1-KNG8xgahazw32ECV34zzCb" 'False) (C1 ('MetaCons "HscolourFlags" 'PrefixI 'True) ((S1 ('MetaSel ('Just "hscolourCommonFlags") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CommonSetupFlags) :*: (S1 ('MetaSel ('Just "hscolourCSS") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)) :*: S1 ('MetaSel ('Just "hscolourExecutables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)))) :*: (S1 ('MetaSel ('Just "hscolourTestSuites") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: (S1 ('MetaSel ('Just "hscolourBenchmarks") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "hscolourForeignLibs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))))))

Install hooks

data CopyFlags #

Flags to copy: (destdir, copy-prefix (backwards compat), verbosity)

Instances

Instances details
Structured CopyFlags 
Instance details

Defined in Distribution.Simple.Setup.Copy

Monoid CopyFlags 
Instance details

Defined in Distribution.Simple.Setup.Copy

Semigroup CopyFlags 
Instance details

Defined in Distribution.Simple.Setup.Copy

Generic CopyFlags 
Instance details

Defined in Distribution.Simple.Setup.Copy

Associated Types

type Rep CopyFlags :: Type -> Type #

Show CopyFlags 
Instance details

Defined in Distribution.Simple.Setup.Copy

Binary CopyFlags 
Instance details

Defined in Distribution.Simple.Setup.Copy

type Rep CopyFlags 
Instance details

Defined in Distribution.Simple.Setup.Copy

type Rep CopyFlags = D1 ('MetaData "CopyFlags" "Distribution.Simple.Setup.Copy" "Cabal-3.14.1.1-KNG8xgahazw32ECV34zzCb" 'False) (C1 ('MetaCons "CopyFlags" 'PrefixI 'True) (S1 ('MetaSel ('Just "copyCommonFlags") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CommonSetupFlags) :*: S1 ('MetaSel ('Just "copyDest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag CopyDest))))

Hooks API

These are functions provided as part of the Hooks API. It is recommended to import them from this module as opposed to manually importing them from inside the Cabal module hierarchy.

Copy/install functions

installFileGlob #

Arguments

:: Verbosity 
-> CabalSpecVersion 
-> Maybe (SymbolicPath CWD ('Dir Pkg)) 
-> (Maybe (SymbolicPath CWD ('Dir DataDir)), SymbolicPath Pkg ('Dir DataDir))
(src_dir, dest_dir)
-> RelativePath DataDir 'File

file glob pattern

-> IO () 

Install the files specified by the given glob pattern.

Interacting with the program database

data Program #

Represents a program which can be configured.

Note: rather than constructing this directly, start with simpleProgram and override any extra fields.

Constructors

Program 

Fields

Instances

Instances details
Show Program 
Instance details

Defined in Distribution.Simple.Program.Types

data ConfiguredProgram #

Represents a program which has been configured and is thus ready to be run.

These are usually made by configuring a Program, but if you have to construct one directly then start with simpleConfiguredProgram and override any extra fields.

Constructors

ConfiguredProgram 

Fields

  • programId :: String

    Just the name again

  • programVersion :: Maybe Version

    The version of this program, if it is known.

  • programDefaultArgs :: [String]

    Default command-line args for this program. These flags will appear first on the command line, so they can be overridden by subsequent flags.

  • programOverrideArgs :: [String]

    Override command-line args for this program. These flags will appear last on the command line, so they override all earlier flags.

  • programOverrideEnv :: [(String, Maybe String)]

    Override environment variables for this program. These env vars will extend/override the prevailing environment of the current to form the environment for the new process.

  • programProperties :: Map String String

    A key-value map listing various properties of the program, useful for feature detection. Populated during the configuration step, key names depend on the specific program.

  • programLocation :: ProgramLocation

    Location of the program. eg. /usr/bin/ghc-6.4

  • programMonitorFiles :: [FilePath]

    In addition to the programLocation where the program was found, these are additional locations that were looked at. The combination of ths found location and these not-found locations can be used to monitor to detect when the re-configuring the program might give a different result (e.g. found in a different location).

Instances

Instances details
Structured ConfiguredProgram 
Instance details

Defined in Distribution.Simple.Program.Types

Generic ConfiguredProgram 
Instance details

Defined in Distribution.Simple.Program.Types

Associated Types

type Rep ConfiguredProgram :: Type -> Type #

Read ConfiguredProgram 
Instance details

Defined in Distribution.Simple.Program.Types

Show ConfiguredProgram 
Instance details

Defined in Distribution.Simple.Program.Types

Binary ConfiguredProgram 
Instance details

Defined in Distribution.Simple.Program.Types

Eq ConfiguredProgram 
Instance details

Defined in Distribution.Simple.Program.Types

type Rep ConfiguredProgram 
Instance details

Defined in Distribution.Simple.Program.Types

type Rep ConfiguredProgram = D1 ('MetaData "ConfiguredProgram" "Distribution.Simple.Program.Types" "Cabal-3.14.1.1-KNG8xgahazw32ECV34zzCb" 'False) (C1 ('MetaCons "ConfiguredProgram" 'PrefixI 'True) (((S1 ('MetaSel ('Just "programId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "programVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Version))) :*: (S1 ('MetaSel ('Just "programDefaultArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "programOverrideArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]))) :*: ((S1 ('MetaSel ('Just "programOverrideEnv") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(String, Maybe String)]) :*: S1 ('MetaSel ('Just "programProperties") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map String String))) :*: (S1 ('MetaSel ('Just "programLocation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProgramLocation) :*: S1 ('MetaSel ('Just "programMonitorFiles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath])))))

data ProgramLocation #

Where a program was found. Also tells us whether it's specified by user or not. This includes not just the path, but the program as well.

Constructors

UserSpecified

The user gave the path to this program, eg. --ghc-path=/usr/bin/ghc-6.6

FoundOnSystem

The program was found automatically.

Instances

Instances details
Structured ProgramLocation 
Instance details

Defined in Distribution.Simple.Program.Types

Generic ProgramLocation 
Instance details

Defined in Distribution.Simple.Program.Types

Associated Types

type Rep ProgramLocation :: Type -> Type #

Read ProgramLocation 
Instance details

Defined in Distribution.Simple.Program.Types

Show ProgramLocation 
Instance details

Defined in Distribution.Simple.Program.Types

Binary ProgramLocation 
Instance details

Defined in Distribution.Simple.Program.Types

Eq ProgramLocation 
Instance details

Defined in Distribution.Simple.Program.Types

type Rep ProgramLocation 
Instance details

Defined in Distribution.Simple.Program.Types

type Rep ProgramLocation = D1 ('MetaData "ProgramLocation" "Distribution.Simple.Program.Types" "Cabal-3.14.1.1-KNG8xgahazw32ECV34zzCb" 'False) (C1 ('MetaCons "UserSpecified" 'PrefixI 'True) (S1 ('MetaSel ('Just "locationPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath)) :+: C1 ('MetaCons "FoundOnSystem" 'PrefixI 'True) (S1 ('MetaSel ('Just "locationPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath)))

data ProgramDb #

The configuration is a collection of information about programs. It contains information both about configured programs and also about programs that we are yet to configure.

The idea is that we start from a collection of unconfigured programs and one by one we try to configure them at which point we move them into the configured collection. For unconfigured programs we record not just the Program but also any user-provided arguments and location for the program.

Instances

Instances details
Structured ProgramDb 
Instance details

Defined in Distribution.Simple.Program.Db

Read ProgramDb

Note that this instance does not preserve the known Programs. See restoreProgramDb for details.

Instance details

Defined in Distribution.Simple.Program.Db

Show ProgramDb

Note that this instance does not preserve the known Programs. See restoreProgramDb for details.

Instance details

Defined in Distribution.Simple.Program.Db

Binary ProgramDb

Note that this instance does not preserve the known Programs. See restoreProgramDb for details.

Instance details

Defined in Distribution.Simple.Program.Db

configureUnconfiguredProgram :: Verbosity -> Program -> ProgramDb -> IO (Maybe ConfiguredProgram) #

Try to configure a specific program. If the program is already included in the collection of unconfigured programs then we use any user-supplied location and arguments.

simpleProgram :: String -> Program #

Make a simple named program.

By default we'll just search for it in the path and not try to find the version name. You can override these behaviours if necessary, eg:

(simpleProgram "foo") { programFindLocation = ... , programFindVersion ... }

General Cabal datatypes

data Verbosity #

Instances

Instances details
Parsec Verbosity

Parser verbosity

>>> explicitEitherParsec parsecVerbosity "normal"
Right (Verbosity {vLevel = Normal, vFlags = fromList [], vQuiet = False})
>>> explicitEitherParsec parsecVerbosity "normal+nowrap  "
Right (Verbosity {vLevel = Normal, vFlags = fromList [VNoWrap], vQuiet = False})
>>> explicitEitherParsec parsecVerbosity "normal+nowrap +markoutput"
Right (Verbosity {vLevel = Normal, vFlags = fromList [VNoWrap,VMarkOutput], vQuiet = False})
>>> explicitEitherParsec parsecVerbosity "normal +nowrap +markoutput"
Right (Verbosity {vLevel = Normal, vFlags = fromList [VNoWrap,VMarkOutput], vQuiet = False})
>>> explicitEitherParsec parsecVerbosity "normal+nowrap+markoutput"
Right (Verbosity {vLevel = Normal, vFlags = fromList [VNoWrap,VMarkOutput], vQuiet = False})
>>> explicitEitherParsec parsecVerbosity "deafening+nowrap+stdout+stderr+callsite+callstack"
Right (Verbosity {vLevel = Deafening, vFlags = fromList [VCallStack,VCallSite,VNoWrap,VStderr], vQuiet = False})

Note: this parser will eat trailing spaces.

Instance details

Defined in Distribution.Verbosity

Methods

parsec :: CabalParsing m => m Verbosity #

Pretty Verbosity 
Instance details

Defined in Distribution.Verbosity

Structured Verbosity 
Instance details

Defined in Distribution.Verbosity

Bounded Verbosity 
Instance details

Defined in Distribution.Verbosity

Enum Verbosity 
Instance details

Defined in Distribution.Verbosity

Generic Verbosity 
Instance details

Defined in Distribution.Verbosity

Associated Types

type Rep Verbosity :: Type -> Type #

Read Verbosity 
Instance details

Defined in Distribution.Verbosity

Show Verbosity 
Instance details

Defined in Distribution.Verbosity

Binary Verbosity 
Instance details

Defined in Distribution.Verbosity

Eq Verbosity 
Instance details

Defined in Distribution.Verbosity

Ord Verbosity 
Instance details

Defined in Distribution.Verbosity

type Rep Verbosity 
Instance details

Defined in Distribution.Verbosity

type Rep Verbosity = D1 ('MetaData "Verbosity" "Distribution.Verbosity" "Cabal-3.14.1.1-KNG8xgahazw32ECV34zzCb" 'False) (C1 ('MetaCons "Verbosity" 'PrefixI 'True) (S1 ('MetaSel ('Just "vLevel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VerbosityLevel) :*: (S1 ('MetaSel ('Just "vFlags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set VerbosityFlag)) :*: S1 ('MetaSel ('Just "vQuiet") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))

data Compiler #

Constructors

Compiler 

Fields

Instances

Instances details
Structured Compiler 
Instance details

Defined in Distribution.Simple.Compiler

Generic Compiler 
Instance details

Defined in Distribution.Simple.Compiler

Associated Types

type Rep Compiler :: Type -> Type #

Methods

from :: Compiler -> Rep Compiler x #

to :: Rep Compiler x -> Compiler #

Read Compiler 
Instance details

Defined in Distribution.Simple.Compiler

Show Compiler 
Instance details

Defined in Distribution.Simple.Compiler

Binary Compiler 
Instance details

Defined in Distribution.Simple.Compiler

Methods

put :: Compiler -> Put #

get :: Get Compiler #

putList :: [Compiler] -> Put #

Eq Compiler 
Instance details

Defined in Distribution.Simple.Compiler

type Rep Compiler 
Instance details

Defined in Distribution.Simple.Compiler

type Rep Compiler = D1 ('MetaData "Compiler" "Distribution.Simple.Compiler" "Cabal-3.14.1.1-KNG8xgahazw32ECV34zzCb" 'False) (C1 ('MetaCons "Compiler" 'PrefixI 'True) ((S1 ('MetaSel ('Just "compilerId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CompilerId) :*: (S1 ('MetaSel ('Just "compilerAbiTag") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AbiTag) :*: S1 ('MetaSel ('Just "compilerCompat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [CompilerId]))) :*: (S1 ('MetaSel ('Just "compilerLanguages") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Language, CompilerFlag)]) :*: (S1 ('MetaSel ('Just "compilerExtensions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Extension, Maybe CompilerFlag)]) :*: S1 ('MetaSel ('Just "compilerProperties") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map String String))))))

data Platform #

Constructors

Platform Arch OS 

Instances

Instances details
Parsec Platform 
Instance details

Defined in Distribution.System

Methods

parsec :: CabalParsing m => m Platform #

Pretty Platform 
Instance details

Defined in Distribution.System

Structured Platform 
Instance details

Defined in Distribution.System

Data Platform 
Instance details

Defined in Distribution.System

Methods

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

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

toConstr :: Platform -> Constr #

dataTypeOf :: Platform -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Platform 
Instance details

Defined in Distribution.System

Associated Types

type Rep Platform :: Type -> Type #

Methods

from :: Platform -> Rep Platform x #

to :: Rep Platform x -> Platform #

Read Platform 
Instance details

Defined in Distribution.System

Show Platform 
Instance details

Defined in Distribution.System

Binary Platform 
Instance details

Defined in Distribution.System

Methods

put :: Platform -> Put #

get :: Get Platform #

putList :: [Platform] -> Put #

NFData Platform 
Instance details

Defined in Distribution.System

Methods

rnf :: Platform -> () #

Eq Platform 
Instance details

Defined in Distribution.System

Ord Platform 
Instance details

Defined in Distribution.System

type Rep Platform 
Instance details

Defined in Distribution.System

type Rep Platform = D1 ('MetaData "Platform" "Distribution.System" "Cabal-syntax-3.14.1.0-Cm6co4XoXcLG0FTMtu5Sqa" 'False) (C1 ('MetaCons "Platform" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Arch) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OS)))

newtype Suffix #

A suffix (or file extension).

Mostly used to decide which preprocessor to use, e.g. files with suffix "y" are usually processed by the "happy" build tool.

Constructors

Suffix String 

Instances

Instances details
Pretty Suffix 
Instance details

Defined in Distribution.Simple.PreProcess.Types

Structured Suffix 
Instance details

Defined in Distribution.Simple.PreProcess.Types

IsString Suffix 
Instance details

Defined in Distribution.Simple.PreProcess.Types

Methods

fromString :: String -> Suffix #

Generic Suffix 
Instance details

Defined in Distribution.Simple.PreProcess.Types

Associated Types

type Rep Suffix :: Type -> Type #

Methods

from :: Suffix -> Rep Suffix x #

to :: Rep Suffix x -> Suffix #

Show Suffix 
Instance details

Defined in Distribution.Simple.PreProcess.Types

Binary Suffix 
Instance details

Defined in Distribution.Simple.PreProcess.Types

Methods

put :: Suffix -> Put #

get :: Get Suffix #

putList :: [Suffix] -> Put #

Eq Suffix 
Instance details

Defined in Distribution.Simple.PreProcess.Types

Methods

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

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

Ord Suffix 
Instance details

Defined in Distribution.Simple.PreProcess.Types

type Rep Suffix 
Instance details

Defined in Distribution.Simple.PreProcess.Types

type Rep Suffix = D1 ('MetaData "Suffix" "Distribution.Simple.PreProcess.Types" "Cabal-3.14.1.1-KNG8xgahazw32ECV34zzCb" 'True) (C1 ('MetaCons "Suffix" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

Package information

data LocalBuildConfig #

LocalBuildConfig contains options that can be controlled by the user and serve as inputs to the configuration of a package.

Instances

Instances details
Structured LocalBuildConfig 
Instance details

Defined in Distribution.Types.LocalBuildConfig

Generic LocalBuildConfig 
Instance details

Defined in Distribution.Types.LocalBuildConfig

Associated Types

type Rep LocalBuildConfig :: Type -> Type #

Read LocalBuildConfig 
Instance details

Defined in Distribution.Types.LocalBuildConfig

Show LocalBuildConfig 
Instance details

Defined in Distribution.Types.LocalBuildConfig

Binary LocalBuildConfig 
Instance details

Defined in Distribution.Types.LocalBuildConfig

type Rep LocalBuildConfig 
Instance details

Defined in Distribution.Types.LocalBuildConfig

type Rep LocalBuildConfig = D1 ('MetaData "LocalBuildConfig" "Distribution.Types.LocalBuildConfig" "Cabal-3.14.1.1-KNG8xgahazw32ECV34zzCb" 'False) (C1 ('MetaCons "LocalBuildConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "extraConfigArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: (S1 ('MetaSel ('Just "withPrograms") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProgramDb) :*: S1 ('MetaSel ('Just "withBuildOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuildOptions))))

data LocalBuildInfo #

Data cached after configuration step. See also ConfigFlags.

Instances

Instances details
Structured LocalBuildInfo 
Instance details

Defined in Distribution.Types.LocalBuildInfo

Generic LocalBuildInfo 
Instance details

Defined in Distribution.Types.LocalBuildInfo

Associated Types

type Rep LocalBuildInfo :: Type -> Type #

Read LocalBuildInfo 
Instance details

Defined in Distribution.Types.LocalBuildInfo

Show LocalBuildInfo 
Instance details

Defined in Distribution.Types.LocalBuildInfo

Binary LocalBuildInfo 
Instance details

Defined in Distribution.Types.LocalBuildInfo

type Rep LocalBuildInfo 
Instance details

Defined in Distribution.Types.LocalBuildInfo

type Rep LocalBuildInfo = D1 ('MetaData "LocalBuildInfo" "Distribution.Types.LocalBuildInfo" "Cabal-3.14.1.1-KNG8xgahazw32ECV34zzCb" 'False) (C1 ('MetaCons "NewLocalBuildInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "localBuildDescr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LocalBuildDescr) :*: S1 ('MetaSel ('Just "localBuildConfig") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LocalBuildConfig)))

data PackageBuildDescr #

PackageBuildDescr contains the information Cabal determines after performing package-wide configuration of a package, before doing any per-component configuration.

Instances

Instances details
Structured PackageBuildDescr 
Instance details

Defined in Distribution.Types.LocalBuildConfig

Generic PackageBuildDescr 
Instance details

Defined in Distribution.Types.LocalBuildConfig

Associated Types

type Rep PackageBuildDescr :: Type -> Type #

Read PackageBuildDescr 
Instance details

Defined in Distribution.Types.LocalBuildConfig

Show PackageBuildDescr 
Instance details

Defined in Distribution.Types.LocalBuildConfig

Binary PackageBuildDescr 
Instance details

Defined in Distribution.Types.LocalBuildConfig

type Rep PackageBuildDescr 
Instance details

Defined in Distribution.Types.LocalBuildConfig

data PackageDescription #

This data type is the internal representation of the file pkg.cabal. It contains two kinds of information about the package: information which is needed for all packages, such as the package name and version, and information which is needed for the simple build system only, such as the compiler options and library name.

Constructors

PackageDescription 

Fields

Instances

Instances details
Package PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

HasBuildInfos PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

Structured PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

Data PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

Methods

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

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

toConstr :: PackageDescription -> Constr #

dataTypeOf :: PackageDescription -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

Associated Types

type Rep PackageDescription :: Type -> Type #

Read PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

Show PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

Binary PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

NFData PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

Methods

rnf :: PackageDescription -> () #

Eq PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

Ord PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

type Rep PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

type Rep PackageDescription = D1 ('MetaData "PackageDescription" "Distribution.Types.PackageDescription" "Cabal-syntax-3.14.1.0-Cm6co4XoXcLG0FTMtu5Sqa" 'False) (C1 ('MetaCons "PackageDescription" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "specVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CabalSpecVersion) :*: (S1 ('MetaSel ('Just "package") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PackageIdentifier) :*: S1 ('MetaSel ('Just "licenseRaw") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Either License License)))) :*: ((S1 ('MetaSel ('Just "licenseFiles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RelativePath Pkg 'File]) :*: S1 ('MetaSel ('Just "copyright") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ShortText)) :*: (S1 ('MetaSel ('Just "maintainer") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ShortText) :*: S1 ('MetaSel ('Just "author") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ShortText)))) :*: (((S1 ('MetaSel ('Just "stability") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ShortText) :*: S1 ('MetaSel ('Just "testedWith") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(CompilerFlavor, VersionRange)])) :*: (S1 ('MetaSel ('Just "homepage") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ShortText) :*: S1 ('MetaSel ('Just "pkgUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ShortText))) :*: ((S1 ('MetaSel ('Just "bugReports") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ShortText) :*: S1 ('MetaSel ('Just "sourceRepos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SourceRepo])) :*: (S1 ('MetaSel ('Just "synopsis") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ShortText) :*: S1 ('MetaSel ('Just "description") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ShortText))))) :*: ((((S1 ('MetaSel ('Just "category") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ShortText) :*: S1 ('MetaSel ('Just "customFieldsPD") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(String, String)])) :*: (S1 ('MetaSel ('Just "buildTypeRaw") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe BuildType)) :*: S1 ('MetaSel ('Just "setupBuildInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SetupBuildInfo)))) :*: ((S1 ('MetaSel ('Just "library") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Library)) :*: S1 ('MetaSel ('Just "subLibraries") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Library])) :*: (S1 ('MetaSel ('Just "executables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Executable]) :*: S1 ('MetaSel ('Just "foreignLibs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ForeignLib])))) :*: (((S1 ('MetaSel ('Just "testSuites") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TestSuite]) :*: S1 ('MetaSel ('Just "benchmarks") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Benchmark])) :*: (S1 ('MetaSel ('Just "dataFiles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RelativePath DataDir 'File]) :*: S1 ('MetaSel ('Just "dataDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SymbolicPath Pkg ('Dir DataDir))))) :*: ((S1 ('MetaSel ('Just "extraSrcFiles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RelativePath Pkg 'File]) :*: S1 ('MetaSel ('Just "extraTmpFiles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RelativePath Pkg 'File])) :*: (S1 ('MetaSel ('Just "extraDocFiles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RelativePath Pkg 'File]) :*: S1 ('MetaSel ('Just "extraFiles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RelativePath Pkg 'File])))))))

Component information

data Component #

Instances

Instances details
HasBuildInfo Component 
Instance details

Defined in Distribution.Types.Component

Methods

buildInfo :: Lens' Component BuildInfo #

buildable :: Lens' Component Bool #

buildTools :: Lens' Component [LegacyExeDependency] #

buildToolDepends :: Lens' Component [ExeDependency] #

cppOptions :: Lens' Component [String] #

asmOptions :: Lens' Component [String] #

cmmOptions :: Lens' Component [String] #

ccOptions :: Lens' Component [String] #

cxxOptions :: Lens' Component [String] #

ldOptions :: Lens' Component [String] #

hsc2hsOptions :: Lens' Component [String] #

pkgconfigDepends :: Lens' Component [PkgconfigDependency] #

frameworks :: Lens' Component [RelativePath Framework 'File] #

extraFrameworkDirs :: Lens' Component [SymbolicPath Pkg ('Dir Framework)] #

asmSources :: Lens' Component [SymbolicPath Pkg 'File] #

cmmSources :: Lens' Component [SymbolicPath Pkg 'File] #

cSources :: Lens' Component [SymbolicPath Pkg 'File] #

cxxSources :: Lens' Component [SymbolicPath Pkg 'File] #

jsSources :: Lens' Component [SymbolicPath Pkg 'File] #

hsSourceDirs :: Lens' Component [SymbolicPath Pkg ('Dir Source)] #

otherModules :: Lens' Component [ModuleName] #

virtualModules :: Lens' Component [ModuleName] #

autogenModules :: Lens' Component [ModuleName] #

defaultLanguage :: Lens' Component (Maybe Language) #

otherLanguages :: Lens' Component [Language] #

defaultExtensions :: Lens' Component [Extension] #

otherExtensions :: Lens' Component [Extension] #

oldExtensions :: Lens' Component [Extension] #

extraLibs :: Lens' Component [String] #

extraLibsStatic :: Lens' Component [String] #

extraGHCiLibs :: Lens' Component [String] #

extraBundledLibs :: Lens' Component [String] #

extraLibFlavours :: Lens' Component [String] #

extraDynLibFlavours :: Lens' Component [String] #

extraLibDirs :: Lens' Component [SymbolicPath Pkg ('Dir Lib)] #

extraLibDirsStatic :: Lens' Component [SymbolicPath Pkg ('Dir Lib)] #

includeDirs :: Lens' Component [SymbolicPath Pkg ('Dir Include)] #

includes :: Lens' Component [SymbolicPath Include 'File] #

autogenIncludes :: Lens' Component [RelativePath Include 'File] #

installIncludes :: Lens' Component [RelativePath Include 'File] #

options :: Lens' Component (PerCompilerFlavor [String]) #

profOptions :: Lens' Component (PerCompilerFlavor [String]) #

sharedOptions :: Lens' Component (PerCompilerFlavor [String]) #

profSharedOptions :: Lens' Component (PerCompilerFlavor [String]) #

staticOptions :: Lens' Component (PerCompilerFlavor [String]) #

customFieldsBI :: Lens' Component [(String, String)] #

targetBuildDepends :: Lens' Component [Dependency] #

mixins :: Lens' Component [Mixin] #

Structured Component 
Instance details

Defined in Distribution.Types.Component

Semigroup Component 
Instance details

Defined in Distribution.Types.Component

Generic Component 
Instance details

Defined in Distribution.Types.Component

Associated Types

type Rep Component :: Type -> Type #

Read Component 
Instance details

Defined in Distribution.Types.Component

Show Component 
Instance details

Defined in Distribution.Types.Component

Binary Component 
Instance details

Defined in Distribution.Types.Component

Eq Component 
Instance details

Defined in Distribution.Types.Component

type Rep Component 
Instance details

Defined in Distribution.Types.Component

data ComponentName #

Constructors

CLibName LibraryName 
CNotLibName NotLibComponentName 

Instances

Instances details
Parsec ComponentName 
Instance details

Defined in Distribution.Types.ComponentName

Pretty ComponentName 
Instance details

Defined in Distribution.Types.ComponentName

Structured ComponentName 
Instance details

Defined in Distribution.Types.ComponentName

Generic ComponentName 
Instance details

Defined in Distribution.Types.ComponentName

Associated Types

type Rep ComponentName :: Type -> Type #

Read ComponentName 
Instance details

Defined in Distribution.Types.ComponentName

Show ComponentName 
Instance details

Defined in Distribution.Types.ComponentName

Binary ComponentName 
Instance details

Defined in Distribution.Types.ComponentName

Eq ComponentName 
Instance details

Defined in Distribution.Types.ComponentName

Ord ComponentName 
Instance details

Defined in Distribution.Types.ComponentName

type Rep ComponentName 
Instance details

Defined in Distribution.Types.ComponentName

type Rep ComponentName = D1 ('MetaData "ComponentName" "Distribution.Types.ComponentName" "Cabal-syntax-3.14.1.0-Cm6co4XoXcLG0FTMtu5Sqa" 'False) (C1 ('MetaCons "CLibName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LibraryName)) :+: C1 ('MetaCons "CNotLibName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NotLibComponentName)))

data BuildInfo #

Constructors

BuildInfo 

Fields

Instances

Instances details
Structured BuildInfo 
Instance details

Defined in Distribution.Types.BuildInfo

Data BuildInfo 
Instance details

Defined in Distribution.Types.BuildInfo

Methods

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

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

toConstr :: BuildInfo -> Constr #

dataTypeOf :: BuildInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

Monoid BuildInfo 
Instance details

Defined in Distribution.Types.BuildInfo

Semigroup BuildInfo 
Instance details

Defined in Distribution.Types.BuildInfo

Generic BuildInfo 
Instance details

Defined in Distribution.Types.BuildInfo

Associated Types

type Rep BuildInfo :: Type -> Type #

Read BuildInfo 
Instance details

Defined in Distribution.Types.BuildInfo

Show BuildInfo 
Instance details

Defined in Distribution.Types.BuildInfo

Binary BuildInfo 
Instance details

Defined in Distribution.Types.BuildInfo

NFData BuildInfo 
Instance details

Defined in Distribution.Types.BuildInfo

Methods

rnf :: BuildInfo -> () #

Eq BuildInfo 
Instance details

Defined in Distribution.Types.BuildInfo

Ord BuildInfo 
Instance details

Defined in Distribution.Types.BuildInfo

type Rep BuildInfo 
Instance details

Defined in Distribution.Types.BuildInfo

type Rep BuildInfo = D1 ('MetaData "BuildInfo" "Distribution.Types.BuildInfo" "Cabal-syntax-3.14.1.0-Cm6co4XoXcLG0FTMtu5Sqa" 'False) (C1 ('MetaCons "BuildInfo" 'PrefixI 'True) (((((S1 ('MetaSel ('Just "buildable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "buildTools") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [LegacyExeDependency])) :*: (S1 ('MetaSel ('Just "buildToolDepends") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ExeDependency]) :*: (S1 ('MetaSel ('Just "cppOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "asmOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])))) :*: ((S1 ('MetaSel ('Just "cmmOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: (S1 ('MetaSel ('Just "ccOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "cxxOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]))) :*: (S1 ('MetaSel ('Just "ldOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: (S1 ('MetaSel ('Just "hsc2hsOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "pkgconfigDepends") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PkgconfigDependency]))))) :*: (((S1 ('MetaSel ('Just "frameworks") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RelativePath Framework 'File]) :*: (S1 ('MetaSel ('Just "extraFrameworkDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SymbolicPath Pkg ('Dir Framework)]) :*: S1 ('MetaSel ('Just "asmSources") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SymbolicPath Pkg 'File]))) :*: (S1 ('MetaSel ('Just "cmmSources") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SymbolicPath Pkg 'File]) :*: (S1 ('MetaSel ('Just "cSources") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SymbolicPath Pkg 'File]) :*: S1 ('MetaSel ('Just "cxxSources") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SymbolicPath Pkg 'File])))) :*: ((S1 ('MetaSel ('Just "jsSources") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SymbolicPath Pkg 'File]) :*: (S1 ('MetaSel ('Just "hsSourceDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SymbolicPath Pkg ('Dir Source)]) :*: S1 ('MetaSel ('Just "otherModules") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ModuleName]))) :*: (S1 ('MetaSel ('Just "virtualModules") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ModuleName]) :*: (S1 ('MetaSel ('Just "autogenModules") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ModuleName]) :*: S1 ('MetaSel ('Just "defaultLanguage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Language))))))) :*: ((((S1 ('MetaSel ('Just "otherLanguages") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Language]) :*: (S1 ('MetaSel ('Just "defaultExtensions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Extension]) :*: S1 ('MetaSel ('Just "otherExtensions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Extension]))) :*: (S1 ('MetaSel ('Just "oldExtensions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Extension]) :*: (S1 ('MetaSel ('Just "extraLibs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "extraLibsStatic") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])))) :*: ((S1 ('MetaSel ('Just "extraGHCiLibs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: (S1 ('MetaSel ('Just "extraBundledLibs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "extraLibFlavours") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]))) :*: (S1 ('MetaSel ('Just "extraDynLibFlavours") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: (S1 ('MetaSel ('Just "extraLibDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SymbolicPath Pkg ('Dir Lib)]) :*: S1 ('MetaSel ('Just "extraLibDirsStatic") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SymbolicPath Pkg ('Dir Lib)]))))) :*: (((S1 ('MetaSel ('Just "includeDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SymbolicPath Pkg ('Dir Include)]) :*: (S1 ('MetaSel ('Just "includes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SymbolicPath Include 'File]) :*: S1 ('MetaSel ('Just "autogenIncludes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RelativePath Include 'File]))) :*: (S1 ('MetaSel ('Just "installIncludes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RelativePath Include 'File]) :*: (S1 ('MetaSel ('Just "options") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PerCompilerFlavor [String])) :*: S1 ('MetaSel ('Just "profOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PerCompilerFlavor [String]))))) :*: ((S1 ('MetaSel ('Just "sharedOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PerCompilerFlavor [String])) :*: (S1 ('MetaSel ('Just "profSharedOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PerCompilerFlavor [String])) :*: S1 ('MetaSel ('Just "staticOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PerCompilerFlavor [String])))) :*: (S1 ('MetaSel ('Just "customFieldsBI") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(String, String)]) :*: (S1 ('MetaSel ('Just "targetBuildDepends") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Dependency]) :*: S1 ('MetaSel ('Just "mixins") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Mixin]))))))))

data TargetInfo #

The TargetInfo contains all the information necessary to build a specific target (e.g., componentmodulefile) in a package. In principle, one can get the Component from a ComponentLocalBuildInfo and LocalBuildInfo, but it is much more convenient to have the component in hand.

Instances

Instances details
IsNode TargetInfo 
Instance details

Defined in Distribution.Types.TargetInfo

Associated Types

type Key TargetInfo #

Structured TargetInfo 
Instance details

Defined in Distribution.Types.TargetInfo

Generic TargetInfo 
Instance details

Defined in Distribution.Types.TargetInfo

Associated Types

type Rep TargetInfo :: Type -> Type #

Show TargetInfo 
Instance details

Defined in Distribution.Types.TargetInfo

Binary TargetInfo 
Instance details

Defined in Distribution.Types.TargetInfo

type Key TargetInfo 
Instance details

Defined in Distribution.Types.TargetInfo

type Rep TargetInfo 
Instance details

Defined in Distribution.Types.TargetInfo

type Rep TargetInfo = D1 ('MetaData "TargetInfo" "Distribution.Types.TargetInfo" "Cabal-3.14.1.1-KNG8xgahazw32ECV34zzCb" 'False) (C1 ('MetaCons "TargetInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "targetCLBI") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentLocalBuildInfo) :*: S1 ('MetaSel ('Just "targetComponent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Component)))

data ComponentLocalBuildInfo #

The first five fields are common across all algebraic variants.

Constructors

LibComponentLocalBuildInfo 

Fields

FLibComponentLocalBuildInfo 

Fields

  • componentLocalName :: ComponentName

    It would be very convenient to store the literal Library here, but if we do that, it will get serialized (via the Binary) instance twice. So instead we just provide the ComponentName, which can be used to find the Component in the PackageDescription. NB: eventually, this will NOT uniquely identify the ComponentLocalBuildInfo.

  • componentComponentId :: ComponentId

    The computed ComponentId of this component.

  • componentUnitId :: UnitId

    The computed UnitId which uniquely identifies this component. Might be hashed.

  • componentPackageDeps :: [(UnitId, MungedPackageId)]

    Resolved internal and external package dependencies for this component. The BuildInfo specifies a set of build dependencies that must be satisfied in terms of version ranges. This field fixes those dependencies to the specific versions available on this machine for this compiler.

  • componentIncludes :: [(OpenUnitId, ModuleRenaming)]

    The set of packages that are brought into scope during compilation, including a ModuleRenaming which may used to hide or rename modules. This is what gets translated into -package-id arguments. This is a modernized version of componentPackageDeps, which is kept around for BC purposes.

  • componentExeDeps :: [UnitId]
     
  • componentInternalDeps :: [UnitId]

    The internal dependencies which induce a graph on the ComponentLocalBuildInfo of this package. This does NOT coincide with componentPackageDeps because it ALSO records 'build-tool' dependencies on executables. Maybe one day cabal-install will also handle these correctly too!

ExeComponentLocalBuildInfo 

Fields

  • componentLocalName :: ComponentName

    It would be very convenient to store the literal Library here, but if we do that, it will get serialized (via the Binary) instance twice. So instead we just provide the ComponentName, which can be used to find the Component in the PackageDescription. NB: eventually, this will NOT uniquely identify the ComponentLocalBuildInfo.

  • componentComponentId :: ComponentId

    The computed ComponentId of this component.

  • componentUnitId :: UnitId

    The computed UnitId which uniquely identifies this component. Might be hashed.

  • componentPackageDeps :: [(UnitId, MungedPackageId)]

    Resolved internal and external package dependencies for this component. The BuildInfo specifies a set of build dependencies that must be satisfied in terms of version ranges. This field fixes those dependencies to the specific versions available on this machine for this compiler.

  • componentIncludes :: [(OpenUnitId, ModuleRenaming)]

    The set of packages that are brought into scope during compilation, including a ModuleRenaming which may used to hide or rename modules. This is what gets translated into -package-id arguments. This is a modernized version of componentPackageDeps, which is kept around for BC purposes.

  • componentExeDeps :: [UnitId]
     
  • componentInternalDeps :: [UnitId]

    The internal dependencies which induce a graph on the ComponentLocalBuildInfo of this package. This does NOT coincide with componentPackageDeps because it ALSO records 'build-tool' dependencies on executables. Maybe one day cabal-install will also handle these correctly too!

TestComponentLocalBuildInfo 

Fields

  • componentLocalName :: ComponentName

    It would be very convenient to store the literal Library here, but if we do that, it will get serialized (via the Binary) instance twice. So instead we just provide the ComponentName, which can be used to find the Component in the PackageDescription. NB: eventually, this will NOT uniquely identify the ComponentLocalBuildInfo.

  • componentComponentId :: ComponentId

    The computed ComponentId of this component.

  • componentUnitId :: UnitId

    The computed UnitId which uniquely identifies this component. Might be hashed.

  • componentPackageDeps :: [(UnitId, MungedPackageId)]

    Resolved internal and external package dependencies for this component. The BuildInfo specifies a set of build dependencies that must be satisfied in terms of version ranges. This field fixes those dependencies to the specific versions available on this machine for this compiler.

  • componentIncludes :: [(OpenUnitId, ModuleRenaming)]

    The set of packages that are brought into scope during compilation, including a ModuleRenaming which may used to hide or rename modules. This is what gets translated into -package-id arguments. This is a modernized version of componentPackageDeps, which is kept around for BC purposes.

  • componentExeDeps :: [UnitId]
     
  • componentInternalDeps :: [UnitId]

    The internal dependencies which induce a graph on the ComponentLocalBuildInfo of this package. This does NOT coincide with componentPackageDeps because it ALSO records 'build-tool' dependencies on executables. Maybe one day cabal-install will also handle these correctly too!

BenchComponentLocalBuildInfo 

Fields

  • componentLocalName :: ComponentName

    It would be very convenient to store the literal Library here, but if we do that, it will get serialized (via the Binary) instance twice. So instead we just provide the ComponentName, which can be used to find the Component in the PackageDescription. NB: eventually, this will NOT uniquely identify the ComponentLocalBuildInfo.

  • componentComponentId :: ComponentId

    The computed ComponentId of this component.

  • componentUnitId :: UnitId

    The computed UnitId which uniquely identifies this component. Might be hashed.

  • componentPackageDeps :: [(UnitId, MungedPackageId)]

    Resolved internal and external package dependencies for this component. The BuildInfo specifies a set of build dependencies that must be satisfied in terms of version ranges. This field fixes those dependencies to the specific versions available on this machine for this compiler.

  • componentIncludes :: [(OpenUnitId, ModuleRenaming)]

    The set of packages that are brought into scope during compilation, including a ModuleRenaming which may used to hide or rename modules. This is what gets translated into -package-id arguments. This is a modernized version of componentPackageDeps, which is kept around for BC purposes.

  • componentExeDeps :: [UnitId]
     
  • componentInternalDeps :: [UnitId]

    The internal dependencies which induce a graph on the ComponentLocalBuildInfo of this package. This does NOT coincide with componentPackageDeps because it ALSO records 'build-tool' dependencies on executables. Maybe one day cabal-install will also handle these correctly too!

Instances

Instances details
IsNode ComponentLocalBuildInfo 
Instance details

Defined in Distribution.Types.ComponentLocalBuildInfo

Associated Types

type Key ComponentLocalBuildInfo #

Structured ComponentLocalBuildInfo 
Instance details

Defined in Distribution.Types.ComponentLocalBuildInfo

Generic ComponentLocalBuildInfo 
Instance details

Defined in Distribution.Types.ComponentLocalBuildInfo

Associated Types

type Rep ComponentLocalBuildInfo :: Type -> Type #

Read ComponentLocalBuildInfo 
Instance details

Defined in Distribution.Types.ComponentLocalBuildInfo

Show ComponentLocalBuildInfo 
Instance details

Defined in Distribution.Types.ComponentLocalBuildInfo

Binary ComponentLocalBuildInfo 
Instance details

Defined in Distribution.Types.ComponentLocalBuildInfo

type Key ComponentLocalBuildInfo 
Instance details

Defined in Distribution.Types.ComponentLocalBuildInfo

type Rep ComponentLocalBuildInfo 
Instance details

Defined in Distribution.Types.ComponentLocalBuildInfo

type Rep ComponentLocalBuildInfo = D1 ('MetaData "ComponentLocalBuildInfo" "Distribution.Types.ComponentLocalBuildInfo" "Cabal-3.14.1.1-KNG8xgahazw32ECV34zzCb" 'False) ((C1 ('MetaCons "LibComponentLocalBuildInfo" 'PrefixI 'True) (((S1 ('MetaSel ('Just "componentLocalName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentName) :*: (S1 ('MetaSel ('Just "componentComponentId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentId) :*: S1 ('MetaSel ('Just "componentUnitId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnitId))) :*: (S1 ('MetaSel ('Just "componentIsIndefinite_") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "componentInstantiatedWith") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(ModuleName, OpenModule)]) :*: S1 ('MetaSel ('Just "componentPackageDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(UnitId, MungedPackageId)])))) :*: ((S1 ('MetaSel ('Just "componentIncludes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(OpenUnitId, ModuleRenaming)]) :*: (S1 ('MetaSel ('Just "componentExeDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [UnitId]) :*: S1 ('MetaSel ('Just "componentInternalDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [UnitId]))) :*: ((S1 ('MetaSel ('Just "componentCompatPackageKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "componentCompatPackageName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MungedPackageName)) :*: (S1 ('MetaSel ('Just "componentExposedModules") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ExposedModule]) :*: S1 ('MetaSel ('Just "componentIsPublic") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))) :+: C1 ('MetaCons "FLibComponentLocalBuildInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "componentLocalName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentName) :*: (S1 ('MetaSel ('Just "componentComponentId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentId) :*: S1 ('MetaSel ('Just "componentUnitId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnitId))) :*: ((S1 ('MetaSel ('Just "componentPackageDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(UnitId, MungedPackageId)]) :*: S1 ('MetaSel ('Just "componentIncludes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(OpenUnitId, ModuleRenaming)])) :*: (S1 ('MetaSel ('Just "componentExeDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [UnitId]) :*: S1 ('MetaSel ('Just "componentInternalDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [UnitId]))))) :+: (C1 ('MetaCons "ExeComponentLocalBuildInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "componentLocalName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentName) :*: (S1 ('MetaSel ('Just "componentComponentId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentId) :*: S1 ('MetaSel ('Just "componentUnitId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnitId))) :*: ((S1 ('MetaSel ('Just "componentPackageDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(UnitId, MungedPackageId)]) :*: S1 ('MetaSel ('Just "componentIncludes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(OpenUnitId, ModuleRenaming)])) :*: (S1 ('MetaSel ('Just "componentExeDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [UnitId]) :*: S1 ('MetaSel ('Just "componentInternalDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [UnitId])))) :+: (C1 ('MetaCons "TestComponentLocalBuildInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "componentLocalName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentName) :*: (S1 ('MetaSel ('Just "componentComponentId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentId) :*: S1 ('MetaSel ('Just "componentUnitId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnitId))) :*: ((S1 ('MetaSel ('Just "componentPackageDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(UnitId, MungedPackageId)]) :*: S1 ('MetaSel ('Just "componentIncludes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(OpenUnitId, ModuleRenaming)])) :*: (S1 ('MetaSel ('Just "componentExeDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [UnitId]) :*: S1 ('MetaSel ('Just "componentInternalDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [UnitId])))) :+: C1 ('MetaCons "BenchComponentLocalBuildInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "componentLocalName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentName) :*: (S1 ('MetaSel ('Just "componentComponentId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentId) :*: S1 ('MetaSel ('Just "componentUnitId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnitId))) :*: ((S1 ('MetaSel ('Just "componentPackageDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(UnitId, MungedPackageId)]) :*: S1 ('MetaSel ('Just "componentIncludes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(OpenUnitId, ModuleRenaming)])) :*: (S1 ('MetaSel ('Just "componentExeDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [UnitId]) :*: S1 ('MetaSel ('Just "componentInternalDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [UnitId])))))))

Components

data Library #

Constructors

Library 

Fields

Instances

Instances details
HasBuildInfo Library 
Instance details

Defined in Distribution.Types.Library

Methods

buildInfo :: Lens' Library BuildInfo #

buildable :: Lens' Library Bool #

buildTools :: Lens' Library [LegacyExeDependency] #

buildToolDepends :: Lens' Library [ExeDependency] #

cppOptions :: Lens' Library [String] #

asmOptions :: Lens' Library [String] #

cmmOptions :: Lens' Library [String] #

ccOptions :: Lens' Library [String] #

cxxOptions :: Lens' Library [String] #

ldOptions :: Lens' Library [String] #

hsc2hsOptions :: Lens' Library [String] #

pkgconfigDepends :: Lens' Library [PkgconfigDependency] #

frameworks :: Lens' Library [RelativePath Framework 'File] #

extraFrameworkDirs :: Lens' Library [SymbolicPath Pkg ('Dir Framework)] #

asmSources :: Lens' Library [SymbolicPath Pkg 'File] #

cmmSources :: Lens' Library [SymbolicPath Pkg 'File] #

cSources :: Lens' Library [SymbolicPath Pkg 'File] #

cxxSources :: Lens' Library [SymbolicPath Pkg 'File] #

jsSources :: Lens' Library [SymbolicPath Pkg 'File] #

hsSourceDirs :: Lens' Library [SymbolicPath Pkg ('Dir Source)] #

otherModules :: Lens' Library [ModuleName] #

virtualModules :: Lens' Library [ModuleName] #

autogenModules :: Lens' Library [ModuleName] #

defaultLanguage :: Lens' Library (Maybe Language) #

otherLanguages :: Lens' Library [Language] #

defaultExtensions :: Lens' Library [Extension] #

otherExtensions :: Lens' Library [Extension] #

oldExtensions :: Lens' Library [Extension] #

extraLibs :: Lens' Library [String] #

extraLibsStatic :: Lens' Library [String] #

extraGHCiLibs :: Lens' Library [String] #

extraBundledLibs :: Lens' Library [String] #

extraLibFlavours :: Lens' Library [String] #

extraDynLibFlavours :: Lens' Library [String] #

extraLibDirs :: Lens' Library [SymbolicPath Pkg ('Dir Lib)] #

extraLibDirsStatic :: Lens' Library [SymbolicPath Pkg ('Dir Lib)] #

includeDirs :: Lens' Library [SymbolicPath Pkg ('Dir Include)] #

includes :: Lens' Library [SymbolicPath Include 'File] #

autogenIncludes :: Lens' Library [RelativePath Include 'File] #

installIncludes :: Lens' Library [RelativePath Include 'File] #

options :: Lens' Library (PerCompilerFlavor [String]) #

profOptions :: Lens' Library (PerCompilerFlavor [String]) #

sharedOptions :: Lens' Library (PerCompilerFlavor [String]) #

profSharedOptions :: Lens' Library (PerCompilerFlavor [String]) #

staticOptions :: Lens' Library (PerCompilerFlavor [String]) #

customFieldsBI :: Lens' Library [(String, String)] #

targetBuildDepends :: Lens' Library [Dependency] #

mixins :: Lens' Library [Mixin] #

Structured Library 
Instance details

Defined in Distribution.Types.Library

Data Library 
Instance details

Defined in Distribution.Types.Library

Methods

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

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

toConstr :: Library -> Constr #

dataTypeOf :: Library -> DataType #

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

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

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

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

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

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

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

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

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

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

Monoid Library

This instance is not good.

We need it for addBuildableCondition. More correct method would be some kind of "create empty clone".

More concretely, addBuildableCondition will make `libVisibility = False` libraries when `buildable: false`. This may cause problems.

Instance details

Defined in Distribution.Types.Library

Semigroup Library 
Instance details

Defined in Distribution.Types.Library

Generic Library 
Instance details

Defined in Distribution.Types.Library

Associated Types

type Rep Library :: Type -> Type #

Methods

from :: Library -> Rep Library x #

to :: Rep Library x -> Library #

Read Library 
Instance details

Defined in Distribution.Types.Library

Show Library 
Instance details

Defined in Distribution.Types.Library

Binary Library 
Instance details

Defined in Distribution.Types.Library

Methods

put :: Library -> Put #

get :: Get Library #

putList :: [Library] -> Put #

NFData Library 
Instance details

Defined in Distribution.Types.Library

Methods

rnf :: Library -> () #

Eq Library 
Instance details

Defined in Distribution.Types.Library

Methods

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

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

Ord Library 
Instance details

Defined in Distribution.Types.Library

type Rep Library 
Instance details

Defined in Distribution.Types.Library

data ForeignLib #

A foreign library stanza is like a library stanza, except that the built code is intended for consumption by a non-Haskell client.

Constructors

ForeignLib 

Fields

Instances

Instances details
HasBuildInfo ForeignLib 
Instance details

Defined in Distribution.Types.ForeignLib

Methods

buildInfo :: Lens' ForeignLib BuildInfo #

buildable :: Lens' ForeignLib Bool #

buildTools :: Lens' ForeignLib [LegacyExeDependency] #

buildToolDepends :: Lens' ForeignLib [ExeDependency] #

cppOptions :: Lens' ForeignLib [String] #

asmOptions :: Lens' ForeignLib [String] #

cmmOptions :: Lens' ForeignLib [String] #

ccOptions :: Lens' ForeignLib [String] #

cxxOptions :: Lens' ForeignLib [String] #

ldOptions :: Lens' ForeignLib [String] #

hsc2hsOptions :: Lens' ForeignLib [String] #

pkgconfigDepends :: Lens' ForeignLib [PkgconfigDependency] #

frameworks :: Lens' ForeignLib [RelativePath Framework 'File] #

extraFrameworkDirs :: Lens' ForeignLib [SymbolicPath Pkg ('Dir Framework)] #

asmSources :: Lens' ForeignLib [SymbolicPath Pkg 'File] #

cmmSources :: Lens' ForeignLib [SymbolicPath Pkg 'File] #

cSources :: Lens' ForeignLib [SymbolicPath Pkg 'File] #

cxxSources :: Lens' ForeignLib [SymbolicPath Pkg 'File] #

jsSources :: Lens' ForeignLib [SymbolicPath Pkg 'File] #

hsSourceDirs :: Lens' ForeignLib [SymbolicPath Pkg ('Dir Source)] #

otherModules :: Lens' ForeignLib [ModuleName] #

virtualModules :: Lens' ForeignLib [ModuleName] #

autogenModules :: Lens' ForeignLib [ModuleName] #

defaultLanguage :: Lens' ForeignLib (Maybe Language) #

otherLanguages :: Lens' ForeignLib [Language] #

defaultExtensions :: Lens' ForeignLib [Extension] #

otherExtensions :: Lens' ForeignLib [Extension] #

oldExtensions :: Lens' ForeignLib [Extension] #

extraLibs :: Lens' ForeignLib [String] #

extraLibsStatic :: Lens' ForeignLib [String] #

extraGHCiLibs :: Lens' ForeignLib [String] #

extraBundledLibs :: Lens' ForeignLib [String] #

extraLibFlavours :: Lens' ForeignLib [String] #

extraDynLibFlavours :: Lens' ForeignLib [String] #

extraLibDirs :: Lens' ForeignLib [SymbolicPath Pkg ('Dir Lib)] #

extraLibDirsStatic :: Lens' ForeignLib [SymbolicPath Pkg ('Dir Lib)] #

includeDirs :: Lens' ForeignLib [SymbolicPath Pkg ('Dir Include)] #

includes :: Lens' ForeignLib [SymbolicPath Include 'File] #

autogenIncludes :: Lens' ForeignLib [RelativePath Include 'File] #

installIncludes :: Lens' ForeignLib [RelativePath Include 'File] #

options :: Lens' ForeignLib (PerCompilerFlavor [String]) #

profOptions :: Lens' ForeignLib (PerCompilerFlavor [String]) #

sharedOptions :: Lens' ForeignLib (PerCompilerFlavor [String]) #

profSharedOptions :: Lens' ForeignLib (PerCompilerFlavor [String]) #

staticOptions :: Lens' ForeignLib (PerCompilerFlavor [String]) #

customFieldsBI :: Lens' ForeignLib [(String, String)] #

targetBuildDepends :: Lens' ForeignLib [Dependency] #

mixins :: Lens' ForeignLib [Mixin] #

Structured ForeignLib 
Instance details

Defined in Distribution.Types.ForeignLib

Data ForeignLib 
Instance details

Defined in Distribution.Types.ForeignLib

Methods

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

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

toConstr :: ForeignLib -> Constr #

dataTypeOf :: ForeignLib -> DataType #

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

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

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

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

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

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

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

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

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

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

Monoid ForeignLib 
Instance details

Defined in Distribution.Types.ForeignLib

Semigroup ForeignLib 
Instance details

Defined in Distribution.Types.ForeignLib

Generic ForeignLib 
Instance details

Defined in Distribution.Types.ForeignLib

Associated Types

type Rep ForeignLib :: Type -> Type #

Read ForeignLib 
Instance details

Defined in Distribution.Types.ForeignLib

Show ForeignLib 
Instance details

Defined in Distribution.Types.ForeignLib

Binary ForeignLib 
Instance details

Defined in Distribution.Types.ForeignLib

NFData ForeignLib 
Instance details

Defined in Distribution.Types.ForeignLib

Methods

rnf :: ForeignLib -> () #

Eq ForeignLib 
Instance details

Defined in Distribution.Types.ForeignLib

Ord ForeignLib 
Instance details

Defined in Distribution.Types.ForeignLib

type Rep ForeignLib 
Instance details

Defined in Distribution.Types.ForeignLib

type Rep ForeignLib = D1 ('MetaData "ForeignLib" "Distribution.Types.ForeignLib" "Cabal-syntax-3.14.1.0-Cm6co4XoXcLG0FTMtu5Sqa" 'False) (C1 ('MetaCons "ForeignLib" 'PrefixI 'True) ((S1 ('MetaSel ('Just "foreignLibName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnqualComponentName) :*: (S1 ('MetaSel ('Just "foreignLibType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ForeignLibType) :*: S1 ('MetaSel ('Just "foreignLibOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ForeignLibOption]))) :*: ((S1 ('MetaSel ('Just "foreignLibBuildInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuildInfo) :*: S1 ('MetaSel ('Just "foreignLibVersionInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LibVersionInfo))) :*: (S1 ('MetaSel ('Just "foreignLibVersionLinux") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Version)) :*: S1 ('MetaSel ('Just "foreignLibModDefFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RelativePath Source 'File])))))

data Executable #

Instances

Instances details
HasBuildInfo Executable 
Instance details

Defined in Distribution.Types.Executable

Methods

buildInfo :: Lens' Executable BuildInfo #

buildable :: Lens' Executable Bool #

buildTools :: Lens' Executable [LegacyExeDependency] #

buildToolDepends :: Lens' Executable [ExeDependency] #

cppOptions :: Lens' Executable [String] #

asmOptions :: Lens' Executable [String] #

cmmOptions :: Lens' Executable [String] #

ccOptions :: Lens' Executable [String] #

cxxOptions :: Lens' Executable [String] #

ldOptions :: Lens' Executable [String] #

hsc2hsOptions :: Lens' Executable [String] #

pkgconfigDepends :: Lens' Executable [PkgconfigDependency] #

frameworks :: Lens' Executable [RelativePath Framework 'File] #

extraFrameworkDirs :: Lens' Executable [SymbolicPath Pkg ('Dir Framework)] #

asmSources :: Lens' Executable [SymbolicPath Pkg 'File] #

cmmSources :: Lens' Executable [SymbolicPath Pkg 'File] #

cSources :: Lens' Executable [SymbolicPath Pkg 'File] #

cxxSources :: Lens' Executable [SymbolicPath Pkg 'File] #

jsSources :: Lens' Executable [SymbolicPath Pkg 'File] #

hsSourceDirs :: Lens' Executable [SymbolicPath Pkg ('Dir Source)] #

otherModules :: Lens' Executable [ModuleName] #

virtualModules :: Lens' Executable [ModuleName] #

autogenModules :: Lens' Executable [ModuleName] #

defaultLanguage :: Lens' Executable (Maybe Language) #

otherLanguages :: Lens' Executable [Language] #

defaultExtensions :: Lens' Executable [Extension] #

otherExtensions :: Lens' Executable [Extension] #

oldExtensions :: Lens' Executable [Extension] #

extraLibs :: Lens' Executable [String] #

extraLibsStatic :: Lens' Executable [String] #

extraGHCiLibs :: Lens' Executable [String] #

extraBundledLibs :: Lens' Executable [String] #

extraLibFlavours :: Lens' Executable [String] #

extraDynLibFlavours :: Lens' Executable [String] #

extraLibDirs :: Lens' Executable [SymbolicPath Pkg ('Dir Lib)] #

extraLibDirsStatic :: Lens' Executable [SymbolicPath Pkg ('Dir Lib)] #

includeDirs :: Lens' Executable [SymbolicPath Pkg ('Dir Include)] #

includes :: Lens' Executable [SymbolicPath Include 'File] #

autogenIncludes :: Lens' Executable [RelativePath Include 'File] #

installIncludes :: Lens' Executable [RelativePath Include 'File] #

options :: Lens' Executable (PerCompilerFlavor [String]) #

profOptions :: Lens' Executable (PerCompilerFlavor [String]) #

sharedOptions :: Lens' Executable (PerCompilerFlavor [String]) #

profSharedOptions :: Lens' Executable (PerCompilerFlavor [String]) #

staticOptions :: Lens' Executable (PerCompilerFlavor [String]) #

customFieldsBI :: Lens' Executable [(String, String)] #

targetBuildDepends :: Lens' Executable [Dependency] #

mixins :: Lens' Executable [Mixin] #

Structured Executable 
Instance details

Defined in Distribution.Types.Executable

Data Executable 
Instance details

Defined in Distribution.Types.Executable

Methods

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

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

toConstr :: Executable -> Constr #

dataTypeOf :: Executable -> DataType #

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

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

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

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

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

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

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

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

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

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

Monoid Executable 
Instance details

Defined in Distribution.Types.Executable

Semigroup Executable 
Instance details

Defined in Distribution.Types.Executable

Generic Executable 
Instance details

Defined in Distribution.Types.Executable

Associated Types

type Rep Executable :: Type -> Type #

Read Executable 
Instance details

Defined in Distribution.Types.Executable

Show Executable 
Instance details

Defined in Distribution.Types.Executable

Binary Executable 
Instance details

Defined in Distribution.Types.Executable

NFData Executable 
Instance details

Defined in Distribution.Types.Executable

Methods

rnf :: Executable -> () #

Eq Executable 
Instance details

Defined in Distribution.Types.Executable

Ord Executable 
Instance details

Defined in Distribution.Types.Executable

type Rep Executable 
Instance details

Defined in Distribution.Types.Executable

type Rep Executable = D1 ('MetaData "Executable" "Distribution.Types.Executable" "Cabal-syntax-3.14.1.0-Cm6co4XoXcLG0FTMtu5Sqa" 'False) (C1 ('MetaCons "Executable" 'PrefixI 'True) ((S1 ('MetaSel ('Just "exeName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnqualComponentName) :*: S1 ('MetaSel ('Just "modulePath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (RelativePath Source 'File))) :*: (S1 ('MetaSel ('Just "exeScope") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ExecutableScope) :*: S1 ('MetaSel ('Just "buildInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuildInfo))))

data TestSuite #

A "test-suite" stanza in a cabal file.

Instances

Instances details
HasBuildInfo TestSuite 
Instance details

Defined in Distribution.Types.TestSuite

Methods

buildInfo :: Lens' TestSuite BuildInfo #

buildable :: Lens' TestSuite Bool #

buildTools :: Lens' TestSuite [LegacyExeDependency] #

buildToolDepends :: Lens' TestSuite [ExeDependency] #

cppOptions :: Lens' TestSuite [String] #

asmOptions :: Lens' TestSuite [String] #

cmmOptions :: Lens' TestSuite [String] #

ccOptions :: Lens' TestSuite [String] #

cxxOptions :: Lens' TestSuite [String] #

ldOptions :: Lens' TestSuite [String] #

hsc2hsOptions :: Lens' TestSuite [String] #

pkgconfigDepends :: Lens' TestSuite [PkgconfigDependency] #

frameworks :: Lens' TestSuite [RelativePath Framework 'File] #

extraFrameworkDirs :: Lens' TestSuite [SymbolicPath Pkg ('Dir Framework)] #

asmSources :: Lens' TestSuite [SymbolicPath Pkg 'File] #

cmmSources :: Lens' TestSuite [SymbolicPath Pkg 'File] #

cSources :: Lens' TestSuite [SymbolicPath Pkg 'File] #

cxxSources :: Lens' TestSuite [SymbolicPath Pkg 'File] #

jsSources :: Lens' TestSuite [SymbolicPath Pkg 'File] #

hsSourceDirs :: Lens' TestSuite [SymbolicPath Pkg ('Dir Source)] #

otherModules :: Lens' TestSuite [ModuleName] #

virtualModules :: Lens' TestSuite [ModuleName] #

autogenModules :: Lens' TestSuite [ModuleName] #

defaultLanguage :: Lens' TestSuite (Maybe Language) #

otherLanguages :: Lens' TestSuite [Language] #

defaultExtensions :: Lens' TestSuite [Extension] #

otherExtensions :: Lens' TestSuite [Extension] #

oldExtensions :: Lens' TestSuite [Extension] #

extraLibs :: Lens' TestSuite [String] #

extraLibsStatic :: Lens' TestSuite [String] #

extraGHCiLibs :: Lens' TestSuite [String] #

extraBundledLibs :: Lens' TestSuite [String] #

extraLibFlavours :: Lens' TestSuite [String] #

extraDynLibFlavours :: Lens' TestSuite [String] #

extraLibDirs :: Lens' TestSuite [SymbolicPath Pkg ('Dir Lib)] #

extraLibDirsStatic :: Lens' TestSuite [SymbolicPath Pkg ('Dir Lib)] #

includeDirs :: Lens' TestSuite [SymbolicPath Pkg ('Dir Include)] #

includes :: Lens' TestSuite [SymbolicPath Include 'File] #

autogenIncludes :: Lens' TestSuite [RelativePath Include 'File] #

installIncludes :: Lens' TestSuite [RelativePath Include 'File] #

options :: Lens' TestSuite (PerCompilerFlavor [String]) #

profOptions :: Lens' TestSuite (PerCompilerFlavor [String]) #

sharedOptions :: Lens' TestSuite (PerCompilerFlavor [String]) #

profSharedOptions :: Lens' TestSuite (PerCompilerFlavor [String]) #

staticOptions :: Lens' TestSuite (PerCompilerFlavor [String]) #

customFieldsBI :: Lens' TestSuite [(String, String)] #

targetBuildDepends :: Lens' TestSuite [Dependency] #

mixins :: Lens' TestSuite [Mixin] #

Structured TestSuite 
Instance details

Defined in Distribution.Types.TestSuite

Data TestSuite 
Instance details

Defined in Distribution.Types.TestSuite

Methods

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

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

toConstr :: TestSuite -> Constr #

dataTypeOf :: TestSuite -> DataType #

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

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

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

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

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

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

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

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

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

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

Monoid TestSuite 
Instance details

Defined in Distribution.Types.TestSuite

Semigroup TestSuite 
Instance details

Defined in Distribution.Types.TestSuite

Generic TestSuite 
Instance details

Defined in Distribution.Types.TestSuite

Associated Types

type Rep TestSuite :: Type -> Type #

Read TestSuite 
Instance details

Defined in Distribution.Types.TestSuite

Show TestSuite 
Instance details

Defined in Distribution.Types.TestSuite

Binary TestSuite 
Instance details

Defined in Distribution.Types.TestSuite

NFData TestSuite 
Instance details

Defined in Distribution.Types.TestSuite

Methods

rnf :: TestSuite -> () #

Eq TestSuite 
Instance details

Defined in Distribution.Types.TestSuite

Ord TestSuite 
Instance details

Defined in Distribution.Types.TestSuite

type Rep TestSuite 
Instance details

Defined in Distribution.Types.TestSuite

type Rep TestSuite = D1 ('MetaData "TestSuite" "Distribution.Types.TestSuite" "Cabal-syntax-3.14.1.0-Cm6co4XoXcLG0FTMtu5Sqa" 'False) (C1 ('MetaCons "TestSuite" 'PrefixI 'True) ((S1 ('MetaSel ('Just "testName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnqualComponentName) :*: S1 ('MetaSel ('Just "testInterface") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TestSuiteInterface)) :*: (S1 ('MetaSel ('Just "testBuildInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuildInfo) :*: S1 ('MetaSel ('Just "testCodeGenerators") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]))))

data Benchmark #

A "benchmark" stanza in a cabal file.

Instances

Instances details
HasBuildInfo Benchmark 
Instance details

Defined in Distribution.Types.Benchmark

Methods

buildInfo :: Lens' Benchmark BuildInfo #

buildable :: Lens' Benchmark Bool #

buildTools :: Lens' Benchmark [LegacyExeDependency] #

buildToolDepends :: Lens' Benchmark [ExeDependency] #

cppOptions :: Lens' Benchmark [String] #

asmOptions :: Lens' Benchmark [String] #

cmmOptions :: Lens' Benchmark [String] #

ccOptions :: Lens' Benchmark [String] #

cxxOptions :: Lens' Benchmark [String] #

ldOptions :: Lens' Benchmark [String] #

hsc2hsOptions :: Lens' Benchmark [String] #

pkgconfigDepends :: Lens' Benchmark [PkgconfigDependency] #

frameworks :: Lens' Benchmark [RelativePath Framework 'File] #

extraFrameworkDirs :: Lens' Benchmark [SymbolicPath Pkg ('Dir Framework)] #

asmSources :: Lens' Benchmark [SymbolicPath Pkg 'File] #

cmmSources :: Lens' Benchmark [SymbolicPath Pkg 'File] #

cSources :: Lens' Benchmark [SymbolicPath Pkg 'File] #

cxxSources :: Lens' Benchmark [SymbolicPath Pkg 'File] #

jsSources :: Lens' Benchmark [SymbolicPath Pkg 'File] #

hsSourceDirs :: Lens' Benchmark [SymbolicPath Pkg ('Dir Source)] #

otherModules :: Lens' Benchmark [ModuleName] #

virtualModules :: Lens' Benchmark [ModuleName] #

autogenModules :: Lens' Benchmark [ModuleName] #

defaultLanguage :: Lens' Benchmark (Maybe Language) #

otherLanguages :: Lens' Benchmark [Language] #

defaultExtensions :: Lens' Benchmark [Extension] #

otherExtensions :: Lens' Benchmark [Extension] #

oldExtensions :: Lens' Benchmark [Extension] #

extraLibs :: Lens' Benchmark [String] #

extraLibsStatic :: Lens' Benchmark [String] #

extraGHCiLibs :: Lens' Benchmark [String] #

extraBundledLibs :: Lens' Benchmark [String] #

extraLibFlavours :: Lens' Benchmark [String] #

extraDynLibFlavours :: Lens' Benchmark [String] #

extraLibDirs :: Lens' Benchmark [SymbolicPath Pkg ('Dir Lib)] #

extraLibDirsStatic :: Lens' Benchmark [SymbolicPath Pkg ('Dir Lib)] #

includeDirs :: Lens' Benchmark [SymbolicPath Pkg ('Dir Include)] #

includes :: Lens' Benchmark [SymbolicPath Include 'File] #

autogenIncludes :: Lens' Benchmark [RelativePath Include 'File] #

installIncludes :: Lens' Benchmark [RelativePath Include 'File] #

options :: Lens' Benchmark (PerCompilerFlavor [String]) #

profOptions :: Lens' Benchmark (PerCompilerFlavor [String]) #

sharedOptions :: Lens' Benchmark (PerCompilerFlavor [String]) #

profSharedOptions :: Lens' Benchmark (PerCompilerFlavor [String]) #

staticOptions :: Lens' Benchmark (PerCompilerFlavor [String]) #

customFieldsBI :: Lens' Benchmark [(String, String)] #

targetBuildDepends :: Lens' Benchmark [Dependency] #

mixins :: Lens' Benchmark [Mixin] #

Structured Benchmark 
Instance details

Defined in Distribution.Types.Benchmark

Data Benchmark 
Instance details

Defined in Distribution.Types.Benchmark

Methods

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

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

toConstr :: Benchmark -> Constr #

dataTypeOf :: Benchmark -> DataType #

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

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

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

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

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

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

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

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

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

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

Monoid Benchmark 
Instance details

Defined in Distribution.Types.Benchmark

Semigroup Benchmark 
Instance details

Defined in Distribution.Types.Benchmark

Generic Benchmark 
Instance details

Defined in Distribution.Types.Benchmark

Associated Types

type Rep Benchmark :: Type -> Type #

Read Benchmark 
Instance details

Defined in Distribution.Types.Benchmark

Show Benchmark 
Instance details

Defined in Distribution.Types.Benchmark

Binary Benchmark 
Instance details

Defined in Distribution.Types.Benchmark

NFData Benchmark 
Instance details

Defined in Distribution.Types.Benchmark

Methods

rnf :: Benchmark -> () #

Eq Benchmark 
Instance details

Defined in Distribution.Types.Benchmark

Ord Benchmark 
Instance details

Defined in Distribution.Types.Benchmark

type Rep Benchmark 
Instance details

Defined in Distribution.Types.Benchmark

type Rep Benchmark = D1 ('MetaData "Benchmark" "Distribution.Types.Benchmark" "Cabal-syntax-3.14.1.0-Cm6co4XoXcLG0FTMtu5Sqa" 'False) (C1 ('MetaCons "Benchmark" 'PrefixI 'True) (S1 ('MetaSel ('Just "benchmarkName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnqualComponentName) :*: (S1 ('MetaSel ('Just "benchmarkInterface") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BenchmarkInterface) :*: S1 ('MetaSel ('Just "benchmarkBuildInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuildInfo))))

data LibraryName #

Instances

Instances details
Structured LibraryName 
Instance details

Defined in Distribution.Types.LibraryName

Data LibraryName 
Instance details

Defined in Distribution.Types.LibraryName

Methods

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

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

toConstr :: LibraryName -> Constr #

dataTypeOf :: LibraryName -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic LibraryName 
Instance details

Defined in Distribution.Types.LibraryName

Associated Types

type Rep LibraryName :: Type -> Type #

Read LibraryName 
Instance details

Defined in Distribution.Types.LibraryName

Show LibraryName 
Instance details

Defined in Distribution.Types.LibraryName

Binary LibraryName 
Instance details

Defined in Distribution.Types.LibraryName

NFData LibraryName 
Instance details

Defined in Distribution.Types.LibraryName

Methods

rnf :: LibraryName -> () #

Eq LibraryName 
Instance details

Defined in Distribution.Types.LibraryName

Ord LibraryName 
Instance details

Defined in Distribution.Types.LibraryName

type Rep LibraryName 
Instance details

Defined in Distribution.Types.LibraryName

type Rep LibraryName = D1 ('MetaData "LibraryName" "Distribution.Types.LibraryName" "Cabal-syntax-3.14.1.0-Cm6co4XoXcLG0FTMtu5Sqa" 'False) (C1 ('MetaCons "LMainLibName" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LSubLibName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnqualComponentName)))

emptyForeignLib :: ForeignLib #

An empty foreign library.