Merge pull request #5107 from unisonweb/24-06-13-revamp-todo

This commit is contained in:
Arya Irani 2024-06-24 12:08:27 -04:00 committed by GitHub
commit 7172bb8e4f
No known key found for this signature in database
GPG Key ID: B5690EEEBB952194
18 changed files with 336 additions and 805 deletions

View File

@ -63,6 +63,7 @@ module U.Codebase.Sqlite.Operations
causalHashesByPrefix,
-- ** dependents index
directDependenciesOfScope,
dependents,
dependentsOfComponent,
dependentsWithinScope,
@ -205,6 +206,7 @@ import Unison.NameSegment.Internal qualified as NameSegment
import Unison.Prelude
import Unison.ShortHash (ShortCausalHash (..), ShortNamespaceHash (..))
import Unison.Sqlite
import Unison.Util.Defns (DefnsF)
import Unison.Util.List qualified as List
import Unison.Util.Map qualified as Map
import Unison.Util.Monoid (foldMapM)
@ -1121,6 +1123,21 @@ causalHashesByPrefix (ShortCausalHash b32prefix) = do
hashes <- traverse (Q.expectHash . Db.unCausalHashId) hashIds
pure $ Set.fromList . map CausalHash $ hashes
directDependenciesOfScope ::
DefnsF Set C.TermReferenceId C.TypeReferenceId ->
Transaction (DefnsF Set C.TermReference C.TypeReference)
directDependenciesOfScope scope0 = do
-- Convert C -> S
scope1 <- bitraverse (Set.traverse c2sReferenceId) (Set.traverse c2sReferenceId) scope0
-- Do the query
dependencies0 <- Q.getDirectDependenciesOfScope scope1
-- Convert S -> C
dependencies1 <- bitraverse (Set.traverse s2cReference) (Set.traverse s2cReference) dependencies0
pure dependencies1
-- | returns a list of known definitions referencing `r`
dependents :: Q.DependentsSelector -> C.Reference -> Transaction (Set C.Reference.Id)
dependents selector r = do

View File

@ -165,6 +165,7 @@ module U.Codebase.Sqlite.Queries
getDependenciesForDependent,
getDependencyIdsForDependent,
getDependenciesBetweenTerms,
getDirectDependenciesOfScope,
getDependentsWithinScope,
-- ** type index
@ -321,7 +322,7 @@ import U.Codebase.Decl qualified as C
import U.Codebase.Decl qualified as C.Decl
import U.Codebase.HashTags (BranchHash (..), CausalHash (..), PatchHash (..))
import U.Codebase.Reference (Reference' (..))
import U.Codebase.Reference qualified as C
import U.Codebase.Reference qualified as C (Reference)
import U.Codebase.Reference qualified as C.Reference
import U.Codebase.Referent qualified as C.Referent
import U.Codebase.Reflog qualified as Reflog
@ -365,10 +366,9 @@ import U.Codebase.Sqlite.Orphans ()
import U.Codebase.Sqlite.Patch.Format qualified as PatchFormat
import U.Codebase.Sqlite.Project (Project (..))
import U.Codebase.Sqlite.ProjectBranch (ProjectBranch (..))
import U.Codebase.Sqlite.Reference qualified as Reference
import U.Codebase.Sqlite.Reference qualified as S
import U.Codebase.Sqlite.Reference qualified as S (Reference, ReferenceH, TermReference, TermReferenceId, TextReference, TypeReference, TypeReferenceId)
import U.Codebase.Sqlite.Reference qualified as S.Reference
import U.Codebase.Sqlite.Referent qualified as Referent
import U.Codebase.Sqlite.Referent qualified as S (TextReferent)
import U.Codebase.Sqlite.Referent qualified as S.Referent
import U.Codebase.Sqlite.RemoteProject (RemoteProject (..))
import U.Codebase.Sqlite.RemoteProjectBranch (RemoteProjectBranch)
@ -399,6 +399,7 @@ import Unison.NameSegment.Internal qualified as NameSegment
import Unison.Prelude
import Unison.Sqlite
import Unison.Util.Alternative qualified as Alternative
import Unison.Util.Defns (Defns (..), DefnsF)
import Unison.Util.FileEmbed (embedProjectStringFile)
import Unison.Util.Lens qualified as Lens
import Unison.Util.Map qualified as Map
@ -1361,7 +1362,7 @@ setNamespaceRoot id =
False -> execute [sql| INSERT INTO namespace_root VALUES (:id) |]
True -> execute [sql| UPDATE namespace_root SET causal_id = :id |]
saveWatch :: WatchKind -> Reference.IdH -> ByteString -> Transaction ()
saveWatch :: WatchKind -> S.Reference.IdH -> ByteString -> Transaction ()
saveWatch k r blob = do
execute
[sql|
@ -1379,7 +1380,7 @@ saveWatch k r blob = do
loadWatch ::
SqliteExceptionReason e =>
WatchKind ->
Reference.IdH ->
S.Reference.IdH ->
(ByteString -> Either e a) ->
Transaction (Maybe a)
loadWatch k r check =
@ -1395,7 +1396,7 @@ loadWatch k r check =
|]
check
loadWatchKindsByReference :: Reference.IdH -> Transaction [WatchKind]
loadWatchKindsByReference :: S.Reference.IdH -> Transaction [WatchKind]
loadWatchKindsByReference r =
queryListCol
[sql|
@ -1407,7 +1408,7 @@ loadWatchKindsByReference r =
AND watch.component_index = @
|]
loadWatchesByWatchKind :: WatchKind -> Transaction [Reference.IdH]
loadWatchesByWatchKind :: WatchKind -> Transaction [S.Reference.IdH]
loadWatchesByWatchKind k =
queryListRow
[sql|
@ -1423,7 +1424,7 @@ clearWatches = do
execute [sql| DELETE FROM watch |]
-- * Index-building
addToTypeIndex :: Reference' TextId HashId -> Referent.Id -> Transaction ()
addToTypeIndex :: S.ReferenceH -> S.Referent.Id -> Transaction ()
addToTypeIndex tp tm =
execute
[sql|
@ -1438,7 +1439,7 @@ addToTypeIndex tp tm =
ON CONFLICT DO NOTHING
|]
getReferentsByType :: Reference' TextId HashId -> Transaction [Referent.Id]
getReferentsByType :: S.ReferenceH -> Transaction [S.Referent.Id]
getReferentsByType r =
queryListRow
[sql|
@ -1452,7 +1453,7 @@ getReferentsByType r =
AND type_reference_component_index IS @
|]
getTypeReferenceForReferent :: Referent.Id -> Transaction (Reference' TextId HashId)
getTypeReferenceForReferent :: S.Referent.Id -> Transaction S.ReferenceH
getTypeReferenceForReferent r =
queryOneRow
[sql|
@ -1467,7 +1468,7 @@ getTypeReferenceForReferent r =
|]
-- todo: error if no results
getTypeReferencesForComponent :: ObjectId -> Transaction [(Reference' TextId HashId, Referent.Id)]
getTypeReferencesForComponent :: ObjectId -> Transaction [(S.ReferenceH, S.Referent.Id)]
getTypeReferencesForComponent oId =
fmap (map fixupTypeIndexRow) $
queryListRow
@ -1553,7 +1554,7 @@ filterTermsByReferenceHavingType typ terms = create *> for_ terms insert *> sele
drop = execute [sql|DROP TABLE filter_query|]
addToTypeMentionsIndex :: Reference' TextId HashId -> Referent.Id -> Transaction ()
addToTypeMentionsIndex :: S.ReferenceH -> S.Referent.Id -> Transaction ()
addToTypeMentionsIndex tp tm =
execute
[sql|
@ -1568,7 +1569,7 @@ addToTypeMentionsIndex tp tm =
ON CONFLICT DO NOTHING
|]
getReferentsByTypeMention :: Reference' TextId HashId -> Transaction [Referent.Id]
getReferentsByTypeMention :: S.ReferenceH -> Transaction [S.Referent.Id]
getReferentsByTypeMention r =
queryListRow
[sql|
@ -1583,7 +1584,7 @@ getReferentsByTypeMention r =
|]
-- todo: error if no results
getTypeMentionsReferencesForComponent :: ObjectId -> Transaction [(Reference' TextId HashId, Referent.Id)]
getTypeMentionsReferencesForComponent :: ObjectId -> Transaction [(S.ReferenceH, S.Referent.Id)]
getTypeMentionsReferencesForComponent r =
fmap (map fixupTypeIndexRow) $
queryListRow
@ -1599,7 +1600,7 @@ getTypeMentionsReferencesForComponent r =
WHERE term_referent_object_id IS :r
|]
fixupTypeIndexRow :: Reference' TextId HashId :. Referent.Id -> (Reference' TextId HashId, Referent.Id)
fixupTypeIndexRow :: S.ReferenceH :. S.Referent.Id -> (S.ReferenceH, S.Referent.Id)
fixupTypeIndexRow (rh :. ri) = (rh, ri)
-- | Delete objects without hashes. An object typically *would* have a hash, but (for example) during a migration in which an object's hash
@ -1653,7 +1654,7 @@ garbageCollectWatchesWithoutObjects = do
(SELECT hash_object.hash_id FROM hash_object)
|]
addToDependentsIndex :: [Reference.Reference] -> Reference.Id -> Transaction ()
addToDependentsIndex :: [S.Reference] -> S.Reference.Id -> Transaction ()
addToDependentsIndex dependencies dependent =
for_ dependencies \dependency ->
execute
@ -1682,7 +1683,7 @@ data DependentsSelector
| ExcludeOwnComponent
-- | Get dependents of a dependency.
getDependentsForDependency :: DependentsSelector -> Reference.Reference -> Transaction (Set Reference.Id)
getDependentsForDependency :: DependentsSelector -> S.Reference -> Transaction (Set S.Reference.Id)
getDependentsForDependency selector dependency = do
dependents <-
queryListRow
@ -1699,19 +1700,19 @@ getDependentsForDependency selector dependency = do
ExcludeSelf -> filter isNotSelfReference dependents
ExcludeOwnComponent -> filter isNotReferenceFromOwnComponent dependents
where
isNotReferenceFromOwnComponent :: Reference.Id -> Bool
isNotReferenceFromOwnComponent :: S.Reference.Id -> Bool
isNotReferenceFromOwnComponent =
case dependency of
ReferenceBuiltin _ -> const True
ReferenceDerived (C.Reference.Id oid0 _pos0) -> \(C.Reference.Id oid1 _pos1) -> oid0 /= oid1
isNotSelfReference :: Reference.Id -> Bool
isNotSelfReference :: S.Reference.Id -> Bool
isNotSelfReference =
case dependency of
ReferenceBuiltin _ -> const True
ReferenceDerived ref -> (ref /=)
getDependentsForDependencyComponent :: ObjectId -> Transaction [Reference.Id]
getDependentsForDependencyComponent :: ObjectId -> Transaction [S.Reference.Id]
getDependentsForDependencyComponent dependency =
filter isNotSelfReference <$>
queryListRow
@ -1722,12 +1723,12 @@ getDependentsForDependencyComponent dependency =
AND dependency_object_id IS :dependency
|]
where
isNotSelfReference :: Reference.Id -> Bool
isNotSelfReference :: S.Reference.Id -> Bool
isNotSelfReference = \case
(C.Reference.Id oid1 _pos1) -> dependency /= oid1
-- | Get non-self dependencies of a user-defined dependent.
getDependenciesForDependent :: Reference.Id -> Transaction [Reference.Reference]
getDependenciesForDependent :: S.Reference.Id -> Transaction [S.Reference]
getDependenciesForDependent dependent@(C.Reference.Id oid0 _) =
fmap (filter isNotSelfReference) $
queryListRow
@ -1738,13 +1739,13 @@ getDependenciesForDependent dependent@(C.Reference.Id oid0 _) =
AND dependent_component_index IS @
|]
where
isNotSelfReference :: Reference.Reference -> Bool
isNotSelfReference :: S.Reference -> Bool
isNotSelfReference = \case
ReferenceBuiltin _ -> True
ReferenceDerived (C.Reference.Id oid1 _) -> oid0 /= oid1
-- | Get non-self, user-defined dependencies of a user-defined dependent.
getDependencyIdsForDependent :: Reference.Id -> Transaction [Reference.Id]
getDependencyIdsForDependent :: S.Reference.Id -> Transaction [S.Reference.Id]
getDependencyIdsForDependent dependent@(C.Reference.Id oid0 _) =
fmap (filter isNotSelfReference) $
queryListRow
@ -1756,7 +1757,7 @@ getDependencyIdsForDependent dependent@(C.Reference.Id oid0 _) =
AND dependent_component_index = @
|]
where
isNotSelfReference :: Reference.Id -> Bool
isNotSelfReference :: S.Reference.Id -> Bool
isNotSelfReference (C.Reference.Id oid1 _) =
oid0 /= oid1
@ -1869,21 +1870,57 @@ getDependenciesBetweenTerms oid1 oid2 =
WHERE path_elem IS NOT null
|]
-- Mitchell says: why are we enabling and disabling ormolu all over this file? Let's just enable. But right now I'm only
-- adding this one query and don't want a big diff in my PR.
{- ORMOLU_ENABLE -}
getDirectDependenciesOfScope ::
DefnsF Set S.TermReferenceId S.TypeReferenceId ->
Transaction (DefnsF Set S.TermReference S.TypeReference)
getDirectDependenciesOfScope scope = do
let tempTableName = [sql| temp_dependents |]
-- Populate a temporary table with all of the references in `scope`
createTemporaryTableOfReferenceIds tempTableName (Set.union scope.terms scope.types)
-- Get their direct dependencies (tagged with object type)
dependencies0 <-
queryListRow @(S.Reference :. Only ObjectType)
[sql|
SELECT d.dependency_builtin, d.dependency_object_id, d.dependency_component_index, o.type_id
FROM dependents_index d
JOIN object o ON d.dependency_object_id = o.id
WHERE (d.dependent_object_id, d.dependent_component_index) IN (
SELECT object_id, component_index
FROM $tempTableName
)
|]
-- Drop the temporary table
execute [sql| DROP TABLE $tempTableName |]
-- Post-process the query result
let dependencies1 =
List.foldl'
( \deps -> \case
dep :. Only TermComponent -> Defns (Set.insert dep deps.terms) deps.types
dep :. Only DeclComponent -> Defns deps.terms (Set.insert dep deps.types)
_ -> deps -- impossible; could error here
)
(Defns Set.empty Set.empty)
dependencies0
pure dependencies1
{- ORMOLU_DISABLE -}
-- | `getDependentsWithinScope scope query` returns all of transitive dependents of `query` that are in `scope` (not
-- including `query` itself). Each dependent is also tagged with whether it is a term or decl.
getDependentsWithinScope :: Set Reference.Id -> Set S.Reference -> Transaction (Map Reference.Id ObjectType)
getDependentsWithinScope :: Set S.Reference.Id -> Set S.Reference -> Transaction (Map S.Reference.Id ObjectType)
getDependentsWithinScope scope query = do
-- Populate a temporary table with all of the references in `scope`
execute
[sql|
CREATE TEMPORARY TABLE dependents_search_scope (
dependent_object_id INTEGER NOT NULL,
dependent_component_index INTEGER NOT NULL,
PRIMARY KEY (dependent_object_id, dependent_component_index)
)
|]
for_ scope \r ->
execute [sql|INSERT INTO dependents_search_scope VALUES (@r, @)|]
createTemporaryTableOfReferenceIds [sql| dependents_search_scope |] scope
-- Populate a temporary table with all of the references in `query`
execute
@ -1917,7 +1954,7 @@ getDependentsWithinScope scope query = do
-- We use `UNION` rather than `UNION ALL` so as to not track down the transitive dependents of any particular
-- reference more than once.
result :: [Reference.Id :. Only ObjectType] <- queryListRow [sql|
result :: [S.Reference.Id :. Only ObjectType] <- queryListRow [sql|
WITH RECURSIVE transitive_dependents (dependent_object_id, dependent_component_index, type_id) AS (
SELECT d.dependent_object_id, d.dependent_component_index, object.type_id
FROM dependents_index d
@ -1927,8 +1964,8 @@ getDependentsWithinScope scope query = do
AND q.dependency_object_id IS d.dependency_object_id
AND q.dependency_component_index IS d.dependency_component_index
JOIN dependents_search_scope s
ON s.dependent_object_id = d.dependent_object_id
AND s.dependent_component_index = d.dependent_component_index
ON s.object_id = d.dependent_object_id
AND s.component_index = d.dependent_component_index
UNION SELECT d.dependent_object_id, d.dependent_component_index, object.type_id
FROM dependents_index d
@ -1937,15 +1974,28 @@ getDependentsWithinScope scope query = do
ON t.dependent_object_id = d.dependency_object_id
AND t.dependent_component_index = d.dependency_component_index
JOIN dependents_search_scope s
ON s.dependent_object_id = d.dependent_object_id
AND s.dependent_component_index = d.dependent_component_index
ON s.object_id = d.dependent_object_id
AND s.component_index = d.dependent_component_index
)
SELECT * FROM transitive_dependents
|]
execute [sql|DROP TABLE dependents_search_scope|]
execute [sql|DROP TABLE dependencies_query|]
execute [sql| DROP TABLE dependents_search_scope |]
execute [sql| DROP TABLE dependencies_query |]
pure . Map.fromList $ [(r, t) | r :. Only t <- result]
createTemporaryTableOfReferenceIds :: Sql -> Set S.Reference.Id -> Transaction ()
createTemporaryTableOfReferenceIds tableName refs = do
execute
[sql|
CREATE TEMPORARY TABLE $tableName (
object_id INTEGER NOT NULL,
component_index INTEGER NOT NULL,
PRIMARY KEY (object_id, component_index)
)
|]
for_ refs \ref ->
execute [sql| INSERT INTO $tableName VALUES (@ref, @) |]
objectIdByBase32Prefix :: ObjectType -> Text -> Transaction [ObjectId]
objectIdByBase32Prefix objType prefix =
queryListCol
@ -2086,7 +2136,7 @@ deleteNameLookupsExceptFor hashIds = do
|]
-- | Insert the given set of term names into the name lookup table
insertScopedTermNames :: BranchHashId -> [NamedRef (Referent.TextReferent, Maybe NamedRef.ConstructorType)] -> Transaction ()
insertScopedTermNames :: BranchHashId -> [NamedRef (S.TextReferent, Maybe NamedRef.ConstructorType)] -> Transaction ()
insertScopedTermNames bhId = do
traverse_ \name0 -> do
let name = NamedRef.ScopedRow (refToRow <$> name0)
@ -2106,11 +2156,11 @@ insertScopedTermNames bhId = do
VALUES (:bhId, @name, @, @, @, @, @, @, @)
|]
where
refToRow :: (Referent.TextReferent, Maybe NamedRef.ConstructorType) -> (Referent.TextReferent :. Only (Maybe NamedRef.ConstructorType))
refToRow :: (S.TextReferent, Maybe NamedRef.ConstructorType) -> (S.TextReferent :. Only (Maybe NamedRef.ConstructorType))
refToRow (ref, ct) = ref :. Only ct
-- | Insert the given set of type names into the name lookup table
insertScopedTypeNames :: BranchHashId -> [NamedRef Reference.TextReference] -> Transaction ()
insertScopedTypeNames :: BranchHashId -> [NamedRef S.TextReference] -> Transaction ()
insertScopedTypeNames bhId =
traverse_ \name0 -> do
let name = NamedRef.ScopedRow name0
@ -2129,7 +2179,7 @@ insertScopedTypeNames bhId =
|]
-- | Remove the given set of term names into the name lookup table
removeScopedTermNames :: BranchHashId -> [NamedRef Referent.TextReferent] -> Transaction ()
removeScopedTermNames :: BranchHashId -> [NamedRef S.TextReferent] -> Transaction ()
removeScopedTermNames bhId names = do
for_ names \name ->
execute
@ -2144,7 +2194,7 @@ removeScopedTermNames bhId names = do
|]
-- | Remove the given set of term names into the name lookup table
removeScopedTypeNames :: BranchHashId -> [NamedRef Reference.TextReference] -> Transaction ()
removeScopedTypeNames :: BranchHashId -> [NamedRef S.TextReference] -> Transaction ()
removeScopedTypeNames bhId names = do
for_ names \name ->
execute
@ -2203,9 +2253,9 @@ likeEscape escapeChar pat =
--
-- Get the list of a term names in the provided name lookup and relative namespace.
-- Includes dependencies, but not transitive dependencies.
termNamesWithinNamespace :: BranchHashId -> PathSegments -> Transaction [NamedRef (Referent.TextReferent, Maybe NamedRef.ConstructorType)]
termNamesWithinNamespace :: BranchHashId -> PathSegments -> Transaction [NamedRef (S.TextReferent, Maybe NamedRef.ConstructorType)]
termNamesWithinNamespace bhId namespace = do
results :: [NamedRef (Referent.TextReferent :. Only (Maybe NamedRef.ConstructorType))] <-
results :: [NamedRef (S.TextReferent :. Only (Maybe NamedRef.ConstructorType))] <-
queryListRow
[sql|
SELECT reversed_name, referent_builtin, referent_component_hash, referent_component_index, referent_constructor_index, referent_constructor_type
@ -2236,7 +2286,7 @@ termNamesWithinNamespace bhId namespace = do
--
-- Get the list of a type names in the provided name lookup and relative namespace.
-- Includes dependencies, but not transitive dependencies.
typeNamesWithinNamespace :: BranchHashId -> PathSegments -> Transaction [NamedRef Reference.TextReference]
typeNamesWithinNamespace :: BranchHashId -> PathSegments -> Transaction [NamedRef S.TextReference]
typeNamesWithinNamespace bhId namespace =
queryListRow
[sql|
@ -2265,13 +2315,13 @@ typeNamesWithinNamespace bhId namespace =
-- is only true on Share.
--
-- Get the list of term names within a given namespace which have the given suffix.
termNamesBySuffix :: BranchHashId -> PathSegments -> ReversedName -> Transaction [NamedRef (Referent.TextReferent, Maybe NamedRef.ConstructorType)]
termNamesBySuffix :: BranchHashId -> PathSegments -> ReversedName -> Transaction [NamedRef (S.TextReferent, Maybe NamedRef.ConstructorType)]
termNamesBySuffix bhId namespaceRoot suffix = do
Debug.debugM Debug.Server "termNamesBySuffix" (namespaceRoot, suffix)
let namespaceGlob = toNamespaceGlob namespaceRoot
let lastSegment = NonEmpty.head . into @(NonEmpty Text) $ suffix
let reversedNameGlob = toSuffixGlob suffix
results :: [NamedRef (Referent.TextReferent :. Only (Maybe NamedRef.ConstructorType))] <-
results :: [NamedRef (S.TextReferent :. Only (Maybe NamedRef.ConstructorType))] <-
-- Note: It may seem strange that we do a last_name_segment constraint AND a reversed_name
-- GLOB, but this helps improve query performance.
-- The SQLite query optimizer is smart enough to do a prefix-search on globs, but will
@ -2304,7 +2354,7 @@ termNamesBySuffix bhId namespaceRoot suffix = do
-- is only true on Share.
--
-- Get the list of type names within a given namespace which have the given suffix.
typeNamesBySuffix :: BranchHashId -> PathSegments -> ReversedName -> Transaction [NamedRef Reference.TextReference]
typeNamesBySuffix :: BranchHashId -> PathSegments -> ReversedName -> Transaction [NamedRef S.TextReference]
typeNamesBySuffix bhId namespaceRoot suffix = do
Debug.debugM Debug.Server "typeNamesBySuffix" (namespaceRoot, suffix)
let namespaceGlob = toNamespaceGlob namespaceRoot
@ -2343,10 +2393,10 @@ typeNamesBySuffix bhId namespaceRoot suffix = do
-- id. It's the caller's job to select the correct name lookup for your exact name.
--
-- See termRefsForExactName in U.Codebase.Sqlite.Operations
termRefsForExactName :: BranchHashId -> ReversedName -> Transaction [NamedRef (Referent.TextReferent, Maybe NamedRef.ConstructorType)]
termRefsForExactName :: BranchHashId -> ReversedName -> Transaction [NamedRef (S.TextReferent, Maybe NamedRef.ConstructorType)]
termRefsForExactName bhId reversedSegments = do
let reversedName = toReversedName reversedSegments
results :: [NamedRef (Referent.TextReferent :. Only (Maybe NamedRef.ConstructorType))] <-
results :: [NamedRef (S.TextReferent :. Only (Maybe NamedRef.ConstructorType))] <-
queryListRow
[sql|
SELECT reversed_name, referent_builtin, referent_component_hash, referent_component_index, referent_constructor_index, referent_constructor_type
@ -2366,7 +2416,7 @@ termRefsForExactName bhId reversedSegments = do
-- id. It's the caller's job to select the correct name lookup for your exact name.
--
-- See termRefsForExactName in U.Codebase.Sqlite.Operations
typeRefsForExactName :: BranchHashId -> ReversedName -> Transaction [NamedRef Reference.TextReference]
typeRefsForExactName :: BranchHashId -> ReversedName -> Transaction [NamedRef S.TextReference]
typeRefsForExactName bhId reversedSegments = do
let reversedName = toReversedName reversedSegments
queryListRow
@ -2382,7 +2432,7 @@ typeRefsForExactName bhId reversedSegments = do
--
-- Get the list of term names for a given Referent within a given namespace.
-- Considers one level of dependencies, but not transitive dependencies.
termNamesForRefWithinNamespace :: BranchHashId -> PathSegments -> Referent.TextReferent -> Maybe ReversedName -> Transaction [ReversedName]
termNamesForRefWithinNamespace :: BranchHashId -> PathSegments -> S.TextReferent -> Maybe ReversedName -> Transaction [ReversedName]
termNamesForRefWithinNamespace bhId namespaceRoot ref maySuffix = do
let namespaceGlob = toNamespaceGlob namespaceRoot
let suffixGlob = case maySuffix of
@ -2431,7 +2481,7 @@ termNamesForRefWithinNamespace bhId namespaceRoot ref maySuffix = do
--
-- Get the list of type names for a given Reference within a given namespace.
-- Considers one level of dependencies, but not transitive dependencies.
typeNamesForRefWithinNamespace :: BranchHashId -> PathSegments -> Reference.TextReference -> Maybe ReversedName -> Transaction [ReversedName]
typeNamesForRefWithinNamespace :: BranchHashId -> PathSegments -> S.TextReference -> Maybe ReversedName -> Transaction [ReversedName]
typeNamesForRefWithinNamespace bhId namespaceRoot ref maySuffix = do
let namespaceGlob = toNamespaceGlob namespaceRoot
let suffixGlob = case maySuffix of
@ -2511,7 +2561,7 @@ transitiveDependenciesSql rootBranchHashId =
-- Note: this returns the first name it finds by searching in order of:
-- Names in the current namespace, then names in the current namespace's dependencies, then
-- through the current namespace's dependencies' dependencies, etc.
recursiveTermNameSearch :: BranchHashId -> Referent.TextReferent -> Transaction (Maybe ReversedName)
recursiveTermNameSearch :: BranchHashId -> S.TextReferent -> Transaction (Maybe ReversedName)
recursiveTermNameSearch bhId ref = do
queryMaybeColCheck
[sql|
@ -2548,7 +2598,7 @@ recursiveTermNameSearch bhId ref = do
-- Note: this returns the first name it finds by searching in order of:
-- Names in the current namespace, then names in the current namespace's dependencies, then
-- through the current namespace's dependencies' dependencies, etc.
recursiveTypeNameSearch :: BranchHashId -> Reference.TextReference -> Transaction (Maybe ReversedName)
recursiveTypeNameSearch :: BranchHashId -> S.TextReference -> Transaction (Maybe ReversedName)
recursiveTypeNameSearch bhId ref = do
queryMaybeColCheck
[sql|
@ -2589,13 +2639,13 @@ recursiveTypeNameSearch bhId ref = do
-- the longest matching suffix.
--
-- Considers one level of dependencies, but not transitive dependencies.
longestMatchingTermNameForSuffixification :: BranchHashId -> PathSegments -> NamedRef Referent.TextReferent -> Transaction (Maybe (NamedRef (Referent.TextReferent, Maybe NamedRef.ConstructorType)))
longestMatchingTermNameForSuffixification :: BranchHashId -> PathSegments -> NamedRef S.TextReferent -> Transaction (Maybe (NamedRef (S.TextReferent, Maybe NamedRef.ConstructorType)))
longestMatchingTermNameForSuffixification bhId namespaceRoot (NamedRef.NamedRef {reversedSegments = revSuffix@(ReversedName (lastSegment NonEmpty.:| _)), ref}) = do
let namespaceGlob = toNamespaceGlob namespaceRoot <> ".*"
let loop :: [Text] -> MaybeT Transaction (NamedRef (Referent.TextReferent, Maybe NamedRef.ConstructorType))
let loop :: [Text] -> MaybeT Transaction (NamedRef (S.TextReferent, Maybe NamedRef.ConstructorType))
loop [] = empty
loop (suffGlob : rest) = do
result :: Maybe (NamedRef (Referent.TextReferent :. Only (Maybe NamedRef.ConstructorType))) <-
result :: Maybe (NamedRef (S.TextReferent :. Only (Maybe NamedRef.ConstructorType))) <-
lift $
queryMaybeRow
-- Note: It may seem strange that we do a last_name_segment constraint AND a reversed_name
@ -2664,13 +2714,13 @@ longestMatchingTermNameForSuffixification bhId namespaceRoot (NamedRef.NamedRef
-- the longest matching suffix.
--
-- Considers one level of dependencies, but not transitive dependencies.
longestMatchingTypeNameForSuffixification :: BranchHashId -> PathSegments -> NamedRef Reference.TextReference -> Transaction (Maybe (NamedRef Reference.TextReference))
longestMatchingTypeNameForSuffixification :: BranchHashId -> PathSegments -> NamedRef S.TextReference -> Transaction (Maybe (NamedRef S.TextReference))
longestMatchingTypeNameForSuffixification bhId namespaceRoot (NamedRef.NamedRef {reversedSegments = revSuffix@(ReversedName (lastSegment NonEmpty.:| _)), ref}) = do
let namespaceGlob = toNamespaceGlob namespaceRoot <> ".*"
let loop :: [Text] -> MaybeT Transaction (NamedRef Reference.TextReference)
let loop :: [Text] -> MaybeT Transaction (NamedRef S.TextReference)
loop [] = empty
loop (suffGlob : rest) = do
result :: Maybe (NamedRef (Reference.TextReference)) <-
result :: Maybe (NamedRef (S.TextReference)) <-
lift $
queryMaybeRow
-- Note: It may seem strange that we do a last_name_segment constraint AND a reversed_name
@ -3036,12 +3086,12 @@ saveTermComponent hh@HashHandle {toReference, toReferenceMentions} maybeEncodedT
tpRefs' = Foldable.toList $ C.Type.dependencies tp
getTermSRef :: S.Term.TermRef -> S.Reference
getTermSRef = \case
C.ReferenceBuiltin t -> C.ReferenceBuiltin (tIds Vector.! fromIntegral t)
ReferenceBuiltin t -> ReferenceBuiltin (tIds Vector.! fromIntegral t)
C.Reference.Derived Nothing i -> C.Reference.Derived oId i -- index self-references
C.Reference.Derived (Just h) i -> C.Reference.Derived (oIds Vector.! fromIntegral h) i
getTypeSRef :: S.Term.TypeRef -> S.Reference
getTypeSRef = \case
C.ReferenceBuiltin t -> C.ReferenceBuiltin (tIds Vector.! fromIntegral t)
ReferenceBuiltin t -> ReferenceBuiltin (tIds Vector.! fromIntegral t)
C.Reference.Derived h i -> C.Reference.Derived (oIds Vector.! fromIntegral h) i
getSTypeLink = getTypeSRef
getSTermLink :: S.Term.TermLink -> S.Reference
@ -3096,7 +3146,7 @@ saveDeclComponent hh@HashHandle {toReferenceDecl, toReferenceDeclMentions} maybe
dependencies :: Set S.Decl.TypeRef = C.Decl.dependencies decl
getSRef :: C.Reference.Reference' LocalTextId (Maybe LocalDefnId) -> S.Reference.Reference
getSRef = \case
C.ReferenceBuiltin t -> C.ReferenceBuiltin (tIds Vector.! fromIntegral t)
ReferenceBuiltin t -> ReferenceBuiltin (tIds Vector.! fromIntegral t)
C.Reference.Derived Nothing i -> C.Reference.Derived oId i -- index self-references
C.Reference.Derived (Just h) i -> C.Reference.Derived (oIds Vector.! fromIntegral h) i
in (Set.map getSRef dependencies, self)
@ -4144,7 +4194,7 @@ loadMostRecentBranch projectId =
-- | Searches for all names within the given name lookup which contain the provided list of segments
-- in order.
-- Search is case insensitive.
fuzzySearchTerms :: Bool -> BranchHashId -> Int -> PathSegments -> [Text] -> Transaction [(NamedRef (Referent.TextReferent, Maybe NamedRef.ConstructorType))]
fuzzySearchTerms :: Bool -> BranchHashId -> Int -> PathSegments -> [Text] -> Transaction [(NamedRef (S.TextReferent, Maybe NamedRef.ConstructorType))]
fuzzySearchTerms includeDependencies bhId limit namespace querySegments = do
-- Union in the dependencies if required.
let dependenciesSql =
@ -4179,14 +4229,14 @@ fuzzySearchTerms includeDependencies bhId limit namespace querySegments = do
where
namespaceGlob = toNamespaceGlob namespace
preparedQuery = prepareFuzzyQuery '\\' querySegments
unRow :: NamedRef (Referent.TextReferent :. Only (Maybe NamedRef.ConstructorType)) -> NamedRef (Referent.TextReferent, Maybe NamedRef.ConstructorType)
unRow :: NamedRef (S.TextReferent :. Only (Maybe NamedRef.ConstructorType)) -> NamedRef (S.TextReferent, Maybe NamedRef.ConstructorType)
unRow = fmap \(a :. Only b) -> (a, b)
-- | Searches for all names within the given name lookup which contain the provided list of segments
-- in order.
--
-- Search is case insensitive.
fuzzySearchTypes :: Bool -> BranchHashId -> Int -> PathSegments -> [Text] -> Transaction [(NamedRef Reference.TextReference)]
fuzzySearchTypes :: Bool -> BranchHashId -> Int -> PathSegments -> [Text] -> Transaction [(NamedRef S.TextReference)]
fuzzySearchTypes includeDependencies bhId limit namespace querySegments = do
-- Union in the dependencies if required.
let dependenciesSql =

View File

@ -14,12 +14,20 @@ import Unison.Sqlite (FromField, FromRow (fromRow), Only (..), RowParser, SQLDat
type Reference = Reference' TextId ObjectId
type TermReference = Reference
type TypeReference = Reference
-- | The name lookup table uses this because normalizing/denormalizing hashes to ids is slower
-- than we'd like when writing/reading the entire name lookup table.
type TextReference = Reference' Text Base32Hex
type Id = Id' ObjectId
type TermReferenceId = Id
type TypeReferenceId = Id
type LocalReferenceH = Reference' LocalTextId LocalHashId
type LocalReference = Reference' LocalTextId LocalDefnId

View File

@ -39,6 +39,7 @@ dependencies:
- unison-util-base32hex
- unison-util-cache
- unison-util-file-embed
- unison-util-nametree
- unison-util-serialization
- unison-util-term
- unliftio
@ -71,6 +72,7 @@ default-extensions:
- MultiParamTypeClasses
- NamedFieldPuns
- OverloadedLabels
- OverloadedRecordDot
- OverloadedStrings
- PatternSynonyms
- QuasiQuotes

View File

@ -91,6 +91,7 @@ library
MultiParamTypeClasses
NamedFieldPuns
OverloadedLabels
OverloadedRecordDot
OverloadedStrings
PatternSynonyms
QuasiQuotes
@ -132,6 +133,7 @@ library
, unison-util-base32hex
, unison-util-cache
, unison-util-file-embed
, unison-util-nametree
, unison-util-serialization
, unison-util-term
, unliftio

View File

@ -90,7 +90,9 @@ module Unison.Codebase.Branch
deepPaths,
deepReferents,
deepTermReferences,
deepTermReferenceIds,
deepTypeReferences,
deepTypeReferenceIds,
consBranchSnapshot,
)
where
@ -136,7 +138,7 @@ import Unison.Name qualified as Name
import Unison.NameSegment (NameSegment)
import Unison.NameSegment qualified as NameSegment
import Unison.Prelude hiding (empty)
import Unison.Reference (TermReference, TypeReference)
import Unison.Reference (TermReference, TermReferenceId, TypeReference, TypeReferenceId)
import Unison.Referent (Referent)
import Unison.Referent qualified as Referent
import Unison.Util.List qualified as List
@ -146,6 +148,7 @@ import Unison.Util.Set qualified as Set
import Unison.Util.Star2 qualified as Star2
import Witherable (FilterableWithIndex (imapMaybe))
import Prelude hiding (head, read, subtract)
import qualified Unison.Reference as Reference
instance AsEmpty (Branch m) where
_Empty = prism' (const empty) matchEmpty
@ -201,9 +204,18 @@ deepTermReferences :: Branch0 m -> Set TermReference
deepTermReferences =
Set.mapMaybe Referent.toTermReference . deepReferents
deepTermReferenceIds :: Branch0 m -> Set TermReferenceId
deepTermReferenceIds =
Set.mapMaybe Referent.toTermReferenceId . deepReferents
deepTypeReferences :: Branch0 m -> Set TypeReference
deepTypeReferences = R.dom . deepTypes
deepTypeReferenceIds :: Branch0 m -> Set TypeReferenceId
deepTypeReferenceIds =
Set.mapMaybe Reference.toId . deepTypeReferences
namespaceStats :: Branch0 m -> NamespaceStats
namespaceStats b =
NamespaceStats

View File

@ -41,7 +41,6 @@ import Unison.Cli.MonadUtils qualified as Cli
import Unison.Cli.NamesUtils qualified as Cli
import Unison.Cli.PrettyPrintUtils qualified as Cli
import Unison.Cli.ProjectUtils qualified as ProjectUtils
import Unison.Codebase (Codebase)
import Unison.Codebase qualified as Codebase
import Unison.Codebase.Branch (Branch (..), Branch0)
import Unison.Codebase.Branch qualified as Branch
@ -51,7 +50,6 @@ import Unison.Codebase.BranchUtil qualified as BranchUtil
import Unison.Codebase.Causal qualified as Causal
import Unison.Codebase.Editor.AuthorInfo (AuthorInfo (..))
import Unison.Codebase.Editor.AuthorInfo qualified as AuthorInfo
import Unison.Codebase.Editor.DisplayObject
import Unison.Codebase.Editor.HandleInput.AddRun (handleAddRun)
import Unison.Codebase.Editor.HandleInput.AuthLogin (authLogin)
import Unison.Codebase.Editor.HandleInput.Branch (handleBranch)
@ -79,6 +77,7 @@ import Unison.Codebase.Editor.HandleInput.NamespaceDiffUtils (diffHelper)
import Unison.Codebase.Editor.HandleInput.ProjectClone (handleClone)
import Unison.Codebase.Editor.HandleInput.ProjectCreate (projectCreate)
import Unison.Codebase.Editor.HandleInput.ProjectRename (handleProjectRename)
import Unison.Codebase.Editor.HandleInput.Todo (handleTodo)
import Unison.Codebase.Editor.HandleInput.ProjectSwitch (projectSwitch)
import Unison.Codebase.Editor.HandleInput.Projects (handleProjects)
import Unison.Codebase.Editor.HandleInput.Pull (handlePull, mergeBranchAndPropagateDefaultPatch)
@ -102,11 +101,8 @@ import Unison.Codebase.Editor.RemoteRepo qualified as RemoteRepo
import Unison.Codebase.Editor.Slurp qualified as Slurp
import Unison.Codebase.Editor.SlurpResult qualified as SlurpResult
import Unison.Codebase.Editor.StructuredArgument qualified as SA
import Unison.Codebase.Editor.TodoOutput qualified as TO
import Unison.Codebase.IntegrityCheck qualified as IntegrityCheck (integrityCheckFullCodebase)
import Unison.Codebase.Metadata qualified as Metadata
import Unison.Codebase.Patch (Patch (..))
import Unison.Codebase.Patch qualified as Patch
import Unison.Codebase.Path (Path, Path' (..))
import Unison.Codebase.Path qualified as HQSplit'
import Unison.Codebase.Path qualified as Path
@ -183,7 +179,6 @@ import Unison.Util.Relation qualified as R
import Unison.Util.Relation qualified as Relation
import Unison.Util.Set qualified as Set
import Unison.Util.Star2 qualified as Star2
import Unison.Util.TransitiveClosure (transitiveClosure)
import Unison.Var (Var)
import Unison.Var qualified as Var
import Unison.WatchKind qualified as WK
@ -731,10 +726,7 @@ loop e = do
currentNames <- Branch.toNames <$> Cli.getCurrentBranch0
let sr = Slurp.slurpFile uf vars Slurp.UpdateOp currentNames
previewResponse sourceName sr uf
TodoI patchPath branchPath' -> do
patch <- Cli.getPatchAt (fromMaybe Cli.defaultPatchPath patchPath)
branchPath <- Cli.resolvePath' branchPath'
doShowTodoOutput patch branchPath
TodoI -> handleTodo
TestI testInput -> Tests.handleTest testInput
ExecuteI main args -> handleRun False main args
MakeStandaloneI output main -> doCompile False output main
@ -1420,58 +1412,6 @@ doDisplay outputLoc names tm = do
else do
writeUtf8 filePath txt
-- | Show todo output if there are any conflicts or edits.
doShowTodoOutput :: Patch -> Path.Absolute -> Cli ()
doShowTodoOutput patch scopePath = do
Cli.Env {codebase} <- ask
names0 <- Branch.toNames <$> Cli.getBranch0At scopePath
todo <- Cli.runTransaction (checkTodo codebase patch names0)
if TO.noConflicts todo && TO.noEdits todo
then Cli.respond NoConflictsOrEdits
else do
Cli.setNumberedArgs $
SA.HashQualified . HQ.HashOnly . Reference.toShortHash . view _2
<$> fst (TO.todoFrontierDependents todo)
pped <- Cli.currentPrettyPrintEnvDecl
Cli.respondNumbered $ TodoOutput pped todo
checkTodo :: Codebase m Symbol Ann -> Patch -> Names -> Sqlite.Transaction (TO.TodoOutput Symbol Ann)
checkTodo codebase patch names0 = do
let -- Get the dependents of a reference which:
-- 1. Don't appear on the LHS of this patch
-- 2. Have a name in this namespace
getDependents :: Reference -> Sqlite.Transaction (Set Reference)
getDependents ref = do
dependents <- Codebase.dependents Queries.ExcludeSelf ref
pure (dependents & removeEditedThings & removeNamelessThings)
-- (r,r2) ∈ dependsOn if r depends on r2, excluding self-references (i.e. (r,r))
dependsOn <- Monoid.foldMapM (\ref -> R.fromManyDom <$> getDependents ref <*> pure ref) edited
let dirty = R.dom dependsOn
transitiveDirty <- transitiveClosure getDependents dirty
(frontierTerms, frontierTypes) <- loadDisplayInfo codebase (R.ran dependsOn)
(dirtyTerms, dirtyTypes) <- loadDisplayInfo codebase dirty
pure $
TO.TodoOutput
(Set.size transitiveDirty)
(frontierTerms, frontierTypes)
(score dirtyTerms, score dirtyTypes)
(Names.conflicts names0)
(Patch.conflicts patch)
where
-- Remove from a all references that were edited, i.e. appear on the LHS of this patch.
removeEditedThings :: Set Reference -> Set Reference
removeEditedThings =
(`Set.difference` edited)
-- Remove all references that don't have a name in the given namespace
removeNamelessThings :: Set Reference -> Set Reference
removeNamelessThings =
Set.filter (Names.contains names0)
-- todo: something more intelligent here?
score :: [(a, b)] -> [(TO.Score, a, b)]
score = map (\(x, y) -> (1, x, y))
edited :: Set Reference
edited = R.dom (Patch._termEdits patch) <> R.dom (Patch._typeEdits patch)
confirmedCommand :: Input -> Cli Bool
confirmedCommand i = do
loopState <- State.get
@ -1770,27 +1710,6 @@ docsI src = do
displayI ConsoleLocation (Names.longestTermName 10 (Set.findMin s) namesInFile)
_ -> displayI ConsoleLocation dotDoc
loadDisplayInfo ::
Codebase m Symbol Ann ->
Set Reference ->
Sqlite.Transaction
( [(Reference, Maybe (Type Symbol Ann))],
[(Reference, DisplayObject () (DD.Decl Symbol Ann))]
)
loadDisplayInfo codebase refs = do
termRefs <- filterM (Codebase.isTerm codebase) (toList refs)
typeRefs <- filterM (Codebase.isType codebase) (toList refs)
terms <- forM termRefs $ \r -> (r,) <$> Codebase.getTypeOfTerm codebase r
types <- forM typeRefs $ \r -> (r,) <$> loadTypeDisplayObject codebase r
pure (terms, types)
loadTypeDisplayObject :: Codebase m Symbol Ann -> Reference -> Sqlite.Transaction (DisplayObject () (DD.Decl Symbol Ann))
loadTypeDisplayObject codebase = \case
Reference.Builtin _ -> pure (BuiltinObject ())
Reference.DerivedId id ->
maybe (MissingObject $ Reference.idToShortHash id) UserObject
<$> Codebase.getTypeDeclaration codebase id
lexedSource :: Text -> Text -> Cli (Text, [L.Token L.Lexeme])
lexedSource name src = do
let tokens = L.lexer (Text.unpack name) (Text.unpack src)

View File

@ -0,0 +1,51 @@
-- | @todo@ input handler
module Unison.Codebase.Editor.HandleInput.Todo
( handleTodo,
)
where
import Data.Set qualified as Set
import U.Codebase.Sqlite.Operations qualified as Operations
import Unison.Cli.Monad (Cli)
import Unison.Cli.Monad qualified as Cli
import Unison.Cli.MonadUtils qualified as Cli
import Unison.Cli.PrettyPrintUtils qualified as Cli
import Unison.Codebase qualified as Codebase
import Unison.Codebase.Branch qualified as Branch
import Unison.Codebase.Branch.Names qualified as Branch
import Unison.Codebase.Editor.Output
import Unison.Codebase.Editor.TodoOutput qualified as TO
import Unison.Names qualified as Names
import Unison.Util.Defns (Defns (..))
handleTodo :: Cli ()
handleTodo = do
-- For now, we don't go through any great trouble to seek out the root of the project branch. Just assume the current
-- namespace is the root, which will be the case unless the user uses `deprecated.cd`.
currentNamespace <- Cli.getCurrentBranch0
let currentNamespaceWithoutLibdeps = Branch.deleteLibdeps currentNamespace
(hashLen, directDependencies) <-
Cli.runTransaction do
hashLen <- Codebase.hashLength
directDependencies <-
Operations.directDependenciesOfScope
Defns
{ terms = Branch.deepTermReferenceIds currentNamespaceWithoutLibdeps,
types = Branch.deepTypeReferenceIds currentNamespaceWithoutLibdeps
}
pure (hashLen, directDependencies)
let todo =
TO.TodoOutput
{ directDependenciesWithoutNames =
Defns
{ terms = Set.difference directDependencies.terms (Branch.deepTermReferences currentNamespace),
types = Set.difference directDependencies.types (Branch.deepTypeReferences currentNamespace)
},
nameConflicts = Names.conflicts (Branch.toNames currentNamespaceWithoutLibdeps)
}
pped <- Cli.currentPrettyPrintEnvDecl
Cli.respondNumbered (TodoOutput hashLen pped todo)

View File

@ -150,7 +150,7 @@ data Input
| UpdateI OptionalPatch (Set Name)
| Update2I
| PreviewUpdateI (Set Name)
| TodoI (Maybe PatchPath) Path'
| TodoI
| UndoI
| -- First `Maybe Int` is cap on number of results, if any
-- Second `Maybe Int` is cap on diff elements shown, if any

View File

@ -117,8 +117,7 @@ data NumberedOutput
| ShowDiffAfterPull Path.Path' Path.Absolute PPE.PrettyPrintEnv (BranchDiffOutput Symbol Ann)
| -- <authorIdentifier> <authorPath> <relativeBase>
ShowDiffAfterCreateAuthor NameSegment Path.Path' Path.Absolute PPE.PrettyPrintEnv (BranchDiffOutput Symbol Ann)
| -- | Invariant: there's at least one conflict or edit in the TodoOutput.
TodoOutput PPE.PrettyPrintEnvDecl (TO.TodoOutput Symbol Ann)
| TodoOutput !Int !PPE.PrettyPrintEnvDecl !(TO.TodoOutput Symbol Ann)
| -- | CantDeleteDefinitions ppe couldntDelete becauseTheseStillReferenceThem
CantDeleteDefinitions PPE.PrettyPrintEnvDecl (Map LabeledDependency (NESet LabeledDependency))
| -- | CantDeleteNamespace ppe couldntDelete becauseTheseStillReferenceThem
@ -293,8 +292,6 @@ data Output
| PreviewMergeAlreadyUpToDate
(Either Path' (ProjectAndBranch Sqlite.Project Sqlite.ProjectBranch))
(Either Path' (ProjectAndBranch Sqlite.Project Sqlite.ProjectBranch))
| -- | No conflicts or edits remain for the current patch.
NoConflictsOrEdits
| NotImplemented
| NoBranchWithHash ShortCausalHash
| ListDependencies PPE.PrettyPrintEnv (Set LabeledDependency) [HQ.HashQualified Name] [HQ.HashQualified Name] -- types, terms
@ -555,7 +552,6 @@ isFailure o = case o of
MergeAlreadyUpToDate {} -> False
MergeAlreadyUpToDate2 {} -> False
PreviewMergeAlreadyUpToDate {} -> False
NoConflictsOrEdits {} -> False
ListShallow _ es -> null es
HashAmbiguous {} -> True
ShowReflog {} -> False
@ -671,4 +667,4 @@ isNumberedFailure = \case
ShowDiffAfterUndo {} -> False
ShowDiffNamespace _ _ _ bd -> BD.isEmpty bd
ListNamespaceDependencies {} -> False
TodoOutput _ todo -> TO.todoScore todo > 0 || not (TO.noConflicts todo)
TodoOutput {} -> False

View File

@ -1,70 +1,19 @@
{-# LANGUAGE RecordWildCards #-}
module Unison.Codebase.Editor.TodoOutput
( TodoOutput (..),
noConflicts,
)
where
module Unison.Codebase.Editor.TodoOutput where
import Data.Set qualified as Set
import Unison.Codebase.Editor.DisplayObject (DisplayObject (UserObject))
import Unison.Codebase.Patch (Patch)
import Unison.Codebase.Patch qualified as Patch
import Unison.DataDeclaration (Decl)
import Unison.DataDeclaration qualified as DD
import Unison.LabeledDependency (LabeledDependency)
import Unison.LabeledDependency qualified as LD
import Unison.Names (Names)
import Unison.Names qualified as Names
import Unison.Prelude
import Unison.Reference (Reference)
import Unison.Type (Type)
import Unison.Type qualified as Type
import Unison.Util.Relation qualified as R
type Score = Int
import Unison.Reference (TermReference, TypeReference)
import Unison.Util.Defns (DefnsF)
data TodoOutput v a = TodoOutput
{ todoScore :: Score,
todoFrontier ::
( [(Reference, Maybe (Type v a))],
[(Reference, DisplayObject () (Decl v a))]
),
todoFrontierDependents ::
( [(Score, Reference, Maybe (Type v a))],
[(Score, Reference, DisplayObject () (Decl v a))]
),
nameConflicts :: Names,
editConflicts :: Patch
{ directDependenciesWithoutNames :: DefnsF Set TermReference TypeReference,
nameConflicts :: Names
}
labeledDependencies :: (Ord v) => TodoOutput v a -> Set LabeledDependency
labeledDependencies TodoOutput {..} =
Set.fromList
( -- term refs
[LD.termRef r | (r, _) <- fst todoFrontier]
<> [LD.termRef r | (_, r, _) <- fst todoFrontierDependents]
<> [LD.typeRef r | (r, _) <- snd todoFrontier]
<> [LD.typeRef r | (_, r, _) <- snd todoFrontierDependents]
<>
-- types of term refs
[ LD.typeRef r | (_, Just t) <- fst todoFrontier, r <- toList (Type.dependencies t)
]
<> [ LD.typeRef r | (_, _, Just t) <- fst todoFrontierDependents, r <- toList (Type.dependencies t)
]
<>
-- and decls of type refs
[ labeledDep | (declRef, UserObject d) <- snd todoFrontier, labeledDep <- toList (DD.labeledDeclDependenciesIncludingSelf declRef d)
]
<> [ labeledDep | (_, declRef, UserObject d) <- snd todoFrontierDependents, labeledDep <- toList (DD.labeledDeclDependenciesIncludingSelf declRef d)
]
)
<>
-- name conflicts
Set.map LD.referent (R.ran (Names.terms nameConflicts))
<> Set.map LD.typeRef (R.ran (Names.types nameConflicts))
<> Patch.labeledDependencies editConflicts
noConflicts :: TodoOutput v a -> Bool
noConflicts todo =
nameConflicts todo == mempty && editConflicts todo == Patch.empty
noEdits :: TodoOutput v a -> Bool
noEdits todo =
todoScore todo == 0
nameConflicts todo == mempty

View File

@ -757,30 +757,15 @@ todo =
"todo"
[]
I.Visible
[("patch", Optional, patchArg), ("namespace", Optional, namespaceArg)]
( P.wrapColumn2
[ ( makeExample' todo,
"lists the refactor work remaining in the default patch for the current"
<> " namespace."
),
( makeExample todo ["<patch>"],
"lists the refactor work remaining in the given patch in the current "
<> "namespace."
),
( makeExample todo ["<patch>", "[path]"],
"lists the refactor work remaining in the given patch in given namespace."
)
]
[]
( P.wrap $
makeExample' todo
<> "lists the current namespace's outstanding issues, including conflicted names, dependencies with missing"
<> "names, and merge precondition violations."
)
\case
patchStr : ws -> first warn $ do
patch <- handleSplit'Arg patchStr
branch <- case ws of
[] -> pure Path.relativeEmpty'
[pathStr] -> handlePath'Arg pathStr
_ -> Left "`todo` just takes a patch and one optional namespace"
Right $ Input.TodoI (Just patch) branch
[] -> Right $ Input.TodoI Nothing Path.relativeEmpty'
[] -> Right Input.TodoI
_ -> Left (I.help todo)
load :: InputPattern
load =

View File

@ -65,7 +65,6 @@ import Unison.Codebase.Editor.StructuredArgument (StructuredArgument)
import Unison.Codebase.Editor.StructuredArgument qualified as SA
import Unison.Codebase.Editor.TodoOutput qualified as TO
import Unison.Codebase.IntegrityCheck (IntegrityResult (..), prettyPrintIntegrityErrors)
import Unison.Codebase.Patch (Patch (..))
import Unison.Codebase.Patch qualified as Patch
import Unison.Codebase.Path qualified as Path
import Unison.Codebase.PushBehavior qualified as PushBehavior
@ -73,8 +72,6 @@ import Unison.Codebase.Runtime qualified as Runtime
import Unison.Codebase.ShortCausalHash (ShortCausalHash)
import Unison.Codebase.ShortCausalHash qualified as SCH
import Unison.Codebase.SqliteCodebase.Conversions qualified as Cv
import Unison.Codebase.TermEdit qualified as TermEdit
import Unison.Codebase.TypeEdit qualified as TypeEdit
import Unison.CommandLine (bigproblem, note, tip)
import Unison.CommandLine.FZFResolvers qualified as FZFResolvers
import Unison.CommandLine.InputPattern (InputPattern)
@ -137,7 +134,6 @@ import Unison.Syntax.NamePrinter
prettyReference,
prettyReferent,
prettyShortHash,
styleHashQualified,
)
import Unison.Syntax.NameSegment qualified as NameSegment
import Unison.Syntax.TermPrinter qualified as TermPrinter
@ -146,6 +142,7 @@ import Unison.Term (Term)
import Unison.Term qualified as Term
import Unison.Type (Type)
import Unison.UnisonFile qualified as UF
import Unison.Util.Defns (Defns (..))
import Unison.Util.List qualified as List
import Unison.Util.Monoid (intercalateMap)
import Unison.Util.Monoid qualified as Monoid
@ -310,7 +307,7 @@ notifyNumbered = \case
]
)
(showDiffNamespace ShowNumbers ppe (absPathToBranchId bAbs) (absPathToBranchId bAbs) diff)
TodoOutput names todo -> todoOutput names todo
TodoOutput hashLen names todo -> todoOutput hashLen names todo
CantDeleteDefinitions ppeDecl endangerments ->
( P.warnCallout $
P.lines
@ -1483,8 +1480,6 @@ notifyUser dir = \case
<> P.group (prettyNamespaceKey src <> ".")
DumpNumberedArgs schLength args ->
pure . P.numberedList $ fmap (P.text . IP.formatStructuredArgument (pure schLength)) args
NoConflictsOrEdits ->
pure (P.okCallout "No conflicts or edits in progress.")
HelpMessage pat -> pure $ IP.showPatternHelp pat
NoOp -> pure $ P.string "I didn't make any changes."
DumpBitBooster head map ->
@ -2616,8 +2611,7 @@ renderNameConflicts ppe conflictedNames = do
[ prettyConflictedTypes,
prettyConflictedTerms,
tip $
"This occurs when merging branches that both independently introduce the same name."
<> "Use "
"Use "
<> makeExample'
( if (not . null) conflictedTypeNames
then IP.renameType
@ -2635,7 +2629,7 @@ renderNameConflicts ppe conflictedNames = do
showConflictedNames :: Pretty -> Map Name [HQ.HashQualified Name] -> Numbered Pretty
showConflictedNames thingKind conflictedNames =
P.lines <$> do
for (Map.toList conflictedNames) $ \(name, hashes) -> do
for (Map.toList conflictedNames) \(name, hashes) -> do
prettyConflicts <- for hashes \hash -> do
n <- addNumberedArg $ SA.HashQualified hash
pure $ formatNum n <> (P.blue . P.syntaxToColor . prettyHashQualified $ hash)
@ -2646,75 +2640,18 @@ renderNameConflicts ppe conflictedNames = do
<> P.green (prettyName name)
<> " has conflicting definitions:"
)
`P.hang` P.lines prettyConflicts
renderEditConflicts ::
PPE.PrettyPrintEnv -> Patch -> Numbered Pretty
renderEditConflicts ppe Patch {..} = do
formattedConflicts <- for editConflicts formatConflict
pure . Monoid.unlessM (null editConflicts) . P.callout "" . P.sep "\n\n" $
[ P.wrap $
"These"
<> P.bold "definitions were edited differently"
<> "in namespaces that have been merged into this one."
<> "You'll have to tell me what to use as the new definition:",
P.indentN 2 (P.lines formattedConflicts)
-- , tip $ "Use " <> makeExample IP.resolve [name (head editConflicts), " <replacement>"] <> " to pick a replacement." -- todo: eventually something with `edit`
]
where
-- todo: could possibly simplify all of this, but today is a copy/paste day.
editConflicts :: [Either (Reference, Set TypeEdit.TypeEdit) (Reference, Set TermEdit.TermEdit)]
editConflicts =
(fmap Left . Map.toList . R.toMultimap . R.filterManyDom $ _typeEdits)
<> (fmap Right . Map.toList . R.toMultimap . R.filterManyDom $ _termEdits)
numberedHQName :: HQ.HashQualified Name -> Numbered Pretty
numberedHQName hqName = do
n <- addNumberedArg $ SA.HashQualified hqName
pure $ formatNum n <> styleHashQualified P.bold hqName
formatTypeEdits ::
(Reference, Set TypeEdit.TypeEdit) ->
Numbered Pretty
formatTypeEdits (r, toList -> es) = do
replacedType <- numberedHQName (PPE.typeName ppe r)
replacements <- for [PPE.typeName ppe r | TypeEdit.Replace r <- es] numberedHQName
pure . P.wrap $
"The type"
<> replacedType
<> "was"
<> ( if TypeEdit.Deprecate `elem` es
then "deprecated and also replaced with"
else "replaced with"
)
`P.hang` P.lines replacements
formatTermEdits ::
(Reference.TermReference, Set TermEdit.TermEdit) ->
Numbered Pretty
formatTermEdits (r, toList -> es) = do
replacedTerm <- numberedHQName (PPE.termName ppe (Referent.Ref r))
replacements <- for [PPE.termName ppe (Referent.Ref r) | TermEdit.Replace r _ <- es] numberedHQName
pure . P.wrap $
"The term"
<> replacedTerm
<> "was"
<> ( if TermEdit.Deprecate `elem` es
then "deprecated and also replaced with"
else "replaced with"
)
`P.hang` P.lines replacements
formatConflict ::
Either
(Reference, Set TypeEdit.TypeEdit)
(Reference.TermReference, Set TermEdit.TermEdit) ->
Numbered Pretty
formatConflict = either formatTypeEdits formatTermEdits
<> P.newline
<> P.newline
<> P.indentN 2 (P.lines prettyConflicts)
type Numbered = State.State (Int, Seq.Seq StructuredArgument)
addNumberedArg :: StructuredArgument -> Numbered Int
addNumberedArg s = do
(n, args) <- State.get
State.put (n + 1, args Seq.|> s)
pure $ (n + 1)
let !n' = n + 1
State.put (n', args Seq.|> s)
pure n'
formatNum :: Int -> Pretty
formatNum n = P.string (show n <> ". ")
@ -2724,90 +2661,49 @@ runNumbered m =
let (a, (_, args)) = State.runState m (0, mempty)
in (a, Foldable.toList args)
todoOutput :: (Var v) => PPED.PrettyPrintEnvDecl -> TO.TodoOutput v a -> (Pretty, NumberedArgs)
todoOutput ppe todo = runNumbered do
conflicts <- todoConflicts
edits <- todoEdits
pure (conflicts <> edits)
where
ppeu = PPED.unsuffixifiedPPE ppe
ppes = PPED.suffixifiedPPE ppe
(frontierTerms, frontierTypes) = TO.todoFrontier todo
(dirtyTerms, dirtyTypes) = TO.todoFrontierDependents todo
corruptTerms =
[(PPE.termName ppeu (Referent.Ref r), r) | (r, Nothing) <- frontierTerms]
corruptTypes =
[(PPE.typeName ppeu r, r) | (r, MissingObject _) <- frontierTypes]
goodTerms ts =
[(Referent.Ref r, PPE.termName ppeu (Referent.Ref r), typ) | (r, Just typ) <- ts]
todoConflicts :: Numbered Pretty
todoConflicts = do
todoOutput :: (Var v) => Int -> PPED.PrettyPrintEnvDecl -> TO.TodoOutput v a -> (Pretty, NumberedArgs)
todoOutput hashLen ppe todo =
runNumbered do
prettyConflicts <-
if TO.noConflicts todo
then pure mempty
else do
editConflicts <- renderEditConflicts ppeu (TO.editConflicts todo)
nameConflicts <- renderNameConflicts ppeu conflictedNames
pure $ P.lines . P.nonEmpty $ [editConflicts, nameConflicts]
where
-- If a conflict is both an edit and a name conflict, we show it in the edit
-- conflicts section
conflictedNames :: Names
conflictedNames = removeEditConflicts (TO.editConflicts todo) (TO.nameConflicts todo)
-- e.g. `foo#a` has been independently updated to `foo#b` and `foo#c`.
-- This means there will be a name conflict:
-- foo -> #b
-- foo -> #c
-- as well as an edit conflict:
-- #a -> #b
-- #a -> #c
-- We want to hide/ignore the name conflicts that are also targets of an
-- edit conflict, so that the edit conflict will be dealt with first.
-- For example, if hash `h` has multiple edit targets { #x, #y, #z, ...},
-- we'll temporarily remove name conflicts pointing to { #x, #y, #z, ...}.
removeEditConflicts :: Patch -> Names -> Names
removeEditConflicts Patch {..} Names {..} = Names terms' types'
where
terms' = R.filterRan (`Set.notMember` conflictedTermEditTargets) terms
types' = R.filterRan (`Set.notMember` conflictedTypeEditTargets) types
conflictedTypeEditTargets :: Set Reference
conflictedTypeEditTargets =
Set.fromList $ toList (R.ran typeEditConflicts) >>= TypeEdit.references
conflictedTermEditTargets :: Set Referent.Referent
conflictedTermEditTargets =
Set.fromList . fmap Referent.Ref $
toList (R.ran termEditConflicts) >>= TermEdit.references
typeEditConflicts = R.filterDom (`R.manyDom` _typeEdits) _typeEdits
termEditConflicts = R.filterDom (`R.manyDom` _termEdits) _termEdits
else renderNameConflicts ppeu todo.nameConflicts
todoEdits :: Numbered Pretty
todoEdits = do
numberedTypes <- for (unscore <$> dirtyTypes) \(ref, displayObj) -> do
n <- addNumberedArg . SA.HashQualified $ PPE.typeName ppeu ref
pure $ formatNum n <> prettyDeclPair ppeu (ref, displayObj)
let filteredTerms = goodTerms (unscore <$> dirtyTerms)
termNumbers <- for filteredTerms \(ref, _, _) -> do
n <- addNumberedArg . SA.HashQualified $ PPE.termName ppeu ref
pure $ formatNum n
let formattedTerms = TypePrinter.prettySignaturesCT ppes filteredTerms
numberedTerms = zipWith (<>) termNumbers formattedTerms
pure $
Monoid.unlessM (TO.noEdits todo) . P.callout "🚧" . P.sep "\n\n" . P.nonEmpty $
[ P.wrap
( "The namespace has"
<> fromString (show (TO.todoScore todo))
<> "transitive dependent(s) left to upgrade."
<> "Your edit frontier is the dependents of these definitions:"
),
P.indentN 2 . P.lines $
( (prettyDeclPair ppeu <$> toList frontierTypes)
++ TypePrinter.prettySignaturesCT ppes (goodTerms frontierTerms)
),
P.wrap "I recommend working on them in the following order:",
P.lines $ numberedTypes ++ numberedTerms,
formatMissingStuff corruptTerms corruptTypes
]
unscore :: (a, b, c) -> (b, c)
unscore (_score, b, c) = (b, c)
prettyDirectTermDependenciesWithoutNames <- do
if Set.null todo.directDependenciesWithoutNames.terms
then pure mempty
else do
terms <-
for (Set.toList todo.directDependenciesWithoutNames.terms) \term -> do
n <- addNumberedArg (SA.HashQualified (HQ.HashOnly (Reference.toShortHash term)))
pure (formatNum n <> P.syntaxToColor (prettyReference hashLen term))
pure $
P.wrap "These terms do not have any names in the current namespace:"
<> P.newline
<> P.newline
<> P.indentN 2 (P.lines terms)
prettyDirectTypeDependenciesWithoutNames <- do
if Set.null todo.directDependenciesWithoutNames.types
then pure mempty
else do
types <-
for (Set.toList todo.directDependenciesWithoutNames.types) \typ -> do
n <- addNumberedArg (SA.HashQualified (HQ.HashOnly (Reference.toShortHash typ)))
pure (formatNum n <> P.syntaxToColor (prettyReference hashLen typ))
pure $
P.wrap "These types do not have any names in the current namespace:"
<> P.newline
<> P.newline
<> P.indentN 2 (P.lines types)
(pure . P.sep "\n\n" . P.nonEmpty)
[ prettyConflicts,
prettyDirectTermDependenciesWithoutNames,
prettyDirectTypeDependenciesWithoutNames
]
where
ppeu = PPED.unsuffixifiedPPE ppe
listOfDefinitions ::
(Var v) => Input.FindScope -> PPE.PrettyPrintEnv -> E.ListDetailed -> [SR'.SearchResult' v a] -> IO Pretty

View File

@ -87,6 +87,7 @@ library
Unison.Codebase.Editor.HandleInput.ShowDefinition
Unison.Codebase.Editor.HandleInput.TermResolution
Unison.Codebase.Editor.HandleInput.Tests
Unison.Codebase.Editor.HandleInput.Todo
Unison.Codebase.Editor.HandleInput.UI
Unison.Codebase.Editor.HandleInput.Update
Unison.Codebase.Editor.HandleInput.Update2

View File

@ -179,14 +179,10 @@ Merge back into the ancestor.
.s> todo
No conflicts or edits in progress.
.m> todo
No conflicts or edits in progress.
```

View File

@ -106,9 +106,7 @@ Let's do the update now, and verify that the definitions all look good and there
.a2> todo
No conflicts or edits in progress.
```
## Record updates
@ -213,8 +211,6 @@ And checking that after updating this record, there's nothing `todo`:
.a4> todo
No conflicts or edits in progress.
```

View File

@ -1,139 +1,27 @@
# Test the `todo` command
# Conflicted names
## Simple type-changing update.
The todo command shows conflicted names (not demonstrated here yet because it is not easy to create them for tests, yet).
# Direct dependencies without names
The `todo` command shows hashes of direct dependencies of local (outside `lib`) definitions that don't have names in
the current namespace.
```ucm:hide
.simple> builtins.merge
```
```unison:hide
x = 1
useX = x + 10
type MyType = MyType Nat
useMyType = match MyType 1 with
MyType a -> a + 10
```
```ucm:hide
.simple> add
```
Perform a type-changing update so dependents are added to our update frontier.
```unison:hide
x = -1
type MyType = MyType Text
```
```ucm:error
.simple> update.old
.simple> todo
```
## A merge with conflicting updates.
```ucm:hide
.mergeA> builtins.merge
```
```unison:hide
x = 1
type MyType = MyType
```
Set up two branches with the same starting point.
```ucm:hide
.mergeA> add
.> fork .mergeA .mergeB
```
Update `x` to a different term in each branch.
```unison:hide
x = 2
type MyType = MyType Nat
```
```ucm:hide
.mergeA> update.old
```
```unison:hide
x = 3
type MyType = MyType Int
```
```ucm:hide
.mergeB> update.old
```
```ucm:error
.mergeA> merge.old .mergeB
.mergeA> todo
```
## A named value that appears on the LHS of a patch isn't shown
```ucm:hide
.lhs> builtins.merge
project/main> builtins.mergeio lib.builtins
```
```unison
foo = 801
foo.bar = 15
baz = foo.bar + foo.bar
```
```ucm
.lhs> add
project/main> add
project/main> delete.namespace.force foo
project/main> todo
```
```unison
foo = 802
```
```ucm
.lhs> update.old
```
```unison
oldfoo = 801
```
```ucm
.lhs> add
.lhs> todo
```
## A type-changing update to one element of a cycle, which doesn't propagate to the other
```ucm:hide
.cycle2> builtins.merge
```
```unison
even = cases
0 -> true
n -> odd (drop 1 n)
odd = cases
0 -> false
n -> even (drop 1 n)
```
```ucm
.cycle2> add
```
```unison
even = 17
```
```ucm
.cycle2> update.old
```
```ucm:error
.cycle2> todo
project/main> delete.project project
```

View File

@ -1,137 +1,15 @@
# Test the `todo` command
# Conflicted names
## Simple type-changing update.
The todo command shows conflicted names (not demonstrated here yet because it is not easy to create them for tests, yet).
# Direct dependencies without names
The `todo` command shows hashes of direct dependencies of local (outside `lib`) definitions that don't have names in
the current namespace.
```unison
x = 1
useX = x + 10
type MyType = MyType Nat
useMyType = match MyType 1 with
MyType a -> a + 10
```
Perform a type-changing update so dependents are added to our update frontier.
```unison
x = -1
type MyType = MyType Text
```
```ucm
.simple> update.old
⍟ I've updated these names to your new definition:
type MyType
x : Int
.simple> todo
🚧
The namespace has 2 transitive dependent(s) left to upgrade.
Your edit frontier is the dependents of these definitions:
type #vijug0om28
#gjmq673r1v : Nat
I recommend working on them in the following order:
1. useMyType : Nat
2. useX : Nat
```
## A merge with conflicting updates.
```unison
x = 1
type MyType = MyType
```
Set up two branches with the same starting point.
Update `x` to a different term in each branch.
```unison
x = 2
type MyType = MyType Nat
```
```unison
x = 3
type MyType = MyType Int
```
```ucm
.mergeA> merge.old .mergeB
Here's what's changed in the current namespace after the
merge:
New name conflicts:
1. type MyType#ig1g2ka7lv
2. ┌ type MyType#8c6f40i3tj
3. └ type MyType#ig1g2ka7lv
4. MyType.MyType#ig1g2ka7lv#0 : Nat -> MyType#ig1g2ka7lv
5. ┌ MyType.MyType#8c6f40i3tj#0 : Int -> MyType#8c6f40i3tj
6. └ MyType.MyType#ig1g2ka7lv#0 : Nat -> MyType#ig1g2ka7lv
7. x#dcgdua2lj6 : Nat
8. ┌ x#dcgdua2lj6 : Nat
9. └ x#f3lgjvjqoo : Nat
Updates:
10. patch patch (added 2 updates)
Tip: You can use `todo` to see if this generated any work to
do in this namespace and `test` to run the tests. Or you
can use `undo` or `reflog` to undo the results of this
merge.
Applying changes from patch...
I tried to auto-apply the patch, but couldn't because it
contained contradictory entries.
.mergeA> todo
These definitions were edited differently in namespaces that
have been merged into this one. You'll have to tell me what to
use as the new definition:
The type 1. #8h7qq3ougl was replaced with
2. MyType#8c6f40i3tj
3. MyType#ig1g2ka7lv
The term 4. #gjmq673r1v was replaced with
5. x#dcgdua2lj6
6. x#f3lgjvjqoo
The term MyType.MyType has conflicting definitions:
7. MyType.MyType#8c6f40i3tj#0
8. MyType.MyType#ig1g2ka7lv#0
Tip: This occurs when merging branches that both independently
introduce the same name. Use `move.term` or `delete.term`
to resolve the conflicts.
```
## A named value that appears on the LHS of a patch isn't shown
```unison
foo = 801
foo.bar = 15
baz = foo.bar + foo.bar
```
```ucm
@ -144,149 +22,34 @@ foo = 801
⍟ These new definitions are ok to `add`:
foo : Nat
baz : Nat
foo.bar : Nat
```
```ucm
.lhs> add
project/main> add
⍟ I've added these definitions:
foo : Nat
```
```unison
foo = 802
```
```ucm
Loading changes detected in scratch.u.
I found and typechecked these definitions in scratch.u. If you
do an `add` or `update`, here's how your codebase would
change:
⍟ These names already exist. You can `update` them to your
new definition:
foo : Nat
```
```ucm
.lhs> update.old
⍟ I've updated these names to your new definition:
foo : Nat
```
```unison
oldfoo = 801
```
```ucm
Loading changes detected in scratch.u.
I found and typechecked these definitions in scratch.u. If you
do an `add` or `update`, here's how your codebase would
change:
⍟ These new definitions are ok to `add`:
oldfoo : Nat
```
```ucm
.lhs> add
⍟ I've added these definitions:
oldfoo : Nat
.lhs> todo
No conflicts or edits in progress.
```
## A type-changing update to one element of a cycle, which doesn't propagate to the other
```unison
even = cases
0 -> true
n -> odd (drop 1 n)
odd = cases
0 -> false
n -> even (drop 1 n)
```
```ucm
Loading changes detected in scratch.u.
I found and typechecked these definitions in scratch.u. If you
do an `add` or `update`, here's how your codebase would
change:
⍟ These new definitions are ok to `add`:
even : Nat -> Boolean
odd : Nat -> Boolean
```
```ucm
.cycle2> add
⍟ I've added these definitions:
even : Nat -> Boolean
odd : Nat -> Boolean
```
```unison
even = 17
```
```ucm
Loading changes detected in scratch.u.
I found and typechecked these definitions in scratch.u. If you
do an `add` or `update`, here's how your codebase would
change:
⍟ These names already exist. You can `update` them to your
new definition:
even : Nat
```
```ucm
.cycle2> update.old
⍟ I've updated these names to your new definition:
even : Nat
```
```ucm
.cycle2> todo
🚧
The namespace has 1 transitive dependent(s) left to upgrade.
Your edit frontier is the dependents of these definitions:
#kkohl7ba1e : Nat -> Boolean
I recommend working on them in the following order:
1. odd : Nat -> Boolean
baz : Nat
foo.bar : Nat
project/main> delete.namespace.force foo
Done.
⚠️
Of the things I deleted, the following are still used in the
following definitions. They now contain un-named references.
Dependency Referenced In
bar 1. baz
project/main> todo
These terms do not have any names in the current namespace:
1. #1jujb8oelv
```