Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
Show all changes
68 commits
Select commit Hold shift + click to select a range
20489a7
feat(Cabal,Cabal-syntax): add per-file options to extra source files
andreabedini Mar 6, 2025
5c83c48
feat(Cabal): do not wrap logging by default
andreabedini Jun 5, 2025
dfcc65f
feat(Cabal, Cabal-syntax): support generated cmm-sources
andreabedini Mar 13, 2025
97f7aff
refactor(cabal-install-solver)!: remove base shim
andreabedini Mar 20, 2025
d975d43
refactor(cabal-install-solver)!: remove dead code
andreabedini Mar 14, 2025
1023f44
refactor(cabal-install,Cabal): move programDbSignature to Cabal
andreabedini Mar 19, 2025
e2b7b85
refactor(cabal-install): separate GenericReadyPackage from ReadyPackage
andreabedini May 8, 2025
f47840d
refactor(cabal-install): simplify the logic behind pkgsUseSharedLibr…
andreabedini Mar 21, 2025
5ec63e5
refactor(cabal-install): remove independent goals
andreabedini Mar 19, 2025
929676c
refactor(cabal-install): remove base-on-base trick
andreabedini Apr 23, 2025
ce05b66
refactor(cabal-install): remove storePackageDBStack
andreabedini Apr 9, 2025
f493e3a
refactor(cabal-install): resolve package dbs during planning
andreabedini Apr 8, 2025
db76bd1
refactor(cabal-install-solver): remove workaround for bug closed year…
andreabedini Apr 23, 2025
086ccc2
refactor(cabal-install): remove workaround for build tools listed as …
andreabedini May 5, 2025
6d741d4
refactor(cabal-install): move elabInstantiatedWith and elabLinkedInst…
andreabedini May 5, 2025
dd1bd2a
feat(cabal-install-solver): introduce Stage and Toolchain
andreabedini Mar 20, 2025
ca0a28d
feat(cabal-install): introduce ProjectConfigToolchain
andreabedini Apr 2, 2025
97a950d
feat(cabal-install-solver): all of it, second part
andreabedini Mar 21, 2025
d4252a5
refactor(cabal-install): don't check for compiler support before usi…
andreabedini Jul 24, 2025
085bbd3
feat(cabal-install): add build compiler option
andreabedini Mar 20, 2025
4b55c76
feat(cabal-install): all of it
andreabedini Mar 21, 2025
059f001
feat(cabal-install): add stage to ConstraintScope and UserConstraint
andreabedini Apr 2, 2025
a70bb7d
refactor(cabal-install-solver): improve messages
andreabedini Apr 23, 2025
ac8916a
refactor(cabal-install): use a pretty printer in showDepResolverParams
andreabedini Apr 23, 2025
c303cc0
refactor(cabal-install, cabal-install-solver): avoid using "error" in…
andreabedini Jul 2, 2025
d6f9a12
refactor(cabal-install-solver): add Show instance for Progress
andreabedini Jul 2, 2025
20aa401
feat(cabal-install-solver): add null to ComponentDeps
andreabedini Apr 23, 2025
f5a1571
feat(cabal-install-solver): add Pretty instance for SolverId
andreabedini Apr 23, 2025
cb41f5f
refactor(cabal-install): merge two almost identical functions
andreabedini Apr 28, 2025
4d51ab9
chore(cabal-install-solver): add comments and improve readability
andreabedini Apr 29, 2025
c213cea
feat(cabal-install, cabal-install-solver): track stage in SolverId
andreabedini Jul 2, 2025
4015ef0
fix(cabal-install): rewrite dependencyInconsistencies
andreabedini May 1, 2025
ca8828f
chore(cabal-install-solver): remove traceTree
andreabedini Jun 23, 2025
f8cec88
refactor(cabal-install-solver): refactor modularResolver
andreabedini Jun 23, 2025
8a9dd0d
refactor(cabal-install): generalise GenericInstallPlan to arbitrary n…
andreabedini Aug 7, 2025
5b1512a
chore(Cabal): update reference to backpack-include field, now called …
andreabedini May 6, 2025
9b7301c
feat: add a bunch of HasCallStack
andreabedini Jun 25, 2025
e80cdcb
fix: use nodeKey in fromSolverInstallPlanWithProgress
andreabedini May 19, 2025
f5e1246
propagate stage trough elaborateProjectPlanning
andreabedini May 5, 2025
69b38ad
fix(cabal-install): rewrite instantiateInstallPlan
andreabedini Aug 7, 2025
2004bb9
refactor(cabal-install): reduce scope in ProjectPlanning
andreabedini Jul 14, 2025
4bc268e
refactor(cabal-install): readability improvements
andreabedini May 20, 2025
332b6ec
fix(cabal-install): use the correct stage for setup deps
andreabedini May 27, 2025
e1f578c
refactor(cabal-install): rebuildTargets
andreabedini May 27, 2025
9b631dd
feat(cabal-install): more logging in buildAndRegisterUnpackedPackage
andreabedini May 27, 2025
2439bf7
fix(cabal-install): use the correct packagedb for setup
andreabedini Jun 25, 2025
cdee761
fix(cabal-install): fix pkgsToBuildInPlaceOnly
andreabedini May 28, 2025
19bebc9
refactor(cabal-install): seprate build directories and drop -inplace
andreabedini Jul 26, 2025
906436a
refactor(cabal-install): remove dead code
andreabedini Jul 26, 2025
af46dba
fix(Cabal): do not use GHC to configure LD
angerman May 22, 2025
a8050fc
feat(cabal-install): add parser for UserQualExe
andreabedini Jul 10, 2025
95945f7
feat(cabal-install): add ScopeAnyExeQualifier and UserAnyExeQualifier
andreabedini Jul 10, 2025
f0bbf0b
feature(cabal-install): automatically copy executables into build dir…
andreabedini Jun 5, 2025
94e60c4
refactor(cabal-install): refactor InstallPlan.problems
andreabedini Jul 28, 2025
23e01da
refactor(cabal-install): use LogProgress in InstallPlan
andreabedini Aug 1, 2025
c6b347f
feat(cabal-install): implicilty monitor our own executable to burst s…
andreabedini Aug 1, 2025
aff15c3
refactor(cabal-install): add more HasCallstack
andreabedini Aug 7, 2025
eab5a10
refactor(Cabal): add a stack trace to dieProgress
andreabedini Aug 7, 2025
65a4fb1
refactor(Cabal-syntax): Improve Graph.broken
andreabedini Aug 4, 2025
4517220
refactor(cabal-install): harmonise various dependency functions
andreabedini Aug 4, 2025
c10331b
debug: log why not registering
andreabedini Aug 5, 2025
08f604f
refactor(cabal-install): rename, format and comment
andreabedini Aug 5, 2025
86116e1
refactor(cabal-install): pkgDependsOnSelfLib should not hide failures
andreabedini Aug 5, 2025
a6cab47
fix(Cabal): do not print finalized package description, it loops
andreabedini Aug 6, 2025
fdf8b59
feature(cabal-install): improve logging of setup arguments
andreabedini Aug 6, 2025
4f0b69a
fix(Cabal): fix abi tag in case ghc's unit-id is the same as the comp…
andreabedini Aug 7, 2025
ab0a509
fix(Cabal): disable logging of the response file
andreabedini Jul 30, 2025
bc52b09
fixup! fix(Cabal): do not use GHC to configure LD
angerman Aug 26, 2025
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
16 changes: 15 additions & 1 deletion Cabal-described/src/Distribution/Described.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE DataKinds #-}
module Distribution.Described (
Described (..),
describeDoc,
Expand Down Expand Up @@ -79,6 +80,7 @@ import Distribution.Types.Dependency (Dependency)
import Distribution.Types.ExecutableScope (ExecutableScope)
import Distribution.Types.ExeDependency (ExeDependency)
import Distribution.Types.ExposedModule (ExposedModule)
import Distribution.Types.ExtraSource (ExtraSource)
import Distribution.Types.Flag (FlagAssignment, FlagName)
import Distribution.Types.ForeignLib (LibVersionInfo)
import Distribution.Types.ForeignLibOption (ForeignLibOption)
Expand All @@ -98,7 +100,7 @@ import Distribution.Types.SourceRepo (RepoType)
import Distribution.Types.TestType (TestType)
import Distribution.Types.UnitId (UnitId)
import Distribution.Types.UnqualComponentName (UnqualComponentName)
import Distribution.Utils.Path (SymbolicPath, RelativePath)
import Distribution.Utils.Path (SymbolicPath, RelativePath, FileOrDir(..), Pkg, Build)
import Distribution.Verbosity (Verbosity)
import Distribution.Version (Version, VersionRange)
import Language.Haskell.Extension (Extension, Language, knownLanguages)
Expand Down Expand Up @@ -405,6 +407,18 @@ instance Described ExposedModule where
instance Described Extension where
describe _ = RETodo

instance Described (ExtraSource Build) where
describe _ = REAppend
[ describe (Proxy :: Proxy (SymbolicPath Build File))
, REOpt (reChar '(' <> reSpacedList (describe (Proxy :: Proxy Token')) <> reChar ')')
]

instance Described (ExtraSource Pkg) where
describe _ = REAppend
[ describe (Proxy :: Proxy (SymbolicPath Pkg File))
, REOpt (reChar '(' <> reSpacedList (describe (Proxy :: Proxy Token')) <> reChar ')')
]

instance Described FlagAssignment where
describe _ = REMunch RESpaces1 $
REUnion [fromString "+", fromString "-"] <> describe (Proxy :: Proxy FlagName)
Expand Down
1 change: 1 addition & 0 deletions Cabal-syntax/Cabal-syntax.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -141,6 +141,7 @@ library
Distribution.Types.Executable
Distribution.Types.Executable.Lens
Distribution.Types.ExecutableScope
Distribution.Types.ExtraSource
Distribution.Types.ExposedModule
Distribution.Types.Flag
Distribution.Types.ForeignLib
Expand Down
30 changes: 20 additions & 10 deletions Cabal-syntax/src/Distribution/Compat/Graph.hs
Original file line number Diff line number Diff line change
Expand Up @@ -100,10 +100,11 @@ import Distribution.Utils.Structured (Structure (..), Structured (..))
import qualified Data.Array as Array
import qualified Data.Foldable as Foldable
import qualified Data.Graph as G
import qualified Data.List.NonEmpty as NE
import qualified Data.Map.Strict as Map
import qualified Data.Set as Set
import qualified Data.Tree as Tree
import qualified Distribution.Compat.Prelude as Prelude
import GHC.Stack (HasCallStack)

-- | A graph of nodes @a@. The nodes are expected to have instance
-- of class 'IsNode'.
Expand All @@ -114,7 +115,7 @@ data Graph a = Graph
, graphAdjoint :: G.Graph
, graphVertexToNode :: G.Vertex -> a
, graphKeyToVertex :: Key a -> Maybe G.Vertex
, graphBroken :: [(a, [Key a])]
, graphBroken :: [(a, NonEmpty (Key a))]
}

-- NB: Not a Functor! (or Traversable), because you need
Expand Down Expand Up @@ -284,7 +285,7 @@ cycles g = [vs | CyclicSCC vs <- stronglyConnComp g]
-- | /O(1)/. Return a list of nodes paired with their broken
-- neighbors (i.e., neighbor keys which are not in the graph).
-- Requires amortized construction of graph.
broken :: Graph a -> [(a, [Key a])]
broken :: Graph a -> [(a, NonEmpty (Key a))]
broken g = graphBroken g

-- | Lookup the immediate neighbors from a key in the graph.
Expand Down Expand Up @@ -343,7 +344,7 @@ revTopSort g = map (graphVertexToNode g) $ G.topSort (graphAdjoint g)
-- if you can't fulfill this invariant use @'fromList' ('Data.Map.elems' m)@
-- instead. The values of the map are assumed to already
-- be in WHNF.
fromMap :: IsNode a => Map (Key a) a -> Graph a
fromMap :: forall a. (IsNode a, Eq (Key a)) => Map (Key a) a -> Graph a
fromMap m =
Graph
{ graphMap = m
Expand All @@ -352,17 +353,26 @@ fromMap m =
, graphAdjoint = G.transposeG g
, graphVertexToNode = vertex_to_node
, graphKeyToVertex = key_to_vertex
, graphBroken = broke
, graphBroken =
map (\ns'' -> (fst (NE.head ns''), NE.map snd ns'')) $
NE.groupWith (nodeKey . fst) $
brokenEdges'
}
where
try_key_to_vertex k = maybe (Left k) Right (key_to_vertex k)
brokenEdges' :: [(a, Key a)]
brokenEdges' = concat brokenEdges

brokenEdges :: [[(a, Key a)]]
(brokenEdges, edges) =
unzip $
[ partitionEithers (map try_key_to_vertex (nodeNeighbors n))
unzip
[ partitionEithers
[ case key_to_vertex n' of
Just v -> Right v
Nothing -> Left (n, n')
| n' <- nodeNeighbors n
]
| n <- ns
]
broke = filter (not . Prelude.null . snd) (zip ns brokenEdges)

g = Array.listArray bounds edges

Expand All @@ -377,7 +387,7 @@ fromMap m =
bounds = (0, Map.size m - 1)

-- | /O(V log V)/. Convert a list of nodes (with distinct keys) into a graph.
fromDistinctList :: (IsNode a, Show (Key a)) => [a] -> Graph a
fromDistinctList :: HasCallStack => (IsNode a, Show (Key a)) => [a] -> Graph a
fromDistinctList =
fromMap
. Map.fromListWith (\_ -> duplicateError)
Expand Down
4 changes: 4 additions & 0 deletions Cabal-syntax/src/Distribution/PackageDescription.hs
Original file line number Diff line number Diff line change
Expand Up @@ -48,6 +48,9 @@ module Distribution.PackageDescription
, module Distribution.Types.HookedBuildInfo
, module Distribution.Types.SetupBuildInfo

-- * Extra sources
, module Distribution.Types.ExtraSource

-- * Flags
, module Distribution.Types.Flag

Expand Down Expand Up @@ -99,6 +102,7 @@ import Distribution.Types.Dependency
import Distribution.Types.ExeDependency
import Distribution.Types.Executable
import Distribution.Types.ExecutableScope
import Distribution.Types.ExtraSource
import Distribution.Types.Flag
import Distribution.Types.ForeignLib
import Distribution.Types.ForeignLibOption
Expand Down
27 changes: 22 additions & 5 deletions Cabal-syntax/src/Distribution/PackageDescription/FieldGrammar.hs
Original file line number Diff line number Diff line change
Expand Up @@ -174,6 +174,8 @@ libraryFieldGrammar
, c (List CommaFSep (Identity PkgconfigDependency) PkgconfigDependency)
, c (List CommaVCat (Identity Dependency) Dependency)
, c (List CommaVCat (Identity Mixin) Mixin)
, c (List VCat (Identity (ExtraSource Pkg)) (ExtraSource Pkg))
, c (List VCat (Identity (ExtraSource Build)) (ExtraSource Build))
, c (List CommaVCat (Identity ModuleReexport) ModuleReexport)
, c (List FSep (MQuoted Extension) Extension)
, c (List FSep (MQuoted Language) Language)
Expand Down Expand Up @@ -224,6 +226,8 @@ foreignLibFieldGrammar
, c (List CommaFSep (Identity PkgconfigDependency) PkgconfigDependency)
, c (List CommaVCat (Identity Dependency) Dependency)
, c (List CommaVCat (Identity Mixin) Mixin)
, c (List VCat (Identity (ExtraSource Pkg)) (ExtraSource Pkg))
, c (List VCat (Identity (ExtraSource Build)) (ExtraSource Build))
, c (List FSep (Identity ForeignLibOption) ForeignLibOption)
, c (List FSep (MQuoted Extension) Extension)
, c (List FSep (MQuoted Language) Language)
Expand Down Expand Up @@ -263,6 +267,8 @@ executableFieldGrammar
, c (List CommaFSep (Identity PkgconfigDependency) PkgconfigDependency)
, c (List CommaVCat (Identity Dependency) Dependency)
, c (List CommaVCat (Identity Mixin) Mixin)
, c (List VCat (Identity (ExtraSource Pkg)) (ExtraSource Pkg))
, c (List VCat (Identity (ExtraSource Build)) (ExtraSource Build))
, c (List FSep (MQuoted Extension) Extension)
, c (List FSep (MQuoted Language) Language)
, c (List FSep Token String)
Expand Down Expand Up @@ -339,6 +345,8 @@ testSuiteFieldGrammar
, c (List CommaFSep Token String)
, c (List CommaVCat (Identity Dependency) Dependency)
, c (List CommaVCat (Identity Mixin) Mixin)
, c (List VCat (Identity (ExtraSource Pkg)) (ExtraSource Pkg))
, c (List VCat (Identity (ExtraSource Build)) (ExtraSource Build))
, c (List FSep (MQuoted Extension) Extension)
, c (List FSep (MQuoted Language) Language)
, c (List FSep Token String)
Expand Down Expand Up @@ -483,6 +491,8 @@ benchmarkFieldGrammar
, c (List CommaFSep (Identity PkgconfigDependency) PkgconfigDependency)
, c (List CommaVCat (Identity Dependency) Dependency)
, c (List CommaVCat (Identity Mixin) Mixin)
, c (List VCat (Identity (ExtraSource Pkg)) (ExtraSource Pkg))
, c (List VCat (Identity (ExtraSource Build)) (ExtraSource Build))
, c (List FSep (MQuoted Extension) Extension)
, c (List FSep (MQuoted Language) Language)
, c (List FSep Token String)
Expand Down Expand Up @@ -585,6 +595,8 @@ buildInfoFieldGrammar
, c (List CommaFSep (Identity PkgconfigDependency) PkgconfigDependency)
, c (List CommaVCat (Identity Dependency) Dependency)
, c (List CommaVCat (Identity Mixin) Mixin)
, c (List VCat (Identity (ExtraSource Pkg)) (ExtraSource Pkg))
, c (List VCat (Identity (ExtraSource Build)) (ExtraSource Build))
, c (List FSep (MQuoted Extension) Extension)
, c (List FSep (MQuoted Language) Language)
, c (List FSep Token String)
Expand Down Expand Up @@ -629,14 +641,16 @@ buildInfoFieldGrammar =
<*> monoidalFieldAla "pkgconfig-depends" (alaList CommaFSep) L.pkgconfigDepends
<*> monoidalFieldAla "frameworks" (alaList' FSep RelativePathNT) L.frameworks
<*> monoidalFieldAla "extra-framework-dirs" (alaList' FSep SymbolicPathNT) L.extraFrameworkDirs
<*> monoidalFieldAla "asm-sources" (alaList' VCat SymbolicPathNT) L.asmSources
<*> monoidalFieldAla "asm-sources" formatExtraSources L.asmSources
^^^ availableSince CabalSpecV3_0 []
<*> monoidalFieldAla "cmm-sources" (alaList' VCat SymbolicPathNT) L.cmmSources
<*> monoidalFieldAla "cmm-sources" formatExtraSources L.cmmSources
^^^ availableSince CabalSpecV3_0 []
<*> monoidalFieldAla "c-sources" (alaList' VCat SymbolicPathNT) L.cSources
<*> monoidalFieldAla "cxx-sources" (alaList' VCat SymbolicPathNT) L.cxxSources
<*> monoidalFieldAla "autogen-cmm-sources" formatExtraSources L.autogenCmmSources
-- FIXME ^^^ availableSince CabalSpecV3_0 []
<*> monoidalFieldAla "c-sources" formatExtraSources L.cSources
<*> monoidalFieldAla "cxx-sources" formatExtraSources L.cxxSources
^^^ availableSince CabalSpecV2_2 []
<*> monoidalFieldAla "js-sources" (alaList' VCat SymbolicPathNT) L.jsSources
<*> monoidalFieldAla "js-sources" formatExtraSources L.jsSources
<*> hsSourceDirsGrammar
<*> monoidalFieldAla "other-modules" formatOtherModules L.otherModules
<*> monoidalFieldAla "virtual-modules" (alaList' VCat MQuoted) L.virtualModules
Expand Down Expand Up @@ -836,6 +850,9 @@ formatOtherExtensions = alaList' FSep MQuoted
formatOtherModules :: [ModuleName] -> List VCat (MQuoted ModuleName) ModuleName
formatOtherModules = alaList' VCat MQuoted

formatExtraSources :: [ExtraSource pkg] -> List VCat (Identity (ExtraSource pkg)) (ExtraSource pkg)
formatExtraSources = alaList' VCat Identity

-------------------------------------------------------------------------------
-- newtypes
-------------------------------------------------------------------------------
Expand Down
24 changes: 16 additions & 8 deletions Cabal-syntax/src/Distribution/Types/BuildInfo.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,6 +21,7 @@ import Prelude ()

import Distribution.Types.Dependency
import Distribution.Types.ExeDependency
import Distribution.Types.ExtraSource
import Distribution.Types.LegacyExeDependency
import Distribution.Types.Mixin
import Distribution.Types.PkgconfigDependency
Expand Down Expand Up @@ -72,14 +73,19 @@ data BuildInfo = BuildInfo
, frameworks :: [RelativePath Framework File]
-- ^ support frameworks for Mac OS X
, extraFrameworkDirs :: [SymbolicPath Pkg (Dir Framework)]
-- ^ extra locations to find frameworks.
, asmSources :: [SymbolicPath Pkg File]
-- ^ Assembly files.
, cmmSources :: [SymbolicPath Pkg File]
-- ^ C-- files.
, cSources :: [SymbolicPath Pkg File]
, cxxSources :: [SymbolicPath Pkg File]
, jsSources :: [SymbolicPath Pkg File]
-- ^ extra locations to find frameworks
, asmSources :: [ExtraSource Pkg]
-- ^ Assembly source files
, cmmSources :: [ExtraSource Pkg]
-- ^ C-- source files
, autogenCmmSources :: [ExtraSource Build]
-- ^ C-- generated source files
, cSources :: [ExtraSource Pkg]
-- ^ C source files
, cxxSources :: [ExtraSource Pkg]
-- ^ C++ source files
, jsSources :: [ExtraSource Pkg]
-- ^ JavaScript source file
, hsSourceDirs :: [SymbolicPath Pkg (Dir Source)]
-- ^ where to look for the Haskell module hierarchy
, -- NB: these are symbolic paths are not relative paths,
Expand Down Expand Up @@ -171,6 +177,7 @@ instance Monoid BuildInfo where
, extraFrameworkDirs = []
, asmSources = []
, cmmSources = []
, autogenCmmSources = []
, cSources = []
, cxxSources = []
, jsSources = []
Expand Down Expand Up @@ -225,6 +232,7 @@ instance Semigroup BuildInfo where
, extraFrameworkDirs = combineNub extraFrameworkDirs
, asmSources = combineNub asmSources
, cmmSources = combineNub cmmSources
, autogenCmmSources = combineNub autogenCmmSources
, cSources = combineNub cSources
, cxxSources = combineNub cxxSources
, jsSources = combineNub jsSources
Expand Down
17 changes: 11 additions & 6 deletions Cabal-syntax/src/Distribution/Types/BuildInfo/Lens.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,7 @@ import Distribution.ModuleName (ModuleName)
import Distribution.Types.BuildInfo (BuildInfo)
import Distribution.Types.Dependency (Dependency)
import Distribution.Types.ExeDependency (ExeDependency)
import Distribution.Types.ExtraSource (ExtraSource)
import Distribution.Types.LegacyExeDependency (LegacyExeDependency)
import Distribution.Types.Mixin (Mixin)
import Distribution.Types.PkgconfigDependency (PkgconfigDependency)
Expand Down Expand Up @@ -83,23 +84,27 @@ class HasBuildInfo a where
extraFrameworkDirs = buildInfo . extraFrameworkDirs
{-# INLINE extraFrameworkDirs #-}

asmSources :: Lens' a [SymbolicPath Pkg File]
asmSources :: Lens' a [ExtraSource Pkg]
asmSources = buildInfo . asmSources
{-# INLINE asmSources #-}

cmmSources :: Lens' a [SymbolicPath Pkg File]
autogenCmmSources :: Lens' a [ExtraSource Build]
autogenCmmSources = buildInfo . autogenCmmSources
{-# INLINE autogenCmmSources #-}

cmmSources :: Lens' a [ExtraSource Pkg]
cmmSources = buildInfo . cmmSources
{-# INLINE cmmSources #-}

cSources :: Lens' a [SymbolicPath Pkg File]
cSources :: Lens' a [ExtraSource Pkg]
cSources = buildInfo . cSources
{-# INLINE cSources #-}

cxxSources :: Lens' a [SymbolicPath Pkg File]
cxxSources :: Lens' a [ExtraSource Pkg]
cxxSources = buildInfo . cxxSources
{-# INLINE cxxSources #-}

jsSources :: Lens' a [SymbolicPath Pkg File]
jsSources :: Lens' a [ExtraSource Pkg]
jsSources = buildInfo . jsSources
{-# INLINE jsSources #-}

Expand Down Expand Up @@ -274,7 +279,7 @@ instance HasBuildInfo BuildInfo where
cSources f s = fmap (\x -> s{T.cSources = x}) (f (T.cSources s))
{-# INLINE cSources #-}

cxxSources f s = fmap (\x -> s{T.cSources = x}) (f (T.cxxSources s))
cxxSources f s = fmap (\x -> s{T.cxxSources = x}) (f (T.cxxSources s))
{-# INLINE cxxSources #-}

jsSources f s = fmap (\x -> s{T.jsSources = x}) (f (T.jsSources s))
Expand Down
Loading