Skip to content
Snippets Groups Projects
Unverified Commit 999776e1 authored by Rodrigo Mesquita's avatar Rodrigo Mesquita :seedling: Committed by GitHub
Browse files

Allow package to be listed twice in cabal.project (#9449)


This makes `checkTarget` a little smarter by deduplicating the
`TargetPackage` so as not to error out when the user has the line

    package: .

twice in their `cabal.project`.

Fixes #9448

Co-authored-by: default avatarmergify[bot] <37929162+mergify[bot]@users.noreply.github.com>
parent d9af0dce
No related branches found
No related tags found
No related merge requests found
Pipeline #87410 passed
......@@ -3,6 +3,7 @@
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE ViewPatterns #-}
-- | This module deals with building and incrementally rebuilding a collection
-- of packages. It is what backs the @cabal build@ and @configure@ commands,
......@@ -642,7 +643,7 @@ resolveTargets
checkTarget :: TargetSelector -> Either (TargetProblem err) [(UnitId, ComponentTarget)]
-- We can ask to build any whole package, project-local or a dependency
checkTarget bt@(TargetPackage _ [pkgid] mkfilter)
checkTarget bt@(TargetPackage _ (ordNub -> [pkgid]) mkfilter)
| Just ats <-
fmap (maybe id filterTargetsKind mkfilter) $
Map.lookup pkgid availableTargetsByPackageId =
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment