Skip to content

Commit fae54bd

Browse files
committed
WIP transitive deps
1 parent 62f9947 commit fae54bd

File tree

1 file changed

+21
-3
lines changed

1 file changed

+21
-3
lines changed

src/Share/NamespaceDiffs2.hs

Lines changed: 21 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
{-# LANGUAGE DataKinds #-}
2+
13
-- | Logic for computing the differerences between two namespaces,
24
-- typically used when showing the differences caused by a contribution.
35
module Share.NamespaceDiffs2
@@ -54,7 +56,9 @@ import Unison.Symbol (Symbol)
5456
import Unison.Syntax.NameSegment qualified as NameSegment
5557
import Unison.Syntax.Parser qualified as Parser
5658
import Unison.Term (Term)
59+
import Unison.Term qualified as Term
5760
import Unison.Type (Type)
61+
import Unison.Type qualified as Type
5862
import Unison.Typechecker.TypeLookup qualified as TL
5963
import Unison.Util.Defns (Defns (..), DefnsF)
6064
import Unison.Util.Nametree (Nametree)
@@ -182,8 +186,22 @@ typeLookupFromHydratedDefs hydratedDefns@(Defns {terms, types}) = do
182186

183187
-- | Find the references for every dependent on a core dependency which is within
184188
-- alice/bob. These definitions will be loaded into the Unison File to be re-parsed.
185-
coreDependencyTransitiveDependents :: (DefnsF Set TermReference TypeReference) -> m (DefnsF Set TermReferenceId TypeReferenceId)
186-
coreDependencyTransitiveDependents = undefined
189+
coreDependencyTransitiveDependents ::
190+
(DefnsF Set TermReference TypeReference) ->
191+
( DefnsF
192+
(Map Name)
193+
(TermReferenceId, (Term Symbol Ann, Type Symbol Ann))
194+
(TypeReferenceId, Decl Symbol Ann)
195+
) ->
196+
(DefnsF Set TermReferenceId TypeReferenceId)
197+
coreDependencyTransitiveDependents core@(Defns {terms = coreTerms, types = coreTypes}) hydratedDefns@(Defns {terms = hydratedTerms, types = hydratedTypes}) = undefined
198+
where
199+
defnDependencies :: (Map TermReferenceId (Set TermReferenceId, Set TypeReferenceId), Map TypeReferenceId (Set TypeReferenceId))
200+
defnDependencies =
201+
hydratedTerms
202+
& ifoldMap \refId (trm, typ) ->
203+
Term.dependencies trm
204+
& over (field @"types") <>~ Type.dependencies typ
187205

188206
causalFromMergeBlob5 :: Mergeblob5.Mergeblob5 -> m CausalId
189207
causalFromMergeBlob5 = undefined
@@ -193,7 +211,7 @@ mergeCausals causals3 codebases3 = runExceptT do
193211
(names3, mergeBlob1) <- computeMergeblob1 causals3
194212
mergeBlob2 <- except . mapLeft MergeBlob2Error $ Mergeblob2.makeMergeblob2 mergeBlob1
195213

196-
transitiveDependents2 <- for mergeBlob2.coreDependencies coreDependencyTransitiveDependents
214+
let transitiveDependents2 = Zip.zipWith coreDependencyTransitiveDependents mergeBlob2.coreDependencies mergeBlob2.hydratedDefns
197215
-- These names are garbage, but just need to have a unique name for every reference in
198216
-- scope so we can round-trip through a file, no user should ever see them.
199217
let combinedNames =

0 commit comments

Comments
 (0)