make LTS branch pre-releases
[cabal.git] / Cabal-syntax / src / Distribution / Types / ComponentRequestedSpec.hs
blob224b38c839d93da42cdafb73bcb4ae5e636de95f
1 {-# LANGUAGE DeriveDataTypeable #-}
2 {-# LANGUAGE DeriveGeneric #-}
4 module Distribution.Types.ComponentRequestedSpec
5 ( -- $buildable_vs_enabled_components
6 ComponentRequestedSpec (..)
7 , ComponentDisabledReason (..)
8 , defaultComponentRequestedSpec
9 , componentNameRequested
10 , componentEnabled
11 , componentDisabledReason
12 ) where
14 import Distribution.Compat.Prelude
15 import Prelude ()
17 import Distribution.Types.Component -- TODO: maybe remove me?
18 import Distribution.Types.ComponentName
20 import Distribution.Pretty (prettyShow)
22 -- $buildable_vs_enabled_components
23 -- #buildable_vs_enabled_components#
25 -- = Note: Buildable versus requested versus enabled components
26 -- What's the difference between a buildable component (ala
27 -- 'componentBuildable'), a requested component
28 -- (ala 'componentNameRequested'), and an enabled component (ala
29 -- 'componentEnabled')?
31 -- A component is __buildable__ if, after resolving flags and
32 -- conditionals, there is no @buildable: False@ property in it.
33 -- This is a /static/ property that arises from the
34 -- Cabal file and the package description flattening; once we have
35 -- a 'PackageDescription' buildability is known.
37 -- A component is __requested__ if a user specified, via a
38 -- the flags and arguments passed to configure, that it should be
39 -- built. E.g., @--enable-tests@ or @--enable-benchmarks@ request
40 -- all tests and benchmarks, if they are provided. What is requested
41 -- can be read off directly from 'ComponentRequestedSpec'. A requested
42 -- component is not always buildable; e.g., a user may @--enable-tests@
43 -- but one of the test suites may have @buildable: False@.
45 -- A component is __enabled__ if it is BOTH buildable
46 -- and requested. Once we have a 'LocalBuildInfo', whether or not a
47 -- component is enabled is known.
49 -- Generally speaking, most Cabal API code cares if a component
50 -- is enabled. (For example, if you want to run a preprocessor on each
51 -- component prior to building them, you want to run this on each
52 -- /enabled/ component.)
54 -- Note that post-configuration, you will generally not see a
55 -- non-buildable 'Component'. This is because 'flattenPD' will drop
56 -- any such components from 'PackageDescription'. See #3858 for
57 -- an example where this causes problems.
59 -- | Describes what components are enabled by user-interaction.
60 -- See also this note in
61 -- "Distribution.Types.ComponentRequestedSpec#buildable_vs_enabled_components".
63 -- @since 2.0.0.2
64 data ComponentRequestedSpec
65 = ComponentRequestedSpec
66 { testsRequested :: Bool
67 , benchmarksRequested :: Bool
69 | OneComponentRequestedSpec ComponentName
70 deriving (Generic, Read, Show, Eq, Typeable)
72 instance Binary ComponentRequestedSpec
73 instance Structured ComponentRequestedSpec
75 -- | The default set of enabled components. Historically tests and
76 -- benchmarks are NOT enabled by default.
78 -- @since 2.0.0.2
79 defaultComponentRequestedSpec :: ComponentRequestedSpec
80 defaultComponentRequestedSpec = ComponentRequestedSpec False False
82 -- | Is this component enabled? See also this note in
83 -- "Distribution.Types.ComponentRequestedSpec#buildable_vs_enabled_components".
85 -- @since 2.0.0.2
86 componentEnabled :: ComponentRequestedSpec -> Component -> Bool
87 componentEnabled enabled = isNothing . componentDisabledReason enabled
89 -- | Is this component name enabled? See also this note in
90 -- "Distribution.Types.ComponentRequestedSpec#buildable_vs_enabled_components".
92 -- @since 2.0.0.2
93 componentNameRequested :: ComponentRequestedSpec -> ComponentName -> Bool
94 componentNameRequested enabled = isNothing . componentNameNotRequestedReason enabled
96 -- | Is this component disabled, and if so, why?
98 -- @since 2.0.0.2
99 componentDisabledReason
100 :: ComponentRequestedSpec
101 -> Component
102 -> Maybe ComponentDisabledReason
103 componentDisabledReason enabled comp
104 | not (componentBuildable comp) = Just DisabledComponent
105 | otherwise = componentNameNotRequestedReason enabled (componentName comp)
107 -- | Is this component name disabled, and if so, why?
109 -- @since 2.0.0.2
110 componentNameNotRequestedReason
111 :: ComponentRequestedSpec
112 -> ComponentName
113 -> Maybe ComponentDisabledReason
114 componentNameNotRequestedReason
115 ComponentRequestedSpec{testsRequested = False}
116 (CTestName _) =
117 Just DisabledAllTests
118 componentNameNotRequestedReason
119 ComponentRequestedSpec{benchmarksRequested = False}
120 (CBenchName _) =
121 Just DisabledAllBenchmarks
122 componentNameNotRequestedReason ComponentRequestedSpec{} _ = Nothing
123 componentNameNotRequestedReason (OneComponentRequestedSpec cname) c
124 | c == cname = Nothing
125 | otherwise = Just (DisabledAllButOne (prettyShow cname))
127 -- | A reason explaining why a component is disabled.
129 -- @since 2.0.0.2
130 data ComponentDisabledReason
131 = DisabledComponent
132 | DisabledAllTests
133 | DisabledAllBenchmarks
134 | DisabledAllButOne String