Skip to content

Commit 78afc12

Browse files
committed
Drop debug
1 parent 51d9f95 commit 78afc12

File tree

7 files changed

+22
-40
lines changed

7 files changed

+22
-40
lines changed

Cabal/src/Distribution/Simple/PackageIndex.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -169,7 +169,6 @@ instance Semigroup (PackageIndex IPI.InstalledPackageInfo) where
169169
{-# NOINLINE invariant #-}
170170
invariant :: WithCallStack (InstalledPackageIndex -> Bool)
171171
invariant (PackageIndex pids pnames) =
172-
trace (show pids' ++ "\n" ++ show pnames') $
173172
pids' == pnames'
174173
where
175174
pids' = map installedUnitId (Map.elems pids)
@@ -335,7 +334,7 @@ deleteSourcePackageId pkgid original@(PackageIndex pids pnames) =
335334
Just pvers -> case Map.lookup (packageVersion pkgid) pvers of
336335
Nothing -> original
337336
Just pkgs ->
338-
traceShow (pkgid, pkgs) $ mkPackageIndex
337+
mkPackageIndex
339338
(foldl' (flip (Map.delete . installedUnitId)) pids pkgs)
340339
-- (Map.update deletePkgInstance (installedUnitId pkgid) pids)
341340
(deletePkgName pnames)

cabal-install-solver/src/Distribution/Solver/Modular.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -81,7 +81,7 @@ showCP (CP qpi fa es ds) =
8181
-- solver. Performs the necessary translations before and after.
8282
modularResolver :: SolverConfig -> DependencyResolver loc
8383
modularResolver sc toolchains biidx iidx sidx pkgConfigDB pprefs pcs pns = do
84-
(assignment, revdepmap) <- solve' sc toolchains (trace (showIdx idx) idx) pkgConfigDB pprefs gcs pns
84+
(assignment, revdepmap) <- solve' sc toolchains idx pkgConfigDB pprefs gcs pns
8585
let cp = toCPs assignment revdepmap
8686
Step (show (vcat (map showCP cp))) $
8787
return $ postprocess assignment revdepmap

cabal-install-solver/src/Distribution/Solver/Modular/IndexConversion.hs

Lines changed: 2 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -63,13 +63,11 @@ convPIs :: Toolchains -> Map PN [LabeledPackageConstraint]
6363
-> CI.PackageIndex (SourcePackage loc)
6464
-> Index
6565
convPIs toolchains constraints sip strfl solveExes biidx iidx sidx =
66-
mkIndex $ (trace (pp "BIPIs" bipis) bipis) ++ (trace (pp "HIPIs" hipis) hipis) ++ (trace (pp "SPIs" spis) spis)
66+
mkIndex $ bipis ++ hipis ++ spis
6767
where bipis = convIPI' toolchains sip biidx
6868
hipis = convIPI' toolchains sip iidx
6969
ipis = bipis ++ hipis
7070
spis = convSPI' toolchains constraints strfl solveExes sidx
71-
pp :: String -> [(PN, I, PInfo)] -> String
72-
pp label xs = unlines $ ("=== " ++ label ++ ":\n"):(map (\(pn, i, pi) -> show pn ++ " " ++ show i) xs)
7371

7472
-- | Convert a Cabal installed package index to the simpler,
7573
-- more uniform index format of the solver.
@@ -158,7 +156,7 @@ convIP toolchains idx ipi =
158156
convIPId :: Toolchains -> DependencyReason PN -> Component -> SI.InstalledPackageIndex -> UnitId -> Either UnitId (FlaggedDep PN)
159157
convIPId toolchains dr comp idx ipid =
160158
case SI.lookupUnitId idx ipid of
161-
Nothing -> traceShow (show comp ++ ": Failed to find: " ++ show ipid ++ " in index.") $ Left ipid
159+
Nothing -> Left ipid
162160
Just ipi -> let (pn, i) = convId toolchains ipi
163161
name = ExposedLib LMainLibName -- TODO: Handle sub-libraries.
164162
in Right (D.Simple (LDep dr (Dep (PkgComponent pn name) (Fixed i))) comp)

cabal-install-solver/src/Distribution/Solver/Modular/Solver.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -105,7 +105,7 @@ solve sc toolchains idx pkgConfigDB userPrefs userConstraints userGoals =
105105
traceTree "cycles.json" id .
106106
detectCycles .
107107
traceTree "heuristics.json" id .
108-
stageBuildDeps "post-pref: " .
108+
-- stageBuildDeps "post-pref: " .
109109
trav (
110110
heuristicsPhase .
111111
preferencesPhase .
@@ -115,9 +115,9 @@ solve sc toolchains idx pkgConfigDB userPrefs userConstraints userGoals =
115115
validationCata .
116116
traceTree "pruned.json" id .
117117
trav prunePhase .
118-
stageBuildDeps "post-prune: " .
118+
-- stageBuildDeps "post-prune: " .
119119
(if buildIsHost toolchains then id else trav P.pruneHostFromSetup) .
120-
stageBuildDeps "build: " .
120+
-- stageBuildDeps "build: " .
121121
traceTree "build.json" id $
122122
buildPhase
123123
where

cabal-install/src/Distribution/Client/Dependency.hs

Lines changed: 1 addition & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -935,25 +935,12 @@ validateSolverResult
935935
-> [ResolverPackage UnresolvedPkgLoc]
936936
-> SolverInstallPlan
937937
validateSolverResult toolchains indepGoals pkgs =
938-
case planPackagesProblems toolchains (trace (dump pkgs) pkgs) of
938+
case planPackagesProblems toolchains pkgs of
939939
[] -> case SolverInstallPlan.new indepGoals graph of
940940
Right plan -> plan
941941
Left problems -> error (formatPlanProblems problems)
942942
problems -> error (formatPkgProblems problems)
943943
where
944-
dump :: [ResolverPackage UnresolvedPkgLoc] -> String
945-
dump xs = unlines $
946-
"=== DUMP ===":[unlines $ (resolverPkgHead x ++ show (packageId x)):[ "- "++ solverIdHead y ++ show (solverSrcId y)
947-
| y <- CD.flatDeps (resolverPackageLibDeps x)]
948-
| x <- xs ]
949-
++ ["=== /DUMP =="]
950-
951-
solverIdHead :: SolverId -> String
952-
solverIdHead (PreExistingId{}) = "[PE]"
953-
solverIdHead (PlannedId {}) = "[PL]"
954-
955-
resolverPkgHead (PreExisting _) = "[PE]"
956-
resolverPkgHead (Configured _) = "[CF]"
957944

958945
graph :: Graph.Graph (ResolverPackage UnresolvedPkgLoc)
959946
graph = Graph.fromDistinctList pkgs

cabal-install/src/Distribution/Client/ProjectOrchestration.hs

Lines changed: 2 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -659,8 +659,7 @@ resolveTargets
659659
checkTarget bt@(TargetPackage _ (ordNub -> [pkgid]) mkfilter)
660660
| Just ats <-
661661
fmap (maybe id filterTargetsKind mkfilter) $
662-
(trace (unlines $ ("Failed to find " ++ prettyShow pkgid ++ " in "):[prettyShow k {-# ++ " -> " ++ show v #-} | (k,v) <- Map.toList availableTargetsByPackageId])
663-
(Map.lookup pkgid availableTargetsByPackageId)) =
662+
(Map.lookup pkgid availableTargetsByPackageId) =
664663
fmap (componentTargets WholeComponent) $
665664
selectPackageTargets bt ats
666665
| otherwise =
@@ -689,11 +688,10 @@ resolveTargets
689688
-- FIXME: this is stupid. We do not know what the target selectors HOST compiler is...
690689
-- so we'll assume tere is only a _SINGLE_ match in the map if we ignore the pkgCompiler.
691690
-- This lookup is now O(n) instead of O(log n).
692-
(trace (unlines $ ("Failed to find " ++ prettyShow pkgid ++ ":" ++ show cname ++ " in "):[prettyShow k ++ ":" ++ show k' {-# ++ " -> " ++ show v #-} | ((k,k'),v) <- Map.toList availableTargetsByPackageIdAndComponentName])
693691
(case [v | ((k,k'),v) <- Map.toList availableTargetsByPackageIdAndComponentName
694692
, k{pkgCompiler = Nothing} == pkgid
695693
, k' == cname] of
696-
[match] -> Just match))
694+
[match] -> Just match)
697695
-- (Map.lookup
698696
-- (pkgid, cname)
699697
-- availableTargetsByPackageIdAndComponentName))

cabal-install/src/Distribution/Client/ProjectPlanning.hs

Lines changed: 12 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -849,14 +849,14 @@ rebuildInstallPlan
849849

850850
liftIO $ do
851851
notice verbosity "Resolving dependencies..."
852-
putStrLn "== installedPackages"
853-
putStrLn $ unlines $ map (prettyShow . IPI.sourcePackageId) $ PI.allPackages installedPackages
854-
putStrLn "== binstalledPackages"
855-
putStrLn $ unlines $ map (prettyShow . IPI.sourcePackageId) $ PI.allPackages binstalledPkgIndex
856-
putStrLn "== hinstalledPackages"
857-
putStrLn $ unlines $ map (prettyShow . IPI.sourcePackageId) $ PI.allPackages hinstalledPkgIndex
858-
putStrLn "== localPackages"
859-
putStrLn $ unlines . map (prettyShow . srcpkgPackageId) $ [pkg | SpecificSourcePackage pkg <- localPackages]
852+
-- putStrLn "== installedPackages"
853+
-- putStrLn $ unlines $ map (prettyShow . IPI.sourcePackageId) $ PI.allPackages installedPackages
854+
-- putStrLn "== binstalledPackages"
855+
-- putStrLn $ unlines $ map (prettyShow . IPI.sourcePackageId) $ PI.allPackages binstalledPkgIndex
856+
-- putStrLn "== hinstalledPackages"
857+
-- putStrLn $ unlines $ map (prettyShow . IPI.sourcePackageId) $ PI.allPackages hinstalledPkgIndex
858+
-- putStrLn "== localPackages"
859+
-- putStrLn $ unlines . map (prettyShow . srcpkgPackageId) $ [pkg | SpecificSourcePackage pkg <- localPackages]
860860
planOrError <-
861861
foldProgress logMsg (pure . Left) (pure . Right) $
862862
planPackages
@@ -1782,7 +1782,7 @@ elaborateInstallPlan
17821782
let src_comps = componentsGraphToList g
17831783
infoProgress $
17841784
hang
1785-
(text "Component graph for" <+> pretty pkgid <+> text "at stage " <+> text (show $ elabStage elab0) <<>> colon)
1785+
(text "Component graph for" <+> pretty pkgid <<>> colon)
17861786
4
17871787
(dispComponentsWithDeps src_comps)
17881788
(_, comps) <-
@@ -1973,7 +1973,7 @@ elaborateInstallPlan
19731973
elab0
19741974
{ elabPkgOrComp = ElabComponent $ elab_comp
19751975
}
1976-
cid = case traceShow (elabBuildStyle elab0) (elabBuildStyle elab0) of
1976+
cid = case elabBuildStyle elab0 of
19771977
BuildInplaceOnly{} ->
19781978
mkComponentId $
19791979
prettyShow pkgid
@@ -2363,7 +2363,7 @@ elaborateInstallPlan
23632363
elabPkgSourceLocation = srcloc
23642364
elabPkgSourceHash = case Map.lookup pkgid sourcePackageHashes of
23652365
Just h -> Just h
2366-
Nothing -> trace (unlines $ ("failed to find " ++ prettyShow pkgid ++ " in "):[ prettyShow k ++ " -> " ++ show v | (k, v) <- Map.toList sourcePackageHashes]) Nothing
2366+
Nothing -> Nothing
23672367
elabLocalToProject = isLocalToProject pkg
23682368
elabBuildStyle =
23692369
if shouldBuildInplaceOnly pkg
@@ -2551,7 +2551,7 @@ elaborateInstallPlan
25512551
shouldBuildInplaceOnly pkg =
25522552
Set.member
25532553
(packageId pkg)
2554-
(traceShowId pkgsToBuildInplaceOnly)
2554+
pkgsToBuildInplaceOnly
25552555

25562556

25572557
-- FIXME: This change is stupid, however the previous assumption is

0 commit comments

Comments
 (0)