diff --git a/package.yaml b/package.yaml index 3d5390de..a7506ea1 100644 --- a/package.yaml +++ b/package.yaml @@ -115,6 +115,7 @@ dependencies: - share-auth - unison-hashing-v2 - unison-codebase-sqlite-hashing-v2 +- unison-merge - unison-parser-typechecker - unison-prelude - unison-pretty-printer diff --git a/share-api.cabal b/share-api.cabal index 8f94a7fd..21f8243e 100644 --- a/share-api.cabal +++ b/share-api.cabal @@ -46,6 +46,7 @@ library Share.IDs Share.Metrics Share.Monitoring + Share.Names.Postgres Share.NamespaceDiffs Share.Postgres Share.Postgres.Admin @@ -85,6 +86,7 @@ library Share.Postgres.Users.Queries Share.Prelude Share.Prelude.Orphans + Share.PrettyPrintEnvDecl.Postgres Share.Project Share.Redis Share.Release @@ -170,7 +172,6 @@ library Share.Web.UCM.SyncV2.Impl Share.Web.UCM.SyncV2.Queries Share.Web.UCM.SyncV2.Types - Unison.PrettyPrintEnvDecl.Postgres Unison.Server.NameSearch.Postgres Unison.Server.Share.Definitions Unison.Server.Share.DefinitionSummary @@ -295,6 +296,7 @@ library , unison-core1 , unison-hash , unison-hashing-v2 + , unison-merge , unison-parser-typechecker , unison-prelude , unison-pretty-printer @@ -445,6 +447,7 @@ executable share-api , unison-core1 , unison-hash , unison-hashing-v2 + , unison-merge , unison-parser-typechecker , unison-prelude , unison-pretty-printer diff --git a/sql/2025-02-12_namespace_diff_key.sql b/sql/2025-02-12_namespace_diff_key.sql new file mode 100644 index 00000000..055a7f2b --- /dev/null +++ b/sql/2025-02-12_namespace_diff_key.sql @@ -0,0 +1,17 @@ +-- Recreate namespace diffs table, since we're changing a foreign key reference +-- Could truncate and alter columns instead, but it's more work + +DROP TABLE namespace_diffs; + +CREATE TABLE namespace_diffs ( + left_causal_id INTEGER NOT NULL REFERENCES causals(id) ON DELETE CASCADE, + right_causal_id INTEGER NOT NULL REFERENCES causals(id) ON DELETE CASCADE, + + -- Since different codebases can have different variable names and such we also need to sandbox diffs by codebase owner + left_codebase_owner_user_id UUID NOT NULL REFERENCES users(id) ON DELETE CASCADE, + right_codebase_owner_user_id UUID NOT NULL REFERENCES users(id) ON DELETE CASCADE, + + diff JSONB NOT NULL, + + PRIMARY KEY (left_causal_id, right_causal_id, left_codebase_owner_user_id, right_codebase_owner_user_id) +); diff --git a/src/Share/BackgroundJobs.hs b/src/Share/BackgroundJobs.hs index dec54bb0..8c465a5d 100644 --- a/src/Share/BackgroundJobs.hs +++ b/src/Share/BackgroundJobs.hs @@ -1,6 +1,7 @@ module Share.BackgroundJobs (startWorkers) where import Ki.Unlifted qualified as Ki +import Share.BackgroundJobs.Diffs.ContributionDiffs qualified as ContributionDiffs import Share.BackgroundJobs.Monad (Background) import Share.BackgroundJobs.Search.DefinitionSync qualified as DefnSearch @@ -8,7 +9,7 @@ import Share.BackgroundJobs.Search.DefinitionSync qualified as DefnSearch startWorkers :: Ki.Scope -> Background () startWorkers scope = do DefnSearch.worker scope + ContributionDiffs.worker scope -- Temporary disable background diff jobs until the new diffing logic is done. --- ContributionDiffs.worker scope -- SerializedEntitiesMigration.worker scope diff --git a/src/Share/BackgroundJobs/Diffs/ContributionDiffs.hs b/src/Share/BackgroundJobs/Diffs/ContributionDiffs.hs index 9e41d8ce..261d2a94 100644 --- a/src/Share/BackgroundJobs/Diffs/ContributionDiffs.hs +++ b/src/Share/BackgroundJobs/Diffs/ContributionDiffs.hs @@ -53,17 +53,18 @@ processDiffs authZReceipt = Metrics.recordContributionDiffDuration . runExceptT diffContribution :: AuthZ.AuthZReceipt -> ContributionId -> ExceptT NamespaceDiffError Background () diffContribution authZReceipt contributionId = do - ( project, + ( bestCommonAncestorCausalId, + project, newBranch@Branch {causal = newBranchCausalId}, oldBranch@Branch {causal = oldBranchCausalId} ) <- ExceptT $ PG.tryRunTransaction $ do - Contribution {sourceBranchId = newBranchId, targetBranchId = oldBranchId, projectId} <- ContributionsQ.contributionById contributionId `whenNothingM` throwError (MissingEntityError $ EntityMissing (ErrorID "contribution:missing") "Contribution not found") + Contribution {bestCommonAncestorCausalId, sourceBranchId = newBranchId, targetBranchId = oldBranchId, projectId} <- ContributionsQ.contributionById contributionId `whenNothingM` throwError (MissingEntityError $ EntityMissing (ErrorID "contribution:missing") "Contribution not found") project <- Q.projectById projectId `whenNothingM` throwError (MissingEntityError $ EntityMissing (ErrorID "project:missing") "Project not found") newBranch <- Q.branchById newBranchId `whenNothingM` throwError (MissingEntityError $ EntityMissing (ErrorID "branch:missing") "Source branch not found") oldBranch <- Q.branchById oldBranchId `whenNothingM` throwError (MissingEntityError $ EntityMissing (ErrorID "branch:missing") "Target branch not found") - pure (project, newBranch, oldBranch) + pure (bestCommonAncestorCausalId, project, newBranch, oldBranch) let oldCodebase = Codebase.codebaseForProjectBranch authZReceipt project oldBranch let newCodebase = Codebase.codebaseForProjectBranch authZReceipt project newBranch -- This method saves the diff so it'll be there when we need it, so we don't need to do anything with it. - _ <- Diffs.diffCausals authZReceipt (oldCodebase, oldBranchCausalId) (newCodebase, newBranchCausalId) + _ <- Diffs.diffCausals authZReceipt (oldCodebase, oldBranchCausalId) (newCodebase, newBranchCausalId) bestCommonAncestorCausalId pure () diff --git a/src/Share/BackgroundJobs/Search/DefinitionSync.hs b/src/Share/BackgroundJobs/Search/DefinitionSync.hs index fab498ae..fd46f9b6 100644 --- a/src/Share/BackgroundJobs/Search/DefinitionSync.hs +++ b/src/Share/BackgroundJobs/Search/DefinitionSync.hs @@ -36,6 +36,7 @@ import Share.Postgres.Queries qualified as PG import Share.Postgres.Releases.Queries qualified as RQ import Share.Postgres.Search.DefinitionSearch.Queries qualified as DDQ import Share.Prelude +import Share.PrettyPrintEnvDecl.Postgres qualified as PPEPostgres import Share.Project (Project (..)) import Share.Release (Release (..)) import Share.Utils.Logging qualified as Logging @@ -52,7 +53,6 @@ import Unison.Name qualified as Name import Unison.NameSegment (libSegment) import Unison.PrettyPrintEnv qualified as PPE import Unison.PrettyPrintEnvDecl qualified as PPED -import Unison.PrettyPrintEnvDecl.Postgres qualified as PPEPostgres import Unison.Reference (TypeReference) import Unison.Reference qualified as Reference import Unison.Server.Share.DefinitionSummary qualified as Summary @@ -124,10 +124,10 @@ syncRelease authZReceipt releaseId = fmap (fromMaybe []) . runMaybeT $ do let codebaseLoc = Codebase.codebaseLocationForProjectRelease ownerUserId let codebase = Codebase.codebaseEnv authZReceipt codebaseLoc Codebase.codebaseMToTransaction codebase $ do - termsCursor <- lift $ NLOps.termsWithinNamespace nlReceipt bhId + termsCursor <- lift $ NLOps.projectTermsWithinRoot nlReceipt bhId termErrs <- syncTerms namesPerspective bhId projectId releaseId termsCursor - typesCursor <- lift $ NLOps.typesWithinNamespace nlReceipt bhId + typesCursor <- lift $ NLOps.projectTypesWithinRoot nlReceipt bhId typeErrs <- syncTypes namesPerspective projectId releaseId typesCursor pure (termErrs <> typeErrs) diff --git a/src/Share/Codebase.hs b/src/Share/Codebase.hs index 41af11dd..ad33ab6f 100644 --- a/src/Share/Codebase.hs +++ b/src/Share/Codebase.hs @@ -31,6 +31,7 @@ module Share.Codebase expectTypeOfTerms, expectTypeOfReferent, expectTypeOfReferents, + expectTypeOfConstructor, loadTypeOfConstructor, loadTypeOfReferent, loadTypeDeclaration, diff --git a/src/Share/Names/Postgres.hs b/src/Share/Names/Postgres.hs new file mode 100644 index 00000000..7834e767 --- /dev/null +++ b/src/Share/Names/Postgres.hs @@ -0,0 +1,38 @@ +-- | Efficiently fetch a Names object for a given set of labeled dependencies. +module Share.Names.Postgres (namesForReferences) where + +import Control.Lens +import Data.Set qualified as Set +import Share.Postgres qualified as PG +import Share.Postgres.NameLookups.Conversions qualified as CV +import Share.Postgres.NameLookups.Ops qualified as NameLookupOps +import Share.Postgres.NameLookups.Types (NamesPerspective) +import Share.Postgres.NameLookups.Types qualified as NameLookups +import Share.Postgres.Refs.Types +import Share.Prelude +import Unison.LabeledDependency (LabeledDependency) +import Unison.Name (Name) +import Unison.Names (Names) +import Unison.Names qualified as Names +import Unison.Reference qualified as V1 +import Unison.Referent qualified as V1 + +namesForReferences :: forall m. (PG.QueryM m) => NamesPerspective -> Set LabeledDependency -> m Names +namesForReferences namesPerspective refs = do + withPGRefs <- + Set.toList refs + & CV.labeledDependencies1ToPG + (termNames, typeNames) <- foldMapM namesForReference withPGRefs + pure $ Names.fromTermsAndTypes termNames typeNames + where + -- TODO: Can probably speed this up by skipping suffixification. + namesForReference :: Either (V1.Referent, PGReferent) (V1.Reference, PGReference) -> m ([(Name, V1.Referent)], [(Name, V1.Reference)]) + namesForReference = \case + Left (ref, pgref) -> do + termNames <- fmap (bothMap NameLookups.reversedNameToName) <$> NameLookupOps.termNamesForRefWithinNamespace namesPerspective pgref Nothing + let termNames' = termNames <&> \(fqn, _suffixed) -> (fqn, ref) + pure $ (termNames', []) + Right (ref, pgref) -> do + typeNames <- fmap (bothMap NameLookups.reversedNameToName) <$> NameLookupOps.typeNamesForRefWithinNamespace namesPerspective pgref Nothing + let typeNames' = typeNames <&> \(fqn, _suffixed) -> (fqn, ref) + pure $ ([], typeNames') diff --git a/src/Share/NamespaceDiffs.hs b/src/Share/NamespaceDiffs.hs index ddd3aa7a..7e940dc0 100644 --- a/src/Share/NamespaceDiffs.hs +++ b/src/Share/NamespaceDiffs.hs @@ -1,64 +1,115 @@ -{-# LANGUAGE ApplicativeDo #-} - -- | Logic for computing the differerences between two namespaces, -- typically used when showing the differences caused by a contribution. module Share.NamespaceDiffs - ( NamespaceTreeDiff, + ( NamespaceAndLibdepsDiff, + GNamespaceAndLibdepsDiff (..), + NamespaceTreeDiff, + GNamespaceTreeDiff, DiffAtPath (..), NamespaceDiffError (..), DefinitionDiff (..), DefinitionDiffKind (..), - diffTreeNamespaces, + computeThreeWayNamespaceDiff, + compressNameTree, namespaceTreeDiffReferences_, namespaceTreeDiffReferents_, namespaceTreeDiffTermDiffs_, + witherNamespaceTreeDiffTermDiffs, namespaceTreeDiffTypeDiffs_, namespaceTreeDiffRenderedTerms_, namespaceTreeDiffRenderedTypes_, namespaceTreeTermDiffKinds_, + witherNamespaceTreeTermDiffKinds, namespaceTreeTypeDiffKinds_, definitionDiffRendered_, definitionDiffRefs_, definitionDiffDiffs_, + witherDiffAtPathTermDiffs, definitionDiffKindRefs_, definitionDiffKindDiffs_, definitionDiffKindRendered_, + namespaceAndLibdepsDiffDefns_, + namespaceAndLibdepsDiffLibdeps_, ) where import Control.Comonad.Cofree (Cofree) import Control.Comonad.Cofree qualified as Cofree import Control.Lens hiding ((:<)) +import Control.Monad.Except import Data.Align (Semialign (..)) import Data.Either (partitionEithers) import Data.Foldable qualified as Foldable -import Data.List.NonEmpty qualified as NEList +import Data.Functor.Compose (Compose (..)) import Data.Map qualified as Map import Data.Set qualified as Set import Data.Set.NonEmpty (NESet) import Data.Set.NonEmpty qualified as NESet -import Servant (err404, err500) +import Servant (err400, err404, err500) +import Share.Codebase qualified as Codebase +import Share.Names.Postgres qualified as PGNames import Share.Postgres qualified as PG import Share.Postgres.IDs (BranchHashId) -import Share.Postgres.NameLookups.Conversions qualified as Cv +import Share.Postgres.NameLookups.Ops qualified as NL import Share.Postgres.NameLookups.Types (NameLookupReceipt) -import Share.Postgres.NamespaceDiffs qualified as ND +import Share.Postgres.NameLookups.Types qualified as NL import Share.Prelude -import Share.Utils.Logging (Loggable (..)) import Share.Utils.Logging qualified as Logging import Share.Web.Errors -import U.Codebase.Reference qualified as V2 -import U.Codebase.Referent qualified as V2 import Unison.Codebase.Path (Path) import Unison.Codebase.Path qualified as Path +import Unison.DataDeclaration (Decl) +import Unison.LabeledDependency (LabeledDependency) +import Unison.Merge (DiffOp, EitherWay, Mergeblob0, Mergeblob1, ThreeWay (..), TwoOrThreeWay (..), TwoWay (..)) +import Unison.Merge qualified as Merge +import Unison.Merge.DeclCoherencyCheck (IncoherentDeclReason) +import Unison.Merge.HumanDiffOp (HumanDiffOp (..)) +import Unison.Merge.Mergeblob1 qualified as Mergeblob1 +import Unison.Merge.ThreeWay qualified as ThreeWay import Unison.Name (Name) import Unison.Name qualified as Name -import Unison.NameSegment (NameSegment) -import Unison.Util.Monoid qualified as Monoid -import Unison.Util.Relation (Relation) -import Unison.Util.Relation qualified as Rel +import Unison.NameSegment (NameSegment (..)) +import Unison.NameSegment qualified as NameSegment +import Unison.Names (Names) +import Unison.Names qualified as Names +import Unison.Parser.Ann (Ann) +import Unison.Reference (Reference, TermReferenceId, TypeReference, TypeReferenceId) +import Unison.Reference qualified as Reference +import Unison.Referent (Referent) +import Unison.Referent qualified as Referent +import Unison.Symbol (Symbol) +import Unison.Syntax.NameSegment qualified as NameSegment +import Unison.Term (Term) +import Unison.Type (Type) +import Unison.Util.BiMultimap (BiMultimap) +import Unison.Util.BiMultimap qualified as BiMultimap +import Unison.Util.Defns (Defns (..), DefnsF, DefnsF3, alignDefnsWith) +import Unison.Util.Nametree (Nametree (..)) import Unison.Util.Set qualified as Set +data NamespaceDiffError + = ImpossibleError Text + | IncoherentDecl (EitherWay IncoherentDeclReason) + | LibFoundAtUnexpectedPath Path + | MissingEntityError EntityMissing + deriving stock (Eq, Show) + +instance ToServerError NamespaceDiffError where + toServerError = \case + ImpossibleError {} -> (ErrorID "namespace-diff:impossible-error", err500) + IncoherentDecl {} -> (ErrorID "namespace-diff:incoherent-decl", err400) + LibFoundAtUnexpectedPath {} -> (ErrorID "namespace-diff:lib-at-unexpected-path", err400) + MissingEntityError (EntityMissing eId _msg) -> (eId, err404) + +instance Logging.Loggable NamespaceDiffError where + toLog = \case + (ImpossibleError t) -> + Logging.textLog t + & Logging.withSeverity Logging.Error + (IncoherentDecl _) -> Logging.textLog "couldn't diff namespaces due to incoherent decl" + (LibFoundAtUnexpectedPath _) -> Logging.textLog "couldn't diff namespaces due to lib found at unexpected path" + (MissingEntityError e) -> Logging.toLog e + -- | The differences between two namespaces. data DefinitionDiffs name r = DefinitionDiffs { -- Brand new added terms, neither the name nor definition exist in the old namespace. @@ -66,9 +117,10 @@ data DefinitionDiffs name r = DefinitionDiffs -- Removed terms. These names for these definitions were removed, and there are no newly -- added names for these definitions. removed :: Map name r, - -- Updated terms. These names exist in both the old and new namespace, but the definitions - -- assigned to them have changed. + -- Updated terms, split into non-propagated (`updated`) and propagated (`propagated`) updates. These names exist in + -- both the old and new namespace, but the definitions assigned to them have changed. updated :: Map name (r {- old -}, r {- new -}), + propagated :: Map name (r {- old -}, r {- new -}), -- Renamed terms. These definitions exist in both the old and new namespace, but the names have -- changed. renamed :: Map r (NESet name {- old names for this ref -}, NESet name {- new names for this ref -}), @@ -105,18 +157,44 @@ data DefinitionDiffKind r rendered diff = Added r rendered | NewAlias r (NESet Name {- existing names -}) rendered | Removed r rendered - | Updated r {- old -} r {- new -} diff + | -- | A non-propagated update, where old and new have different syntactic hashes. + Updated r {- old -} r {- new -} diff + | -- | A propagated update (old and new are different but have the same syntactic hash) + Propagated r {- old -} r {- new -} diff | -- This definition was removed away from this location and added at the provided names. RenamedTo r (NESet Name) rendered | -- This definition was added at this location and removed from the provided names. RenamedFrom r (NESet Name) rendered deriving stock (Eq, Show, Ord) +instance (Ord r) => Semigroup (DefinitionDiffs Name r) where + d1 <> d2 = + DefinitionDiffs + { added = added d1 <> added d2, + removed = removed d1 <> removed d2, + updated = updated d1 <> updated d2, + propagated = propagated d1 <> propagated d2, + renamed = Map.unionWith (\(a1, b1) (a2, b2) -> (a1 <> a2, b1 <> b2)) (renamed d1) (renamed d2), + newAliases = Map.unionWith (\(a1, b1) (a2, b2) -> (a1 <> a2, b1 <> b2)) (newAliases d1) (newAliases d2) + } + +instance (Ord r) => Monoid (DefinitionDiffs Name r) where + mempty = + DefinitionDiffs + { added = mempty, + removed = mempty, + updated = mempty, + propagated = mempty, + renamed = mempty, + newAliases = mempty + } + definitionDiffKindRefs_ :: Traversal (DefinitionDiffKind r rendered diff) (DefinitionDiffKind r' rendered diff) r r' definitionDiffKindRefs_ f = \case Added r rendered -> Added <$> f r <*> pure rendered NewAlias r ns rendered -> NewAlias <$> f r <*> pure ns <*> pure rendered Removed r rendered -> Removed <$> f r <*> pure rendered + Propagated old new diff -> Propagated <$> f old <*> f new <*> pure diff Updated old new diff -> Updated <$> f old <*> f new <*> pure diff RenamedTo r old rendered -> RenamedTo <$> f r <*> pure old <*> pure rendered RenamedFrom r old rendered -> RenamedFrom <$> f r <*> pure old <*> pure rendered @@ -126,6 +204,7 @@ definitionDiffKindDiffs_ f = \case Added r rendered -> Added r <$> pure rendered NewAlias r ns rendered -> NewAlias r ns <$> pure rendered Removed r rendered -> Removed r <$> pure rendered + Propagated old new diff -> Propagated old new <$> f diff Updated old new diff -> Updated old new <$> f diff RenamedTo r old rendered -> RenamedTo r old <$> pure rendered RenamedFrom r old rendered -> RenamedFrom r old <$> pure rendered @@ -135,29 +214,38 @@ definitionDiffKindRendered_ f = \case Added r rendered -> Added r <$> f rendered NewAlias r ns rendered -> NewAlias r ns <$> f rendered Removed r rendered -> Removed r <$> f rendered + Propagated old new diff -> Propagated old new <$> pure diff Updated old new diff -> Updated old new <$> pure diff RenamedTo r old rendered -> RenamedTo r old <$> f rendered RenamedFrom r old rendered -> RenamedFrom r old <$> f rendered -instance (Ord r) => Semigroup (DefinitionDiffs Name r) where - d1 <> d2 = - DefinitionDiffs - { added = added d1 <> added d2, - removed = removed d1 <> removed d2, - updated = updated d1 <> updated d2, - renamed = Map.unionWith (\(a1, b1) (a2, b2) -> (a1 <> a2, b1 <> b2)) (renamed d1) (renamed d2), - newAliases = Map.unionWith (\(a1, b1) (a2, b2) -> (a1 <> a2, b1 <> b2)) (newAliases d1) (newAliases d2) - } +type NamespaceAndLibdepsDiff referent reference renderedTerm renderedType termDiff typeDiff libdep = + GNamespaceAndLibdepsDiff Path referent reference renderedTerm renderedType termDiff typeDiff libdep -instance (Ord r) => Monoid (DefinitionDiffs Name r) where - mempty = - DefinitionDiffs - { added = mempty, - removed = mempty, - updated = mempty, - renamed = mempty, - newAliases = mempty - } +data GNamespaceAndLibdepsDiff k referent reference renderedTerm renderedType termDiff typeDiff libdep + = NamespaceAndLibdepsDiff + { defns :: GNamespaceTreeDiff k referent reference renderedTerm renderedType termDiff typeDiff, + libdeps :: Map NameSegment (DiffOp libdep) + } + deriving stock (Show) + +namespaceAndLibdepsDiffDefns_ :: + Traversal + (GNamespaceAndLibdepsDiff k referent reference renderedTerm renderedType termDiff typeDiff libdep) + (GNamespaceAndLibdepsDiff k' referent' reference' renderedTerm' renderedType' termDiff' typeDiff' libdep) + (GNamespaceTreeDiff k referent reference renderedTerm renderedType termDiff typeDiff) + (GNamespaceTreeDiff k' referent' reference' renderedTerm' renderedType' termDiff' typeDiff') +namespaceAndLibdepsDiffDefns_ f (NamespaceAndLibdepsDiff defns libdeps) = + NamespaceAndLibdepsDiff <$> f defns <*> pure libdeps + +namespaceAndLibdepsDiffLibdeps_ :: + Traversal + (GNamespaceAndLibdepsDiff k referent reference renderedTerm renderedType termDiff typeDiff libdep) + (GNamespaceAndLibdepsDiff k referent reference renderedTerm renderedType termDiff typeDiff libdep') + (Map NameSegment (DiffOp libdep)) + (Map NameSegment (DiffOp libdep')) +namespaceAndLibdepsDiffLibdeps_ f (NamespaceAndLibdepsDiff defns libdeps) = + NamespaceAndLibdepsDiff defns <$> f libdeps -- | A compressed tree of differences between two namespaces. -- All intermediate namespaces with no differences are compressed into the keys of the @@ -180,7 +268,14 @@ instance (Ord r) => Monoid (DefinitionDiffs Name r) where -- ├── c = DiffAtPath -- └── x = DiffAtPath -- @@ -type NamespaceTreeDiff referent reference renderedTerm renderedType termDiff typeDiff = Cofree (Map Path) (Map NameSegment (DiffAtPath referent reference renderedTerm renderedType termDiff typeDiff)) +type NamespaceTreeDiff referent reference renderedTerm renderedType termDiff typeDiff = + GNamespaceTreeDiff Path referent reference renderedTerm renderedType termDiff typeDiff + +type GNamespaceTreeDiff k referent reference renderedTerm renderedType termDiff typeDiff = + GNamespaceTreeOf k (DiffAtPath referent reference renderedTerm renderedType termDiff typeDiff) + +type GNamespaceTreeOf k a = + Cofree (Map k) (Map NameSegment a) -- | The differences at a specific path in the namespace tree. data DiffAtPath referent reference renderedTerm renderedType termDiff typeDiff = DiffAtPath @@ -210,6 +305,23 @@ diffAtPathTermDiffs_ f (DiffAtPath {termDiffsAtPath, typeDiffsAtPath}) = & (Set.traverse . definitionDiffDiffs_) %%~ f <&> \termDiffsAtPath -> DiffAtPath {typeDiffsAtPath, termDiffsAtPath} +witherDiffAtPathTermDiffs :: + forall f reference referent renderedTerm renderedType termDiff termDiff' typeDiff. + (Applicative f, Ord termDiff', Ord referent, Ord renderedTerm) => + (termDiff -> f (Maybe termDiff')) -> + DiffAtPath referent reference renderedTerm renderedType termDiff typeDiff -> + f (Maybe (DiffAtPath referent reference renderedTerm renderedType termDiff' typeDiff)) +witherDiffAtPathTermDiffs f DiffAtPath {termDiffsAtPath, typeDiffsAtPath} = + g <$> Set.forMaybe termDiffsAtPath (getCompose . (definitionDiffDiffs_ (Compose . f))) + where + g :: + Set (DefinitionDiff referent renderedTerm termDiff') -> + Maybe (DiffAtPath referent reference renderedTerm renderedType termDiff' typeDiff) + g termDiffsAtPath = + if Set.null termDiffsAtPath && Set.null typeDiffsAtPath + then Nothing + else Just DiffAtPath {termDiffsAtPath, typeDiffsAtPath} + -- | A traversal over all the type diffs in a `DiffAtPath`. diffAtPathTypeDiffs_ :: (Ord typeDiff', Ord reference, Ord renderedType) => Traversal (DiffAtPath referent reference renderedTerm renderedType termDiff typeDiff) (DiffAtPath referent reference renderedTerm renderedType termDiff typeDiff') typeDiff typeDiff' diffAtPathTypeDiffs_ f (DiffAtPath {termDiffsAtPath, typeDiffsAtPath}) = @@ -222,6 +334,23 @@ diffAtPathTermDiffKinds_ f (DiffAtPath terms types) = do newTerms <- terms & Set.traverse . definitionDiffKind_ %%~ f pure $ DiffAtPath newTerms types +witherDiffAtPathTermDiffKinds :: + forall f reference referent referent' renderedTerm renderedTerm' renderedType termDiff termDiff' typeDiff. + (Applicative f, Ord renderedTerm', Ord termDiff', Ord referent') => + (DefinitionDiffKind referent renderedTerm termDiff -> f (Maybe (DefinitionDiffKind referent' renderedTerm' termDiff'))) -> + DiffAtPath referent reference renderedTerm renderedType termDiff typeDiff -> + f (Maybe (DiffAtPath referent' reference renderedTerm' renderedType termDiff' typeDiff)) +witherDiffAtPathTermDiffKinds f DiffAtPath {termDiffsAtPath, typeDiffsAtPath} = + g <$> Set.forMaybe termDiffsAtPath (getCompose . definitionDiffKind_ (Compose . f)) + where + g :: + Set (DefinitionDiff referent' renderedTerm' termDiff') -> + Maybe (DiffAtPath referent' reference renderedTerm' renderedType termDiff' typeDiff) + g termDiffsAtPath = + if Set.null termDiffsAtPath && Set.null typeDiffsAtPath + then Nothing + else Just DiffAtPath {termDiffsAtPath, typeDiffsAtPath} + diffAtPathTypeDiffKinds_ :: (Ord renderedType', Ord typeDiff', Ord reference') => Traversal (DiffAtPath referent reference renderedTerm renderedType termDiff typeDiff) (DiffAtPath referent reference' renderedTerm renderedType' termDiff typeDiff') (DefinitionDiffKind reference renderedType typeDiff) (DefinitionDiffKind reference' renderedType' typeDiff') diffAtPathTypeDiffKinds_ f (DiffAtPath terms types) = do newTypes <- types & Set.traverse . definitionDiffKind_ %%~ f @@ -242,24 +371,70 @@ diffAtPathRenderedTypes_ f (DiffAtPath {termDiffsAtPath, typeDiffsAtPath}) = <&> \typeDiffsAtPath -> DiffAtPath {typeDiffsAtPath, termDiffsAtPath} -- | Traversal over all the referents in a `NamespaceTreeDiff`. -namespaceTreeDiffReferents_ :: (Ord referent', Ord termDiff, Ord renderedTerm) => Traversal (NamespaceTreeDiff referent reference renderedTerm renderedType termDiff typeDiff) (NamespaceTreeDiff referent' reference renderedTerm renderedType termDiff typeDiff) referent referent' +namespaceTreeDiffReferents_ :: (Ord referent', Ord termDiff, Ord renderedTerm) => Traversal (GNamespaceTreeDiff k referent reference renderedTerm renderedType termDiff typeDiff) (GNamespaceTreeDiff k referent' reference renderedTerm renderedType termDiff typeDiff) referent referent' namespaceTreeDiffReferents_ = traversed . traversed . diffAtPathReferents_ -- | Traversal over all the references in a `NamespaceTreeDiff`. -namespaceTreeDiffReferences_ :: (Ord reference', Ord typeDiff, Ord renderedType) => Traversal (NamespaceTreeDiff referent reference renderedTerm renderedType termDiff typeDiff) (NamespaceTreeDiff referent reference' renderedTerm renderedType termDiff typeDiff) reference reference' +namespaceTreeDiffReferences_ :: (Ord reference', Ord typeDiff, Ord renderedType) => Traversal (GNamespaceTreeDiff k referent reference renderedTerm renderedType termDiff typeDiff) (GNamespaceTreeDiff k referent reference' renderedTerm renderedType termDiff typeDiff) reference reference' namespaceTreeDiffReferences_ = traversed . traversed . diffAtPathReferences_ namespaceTreeDiffTermDiffs_ :: (Ord termDiff', Ord referent, Ord renderedTerm) => Traversal (NamespaceTreeDiff referent reference renderedTerm renderedType termDiff typeDiff) (NamespaceTreeDiff referent reference renderedTerm renderedType termDiff' typeDiff) termDiff termDiff' namespaceTreeDiffTermDiffs_ = traversed . traversed . diffAtPathTermDiffs_ -namespaceTreeDiffTypeDiffs_ :: (Ord typeDiff', Ord reference, Ord renderedType) => Traversal (NamespaceTreeDiff referent reference renderedTerm renderedType termDiff typeDiff) (NamespaceTreeDiff referent reference renderedTerm renderedType termDiff typeDiff') typeDiff typeDiff' +witherNamespaceTreeDiffTermDiffs :: + forall f k reference referent renderedTerm renderedType termDiff termDiff' typeDiff. + (Monad f, Ord termDiff', Ord referent, Ord renderedTerm) => + (termDiff -> f (Maybe termDiff')) -> + GNamespaceTreeDiff k referent reference renderedTerm renderedType termDiff typeDiff -> + f (GNamespaceTreeDiff k referent reference renderedTerm renderedType termDiff' typeDiff) +witherNamespaceTreeDiffTermDiffs f = + fmap (fromMaybe (Map.empty Cofree.:< Map.empty)) . go + where + go :: + GNamespaceTreeDiff k referent reference renderedTerm renderedType termDiff typeDiff -> + f (Maybe (GNamespaceTreeDiff k referent reference renderedTerm renderedType termDiff' typeDiff)) + go (x Cofree.:< xs) = + g <$> wither (witherDiffAtPathTermDiffs f) x <*> wither go xs + + g :: + Map NameSegment (DiffAtPath referent reference renderedTerm renderedType termDiff' typeDiff) -> + Map k (GNamespaceTreeDiff k referent reference renderedTerm renderedType termDiff' typeDiff) -> + Maybe (GNamespaceTreeDiff k referent reference renderedTerm renderedType termDiff' typeDiff) + g x xs + | Map.null x && Map.null xs = Nothing + | otherwise = Just (x Cofree.:< xs) + +namespaceTreeDiffTypeDiffs_ :: (Ord typeDiff', Ord reference, Ord renderedType) => Traversal (GNamespaceTreeDiff k referent reference renderedTerm renderedType termDiff typeDiff) (GNamespaceTreeDiff k referent reference renderedTerm renderedType termDiff typeDiff') typeDiff typeDiff' namespaceTreeDiffTypeDiffs_ = traversed . traversed . diffAtPathTypeDiffs_ -namespaceTreeTermDiffKinds_ :: (Ord renderedTerm', Ord termDiff', Ord referent') => Traversal (NamespaceTreeDiff referent reference renderedTerm renderedType termDiff typeDiff) (NamespaceTreeDiff referent' reference renderedTerm' renderedType termDiff' typeDiff) (DefinitionDiffKind referent renderedTerm termDiff) (DefinitionDiffKind referent' renderedTerm' termDiff') +namespaceTreeTermDiffKinds_ :: (Ord renderedTerm', Ord termDiff', Ord referent') => Traversal (GNamespaceTreeDiff k referent reference renderedTerm renderedType termDiff typeDiff) (GNamespaceTreeDiff k referent' reference renderedTerm' renderedType termDiff' typeDiff) (DefinitionDiffKind referent renderedTerm termDiff) (DefinitionDiffKind referent' renderedTerm' termDiff') namespaceTreeTermDiffKinds_ = traversed . traversed . diffAtPathTermDiffKinds_ -namespaceTreeTypeDiffKinds_ :: (Ord renderedType', Ord typeDiff', Ord reference') => Traversal (NamespaceTreeDiff referent reference renderedTerm renderedType termDiff typeDiff) (NamespaceTreeDiff referent reference' renderedTerm renderedType' termDiff typeDiff') (DefinitionDiffKind reference renderedType typeDiff) (DefinitionDiffKind reference' renderedType' typeDiff') +witherNamespaceTreeTermDiffKinds :: + forall f k reference referent referent' renderedTerm renderedTerm' renderedType termDiff termDiff' typeDiff. + (Monad f, Ord renderedTerm', Ord termDiff', Ord referent') => + (DefinitionDiffKind referent renderedTerm termDiff -> f (Maybe (DefinitionDiffKind referent' renderedTerm' termDiff'))) -> + GNamespaceTreeDiff k referent reference renderedTerm renderedType termDiff typeDiff -> + f (GNamespaceTreeDiff k referent' reference renderedTerm' renderedType termDiff' typeDiff) +witherNamespaceTreeTermDiffKinds f = + fmap (fromMaybe (Map.empty Cofree.:< Map.empty)) . go + where + go :: + GNamespaceTreeDiff k referent reference renderedTerm renderedType termDiff typeDiff -> + f (Maybe (GNamespaceTreeDiff k referent' reference renderedTerm' renderedType termDiff' typeDiff)) + go (x Cofree.:< xs) = + g <$> wither (witherDiffAtPathTermDiffKinds f) x <*> wither go xs + + g :: + Map NameSegment (DiffAtPath referent' reference renderedTerm' renderedType termDiff' typeDiff) -> + Map k (GNamespaceTreeDiff k referent' reference renderedTerm' renderedType termDiff' typeDiff) -> + Maybe (GNamespaceTreeDiff k referent' reference renderedTerm' renderedType termDiff' typeDiff) + g x xs + | Map.null x && Map.null xs = Nothing + | otherwise = Just (x Cofree.:< xs) + +namespaceTreeTypeDiffKinds_ :: (Ord renderedType', Ord typeDiff', Ord reference') => Traversal (GNamespaceTreeDiff k referent reference renderedTerm renderedType termDiff typeDiff) (GNamespaceTreeDiff k referent reference' renderedTerm renderedType' termDiff typeDiff') (DefinitionDiffKind reference renderedType typeDiff) (DefinitionDiffKind reference' renderedType' typeDiff') namespaceTreeTypeDiffKinds_ = traversed . traversed . diffAtPathTypeDiffKinds_ namespaceTreeDiffRenderedTerms_ :: (Ord termDiff, Ord referent, Ord renderedTerm') => Traversal (NamespaceTreeDiff referent reference renderedTerm renderedType termDiff typeDiff) (NamespaceTreeDiff referent reference renderedTerm' renderedType termDiff typeDiff) renderedTerm renderedTerm' @@ -268,71 +443,63 @@ namespaceTreeDiffRenderedTerms_ = traversed . traversed . diffAtPathRenderedTerm namespaceTreeDiffRenderedTypes_ :: (Ord typeDiff, Ord reference, Ord renderedType') => Traversal (NamespaceTreeDiff referent reference renderedTerm renderedType termDiff typeDiff) (NamespaceTreeDiff referent reference renderedTerm renderedType' termDiff typeDiff) renderedType renderedType' namespaceTreeDiffRenderedTypes_ = traversed . traversed . diffAtPathRenderedTypes_ -data NamespaceDiffError - = ImpossibleError Text - | MissingEntityError EntityMissing - deriving stock (Eq, Show) - -instance ToServerError NamespaceDiffError where - toServerError = \case - ImpossibleError {} -> (ErrorID "namespace-diff:impossible-error", err500) - MissingEntityError (EntityMissing eId _msg) -> (eId, err404) - -instance Logging.Loggable NamespaceDiffError where - toLog = \case - (ImpossibleError t) -> - Logging.textLog t - & Logging.withSeverity Logging.Error - (MissingEntityError e) -> Logging.toLog e - --- | Compute the tree of differences between two namespace hashes. --- Note: This ignores all dependencies in the lib namespace. -diffTreeNamespaces :: (BranchHashId, NameLookupReceipt) -> (BranchHashId, NameLookupReceipt) -> (PG.Transaction e (Either NamespaceDiffError (NamespaceTreeDiff V2.Referent V2.Reference Name Name Name Name))) -diffTreeNamespaces (oldBHId, oldNLReceipt) (newBHId, newNLReceipt) = do - ((oldTerms, newTerms), (oldTypes, newTypes)) <- PG.pipelined do - terms <- ND.getRelevantTermsForDiff oldNLReceipt oldBHId newBHId - types <- ND.getRelevantTypesForDiff newNLReceipt oldBHId newBHId - pure (terms, types) - case diffTreeNamespacesHelper (oldTerms, newTerms) (oldTypes, newTypes) of - Left e -> pure $ Left e - Right nd -> - Right - <$> ( Cv.referentsPGTo2Of (namespaceTreeDiffReferents_) nd - >>= Cv.referencesPGTo2Of (namespaceTreeDiffReferences_) +-- | Convert a `DefinitionDiffs` into a tree of differences. +definitionDiffsToTree :: + forall ref. + (Ord ref) => + DefinitionDiffs Name ref -> + GNamespaceTreeOf NameSegment (Set (DefinitionDiff ref Name Name)) +definitionDiffsToTree dd = + let DefinitionDiffs {added, removed, updated, propagated, renamed, newAliases} = dd + expandedAliases :: Map Name (Set (DefinitionDiffKind ref Name Name)) + expandedAliases = + newAliases + & Map.toList + & foldMap + ( \(r, (existingNames, newNames)) -> + ( Foldable.toList newNames + <&> \newName -> Map.singleton newName (Set.singleton (NewAlias r existingNames newName)) + ) ) - --- | Compute the tree of differences between two namespaces. --- This is the core logic for computing the differences between two namespaces. -diffTreeNamespacesHelper :: - forall referent reference. - (Ord referent, Ord reference) => - (Relation Name referent, Relation Name referent) -> - (Relation Name reference, Relation Name reference) -> - Either NamespaceDiffError (NamespaceTreeDiff referent reference Name Name Name Name) -diffTreeNamespacesHelper (oldTerms, newTerms) (oldTypes, newTypes) = do - termTree <- computeDefinitionDiff oldTerms newTerms <&> definitionDiffsToTree - typeTree <- computeDefinitionDiff oldTypes newTypes <&> definitionDiffsToTree - let compressed = - alignWith combineTermsAndTypes termTree typeTree - & compressNameTree - pure compressed - where - combineTermsAndTypes :: These (Map NameSegment (Set (DefinitionDiff referent Name Name))) (Map NameSegment (Set (DefinitionDiff reference Name Name))) -> Map NameSegment (DiffAtPath referent reference Name Name Name Name) - combineTermsAndTypes = \case - This termsMap -> termsMap <&> \termDiffsAtPath -> DiffAtPath {termDiffsAtPath, typeDiffsAtPath = mempty} - That typesMap -> typesMap <&> \typeDiffsAtPath -> DiffAtPath {typeDiffsAtPath, termDiffsAtPath = mempty} - These trms typs -> alignWith combineNode trms typs - combineNode :: These (Set (DefinitionDiff referent Name Name)) (Set (DefinitionDiff reference Name Name)) -> DiffAtPath referent reference Name Name Name Name - combineNode = \case - This termDiffsAtPath -> DiffAtPath {termDiffsAtPath, typeDiffsAtPath = mempty} - That typeDiffsAtPath -> DiffAtPath {typeDiffsAtPath, termDiffsAtPath = mempty} - These termDiffsAtPath typeDiffsAtPath -> DiffAtPath {typeDiffsAtPath, termDiffsAtPath} + & Map.unionsWith (<>) + expandedRenames :: Map Name (Set (DefinitionDiffKind ref Name Name)) + expandedRenames = + renamed + & Map.toList + & foldMap \(r, (oldNames, newNames)) -> + ( -- We don't currently want to track the old names in a rename, and including them messes up + -- the path-compression for the diff tree, so we just omit them. + -- ( Foldable.toList oldNames + -- <&> \oldName -> Map.singleton oldName (Set.singleton (RenamedTo r newNames)) + -- ) + -- <> + ( Foldable.toList newNames + <&> \newName -> Map.singleton newName (Set.singleton (RenamedFrom r oldNames newName)) + ) + ) + & Map.unionsWith (<>) + diffTree :: Map Name (Set (DefinitionDiffKind ref Name Name)) + diffTree = + Map.unionsWith + (<>) + [ (added & Map.mapWithKey \n r -> Set.singleton $ Added r n), + expandedAliases, + (removed & Map.mapWithKey \n r -> Set.singleton $ Removed r n), + (updated & Map.mapWithKey \name (oldR, newR) -> Set.singleton $ Updated oldR newR name), + (propagated & Map.mapWithKey \name (oldR, newR) -> Set.singleton $ Propagated oldR newR name), + expandedRenames + ] + includeFQNs :: Map Name (Set (DefinitionDiffKind ref Name Name)) -> Map Name (Set (DefinitionDiff ref Name Name)) + includeFQNs m = m & imap \n ds -> (ds & Set.map \d -> DefinitionDiff {kind = d, fqn = n}) + in diffTree + & includeFQNs + & expandNameTree -- Unfolds a Map of names into a Cofree of paths by name segemnt. -- -- >>> import qualified Unison.Syntax.Name as NS -- >>> expandNameTree $ Map.fromList [(NS.unsafeParseText "a.b", "a.b"), (NS.unsafeParseText "a.c", "a.c"), (NS.unsafeParseText "x.y.z", "x.y.z")] --- fromList [] :< fromList [(a,fromList [(b,"a.b"),(c,"a.c")] :< fromList []),(x,fromList [] :< fromList [(y,fromList [(z,"x.y.z")] :< fromList [])])] +-- fromList [] :< fromList [(NameSegment {toUnescapedText = "a"},fromList [(NameSegment {toUnescapedText = "b"},"a.b"),(NameSegment {toUnescapedText = "c"},"a.c")] :< fromList []),(NameSegment {toUnescapedText = "x"},fromList [] :< fromList [(NameSegment {toUnescapedText = "y"},fromList [(NameSegment {toUnescapedText = "z"},"x.y.z")] :< fromList [])])] expandNameTree :: forall a. Map Name a -> Cofree (Map NameSegment) (Map NameSegment a) expandNameTree m = let (here, children) = @@ -344,7 +511,7 @@ expandNameTree m = children & Map.fromListWith Map.union & fmap expandNameTree - in (Map.fromList here) Cofree.:< childMap + in Map.fromList here Cofree.:< childMap where splitNames :: (Name, a) -> Either (NameSegment, a) (NameSegment, Map Name a) splitNames (n, a) = @@ -352,6 +519,28 @@ expandNameTree m = (ns :| []) -> Left (ns, a) (ns :| (r : rs)) -> Right (ns, Map.singleton (Name.fromSegments (r :| rs)) a) +combineTermsAndTypes :: + forall f reference referent. + (Semialign f, Ord reference, Ord referent) => + These + (f (Set (DefinitionDiff referent Name Name))) + (f (Set (DefinitionDiff reference Name Name))) -> + f (DiffAtPath referent reference Name Name Name Name) +combineTermsAndTypes = \case + This termsMap -> termsMap <&> \termDiffsAtPath -> DiffAtPath {termDiffsAtPath, typeDiffsAtPath = mempty} + That typesMap -> typesMap <&> \typeDiffsAtPath -> DiffAtPath {typeDiffsAtPath, termDiffsAtPath = mempty} + These trms typs -> alignWith combineNode trms typs + where + combineNode :: + These + (Set (DefinitionDiff referent Name Name)) + (Set (DefinitionDiff reference Name Name)) -> + DiffAtPath referent reference Name Name Name Name + combineNode = \case + This termDiffsAtPath -> DiffAtPath {termDiffsAtPath, typeDiffsAtPath = mempty} + That typeDiffsAtPath -> DiffAtPath {typeDiffsAtPath, termDiffsAtPath = mempty} + These termDiffsAtPath typeDiffsAtPath -> DiffAtPath {typeDiffsAtPath, termDiffsAtPath} + -- | Collapse all links which have only a single child into a path. -- I.e. the resulting tree will not contain nodes that have only a single namespace child with no diffs. -- @@ -374,121 +563,172 @@ compressNameTree (diffs Cofree.:< children) = (childDiffs Cofree.:< nestedChildren) | null childDiffs, [(k, v)] <- Map.toList nestedChildren -> - (Path.singleton ns <> k, v) + (Path.prefix (Path.singleton ns) (Path.Relative k), v) | otherwise -> (Path.singleton ns, child) ) & Map.fromList in diffs Cofree.:< compressedChildren --- | Compute changes between two unstructured Name relations, determining what has changed and how --- it should be interpreted so it's meaningful to the user. -computeDefinitionDiff :: - (Ord ref) => - Relation Name ref {- Relevant definitions from old namespace -} -> - Relation Name ref {- Relevant definitions from new namespace -} -> - Either NamespaceDiffError (DefinitionDiffs Name ref) -computeDefinitionDiff old new = - (Rel.dom old <> Rel.dom new) - & Monoid.foldMapM - ( \name -> - case (NESet.nonEmptySet (Rel.lookupDom name old), NESet.nonEmptySet (Rel.lookupDom name new)) of - (Nothing, Nothing) -> Left $ ImpossibleError "Name in diff doesn't exist in either old or new namespace" - -- Doesn't exist in the old namespace, it's a new addition or a new alias - (Nothing, Just refs) -> do - -- There shouldn't be multiple refs for the same name, but this wasn't true for the old - -- update process, so we'll just take the first ref. - let ref = NESet.findMin refs - case Set.toList (Rel.lookupRan ref old) of - -- No old names for this ref, so it's a new addition not an alias - [] -> Right $ mempty {added = Map.singleton name ref} - -- There are old names for this ref, but not old refs for this name, so it's - -- either a new alias or a rename. - -- - -- If at least one old name for this ref no longer exists, we treat it like a - -- rename. - (n : ns) -> do - let existingNames = NESet.fromList (n NEList.:| ns) - case NESet.nonEmptySet (Rel.lookupRan ref new) of - Nothing -> Left $ ImpossibleError "Expected to find at least one name for ref in new namespace, since we found the ref by the name." - Just allNewNames -> - case NESet.nonEmptySet (NESet.difference allNewNames existingNames) of - Nothing -> Left $ ImpossibleError "Expected to find at least one new name for ref in new namespace, since we found the ref by the name." - Just newNamesWithoutOldNames -> - case NESet.nonEmptySet (NESet.difference existingNames allNewNames) of - -- If all the old names still exist in the new namespace, it's a new alias. - Nothing -> Right $ mempty {newAliases = Map.singleton ref (existingNames, newNamesWithoutOldNames)} - -- Otherwise, treat it as a rename. - Just namesWhichDisappeared -> Right $ mempty {renamed = Map.singleton ref (namesWhichDisappeared, newNamesWithoutOldNames)} - - -- Doesn't exist in the new namespace, - -- so it's a removal or rename. - (Just refs, Nothing) -> do - refs - & Monoid.foldMapM - ( \ref -> do - case Set.toList (Rel.lookupRan ref new) of - -- No names for this ref, it was removed. - [] -> Right $ mempty {removed = Map.singleton name ref} - newNames -> - newNames - & Monoid.foldMapM (\newName -> Right $ mempty {renamed = Map.singleton ref (NESet.singleton name, NESet.singleton newName)}) - ) - -- Exists in both old and new namespaces, so it's an update - (Just oldRefs, Just newRefs) -> do - -- There should only be one ref for each name in the old and new namespaces, - -- but this wasn't true for the old update process, so we'll just take the - -- first ref. - let (oldRef, newRef) = (NESet.findMin oldRefs, NESet.findMin newRefs) - -- It's possible it's an unchanged ref which we should just ignore. - if oldRef == newRef - then Right mempty - else Right $ mempty {updated = Map.singleton name (NESet.findMin oldRefs, NESet.findMin newRefs)} - ) - --- | Convert a `DefinitionDiffs` into a tree of differences. -definitionDiffsToTree :: forall ref. (Ord ref) => DefinitionDiffs Name ref -> Cofree (Map NameSegment) (Map NameSegment (Set (DefinitionDiff ref Name Name))) -definitionDiffsToTree dd = - let DefinitionDiffs {added, removed, updated, renamed, newAliases} = dd - expandedAliases :: Map Name (Set (DefinitionDiffKind ref Name Name)) - expandedAliases = - newAliases - & Map.toList - & foldMap - ( \(r, (existingNames, newNames)) -> - ( Foldable.toList newNames - <&> \newName -> Map.singleton newName (Set.singleton (NewAlias r existingNames newName)) - ) - ) - & Map.unionsWith (<>) - expandedRenames :: Map Name (Set (DefinitionDiffKind ref Name Name)) - expandedRenames = - renamed - & Map.toList - & foldMap \(r, (oldNames, newNames)) -> - ( -- We don't currently want to track the old names in a rename, and including them messes up - -- the path-compression for the diff tree, so we just omit them. - -- ( Foldable.toList oldNames - -- <&> \oldName -> Map.singleton oldName (Set.singleton (RenamedTo r newNames)) - -- ) - -- <> - ( Foldable.toList newNames - <&> \newName -> Map.singleton newName (Set.singleton (RenamedFrom r oldNames newName)) - ) +computeThreeWayNamespaceDiff :: + TwoWay Codebase.CodebaseEnv -> + TwoOrThreeWay BranchHashId -> + TwoOrThreeWay NameLookupReceipt -> + PG.Transaction NamespaceDiffError (GNamespaceAndLibdepsDiff NameSegment Referent Reference Name Name Name Name BranchHashId) +computeThreeWayNamespaceDiff codebaseEnvs2 branchHashIds3 nameLookupReceipts3 = do + -- Load a flat definitions names (no lib) for Alice/Bob/LCA + defnsNames3 :: TwoOrThreeWay Names <- + sequence (NL.projectNamesWithoutLib <$> nameLookupReceipts3 <*> branchHashIds3) + + -- Unflatten each Names to a Nametree (leniently). Really, only the LCA is "allowed" to break the diff/merge rules of + -- no conflicted names, but we don't enforce that here. If Alice or Bob have a conflicted name for some reason, we'll + -- just silently pick one of the refs and move on. + let defnsNametrees3 :: TwoOrThreeWay (Nametree (DefnsF (Map NameSegment) Referent TypeReference)) + defnsNametrees3 = + Names.lenientToNametree <$> defnsNames3 + + -- Load the shallow libdeps for Alice/Bob/LCA. This can fail with "lib at unexpected path" + libdeps3 :: TwoOrThreeWay (Map NameSegment BranchHashId) <- do + let f :: NameLookupReceipt -> BranchHashId -> PG.Transaction NamespaceDiffError (Map NameSegment BranchHashId) + f nameLookupReceipt branchHashId = do + mounts <- NL.listNameLookupMounts nameLookupReceipt branchHashId + libDepsList <- + for mounts \(NL.PathSegments path, libBhId) -> do + case NameSegment.unsafeParseText <$> path of + [NameSegment.LibSegment, dep] -> pure (dep, libBhId) + p -> throwError $ LibFoundAtUnexpectedPath (Path.fromList p) + pure $ Map.fromList libDepsList + sequence (f <$> nameLookupReceipts3 <*> branchHashIds3) + + -- Make that 0th mergeblob + let blob0 :: Mergeblob0 BranchHashId + blob0 = + Merge.makeMergeblob0 + ThreeWay + { alice = defnsNametrees3.alice, + bob = defnsNametrees3.bob, + lca = fromMaybe Nametree {value = Defns Map.empty Map.empty, children = Map.empty} defnsNametrees3.lca + } + ThreeWay + { alice = libdeps3.alice, + bob = libdeps3.bob, + lca = fromMaybe Map.empty libdeps3.lca + } + + -- Hydrate defns in Alice/Bob/LCA + hydratedDefns3 :: + ThreeWay + ( DefnsF + (Map Name) + (TermReferenceId, (Term Symbol Ann, Type Symbol Ann)) + (TypeReferenceId, Decl Symbol Ann) + ) <- do + let hydrateTerm :: + Codebase.CodebaseEnv -> + TermReferenceId -> + PG.Transaction e (TermReferenceId, (Term Symbol Ann, Type Symbol Ann)) + hydrateTerm codebaseEnv ref = + Codebase.codebaseMToTransaction codebaseEnv do + term <- Codebase.expectTerm ref + pure (ref, term) + hydrateType :: + Codebase.CodebaseEnv -> + TypeReferenceId -> + PG.Transaction e (TypeReferenceId, Decl Symbol Ann) + hydrateType codebaseEnv ref = + Codebase.codebaseMToTransaction codebaseEnv do + type_ <- Codebase.expectTypeDeclaration ref + pure (ref, type_) + f :: + Codebase.CodebaseEnv -> + Defns (BiMultimap Referent Name) (BiMultimap TypeReference Name) -> + PG.Transaction + e + ( DefnsF + (Map Name) + (TermReferenceId, (Term Symbol Ann, Type Symbol Ann)) + (TypeReferenceId, Decl Symbol Ann) ) - & Map.unionsWith (<>) - diffTree :: Map Name (Set (DefinitionDiffKind ref Name Name)) - diffTree = - Map.unionsWith - (<>) - [ (added & Map.mapWithKey \n r -> Set.singleton $ Added r n), - expandedAliases, - (removed & Map.mapWithKey \n r -> Set.singleton $ Removed r n), - (updated & Map.mapWithKey \name (oldR, newR) -> Set.singleton $ Updated oldR newR name), - expandedRenames - ] - includeFQNs :: Map Name (Set (DefinitionDiffKind ref Name Name)) -> Map Name (Set (DefinitionDiff ref Name Name)) - includeFQNs m = m & imap \n ds -> (ds & Set.map \d -> DefinitionDiff {kind = d, fqn = n}) - in diffTree - & includeFQNs - & expandNameTree + f codebaseEnv = + bitraverse + (traverse (hydrateTerm codebaseEnv) . Map.mapMaybe Referent.toTermReferenceId . BiMultimap.range) + (traverse (hydrateType codebaseEnv) . Map.mapMaybe Reference.toId . BiMultimap.range) + + let -- Here we assume that the LCA is in the same codebase as Alice. + codebaseEnvs3 :: ThreeWay Codebase.CodebaseEnv + codebaseEnvs3 = + ThreeWay + { alice = codebaseEnvs2.alice, + bob = codebaseEnvs2.bob, + lca = codebaseEnvs2.alice + } + sequence (f <$> codebaseEnvs3 <*> blob0.defns) + + -- Get a names object that contains just enough names to compute the diff: + names3 :: TwoOrThreeWay Names <- do + -- Massage the hydrated definitions into a set of "labeled dependency" that contains the definitions themselves + -- and their direct references. + -- + -- FIXME: Mitchell wonders why self is necessary. Aren't direct dependency names enough? + let labeledDeps3 :: ThreeWay (Set LabeledDependency) + labeledDeps3 = + Mergeblob1.hydratedDefnsLabeledDependencies <$> hydratedDefns3 + -- Get a names perspective for Alice/Bob/LCA + namesPerspectives3 :: TwoOrThreeWay NL.NamesPerspective <- + for branchHashIds3 \branchHashId -> + NL.namesPerspectiveForRootAndPath branchHashId (mempty @NL.PathSegments) + sequence (PGNames.namesForReferences <$> namesPerspectives3 <*> ThreeWay.toTwoOrThreeWay labeledDeps3) + + blob1 :: Mergeblob1 BranchHashId <- do + let names3' = ThreeWay {alice = names3.alice, bob = names3.bob, lca = fromMaybe (mempty @Names) names3.lca} + case Merge.makeMergeblob1 blob0 names3' hydratedDefns3 of + Right blob -> pure blob + Left err -> throwError (IncoherentDecl err) + + -- Boilerplate conversion: make a "DefinitionDiffs" from the info in a "Mergeblob1". + -- + -- (Mitchell says: I think Share and UCM should share a type here – perhaps DefinitionDiffs should be pushed down? Or + -- is it just isomorphic to something that already exists in UCM?) + -- + -- We start focusing only on Bob here, the contributor, even though Alice could have a diff as well of course (since + -- the LCA is arbitrarily behind Alice). + + let definitionDiffs :: DefnsF (DefinitionDiffs Name) Referent TypeReference + definitionDiffs = + let f :: forall ref. (Ord ref) => Map Name (HumanDiffOp ref) -> DefinitionDiffs Name ref + f = + Map.toList >>> foldMap \(name, op) -> + case op of + HumanDiffOp'Add ref -> mempty {added = Map.singleton name ref} + HumanDiffOp'Delete ref -> mempty {removed = Map.singleton name ref} + HumanDiffOp'Update refs -> mempty {updated = Map.singleton name (refs.old, refs.new)} + HumanDiffOp'PropagatedUpdate refs -> mempty {propagated = Map.singleton name (refs.old, refs.new)} + HumanDiffOp'AliasOf ref names -> + mempty {newAliases = Map.singleton ref (names, NESet.singleton name)} + HumanDiffOp'RenamedFrom ref names -> + mempty {renamed = Map.singleton ref (names, NESet.singleton name)} + HumanDiffOp'RenamedTo ref names -> + mempty {renamed = Map.singleton ref (NESet.singleton name, names)} + in bimap f f blob1.humanDiffsFromLCA.bob + + -- Convert definition diffs to two uncompressed trees of diffs (one for terms, one for types) + let twoUncompressedTrees :: + DefnsF3 + (Cofree (Map NameSegment)) + (Map NameSegment) + Set + (DefinitionDiff Referent Name Name) + (DefinitionDiff TypeReference Name Name) + twoUncompressedTrees = + bimap definitionDiffsToTree definitionDiffsToTree definitionDiffs + + -- Align terms and types trees into one tree (still uncompressed) + let oneUncompressedTree :: GNamespaceTreeDiff NameSegment Referent TypeReference Name Name Name Name + oneUncompressedTree = + alignDefnsWith combineTermsAndTypes twoUncompressedTrees + + pure + NamespaceAndLibdepsDiff + { defns = oneUncompressedTree, + libdeps = blob1.libdepsDiffs.bob + } diff --git a/src/Share/Postgres/Contributions/Queries.hs b/src/Share/Postgres/Contributions/Queries.hs index c8b2c7cd..53fbbd31 100644 --- a/src/Share/Postgres/Contributions/Queries.hs +++ b/src/Share/Postgres/Contributions/Queries.hs @@ -514,32 +514,32 @@ contributionStateTokenById contributionId = do |] getPrecomputedNamespaceDiff :: - (CodebaseEnv, BranchHashId) -> - (CodebaseEnv, BranchHashId) -> + (CodebaseEnv, CausalId) -> + (CodebaseEnv, CausalId) -> PG.Transaction e (Maybe Text) getPrecomputedNamespaceDiff - (CodebaseEnv {codebaseOwner = leftCodebaseUser}, leftBHId) - (CodebaseEnv {codebaseOwner = rightCodebaseUser}, rightBHId) = do + (CodebaseEnv {codebaseOwner = leftCodebaseUser}, leftCausalId) + (CodebaseEnv {codebaseOwner = rightCodebaseUser}, rightCausalId) = do PG.query1Col @Text [PG.sql| SELECT (diff :: text) FROM namespace_diffs nd - WHERE nd.left_namespace_id = #{leftBHId} - AND nd.right_namespace_id = #{rightBHId} + WHERE nd.left_causal_id = #{leftCausalId} + AND nd.right_causal_id = #{rightCausalId} AND nd.left_codebase_owner_user_id = #{leftCodebaseUser} AND nd.right_codebase_owner_user_id = #{rightCodebaseUser} |] savePrecomputedNamespaceDiff :: - (CodebaseEnv, BranchHashId) -> - (CodebaseEnv, BranchHashId) -> + (CodebaseEnv, CausalId) -> + (CodebaseEnv, CausalId) -> Text -> PG.Transaction e () -savePrecomputedNamespaceDiff (CodebaseEnv {codebaseOwner = leftCodebaseUser}, leftBHId) (CodebaseEnv {codebaseOwner = rightCodebaseUser}, rightBHId) diff = do +savePrecomputedNamespaceDiff (CodebaseEnv {codebaseOwner = leftCodebaseUser}, leftCausalId) (CodebaseEnv {codebaseOwner = rightCodebaseUser}, rightCausalId) diff = do PG.execute_ [PG.sql| - INSERT INTO namespace_diffs (left_namespace_id, right_namespace_id, left_codebase_owner_user_id, right_codebase_owner_user_id, diff) - VALUES (#{leftBHId}, #{rightBHId}, #{leftCodebaseUser}, #{rightCodebaseUser}, #{diff}::jsonb) + INSERT INTO namespace_diffs (left_causal_id, right_causal_id, left_codebase_owner_user_id, right_codebase_owner_user_id, diff) + VALUES (#{leftCausalId}, #{rightCausalId}, #{leftCodebaseUser}, #{rightCodebaseUser}, #{diff}::jsonb) ON CONFLICT DO NOTHING |] diff --git a/src/Share/Postgres/NameLookups/Ops.hs b/src/Share/Postgres/NameLookups/Ops.hs index 086ed9f6..953236c2 100644 --- a/src/Share/Postgres/NameLookups/Ops.hs +++ b/src/Share/Postgres/NameLookups/Ops.hs @@ -9,8 +9,10 @@ module Share.Postgres.NameLookups.Ops checkBranchHashNameLookupExists, deleteNameLookupsExceptFor, ensureNameLookupForBranchId, - Q.termsWithinNamespace, - Q.typesWithinNamespace, + Q.projectTermsWithinRoot, + Q.projectTypesWithinRoot, + Q.listNameLookupMounts, + projectNamesWithoutLib, ) where @@ -20,6 +22,7 @@ import Data.List.NonEmpty qualified as NonEmpty import Data.Set qualified as Set import Share.Postgres (QueryM) import Share.Postgres qualified as PG +import Share.Postgres.Cursors qualified as Cursor import Share.Postgres.Hashes.Queries qualified as HashQ import Share.Postgres.IDs import Share.Postgres.NameLookups.Conversions qualified as CV @@ -38,6 +41,8 @@ import Unison.Name (Name) import Unison.Name qualified as Name import Unison.NameSegment.Internal (NameSegment (..)) import Unison.NameSegment.Internal qualified as NameSegment +import Unison.Names (Names) +import Unison.Names qualified as Names import Unison.Reference qualified as V1 import Unison.Referent qualified as V1 import Unison.Util.List qualified as List @@ -187,3 +192,13 @@ ensureNameLookupForBranchId :: (QueryM m) => BranchHashId -> m NameLookupReceipt ensureNameLookupForBranchId branchHashId = do PG.execute_ [PG.sql| SELECT ensure_name_lookup(#{branchHashId}) |] pure $ UnsafeNameLookupReceipt + +-- | Build a 'Names' for all definitions within the given root, without any dependencies. +-- Note: This loads everything into memory at once, so avoid this and prefer streaming when possible. +projectNamesWithoutLib :: (QueryM m) => NameLookupReceipt -> BranchHashId -> m Names +projectNamesWithoutLib !nlr rootBranchHashId = do + termNamesCursor <- Q.projectTermsWithinRootV1 nlr rootBranchHashId + allTerms <- Cursor.foldBatched termNamesCursor 1000 (pure . toList) + typesCursor <- (Q.projectTypesWithinRoot nlr rootBranchHashId) + allTypes <- Cursor.foldBatched typesCursor 1000 (pure . toList) + pure $ Names.fromTermsAndTypes allTerms allTypes diff --git a/src/Share/Postgres/NameLookups/Queries.hs b/src/Share/Postgres/NameLookups/Queries.hs index ee9c194b..92878603 100644 --- a/src/Share/Postgres/NameLookups/Queries.hs +++ b/src/Share/Postgres/NameLookups/Queries.hs @@ -12,8 +12,9 @@ module Share.Postgres.NameLookups.Queries FuzzySearchScore, -- * Cursors - termsWithinNamespace, - typesWithinNamespace, + projectTermsWithinRoot, + projectTermsWithinRootV1, + projectTypesWithinRoot, -- * Name lookup management listNameLookupMounts, @@ -35,8 +36,11 @@ import Share.Postgres.NameLookups.Types import Share.Postgres.Refs.Types (PGReference, PGReferent, referenceFields, referentFields) import Share.Prelude import U.Codebase.Reference (Reference) -import U.Codebase.Referent (ConstructorType, Referent) +import U.Codebase.Referent (ConstructorType) +import U.Codebase.Referent qualified as V2 +import Unison.Codebase.SqliteCodebase.Conversions qualified as Cv import Unison.Name (Name) +import Unison.Referent qualified as V1 import Unison.Util.Monoid qualified as Monoid -- | Get the list of term names and suffixifications for a given Referent within a given namespace. @@ -463,20 +467,31 @@ toNamespacePrefix = \case toReversedNamePrefix :: ReversedName -> Text toReversedNamePrefix suffix = Text.intercalate "." (into @[Text] suffix) <> "." -termsWithinNamespace :: NameLookupReceipt -> BranchHashId -> Transaction e (PGCursor (Name, Referent)) -termsWithinNamespace !_nlReceipt bhId = do - Cursors.newRowCursor @(NamedRef Referent) +-- | Get a cursor over all non-lib terms within the given root branch. +projectTermsWithinRootV1 :: (QueryM m) => NameLookupReceipt -> BranchHashId -> m (PGCursor (Name, V1.Referent)) +projectTermsWithinRootV1 !_nlReceipt bhId = do + Cursors.newRowCursor @(NamedRef (V2.Referent PG.:. PG.Only (Maybe ConstructorType))) "termsForSearchSyncCursor" [sql| - SELECT reversed_name, referent_builtin, referent_component_hash.base32, referent_component_index, referent_constructor_index + SELECT reversed_name, referent_builtin, referent_component_hash.base32, referent_component_index, referent_constructor_index, referent_constructor_type FROM scoped_term_name_lookup LEFT JOIN component_hashes referent_component_hash ON referent_component_hash.id = referent_component_hash_id WHERE root_branch_hash_id = #{bhId} |] - <&> fmap (\NamedRef {reversedSegments, ref} -> (reversedNameToName reversedSegments, ref)) + <&> fmap + ( \NamedRef {reversedSegments, ref} -> (reversedNameToName reversedSegments, referent2to1 ref) + ) + +-- | Get a cursor over all non-lib terms within the given root branch. +projectTermsWithinRoot :: (QueryM m) => NameLookupReceipt -> BranchHashId -> m (PGCursor (Name, V2.Referent)) +projectTermsWithinRoot !nlr bhId = projectTermsWithinRootV1 nlr bhId <&> fmap (over _2 Cv.referent1to2) + +referent2to1 :: (HasCallStack) => (V2.Referent PG.:. PG.Only (Maybe V2.ConstructorType)) -> V1.Referent +referent2to1 (r PG.:. PG.Only mayCT) = Cv.referent2to1UsingCT (fromMaybe (error "Required constructor type for constructor but it was null") mayCT) r -typesWithinNamespace :: NameLookupReceipt -> BranchHashId -> Transaction e (PGCursor (Name, Reference)) -typesWithinNamespace !_nlReceipt bhId = do +-- | Get a cursor over all non-lib types within the given root branch. +projectTypesWithinRoot :: (QueryM m) => NameLookupReceipt -> BranchHashId -> m (PGCursor (Name, Reference)) +projectTypesWithinRoot !_nlReceipt bhId = do Cursors.newRowCursor @(NamedRef Reference) "typesForSearchSyncCursor" [sql| diff --git a/src/Unison/PrettyPrintEnvDecl/Postgres.hs b/src/Share/PrettyPrintEnvDecl/Postgres.hs similarity index 95% rename from src/Unison/PrettyPrintEnvDecl/Postgres.hs rename to src/Share/PrettyPrintEnvDecl/Postgres.hs index 7e384e2f..fe93a337 100644 --- a/src/Unison/PrettyPrintEnvDecl/Postgres.hs +++ b/src/Share/PrettyPrintEnvDecl/Postgres.hs @@ -1,4 +1,4 @@ -module Unison.PrettyPrintEnvDecl.Postgres (ppedForReferences) where +module Share.PrettyPrintEnvDecl.Postgres (ppedForReferences) where import Control.Lens import Data.Map qualified as Map @@ -37,7 +37,7 @@ ppedForReferences namesPerspective refs = do let typeNames' = typeNames <&> \(fqn, suffixed) -> (fqn, suffixed, ref) pure $ ([], typeNames') --- | Given a list of names and a list of names with suffixes, return a PrettyPrintEnvDecl +-- | Given a list of (fqn, suffixified, ref), return a PrettyPrintEnvDecl -- Note: this type of PPE does not (yet) support hash qualifying conflicted names, because this -- would require running additional queries when fetching the names. ppedFromNamesWithSuffixes :: [(Name, Name, V1.Referent)] -> [(Name, Name, V1.Reference)] -> PPED.PrettyPrintEnvDecl diff --git a/src/Share/Web/Share/Contributions/Impl.hs b/src/Share/Web/Share/Contributions/Impl.hs index a32cf5e0..04ac72b7 100644 --- a/src/Share/Web/Share/Contributions/Impl.hs +++ b/src/Share/Web/Share/Contributions/Impl.hs @@ -278,21 +278,20 @@ contributionDiffEndpoint (AuthN.MaybeAuthedUserID mayCallerUserId) userHandle pr newPBSH <- Codebase.runCodebaseTransactionOrRespondError newCodebase $ do lift $ Q.projectBranchShortHandByBranchId newBranchId `whenNothingM` throwError (EntityMissing (ErrorID "branch:missing") "Source branch not found") - let oldCausalId = fromMaybe oldBranchCausalId bestCommonAncestorCausalId - let cacheKeys = [IDs.toText contributionId, IDs.toText newPBSH, IDs.toText oldPBSH, Caching.causalIdCacheKey newBranchCausalId, Caching.causalIdCacheKey oldCausalId] + let cacheKeys = [IDs.toText contributionId, IDs.toText newPBSH, IDs.toText oldPBSH, Caching.causalIdCacheKey newBranchCausalId, Caching.causalIdCacheKey oldBranchCausalId] Caching.cachedResponse authZReceipt "contribution-diff" cacheKeys do - namespaceDiff <- respondExceptT (Diffs.diffCausals authZReceipt (oldCodebase, oldCausalId) (newCodebase, newBranchCausalId)) - (newBranchCausalHash, oldCausalHash) <- PG.runTransaction $ do + namespaceDiff <- respondExceptT (Diffs.diffCausals authZReceipt (oldCodebase, oldBranchCausalId) (newCodebase, newBranchCausalId) bestCommonAncestorCausalId) + (newBranchCausalHash, oldBranchCausalHash) <- PG.runTransaction do newBranchCausalHash <- CausalQ.expectCausalHashesByIdsOf id newBranchCausalId - oldCausalHash <- CausalQ.expectCausalHashesByIdsOf id oldCausalId - pure (newBranchCausalHash, oldCausalHash) + oldBranchCausalHash <- CausalQ.expectCausalHashesByIdsOf id oldBranchCausalId + pure (newBranchCausalHash, oldBranchCausalHash) pure $ ShareNamespaceDiffResponse { project = projectShorthand, newRef = IDs.IsBranchShortHand $ IDs.projectBranchShortHandToBranchShortHand newPBSH, newRefHash = Just $ PrefixedHash newBranchCausalHash, oldRef = IDs.IsBranchShortHand $ IDs.projectBranchShortHandToBranchShortHand oldPBSH, - oldRefHash = Just $ PrefixedHash oldCausalHash, + oldRefHash = Just $ PrefixedHash oldBranchCausalHash, diff = namespaceDiff } where @@ -329,8 +328,11 @@ contributionDiffTermsEndpoint (AuthN.MaybeAuthedUserID mayCallerUserId) userHand let cacheKeys = [IDs.toText contributionId, IDs.toText newPBSH, IDs.toText oldPBSH, Caching.causalIdCacheKey newBranchCausalId, Caching.causalIdCacheKey oldCausalId, Name.toText oldTermName, Name.toText newTermName] Caching.cachedResponse authZReceipt "contribution-diff-terms" cacheKeys do (oldBranchHashId, newBranchHashId) <- PG.runTransaction $ CausalQ.expectNamespaceIdsByCausalIdsOf both (oldCausalId, newBranchCausalId) - termDiff <- respondExceptT (Diffs.diffTerms authZReceipt (oldCodebase, oldBranchHashId, oldTermName) (newCodebase, newBranchHashId, newTermName)) - pure $ + termDiff <- + respondExceptT (Diffs.diffTerms authZReceipt (oldCodebase, oldBranchHashId, oldTermName) (newCodebase, newBranchHashId, newTermName)) + -- Not exactly a "term not found" - one or both term names is a constructor - but probably ok for now + `whenNothingM` respondError (EntityMissing (ErrorID "term:missing") "Term not found") + pure ShareTermDiffResponse { project = projectShorthand, oldBranch = IDs.IsBranchShortHand $ IDs.projectBranchShortHandToBranchShortHand oldPBSH, diff --git a/src/Share/Web/Share/Diffs/Impl.hs b/src/Share/Web/Share/Diffs/Impl.hs index 604e4b44..e2908b3f 100644 --- a/src/Share/Web/Share/Diffs/Impl.hs +++ b/src/Share/Web/Share/Diffs/Impl.hs @@ -1,6 +1,5 @@ module Share.Web.Share.Diffs.Impl - ( diffNamespaces, - diffCausals, + ( diffCausals, diffTerms, diffTypes, ) @@ -19,25 +18,32 @@ import Data.Text.Lazy qualified as TL import Data.Text.Lazy.Encoding qualified as TL import Share.App (AppM) import Share.Codebase qualified as Codebase -import Share.NamespaceDiffs (DefinitionDiff (..), DefinitionDiffKind (..), DiffAtPath (..), NamespaceDiffError (..), NamespaceTreeDiff) +import Share.NamespaceDiffs (DefinitionDiff (..), DefinitionDiffKind (..), DiffAtPath (..), GNamespaceAndLibdepsDiff, GNamespaceTreeDiff, NamespaceAndLibdepsDiff, NamespaceDiffError (..), NamespaceTreeDiff) import Share.NamespaceDiffs qualified as NamespaceDiffs import Share.Postgres qualified as PG import Share.Postgres.Causal.Queries qualified as CausalQ import Share.Postgres.Contributions.Queries qualified as ContributionQ -import Share.Postgres.IDs (BranchHashId, CausalId) +import Share.Postgres.Hashes.Queries qualified as HashQ +import Share.Postgres.IDs (BranchHash, BranchHashId, CausalId) import Share.Postgres.NameLookups.Ops qualified as NLOps import Share.Postgres.NameLookups.Ops qualified as NameLookupOps import Share.Postgres.NameLookups.Types (NameLookupReceipt) import Share.Prelude +import Share.PrettyPrintEnvDecl.Postgres qualified as PPEPostgres import Share.Utils.Aeson (PreEncoded (PreEncoded)) import Share.Web.Authorization (AuthZReceipt) import Share.Web.Errors import U.Codebase.Reference qualified as V2Reference -import U.Codebase.Referent qualified as V2Referent +import Unison.Codebase.SqliteCodebase.Conversions (referent1to2) +import Unison.ConstructorReference (ConstructorReference) +import Unison.Merge (DiffOp (..), TwoOrThreeWay (..), TwoWay (..)) +import Unison.Merge qualified as Merge import Unison.Name (Name) import Unison.NameSegment (NameSegment) import Unison.PrettyPrintEnvDecl qualified as PPED -import Unison.PrettyPrintEnvDecl.Postgres qualified as PPEPostgres +import Unison.Reference (TypeReference) +import Unison.Referent (Referent) +import Unison.Referent qualified as Referent import Unison.Server.Backend.DefinitionDiff qualified as DefinitionDiff import Unison.Server.NameSearch.Postgres qualified as PGNameSearch import Unison.Server.Share.Definitions qualified as Definitions @@ -47,117 +53,207 @@ import Unison.Syntax.Name qualified as Name import Unison.Util.Pretty (Width) import UnliftIO qualified -diffNamespaces :: - AuthZReceipt -> - (BranchHashId, NameLookupReceipt) -> - (BranchHashId, NameLookupReceipt) -> - AppM r (Either NamespaceDiffs.NamespaceDiffError (NamespaceDiffs.NamespaceTreeDiff (TermTag, ShortHash) (TypeTag, ShortHash) Name Name Name Name)) -diffNamespaces !_authZReceipt oldNamespacePair newNamespacePair = do - PG.tryRunTransaction $ do - diff <- NamespaceDiffs.diffTreeNamespaces oldNamespacePair newNamespacePair `whenLeftM` throwError - withTermTags <- - ( diff - & unsafePartsOf NamespaceDiffs.namespaceTreeDiffReferents_ - %%~ ( \refs -> do - termTags <- Codebase.termTagsByReferentsOf traversed refs - pure $ zip termTags (refs <&> V2Referent.toShortHash) - ) - ) - withTermTags - & unsafePartsOf NamespaceDiffs.namespaceTreeDiffReferences_ - %%~ ( \refs -> do - typeTags <- Codebase.typeTagsByReferencesOf traversed refs - pure $ zip typeTags (refs <&> V2Reference.toShortHash) - ) - --- | Find the common ancestor between two causals, then diff diffCausals :: AuthZReceipt -> (Codebase.CodebaseEnv, CausalId) -> (Codebase.CodebaseEnv, CausalId) -> - ExceptT NamespaceDiffs.NamespaceDiffError (AppM r) (PreEncoded (NamespaceDiffs.NamespaceTreeDiff (TermTag, ShortHash) (TypeTag, ShortHash) TermDefinition TypeDefinition TermDefinitionDiff TypeDefinitionDiff)) -diffCausals !authZReceipt (oldCodebase, oldCausalId) (newCodebase, newCausalId) = do - -- Ensure name lookups for each thing we're diffing. - -- We do this in two separate transactions to ensure we can still make progress even if we need to build name lookups. - let getOldBranch = PG.runTransaction $ do - oldBranchHashId <- CausalQ.expectNamespaceIdsByCausalIdsOf id oldCausalId - oldBranchNLReceipt <- NLOps.ensureNameLookupForBranchId oldBranchHashId - pure (oldBranchHashId, oldBranchNLReceipt) - - let getNewBranch = PG.runTransaction $ do - newBranchHashId <- CausalQ.expectNamespaceIdsByCausalIdsOf id newCausalId - newNLReceipt <- NLOps.ensureNameLookupForBranchId newBranchHashId - pure (newBranchHashId, newNLReceipt) - ((oldBranchHashId, oldBranchNLReceipt), (newBranchHashId, newNLReceipt)) <- getOldBranch `concurrentExceptT` getNewBranch - (PG.runTransaction $ ContributionQ.getPrecomputedNamespaceDiff (oldCodebase, oldBranchHashId) (newCodebase, newBranchHashId)) - >>= \case - Just diff -> pure $ PreEncoded $ TL.encodeUtf8 $ TL.fromStrict diff - Nothing -> do - diffWithTags <- ExceptT $ PG.tryRunTransaction $ do - diff <- NamespaceDiffs.diffTreeNamespaces (oldBranchHashId, oldBranchNLReceipt) (newBranchHashId, newNLReceipt) `whenLeftM` throwError - withTermTags <- - ( diff - & unsafePartsOf NamespaceDiffs.namespaceTreeDiffReferents_ - %%~ ( \refs -> do - termTags <- Codebase.termTagsByReferentsOf traversed refs - pure $ zip termTags (refs <&> V2Referent.toShortHash) - ) - ) - withTermTags - & unsafePartsOf NamespaceDiffs.namespaceTreeDiffReferences_ - %%~ ( \refs -> do - typeTags <- Codebase.typeTagsByReferencesOf traversed refs - pure $ zip typeTags (refs <&> V2Reference.toShortHash) - ) - diff <- computeUpdatedDefinitionDiffs authZReceipt (oldCodebase, oldBranchHashId) (newCodebase, newBranchHashId) diffWithTags - let encoded = Aeson.encode . RenderedNamespaceDiff $ diff - PG.runTransaction $ ContributionQ.savePrecomputedNamespaceDiff (oldCodebase, oldBranchHashId) (newCodebase, newBranchHashId) (TL.toStrict $ TL.decodeUtf8 encoded) - pure $ PreEncoded encoded + Maybe CausalId -> + ExceptT + NamespaceDiffs.NamespaceDiffError + (AppM r) + ( PreEncoded + ( NamespaceDiffs.NamespaceAndLibdepsDiff + (TermTag, ShortHash) + (TypeTag, ShortHash) + TermDefinition + TypeDefinition + TermDefinitionDiff + TypeDefinitionDiff + BranchHash + ) + ) +diffCausals !authZReceipt (oldCodebase, oldCausalId) (newCodebase, newCausalId) maybeLcaCausalId = do + -- Ensure name lookups for the things we're diffing. + -- We do this in separate transactions to ensure we can still make progress even if we need to build name lookups. + let getBranch :: CausalId -> ExceptT NamespaceDiffs.NamespaceDiffError (AppM r) (BranchHashId, NameLookupReceipt) + getBranch causalId = + PG.runTransaction do + branchHashId <- CausalQ.expectNamespaceIdsByCausalIdsOf id causalId + nameLookupReceipt <- NLOps.ensureNameLookupForBranchId branchHashId + pure (branchHashId, nameLookupReceipt) + (((oldBranchHashId, oldBranchNLReceipt), (newBranchHashId, newBranchNLReceipt))) <- + getBranch oldCausalId `concurrentExceptT` getBranch newCausalId + PG.runTransaction (ContributionQ.getPrecomputedNamespaceDiff (oldCodebase, oldCausalId) (newCodebase, newCausalId)) >>= \case + Just diff -> pure $ PreEncoded $ TL.encodeUtf8 $ TL.fromStrict diff + Nothing -> do + (maybeLcaBranchHashId, maybeLcaBranchNLReceipt) <- + case maybeLcaCausalId of + Just lcaCausalId -> do + (lcaBranchHashId, lcaBranchNLReceipt) <- getBranch lcaCausalId + pure (Just lcaBranchHashId, Just lcaBranchNLReceipt) + Nothing -> pure (Nothing, Nothing) + diff0 <- + ExceptT do + PG.tryRunTransaction do + -- Do the initial 3-way namespace diff + diff :: + GNamespaceAndLibdepsDiff + NameSegment + Referent + TypeReference + Name + Name + Name + Name + BranchHashId <- + NamespaceDiffs.computeThreeWayNamespaceDiff + TwoWay {alice = oldCodebase, bob = newCodebase} + TwoOrThreeWay {alice = oldBranchHashId, bob = newBranchHashId, lca = maybeLcaBranchHashId} + TwoOrThreeWay {alice = oldBranchNLReceipt, bob = newBranchNLReceipt, lca = maybeLcaBranchNLReceipt} + -- Resolve the term referents to tag + hash + diff1 :: + GNamespaceAndLibdepsDiff + NameSegment + (TermTag, ShortHash) + TypeReference + Name + Name + Name + Name + BranchHashId <- + diff + & unsafePartsOf (NamespaceDiffs.namespaceAndLibdepsDiffDefns_ . NamespaceDiffs.namespaceTreeDiffReferents_) + %%~ \refs -> do + termTags <- Codebase.termTagsByReferentsOf (\f -> traverse (f . referent1to2)) refs + pure $ zip termTags (refs <&> Referent.toShortHash) + -- Resolve the type references to tag + hash + diff2 :: + GNamespaceAndLibdepsDiff + NameSegment + (TermTag, ShortHash) + (TypeTag, ShortHash) + Name + Name + Name + Name + BranchHashId <- + diff1 + & unsafePartsOf (NamespaceDiffs.namespaceAndLibdepsDiffDefns_ . NamespaceDiffs.namespaceTreeDiffReferences_) + %%~ \refs -> do + typeTags <- Codebase.typeTagsByReferencesOf traversed refs + pure $ zip typeTags (refs <&> V2Reference.toShortHash) + -- Resolve libdeps branch hash ids to branch hashes + diff3 :: + GNamespaceAndLibdepsDiff + NameSegment + (TermTag, ShortHash) + (TypeTag, ShortHash) + Name + Name + Name + Name + BranchHash <- + HashQ.expectNamespaceHashesByNamespaceHashIdsOf + (NamespaceDiffs.namespaceAndLibdepsDiffLibdeps_ . traversed . traversed) + diff2 + pure diff3 + -- Resolve the actual term/type definitions. Use the LCA as the "old" (because that's what we're rendering the + -- diff relative to, unless there isn't an LCA (unlikely), in which case we fall back on the other branch (we + -- won't have anything classified as an "update" in this case so it doesn't really matter). + diff1 <- + diff0 + & NamespaceDiffs.namespaceAndLibdepsDiffDefns_ + %%~ computeUpdatedDefinitionDiffs + authZReceipt + (oldCodebase, fromMaybe oldBranchHashId maybeLcaBranchHashId) + (newCodebase, newBranchHashId) + let encoded = Aeson.encode (RenderedNamespaceAndLibdepsDiff diff1) + PG.runTransaction $ + ContributionQ.savePrecomputedNamespaceDiff + (oldCodebase, oldCausalId) + (newCodebase, newCausalId) + (TL.toStrict $ TL.decodeUtf8 encoded) + pure $ PreEncoded encoded computeUpdatedDefinitionDiffs :: + forall a b r. (Ord a, Ord b) => AuthZReceipt -> (Codebase.CodebaseEnv, BranchHashId) -> (Codebase.CodebaseEnv, BranchHashId) -> - (NamespaceDiffs.NamespaceTreeDiff a b Name Name Name Name) -> - ExceptT NamespaceDiffError (AppM r) (NamespaceDiffs.NamespaceTreeDiff a b TermDefinition TypeDefinition TermDefinitionDiff TypeDefinitionDiff) -computeUpdatedDefinitionDiffs !authZReceipt (fromCodebase, fromBHId) (toCodebase, toBHId) diff = do - withTermDiffs <- - diff - & NamespaceDiffs.namespaceTreeDiffTermDiffs_ - %%~ ( \name -> - diffTerms authZReceipt (fromCodebase, fromBHId, name) (toCodebase, toBHId, name) - ) - >>= NamespaceDiffs.namespaceTreeTermDiffKinds_ %%~ renderDiffKind getTermDefinition - withTermDiffs - & NamespaceDiffs.namespaceTreeDiffTypeDiffs_ - %%~ ( \name -> - diffTypes authZReceipt (fromCodebase, fromBHId, name) (toCodebase, toBHId, name) - ) - >>= NamespaceDiffs.namespaceTreeTypeDiffKinds_ %%~ renderDiffKind getTypeDefinition + GNamespaceTreeDiff NameSegment a b Name Name Name Name -> + ExceptT + NamespaceDiffError + (AppM r) + (NamespaceDiffs.NamespaceTreeDiff a b TermDefinition TypeDefinition TermDefinitionDiff TypeDefinitionDiff) +computeUpdatedDefinitionDiffs !authZReceipt (fromCodebase, fromBHId) (toCodebase, toBHId) diff0 = do + diff1 <- + NamespaceDiffs.witherNamespaceTreeDiffTermDiffs + (\name -> diffTerms authZReceipt (fromCodebase, fromBHId, name) (toCodebase, toBHId, name)) + diff0 + diff2 <- + NamespaceDiffs.witherNamespaceTreeTermDiffKinds + (throwAwayConstructorDiffs . renderDiffKind (ExceptT . fmap sequence . getTermDefinition)) + diff1 + diff3 <- + NamespaceDiffs.namespaceTreeDiffTypeDiffs_ + (\name -> diffTypes authZReceipt (fromCodebase, fromBHId, name) (toCodebase, toBHId, name)) + diff2 + diff4 <- + NamespaceDiffs.namespaceTreeTypeDiffKinds_ + (renderDiffKind getTypeDefinition) + diff3 + pure (NamespaceDiffs.compressNameTree diff4) where notFound name t = MissingEntityError $ EntityMissing (ErrorID "definition-not-found") (t <> ": Definition not found: " <> Name.toText name) + + renderDiffKind :: + forall diff m r x. + (Monad m) => + ((Codebase.CodebaseEnv, BranchHashId, Name) -> m (Maybe x)) -> + DefinitionDiffKind r Name diff -> + ExceptT NamespaceDiffError m (DefinitionDiffKind r x diff) renderDiffKind getter = \case Added r name -> Added r <$> (lift (getter (toCodebase, toBHId, name)) `whenNothingM` throwError (notFound name "Added")) NewAlias r existingNames name -> NewAlias r existingNames <$> (lift (getter (toCodebase, toBHId, name)) `whenNothingM` throwError (notFound name "NewAlias")) Removed r name -> Removed r <$> (lift (getter (fromCodebase, fromBHId, name)) `whenNothingM` throwError (notFound name "Removed")) Updated oldRef newRef diff -> pure $ Updated oldRef newRef diff + Propagated oldRef newRef diff -> pure $ Propagated oldRef newRef diff RenamedTo r names name -> RenamedTo r names <$> (lift (getter (fromCodebase, fromBHId, name)) `whenNothingM` throwError (notFound name "RenamedTo")) RenamedFrom r names name -> RenamedFrom r names <$> (lift (getter (toCodebase, toBHId, name)) `whenNothingM` throwError (notFound name "RenamedFrom")) + throwAwayConstructorDiffs :: + ExceptT + NamespaceDiffError + (ExceptT ConstructorReference (AppM r)) + (DefinitionDiffKind a TermDefinition TermDefinitionDiff) -> + ExceptT + NamespaceDiffError + (AppM r) + (Maybe (DefinitionDiffKind a TermDefinition TermDefinitionDiff)) + throwAwayConstructorDiffs m = + lift (runExceptT (runExceptT m)) >>= \case + Left _ref -> pure Nothing + Right (Left err) -> throwError err + Right (Right diff) -> pure (Just diff) + diffTerms :: AuthZReceipt -> (Codebase.CodebaseEnv, BranchHashId, Name) -> (Codebase.CodebaseEnv, BranchHashId, Name) -> - ExceptT NamespaceDiffError (AppM r) TermDefinitionDiff + ExceptT NamespaceDiffError (AppM r) (Maybe TermDefinitionDiff) diffTerms !_authZReceipt old@(_, _, oldName) new@(_, _, newName) = do let getOldTerm = lift (getTermDefinition old) `whenNothingM` throwError (MissingEntityError $ EntityMissing (ErrorID "term-not-found") ("'From' term not found: " <> Name.toText oldName)) let getNewTerm = lift (getTermDefinition new) `whenNothingM` throwError (MissingEntityError $ EntityMissing (ErrorID "term-not-found") ("'To' term not found: " <> Name.toText newName)) - (oldTerm, newTerm) <- getOldTerm `concurrentExceptT` getNewTerm - let termDiffDisplayObject = DefinitionDiff.diffDisplayObjects (termDefinition oldTerm) (termDefinition newTerm) - pure $ TermDefinitionDiff {left = oldTerm, right = newTerm, diff = termDiffDisplayObject} + (getOldTerm `concurrentExceptT` getNewTerm) >>= \case + (Right oldTerm, Right newTerm) -> do + let termDiffDisplayObject = DefinitionDiff.diffDisplayObjects (termDefinition oldTerm) (termDefinition newTerm) + pure (Just TermDefinitionDiff {left = oldTerm, right = newTerm, diff = termDiffDisplayObject}) + -- For later: decide how to render a constructor-to-term or constructor-to-constructor diff + -- Just dropping them from the diff for now + _ -> pure Nothing -getTermDefinition :: (Codebase.CodebaseEnv, BranchHashId, Name) -> AppM r (Maybe TermDefinition) +getTermDefinition :: (Codebase.CodebaseEnv, BranchHashId, Name) -> AppM r (Maybe (Either ConstructorReference TermDefinition)) getTermDefinition (codebase, bhId, name) = do let perspective = mempty (namesPerspective, Identity relocatedName) <- PG.runTransaction $ NameLookupOps.relocateToNameRoot perspective (Identity name) bhId @@ -199,10 +295,16 @@ getTypeDefinition (codebase, bhId, name) = do renderWidth :: Width renderWidth = 80 -newtype RenderedNamespaceDiff = RenderedNamespaceDiff (NamespaceTreeDiff (TermTag, ShortHash) (TypeTag, ShortHash) TermDefinition TypeDefinition TermDefinitionDiff TypeDefinitionDiff) +newtype RenderedNamespaceAndLibdepsDiff + = RenderedNamespaceAndLibdepsDiff + (NamespaceAndLibdepsDiff (TermTag, ShortHash) (TypeTag, ShortHash) TermDefinition TypeDefinition TermDefinitionDiff TypeDefinitionDiff BranchHash) -instance ToJSON RenderedNamespaceDiff where - toJSON (RenderedNamespaceDiff diffs) = namespaceTreeDiffJSON diffs +instance ToJSON RenderedNamespaceAndLibdepsDiff where + toJSON (RenderedNamespaceAndLibdepsDiff diff) = + object + [ "defns" .= namespaceTreeDiffJSON diff.defns, + "libdeps" .= libdepsDiffJSON diff.libdeps + ] where text :: Text -> Text text t = t @@ -219,6 +321,9 @@ instance ToJSON RenderedNamespaceDiff where Updated (oldTag, oldRef) (newTag, newRef) diffVal -> let contents = object ["oldHash" .= oldRef, "newHash" .= newRef, "shortName" .= shortName, "fullName" .= fqn, "oldTag" .= oldTag, "newTag" .= newTag, "diff" .= diffVal] in (newTag, object ["tag" .= text "Updated", "contents" .= contents]) + Propagated (oldTag, oldRef) (newTag, newRef) diffVal -> + let contents = object ["oldHash" .= oldRef, "newHash" .= newRef, "shortName" .= shortName, "fullName" .= fqn, "oldTag" .= oldTag, "newTag" .= newTag, "diff" .= diffVal] + in (newTag, object ["tag" .= text "Propagated", "contents" .= contents]) RenamedTo (defnTag, r) newNames rendered -> let contents = object ["oldShortName" .= shortName, "oldFullName" .= fqn, "newNames" .= newNames, "hash" .= r, "rendered" .= rendered] in (defnTag, object ["tag" .= text "RenamedTo", "contents" .= contents]) @@ -237,7 +342,16 @@ instance ToJSON RenderedNamespaceDiff where typeDefinitionDiffToJSON :: TypeDefinitionDiff -> Value typeDefinitionDiffToJSON (TypeDefinitionDiff {left, right, diff}) = object ["left" .= left, "right" .= right, "diff" .= displayObjectDiffToJSON diff] - namespaceTreeDiffJSON :: NamespaceTreeDiff (TermTag, ShortHash) (TypeTag, ShortHash) TermDefinition TypeDefinition TermDefinitionDiff TypeDefinitionDiff -> Value + + namespaceTreeDiffJSON :: + NamespaceTreeDiff + (TermTag, ShortHash) + (TypeTag, ShortHash) + TermDefinition + TypeDefinition + TermDefinitionDiff + TypeDefinitionDiff -> + Value namespaceTreeDiffJSON (diffs Cofree.:< children) = let changesJSON = diffs @@ -257,7 +371,7 @@ instance ToJSON RenderedNamespaceDiff where & fmap (\(tag, dJSON) -> object ["tag" .= tag, "contents" .= dJSON]) ) ) - & toJSON @([Value]) + & toJSON @[Value] childrenJSON = children & Map.toList @@ -270,6 +384,34 @@ instance ToJSON RenderedNamespaceDiff where "children" .= childrenJSON ] + libdepsDiffJSON :: Map NameSegment (DiffOp BranchHash) -> Value + libdepsDiffJSON = + Map.toList + >>> map + ( \(name, op) -> + case op of + DiffOp'Add hash -> + object + [ "hash" .= hash, + "name" .= name, + "tag" .= ("Added" :: Text) + ] + DiffOp'Delete hash -> + object + [ "hash" .= hash, + "name" .= name, + "tag" .= ("Removed" :: Text) + ] + DiffOp'Update Merge.Updated {old, new} -> + object + [ "name" .= name, + "newHash" .= new, + "oldHash" .= old, + "tag" .= ("Updated" :: Text) + ] + ) + >>> toJSON @[Value] + concurrentExceptT :: (MonadUnliftIO m) => ExceptT e m a -> ExceptT e m b -> ExceptT e m (a, b) concurrentExceptT a b = do (ea, eb) <- lift $ UnliftIO.concurrently (runExceptT a) (runExceptT b) diff --git a/src/Share/Web/Share/Diffs/Types.hs b/src/Share/Web/Share/Diffs/Types.hs index c2e83f7c..3ac48952 100644 --- a/src/Share/Web/Share/Diffs/Types.hs +++ b/src/Share/Web/Share/Diffs/Types.hs @@ -4,14 +4,15 @@ module Share.Web.Share.Diffs.Types where import Data.Aeson import Share.IDs -import Share.NamespaceDiffs (NamespaceTreeDiff) -import Share.Postgres.IDs (CausalHash) +import Share.NamespaceDiffs (NamespaceAndLibdepsDiff) +import Share.Postgres.IDs (BranchHash, CausalHash) import Share.Prelude import Share.Utils.Aeson (PreEncoded) import Unison.Server.Types (DisplayObjectDiff (..), TermDefinition, TermDefinitionDiff (..), TermTag, TypeDefinition, TypeDefinitionDiff (..), TypeTag) import Unison.ShortHash (ShortHash) -type ShareNamespaceDiff = NamespaceTreeDiff (TermTag, ShortHash) (TypeTag, ShortHash) TermDefinition TypeDefinition TermDefinitionDiff TypeDefinitionDiff +type ShareNamespaceDiff = + NamespaceAndLibdepsDiff (TermTag, ShortHash) (TypeTag, ShortHash) TermDefinition TypeDefinition TermDefinitionDiff TypeDefinitionDiff BranchHash data ShareNamespaceDiffResponse = ShareNamespaceDiffResponse { project :: ProjectShortHand, diff --git a/src/Share/Web/Share/Projects/Impl.hs b/src/Share/Web/Share/Projects/Impl.hs index 8e3539ba..d75eac36 100644 --- a/src/Share/Web/Share/Projects/Impl.hs +++ b/src/Share/Web/Share/Projects/Impl.hs @@ -161,16 +161,17 @@ diffNamespacesEndpoint (AuthN.MaybeAuthedUserID callerUserId) userHandle project let cacheKeys = [IDs.toText projectId, IDs.toText oldShortHand, IDs.toText newShortHand, Caching.causalIdCacheKey oldCausalId, Caching.causalIdCacheKey newCausalId] Caching.cachedResponse authZReceipt "project-diff-namespaces" cacheKeys do - (ancestorCausalId, ancestorCausalHash, newCausalHash) <- PG.runTransaction $ do - ancestorCausalId <- fromMaybe oldCausalId <$> CausalQ.bestCommonAncestor oldCausalId newCausalId - (ancestorCausalHash, newCausalHash) <- CausalQ.expectCausalHashesByIdsOf both (ancestorCausalId, newCausalId) - pure (ancestorCausalId, ancestorCausalHash, newCausalHash) - namespaceDiff <- respondExceptT (Diffs.diffCausals authZReceipt (oldCodebase, ancestorCausalId) (newCodebase, newCausalId)) - pure $ + (oldCausalHash, newCausalHash, maybeLcaCausalId) <- + PG.runTransaction do + (oldCausalHash, newCausalHash) <- CausalQ.expectCausalHashesByIdsOf each (oldCausalId, newCausalId) + maybeLcaCausalId <- CausalQ.bestCommonAncestor oldCausalId newCausalId + pure (oldCausalHash, newCausalHash, maybeLcaCausalId) + namespaceDiff <- respondExceptT (Diffs.diffCausals authZReceipt (oldCodebase, oldCausalId) (newCodebase, newCausalId) maybeLcaCausalId) + pure ShareNamespaceDiffResponse { project = projectShortHand, oldRef = oldShortHand, - oldRefHash = Just $ PrefixedHash ancestorCausalHash, + oldRefHash = Just $ PrefixedHash oldCausalHash, newRef = newShortHand, newRefHash = Just $ PrefixedHash newCausalHash, diff = namespaceDiff @@ -198,7 +199,10 @@ projectDiffTermsEndpoint (AuthN.MaybeAuthedUserID callerUserId) userHandle proje let cacheKeys = [IDs.toText projectId, IDs.toText oldShortHand, IDs.toText newShortHand, Caching.branchIdCacheKey oldBhId, Caching.branchIdCacheKey newBhId, Name.toText oldTermName, Name.toText newTermName] Caching.cachedResponse authZReceipt "project-diff-terms" cacheKeys do - termDiff <- respondExceptT (Diffs.diffTerms authZReceipt (oldCodebase, oldBhId, oldTermName) (newCodebase, newBhId, newTermName)) + termDiff <- + respondExceptT (Diffs.diffTerms authZReceipt (oldCodebase, oldBhId, oldTermName) (newCodebase, newBhId, newTermName)) + -- Not exactly a "term not found" - one or both term names is a constructor - but probably ok for now + `whenNothingM` respondError (EntityMissing (ErrorID "term:missing") "Term not found") pure $ ShareTermDiffResponse { project = projectShortHand, diff --git a/src/Unison/Server/Share/DefinitionSummary.hs b/src/Unison/Server/Share/DefinitionSummary.hs index 51a409f3..c01dfebe 100644 --- a/src/Unison/Server/Share/DefinitionSummary.hs +++ b/src/Unison/Server/Share/DefinitionSummary.hs @@ -24,6 +24,7 @@ import Share.Postgres.Hashes.Queries qualified as HashQ import Share.Postgres.IDs (BranchHashId, CausalId) import Share.Postgres.NameLookups.Ops qualified as NLOps import Share.Postgres.NameLookups.Types qualified as NameLookups +import Share.PrettyPrintEnvDecl.Postgres qualified as PPEPostgres import U.Codebase.Referent qualified as V2Referent import Unison.Codebase.Editor.DisplayObject (DisplayObject (..)) import Unison.Codebase.Path qualified as Path @@ -33,15 +34,12 @@ import Unison.Name (Name) import Unison.NameSegment.Internal qualified as NameSegment import Unison.Parser.Ann (Ann) import Unison.Prelude -import Unison.PrettyPrintEnvDecl.Postgres qualified as PPEPostgres import Unison.Reference (Reference) import Unison.Reference qualified as Reference import Unison.Referent (Referent) import Unison.Server.Backend (BackendError (..)) import Unison.Server.Share.DefinitionSummary.Types (TermSummary (..), TypeSummary (..)) -import Unison.Server.Types - ( mayDefaultWidth, - ) +import Unison.Server.Types (mayDefaultWidth) import Unison.Symbol (Symbol) import Unison.Type qualified as Type import Unison.Util.Pretty (Width) diff --git a/src/Unison/Server/Share/Definitions.hs b/src/Unison/Server/Share/Definitions.hs index 427de221..d51d671c 100644 --- a/src/Unison/Server/Share/Definitions.hs +++ b/src/Unison/Server/Share/Definitions.hs @@ -26,10 +26,12 @@ import Share.Postgres.IDs (CausalId) import Share.Postgres.NameLookups.Ops qualified as NameLookupOps import Share.Postgres.NameLookups.Types qualified as NL import Share.Prelude +import Share.PrettyPrintEnvDecl.Postgres qualified as PPEPostgres import Share.Utils.Caching.JSON qualified as Caching import Unison.Codebase.Editor.DisplayObject (DisplayObject) import Unison.Codebase.Path (Path) import Unison.Codebase.Path qualified as Path +import Unison.ConstructorReference (ConstructorReference) import Unison.ConstructorReference qualified as ConstructorReference import Unison.DataDeclaration qualified as DD import Unison.DataDeclaration.Dependencies qualified as DD @@ -40,7 +42,6 @@ import Unison.Name (Name) import Unison.Parser.Ann (Ann) import Unison.PrettyPrintEnv qualified as PPE import Unison.PrettyPrintEnvDecl qualified as PPED -import Unison.PrettyPrintEnvDecl.Postgres qualified as PPEPostgres import Unison.Reference (TermReference, TypeReference) import Unison.Reference qualified as Reference import Unison.Reference qualified as V1 @@ -186,16 +187,19 @@ mkDefinitionsForQuery nameSearch query = do SR.Tp' _ r _ -> Just r _ -> Nothing -termDisplayObjectByName :: NameSearch (PG.Transaction e) -> Name -> CodebaseM e (Maybe (TermReference, DisplayObject (Type Symbol Ann) (Term Symbol Ann))) +-- Nothing means not found +-- Just Left means constructor +-- Just Right means term +termDisplayObjectByName :: + NameSearch (PG.Transaction e) -> + Name -> + CodebaseM e (Maybe (Either ConstructorReference (TermReference, DisplayObject (Type Symbol Ann) (Term Symbol Ann)))) termDisplayObjectByName nameSearch name = runMaybeT do refs <- lift . lift $ NameSearch.lookupRelativeHQRefs' (termSearch nameSearch) NS.ExactName (HQ'.NameOnly name) ref <- fmap NESet.findMin . hoistMaybe $ NESet.nonEmptySet refs case ref of - Referent.Ref r -> (r,) <$> lift (Backend.displayTerm r) - Referent.Con _ _ -> - -- TODO: Should we error here or some other sensible thing rather than returning no - -- result? - empty + Referent.Ref r -> Right . (r,) <$> lift (Backend.displayTerm r) + Referent.Con r _ -> pure (Left r) -- | NOTE: If you're displaying many definitions you should probably generate a single PPED to -- share among all of them, it would be more efficient than generating a PPED per definition. @@ -205,16 +209,19 @@ termDefinitionByName :: Width -> CodebaseRuntime -> Name -> - Codebase.CodebaseM e (Maybe TermDefinition) -termDefinitionByName ppedBuilder nameSearch width rt name = runMaybeT $ do - (ref, displayObject) <- MaybeT $ termDisplayObjectByName nameSearch name - let deps = termDisplayObjectLabeledDependencies ref displayObject - pped <- lift $ ppedBuilder deps - let biasedPPED = PPED.biasTo [name] pped - docRefs <- lift $ Docs.docsForDefinitionName nameSearch name - renderedDocs <- lift $ renderDocRefs ppedBuilder width rt docRefs - let (_ref, syntaxDO) = Backend.termsToSyntaxOf (Suffixify False) width pped id (ref, displayObject) - lift $ Backend.mkTermDefinition biasedPPED width ref renderedDocs (syntaxDO) + Codebase.CodebaseM e (Maybe (Either ConstructorReference TermDefinition)) +termDefinitionByName ppedBuilder nameSearch width rt name = runMaybeT do + MaybeT (termDisplayObjectByName nameSearch name) >>= \case + Right (ref, displayObject) -> do + let deps = termDisplayObjectLabeledDependencies ref displayObject + pped <- lift $ ppedBuilder deps + let biasedPPED = PPED.biasTo [name] pped + docRefs <- lift $ Docs.docsForDefinitionName nameSearch name + renderedDocs <- lift $ renderDocRefs ppedBuilder width rt docRefs + let (_ref, syntaxDO) = Backend.termsToSyntaxOf (Suffixify False) width pped id (ref, displayObject) + defn <- lift $ Backend.mkTermDefinition biasedPPED width ref renderedDocs (syntaxDO) + pure (Right defn) + Left ref -> pure (Left ref) termDisplayObjectLabeledDependencies :: TermReference -> DisplayObject (Type Symbol Ann) (Term Symbol Ann) -> (Set LD.LabeledDependency) termDisplayObjectLabeledDependencies termRef displayObject = do diff --git a/src/Unison/Server/Share/FuzzyFind.hs b/src/Unison/Server/Share/FuzzyFind.hs index 12b739f2..164dd936 100644 --- a/src/Unison/Server/Share/FuzzyFind.hs +++ b/src/Unison/Server/Share/FuzzyFind.hs @@ -32,13 +32,13 @@ import Share.Postgres.NameLookups.Queries qualified as Q import Share.Postgres.NameLookups.Types (NamedRef (..), NamesPerspective (..), PathSegments (..)) import Share.Postgres.NameLookups.Types qualified as NameLookups import Share.Prelude +import Share.PrettyPrintEnvDecl.Postgres qualified as PPED import Unison.Codebase.Editor.DisplayObject import Unison.Codebase.Path qualified as Path import Unison.Codebase.ShortCausalHash qualified as SCH import Unison.Codebase.SqliteCodebase.Conversions qualified as Cv import Unison.NameSegment.Internal (NameSegment (..)) import Unison.PrettyPrintEnvDecl qualified as PPED -import Unison.PrettyPrintEnvDecl.Postgres qualified as PPED import Unison.Server.Backend (termEntryLabeledDependencies, typeEntryLabeledDependencies) import Unison.Server.Syntax (SyntaxText) import Unison.Server.Types diff --git a/src/Unison/Server/Share/RenderDoc.hs b/src/Unison/Server/Share/RenderDoc.hs index 8aaebcda..1246dac8 100644 --- a/src/Unison/Server/Share/RenderDoc.hs +++ b/src/Unison/Server/Share/RenderDoc.hs @@ -19,12 +19,12 @@ import Share.Postgres.IDs (CausalId) import Share.Postgres.NameLookups.Ops qualified as NLOps import Share.Postgres.NameLookups.Types (PathSegments (..)) import Share.Prelude +import Share.PrettyPrintEnvDecl.Postgres qualified as PostgresPPE import Share.Utils.Caching.JSON qualified as Caching import U.Codebase.Causal qualified as V2Causal import Unison.Codebase.Path qualified as Path import Unison.LabeledDependency qualified as LD import Unison.NameSegment.Internal (NameSegment (..)) -import Unison.PrettyPrintEnvDecl.Postgres qualified as PostgresPPE import Unison.Reference qualified as Reference import Unison.Server.Doc (Doc) import Unison.Server.Doc qualified as Doc diff --git a/stack.yaml b/stack.yaml index 82528eb7..e0886a17 100644 --- a/stack.yaml +++ b/stack.yaml @@ -32,6 +32,7 @@ packages: - unison/parser-typechecker - unison/unison-core - unison/unison-hashing-v2 +- unison/unison-merge - unison/unison-runtime - unison/unison-share-api - unison/unison-share-projects-api diff --git a/transcripts/share-apis/contribution-diffs/contribution-diff.json b/transcripts/share-apis/contribution-diffs/contribution-diff.json index f9ad6141..db781a63 100644 --- a/transcripts/share-apis/contribution-diffs/contribution-diff.json +++ b/transcripts/share-apis/contribution-diffs/contribution-diff.json @@ -1,614 +1,387 @@ { "body": { "diff": { - "changes": [ - { - "contents": { + "defns": { + "changes": [ + { "contents": { - "aliasFullName": "ATypeAlias", - "aliasShortName": "ATypeAlias", - "hash": "#bbsbe7lolqunqrftm9jeg299caa91r2mlviqic54toilse443ljup5eojm1et3lqv6ni5gsu9l9hpldptga3cp5e0qffhg36gv5u2jo", - "otherNames": [ - "DataAliasMe" - ], - "rendered": { - "bestTypeName": "ATypeAlias", - "defnTypeTag": "Data", - "typeDefinition": { - "contents": [ - { - "annotation": { - "tag": "DataTypeKeyword" + "contents": { + "aliasFullName": "ATypeAlias", + "aliasShortName": "ATypeAlias", + "hash": "#keu02n8is0irijd65cvuos41kukj3f4ni18mmnudrbll2epo6ftd03nt9l0vqc4fvg98198tefgoupco4o0d0gvnigqgr1bmo2neo88", + "otherNames": [ + "DataAliasMe" + ], + "rendered": { + "bestTypeName": "ATypeAlias", + "defnTypeTag": "Data", + "typeDefinition": { + "contents": [ + { + "annotation": { + "tag": "DataTypeKeyword" + }, + "segment": "type" }, - "segment": "type" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "ATypeAlias", - "tag": "HashQualifier" + { + "annotation": null, + "segment": " " }, - "segment": "ATypeAlias" - }, - { - "annotation": { - "tag": "DelimiterChar" + { + "annotation": { + "contents": "ATypeAlias", + "tag": "HashQualifier" + }, + "segment": "ATypeAlias" }, - "segment": " = " - }, - { - "annotation": { - "contents": "#bbsbe7lolqunqrftm9jeg299caa91r2mlviqic54toilse443ljup5eojm1et3lqv6ni5gsu9l9hpldptga3cp5e0qffhg36gv5u2jo#d0", - "tag": "TermReference" + { + "annotation": { + "tag": "DelimiterChar" + }, + "segment": " = " }, - "segment": "B" - } - ], - "tag": "UserObject" - }, - "typeDocs": [], - "typeNames": [ - "ATypeAlias", - "DataAliasMe" - ] - } + { + "annotation": { + "contents": "#keu02n8is0irijd65cvuos41kukj3f4ni18mmnudrbll2epo6ftd03nt9l0vqc4fvg98198tefgoupco4o0d0gvnigqgr1bmo2neo88#d0", + "tag": "TermReference" + }, + "segment": "B" + } + ], + "tag": "UserObject" + }, + "typeDocs": [], + "typeNames": [ + "ATypeAlias", + "DataAliasMe" + ] + } + }, + "tag": "Aliased" }, - "tag": "Aliased" + "tag": "Data" }, - "tag": "Data" - }, - { - "contents": { + { "contents": { - "aliasFullName": "AbilityAlias", - "aliasShortName": "AbilityAlias", - "hash": "#qfgn5crplnhh308pepplqtleojiqhlpveimv0htug2mqbvhnia7qjfcravqlfb8ooos56jo5qq6brr99gg5kj0g5bgllvgn1nesv608", - "otherNames": [ - "AbilityAliasMe" - ], - "rendered": { - "bestTypeName": "AbilityAlias", - "defnTypeTag": "Ability", - "typeDefinition": { - "contents": [ - { - "annotation": { - "tag": "DataTypeKeyword" - }, - "segment": "ability" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "AbilityAlias", - "tag": "HashQualifier" - }, - "segment": "AbilityAlias" - }, - { - "annotation": { - "tag": "ControlKeyword" - }, - "segment": " where" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "#qfgn5crplnhh308pepplqtleojiqhlpveimv0htug2mqbvhnia7qjfcravqlfb8ooos56jo5qq6brr99gg5kj0g5bgllvgn1nesv608#a0", - "tag": "TermReference" - }, - "segment": "abilityAliasMe" - }, - { - "annotation": { - "tag": "TypeAscriptionColon" - }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "tag": "AbilityBraces" + "contents": { + "aliasFullName": "AbilityAlias", + "aliasShortName": "AbilityAlias", + "hash": "#u9m3jehjj8mtrhh4i4fuk545k3pdged9r0egph91irldf4lc0rsmtma9eoakvv9hoeesciebuqd7kfm0vdnk48gi7q3s7edn5omb65o", + "otherNames": [ + "AbilityAliasMe" + ], + "rendered": { + "bestTypeName": "AbilityAlias", + "defnTypeTag": "Ability", + "typeDefinition": { + "contents": [ + { + "annotation": { + "tag": "DataTypeKeyword" + }, + "segment": "ability" }, - "segment": "{" - }, - { - "annotation": { - "contents": "#qfgn5crplnhh308pepplqtleojiqhlpveimv0htug2mqbvhnia7qjfcravqlfb8ooos56jo5qq6brr99gg5kj0g5bgllvgn1nesv608", - "tag": "TypeReference" + { + "annotation": null, + "segment": " " }, - "segment": "AbilityAlias" - }, - { - "annotation": { - "tag": "AbilityBraces" + { + "annotation": { + "contents": "AbilityAlias", + "tag": "HashQualifier" + }, + "segment": "AbilityAlias" }, - "segment": "}" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "##Nat", - "tag": "TypeReference" + { + "annotation": { + "tag": "ControlKeyword" + }, + "segment": " where" }, - "segment": "Nat" - } - ], - "tag": "UserObject" - }, - "typeDocs": [], - "typeNames": [ - "AbilityAlias", - "AbilityAliasMe" - ] - } - }, - "tag": "Aliased" - }, - "tag": "Ability" - }, - { - "contents": { - "contents": { - "fullName": "AbilityDeleteMe", - "hash": "#val3i3ikhjc998qh1lfefhh08ad77f1eshera5d0hnbrp6qpgmfelbfa96pvsc18d5qd5qm7lij5el0raipb3mbjgalkh7g3aujej1o", - "rendered": { - "bestTypeName": "AbilityDeleteMe", - "defnTypeTag": "Ability", - "typeDefinition": { - "contents": [ - { - "annotation": { - "tag": "DataTypeKeyword" + { + "annotation": null, + "segment": "\n" }, - "segment": "ability" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "AbilityDeleteMe", - "tag": "HashQualifier" + { + "annotation": null, + "segment": " " }, - "segment": "AbilityDeleteMe" - }, - { - "annotation": { - "tag": "ControlKeyword" + { + "annotation": { + "contents": "#u9m3jehjj8mtrhh4i4fuk545k3pdged9r0egph91irldf4lc0rsmtma9eoakvv9hoeesciebuqd7kfm0vdnk48gi7q3s7edn5omb65o#a0", + "tag": "TermReference" + }, + "segment": "abilityAliasMe" }, - "segment": " where" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "#val3i3ikhjc998qh1lfefhh08ad77f1eshera5d0hnbrp6qpgmfelbfa96pvsc18d5qd5qm7lij5el0raipb3mbjgalkh7g3aujej1o#a0", - "tag": "TermReference" + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" }, - "segment": "abilityDeleteMe" - }, - { - "annotation": { - "tag": "TypeAscriptionColon" + { + "annotation": null, + "segment": " " }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "tag": "AbilityBraces" + { + "annotation": { + "tag": "AbilityBraces" + }, + "segment": "{" }, - "segment": "{" - }, - { - "annotation": { - "contents": "#val3i3ikhjc998qh1lfefhh08ad77f1eshera5d0hnbrp6qpgmfelbfa96pvsc18d5qd5qm7lij5el0raipb3mbjgalkh7g3aujej1o", - "tag": "TypeReference" + { + "annotation": { + "contents": "#u9m3jehjj8mtrhh4i4fuk545k3pdged9r0egph91irldf4lc0rsmtma9eoakvv9hoeesciebuqd7kfm0vdnk48gi7q3s7edn5omb65o", + "tag": "TypeReference" + }, + "segment": "AbilityAlias" }, - "segment": "AbilityDeleteMe" - }, - { - "annotation": { - "tag": "AbilityBraces" + { + "annotation": { + "tag": "AbilityBraces" + }, + "segment": "}" }, - "segment": "}" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "##Nat", - "tag": "TypeReference" + { + "annotation": null, + "segment": " " }, - "segment": "Nat" - } - ], - "tag": "UserObject" - }, - "typeDocs": [], - "typeNames": [ - "AbilityDeleteMe" - ] + { + "annotation": { + "contents": "##Nat", + "tag": "TypeReference" + }, + "segment": "Nat" + } + ], + "tag": "UserObject" + }, + "typeDocs": [], + "typeNames": [ + "AbilityAlias", + "AbilityAliasMe" + ] + } }, - "shortName": "AbilityDeleteMe" + "tag": "Aliased" }, - "tag": "Removed" + "tag": "Ability" }, - "tag": "Ability" - }, - { - "contents": { + { "contents": { - "fullName": "AbilityNew", - "hash": "#t66tvdfo0l4pqj6hgav05tqifbuld8dc22g4rom3olfqj7b6cfpvf15j7307j8m2fpdsvcgv4ourrltpjutgpu3bh08efu2jl2nfqq0", - "rendered": { - "bestTypeName": "AbilityNew", - "defnTypeTag": "Ability", - "typeDefinition": { - "contents": [ - { - "annotation": { - "tag": "DataTypeKeyword" + "contents": { + "fullName": "AbilityDeleteMe", + "hash": "#i201btc2422jlmnric78btv3kl1palljsgc55mvm6rb9ofdos9u8mh2jd70uev381oiun4todb8vhkvvpteieshbfsot4slo9cgrjcg", + "rendered": { + "bestTypeName": "AbilityDeleteMe", + "defnTypeTag": "Ability", + "typeDefinition": { + "contents": [ + { + "annotation": { + "tag": "DataTypeKeyword" + }, + "segment": "ability" }, - "segment": "ability" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "AbilityNew", - "tag": "HashQualifier" + { + "annotation": null, + "segment": " " }, - "segment": "AbilityNew" - }, - { - "annotation": { - "tag": "ControlKeyword" + { + "annotation": { + "contents": "AbilityDeleteMe", + "tag": "HashQualifier" + }, + "segment": "AbilityDeleteMe" }, - "segment": " where" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "#t66tvdfo0l4pqj6hgav05tqifbuld8dc22g4rom3olfqj7b6cfpvf15j7307j8m2fpdsvcgv4ourrltpjutgpu3bh08efu2jl2nfqq0#a0", - "tag": "TermReference" + { + "annotation": { + "tag": "ControlKeyword" + }, + "segment": " where" }, - "segment": "abilityNew" - }, - { - "annotation": { - "tag": "TypeAscriptionColon" + { + "annotation": null, + "segment": "\n" }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "tag": "AbilityBraces" + { + "annotation": null, + "segment": " " }, - "segment": "{" - }, - { - "annotation": { - "contents": "#t66tvdfo0l4pqj6hgav05tqifbuld8dc22g4rom3olfqj7b6cfpvf15j7307j8m2fpdsvcgv4ourrltpjutgpu3bh08efu2jl2nfqq0", - "tag": "TypeReference" + { + "annotation": { + "contents": "#i201btc2422jlmnric78btv3kl1palljsgc55mvm6rb9ofdos9u8mh2jd70uev381oiun4todb8vhkvvpteieshbfsot4slo9cgrjcg#a0", + "tag": "TermReference" + }, + "segment": "abilityDeleteMe" }, - "segment": "AbilityNew" - }, - { - "annotation": { - "tag": "AbilityBraces" + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" }, - "segment": "}" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "##Text", - "tag": "TypeReference" + { + "annotation": null, + "segment": " " }, - "segment": "Text" - } - ], - "tag": "UserObject" + { + "annotation": { + "tag": "AbilityBraces" + }, + "segment": "{" + }, + { + "annotation": { + "contents": "#i201btc2422jlmnric78btv3kl1palljsgc55mvm6rb9ofdos9u8mh2jd70uev381oiun4todb8vhkvvpteieshbfsot4slo9cgrjcg", + "tag": "TypeReference" + }, + "segment": "AbilityDeleteMe" + }, + { + "annotation": { + "tag": "AbilityBraces" + }, + "segment": "}" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "##Nat", + "tag": "TypeReference" + }, + "segment": "Nat" + } + ], + "tag": "UserObject" + }, + "typeDocs": [], + "typeNames": [ + "AbilityDeleteMe" + ] }, - "typeDocs": [], - "typeNames": [ - "AbilityNew" - ] + "shortName": "AbilityDeleteMe" }, - "shortName": "AbilityNew" + "tag": "Removed" }, - "tag": "Added" + "tag": "Ability" }, - "tag": "Ability" - }, - { - "contents": { + { "contents": { - "hash": "#iqmiiehu802p15ssntohl6l5kedd0j266rh7815s1t10rfe2bp207vh8ccngrlkii7i32h1n080dggr3r89osrq450kv6dj5uuc0o0o", - "newFullName": "AbilityRenamed", - "newShortName": "AbilityRenamed", - "oldNames": [ - "AbilityRenameMe" - ], - "rendered": { - "bestTypeName": "AbilityRenamed", - "defnTypeTag": "Ability", - "typeDefinition": { - "contents": [ - { - "annotation": { - "tag": "DataTypeKeyword" - }, - "segment": "ability" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "AbilityRenamed", - "tag": "HashQualifier" - }, - "segment": "AbilityRenamed" - }, - { - "annotation": { - "tag": "ControlKeyword" - }, - "segment": " where" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "#iqmiiehu802p15ssntohl6l5kedd0j266rh7815s1t10rfe2bp207vh8ccngrlkii7i32h1n080dggr3r89osrq450kv6dj5uuc0o0o#a0", - "tag": "TermReference" - }, - "segment": "abilityRenameMe" - }, - { - "annotation": { - "tag": "TypeAscriptionColon" - }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "tag": "AbilityBraces" + "contents": { + "fullName": "AbilityNew", + "hash": "#n7jj1pvi6a8689nggmnlhmn8hvkjiu4j5563kojf57dcf8dribv5suliht31nbpgc4501h26geepfg5o8jiid45h6ccmf8ogqu39am0", + "rendered": { + "bestTypeName": "AbilityNew", + "defnTypeTag": "Ability", + "typeDefinition": { + "contents": [ + { + "annotation": { + "tag": "DataTypeKeyword" + }, + "segment": "ability" }, - "segment": "{" - }, - { - "annotation": { - "contents": "#iqmiiehu802p15ssntohl6l5kedd0j266rh7815s1t10rfe2bp207vh8ccngrlkii7i32h1n080dggr3r89osrq450kv6dj5uuc0o0o", - "tag": "TypeReference" + { + "annotation": null, + "segment": " " }, - "segment": "AbilityRenamed" - }, - { - "annotation": { - "tag": "AbilityBraces" + { + "annotation": { + "contents": "AbilityNew", + "tag": "HashQualifier" + }, + "segment": "AbilityNew" }, - "segment": "}" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "##Nat", - "tag": "TypeReference" + { + "annotation": { + "tag": "ControlKeyword" + }, + "segment": " where" }, - "segment": "Nat" - } - ], - "tag": "UserObject" - }, - "typeDocs": [], - "typeNames": [ - "AbilityRenamed" - ] - } - }, - "tag": "RenamedFrom" - }, - "tag": "Ability" - }, - { - "contents": { - "contents": { - "diff": { - "diff": { - "diff": { - "contents": [ { - "diffTag": "both", - "elements": [ - { - "annotation": { - "tag": "DataTypeKeyword" - }, - "segment": "ability" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "AbilityUpdateMe", - "tag": "HashQualifier" - }, - "segment": "AbilityUpdateMe" - }, - { - "annotation": { - "tag": "ControlKeyword" - }, - "segment": " where" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": null, - "segment": " " - } - ] + "annotation": null, + "segment": "\n" + }, + { + "annotation": null, + "segment": " " }, { - "diffTag": "annotationChange", - "fromAnnotation": { - "contents": "#0d5ej3mann48uffjea4epi8ss486689gsj46cscorhs3d4j7ohvj9t7ghg05tra792umcmgjr6lgqkskoo3odge7jm2ci91dlmpefcg#a0", + "annotation": { + "contents": "#n7jj1pvi6a8689nggmnlhmn8hvkjiu4j5563kojf57dcf8dribv5suliht31nbpgc4501h26geepfg5o8jiid45h6ccmf8ogqu39am0#a0", "tag": "TermReference" }, - "segment": "abilityUpdateMe", - "toAnnotation": { - "contents": "#qat72tp0lb43gp5pra5rgobup5r24qrc494crqd5pqjddbneiqdn3hq6puo2344nja1v6cp7aps1p0350ug0f1kvo9cp2gu9l31in18#a0", - "tag": "TermReference" - } + "segment": "abilityNew" }, { - "diffTag": "both", - "elements": [ - { - "annotation": { - "tag": "TypeAscriptionColon" - }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "tag": "AbilityBraces" - }, - "segment": "{" - } - ] + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" }, { - "diffTag": "annotationChange", - "fromAnnotation": { - "contents": "#0d5ej3mann48uffjea4epi8ss486689gsj46cscorhs3d4j7ohvj9t7ghg05tra792umcmgjr6lgqkskoo3odge7jm2ci91dlmpefcg", - "tag": "TypeReference" + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "AbilityBraces" }, - "segment": "AbilityUpdateMe", - "toAnnotation": { - "contents": "#qat72tp0lb43gp5pra5rgobup5r24qrc494crqd5pqjddbneiqdn3hq6puo2344nja1v6cp7aps1p0350ug0f1kvo9cp2gu9l31in18", + "segment": "{" + }, + { + "annotation": { + "contents": "#n7jj1pvi6a8689nggmnlhmn8hvkjiu4j5563kojf57dcf8dribv5suliht31nbpgc4501h26geepfg5o8jiid45h6ccmf8ogqu39am0", "tag": "TypeReference" - } + }, + "segment": "AbilityNew" }, { - "diffTag": "both", - "elements": [ - { - "annotation": { - "tag": "AbilityBraces" - }, - "segment": "}" - }, - { - "annotation": null, - "segment": " " - } - ] + "annotation": { + "tag": "AbilityBraces" + }, + "segment": "}" }, { - "diffTag": "old", - "elements": [ - { - "annotation": { - "contents": "##Nat", - "tag": "TypeReference" - }, - "segment": "Nat" - } - ] + "annotation": null, + "segment": " " }, { - "diffTag": "new", - "elements": [ - { - "annotation": { - "contents": "##Text", - "tag": "TypeReference" - }, - "segment": "Text" - } - ] + "annotation": { + "contents": "##Text", + "tag": "TypeReference" + }, + "segment": "Text" } ], "tag": "UserObject" }, - "diffKind": "diff" + "typeDocs": [], + "typeNames": [ + "AbilityNew" + ] }, - "left": { - "bestTypeName": "AbilityUpdateMe", + "shortName": "AbilityNew" + }, + "tag": "Added" + }, + "tag": "Ability" + }, + { + "contents": { + "contents": { + "hash": "#lh3ufh51cghv5sn14ckq9f2urei00i6adqj3d0vovc51c6f18bhauqfjhkm34227ediga6mc5dp58inn4j714rhenig2jsps9ima7do", + "newFullName": "AbilityRenamed", + "newShortName": "AbilityRenamed", + "oldNames": [ + "AbilityRenameMe" + ], + "rendered": { + "bestTypeName": "AbilityRenamed", "defnTypeTag": "Ability", "typeDefinition": { "contents": [ @@ -624,10 +397,10 @@ }, { "annotation": { - "contents": "AbilityUpdateMe", + "contents": "AbilityRenamed", "tag": "HashQualifier" }, - "segment": "AbilityUpdateMe" + "segment": "AbilityRenamed" }, { "annotation": { @@ -645,16 +418,405 @@ }, { "annotation": { - "contents": "#0d5ej3mann48uffjea4epi8ss486689gsj46cscorhs3d4j7ohvj9t7ghg05tra792umcmgjr6lgqkskoo3odge7jm2ci91dlmpefcg#a0", + "contents": "#lh3ufh51cghv5sn14ckq9f2urei00i6adqj3d0vovc51c6f18bhauqfjhkm34227ediga6mc5dp58inn4j714rhenig2jsps9ima7do#a0", "tag": "TermReference" }, - "segment": "abilityUpdateMe" + "segment": "abilityRenameMe" + }, + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "AbilityBraces" + }, + "segment": "{" + }, + { + "annotation": { + "contents": "#lh3ufh51cghv5sn14ckq9f2urei00i6adqj3d0vovc51c6f18bhauqfjhkm34227ediga6mc5dp58inn4j714rhenig2jsps9ima7do", + "tag": "TypeReference" + }, + "segment": "AbilityRenamed" + }, + { + "annotation": { + "tag": "AbilityBraces" + }, + "segment": "}" + }, + { + "annotation": null, + "segment": " " }, { "annotation": { - "tag": "TypeAscriptionColon" + "contents": "##Nat", + "tag": "TypeReference" + }, + "segment": "Nat" + } + ], + "tag": "UserObject" + }, + "typeDocs": [], + "typeNames": [ + "AbilityRenamed" + ] + } + }, + "tag": "RenamedFrom" + }, + "tag": "Ability" + }, + { + "contents": { + "contents": { + "diff": { + "diff": { + "diff": { + "contents": [ + { + "diffTag": "both", + "elements": [ + { + "annotation": { + "tag": "DataTypeKeyword" + }, + "segment": "ability" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "AbilityUpdateMe", + "tag": "HashQualifier" + }, + "segment": "AbilityUpdateMe" + }, + { + "annotation": { + "tag": "ControlKeyword" + }, + "segment": " where" + }, + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": null, + "segment": " " + } + ] + }, + { + "diffTag": "annotationChange", + "fromAnnotation": { + "contents": "#8u70g0vaddp9jm3egoq434qialp8hdnjfh8ah8mqjau0i5lmdikt9qbe491ss53i71976fftb2o90ii6gckvs0i2lhovs1n6h0huhb0#a0", + "tag": "TermReference" + }, + "segment": "abilityUpdateMe", + "toAnnotation": { + "contents": "#nnulmopbjndcs4si1mop30dm01nlum2k7m6j4mmd1df2e63m09lchh2j1gkqd4gua3bl0g3j6hgn76rmc495au8cpr0t83oqoho0sng#a0", + "tag": "TermReference" + } + }, + { + "diffTag": "both", + "elements": [ + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "AbilityBraces" + }, + "segment": "{" + } + ] + }, + { + "diffTag": "annotationChange", + "fromAnnotation": { + "contents": "#8u70g0vaddp9jm3egoq434qialp8hdnjfh8ah8mqjau0i5lmdikt9qbe491ss53i71976fftb2o90ii6gckvs0i2lhovs1n6h0huhb0", + "tag": "TypeReference" + }, + "segment": "AbilityUpdateMe", + "toAnnotation": { + "contents": "#nnulmopbjndcs4si1mop30dm01nlum2k7m6j4mmd1df2e63m09lchh2j1gkqd4gua3bl0g3j6hgn76rmc495au8cpr0t83oqoho0sng", + "tag": "TypeReference" + } + }, + { + "diffTag": "both", + "elements": [ + { + "annotation": { + "tag": "AbilityBraces" + }, + "segment": "}" + }, + { + "annotation": null, + "segment": " " + } + ] + }, + { + "diffTag": "old", + "elements": [ + { + "annotation": { + "contents": "##Nat", + "tag": "TypeReference" + }, + "segment": "Nat" + } + ] + }, + { + "diffTag": "new", + "elements": [ + { + "annotation": { + "contents": "##Text", + "tag": "TypeReference" + }, + "segment": "Text" + } + ] + } + ], + "tag": "UserObject" + }, + "diffKind": "diff" + }, + "left": { + "bestTypeName": "AbilityUpdateMe", + "defnTypeTag": "Ability", + "typeDefinition": { + "contents": [ + { + "annotation": { + "tag": "DataTypeKeyword" + }, + "segment": "ability" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "AbilityUpdateMe", + "tag": "HashQualifier" + }, + "segment": "AbilityUpdateMe" + }, + { + "annotation": { + "tag": "ControlKeyword" + }, + "segment": " where" + }, + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "#8u70g0vaddp9jm3egoq434qialp8hdnjfh8ah8mqjau0i5lmdikt9qbe491ss53i71976fftb2o90ii6gckvs0i2lhovs1n6h0huhb0#a0", + "tag": "TermReference" + }, + "segment": "abilityUpdateMe" + }, + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "AbilityBraces" + }, + "segment": "{" + }, + { + "annotation": { + "contents": "#8u70g0vaddp9jm3egoq434qialp8hdnjfh8ah8mqjau0i5lmdikt9qbe491ss53i71976fftb2o90ii6gckvs0i2lhovs1n6h0huhb0", + "tag": "TypeReference" + }, + "segment": "AbilityUpdateMe" + }, + { + "annotation": { + "tag": "AbilityBraces" + }, + "segment": "}" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "##Nat", + "tag": "TypeReference" + }, + "segment": "Nat" + } + ], + "tag": "UserObject" + }, + "typeDocs": [], + "typeNames": [ + "AbilityUpdateMe" + ] + }, + "right": { + "bestTypeName": "AbilityUpdateMe", + "defnTypeTag": "Ability", + "typeDefinition": { + "contents": [ + { + "annotation": { + "tag": "DataTypeKeyword" + }, + "segment": "ability" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "AbilityUpdateMe", + "tag": "HashQualifier" + }, + "segment": "AbilityUpdateMe" + }, + { + "annotation": { + "tag": "ControlKeyword" + }, + "segment": " where" + }, + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "#nnulmopbjndcs4si1mop30dm01nlum2k7m6j4mmd1df2e63m09lchh2j1gkqd4gua3bl0g3j6hgn76rmc495au8cpr0t83oqoho0sng#a0", + "tag": "TermReference" + }, + "segment": "abilityUpdateMe" + }, + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "AbilityBraces" + }, + "segment": "{" + }, + { + "annotation": { + "contents": "#nnulmopbjndcs4si1mop30dm01nlum2k7m6j4mmd1df2e63m09lchh2j1gkqd4gua3bl0g3j6hgn76rmc495au8cpr0t83oqoho0sng", + "tag": "TypeReference" + }, + "segment": "AbilityUpdateMe" + }, + { + "annotation": { + "tag": "AbilityBraces" + }, + "segment": "}" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "##Text", + "tag": "TypeReference" + }, + "segment": "Text" + } + ], + "tag": "UserObject" + }, + "typeDocs": [], + "typeNames": [ + "AbilityUpdateMe" + ] + } + }, + "fullName": "AbilityUpdateMe", + "newHash": "#nnulmopbjndcs4si1mop30dm01nlum2k7m6j4mmd1df2e63m09lchh2j1gkqd4gua3bl0g3j6hgn76rmc495au8cpr0t83oqoho0sng", + "newTag": "Ability", + "oldHash": "#8u70g0vaddp9jm3egoq434qialp8hdnjfh8ah8mqjau0i5lmdikt9qbe491ss53i71976fftb2o90ii6gckvs0i2lhovs1n6h0huhb0", + "oldTag": "Ability", + "shortName": "AbilityUpdateMe" + }, + "tag": "Updated" + }, + "tag": "Ability" + }, + { + "contents": { + "contents": { + "fullName": "DataDeleteMe", + "hash": "#fhc8jn2bhvfdnfr89dv2jf7tekuesna7gvje4ck6lfheh9rb184q4ddd29vm9mvfm6u1a98kpgditn8vb09durtel67rpof1c62535o", + "rendered": { + "bestTypeName": "DataDeleteMe", + "defnTypeTag": "Data", + "typeDefinition": { + "contents": [ + { + "annotation": { + "tag": "DataTypeKeyword" }, - "segment": " :" + "segment": "type" }, { "annotation": null, @@ -662,52 +824,237 @@ }, { "annotation": { - "tag": "AbilityBraces" - }, - "segment": "{" - }, - { - "annotation": { - "contents": "#0d5ej3mann48uffjea4epi8ss486689gsj46cscorhs3d4j7ohvj9t7ghg05tra792umcmgjr6lgqkskoo3odge7jm2ci91dlmpefcg", - "tag": "TypeReference" + "contents": "DataDeleteMe", + "tag": "HashQualifier" }, - "segment": "AbilityUpdateMe" + "segment": "DataDeleteMe" }, { "annotation": { - "tag": "AbilityBraces" + "tag": "DelimiterChar" }, - "segment": "}" - }, - { - "annotation": null, - "segment": " " + "segment": " = " }, { "annotation": { - "contents": "##Nat", - "tag": "TypeReference" + "contents": "#fhc8jn2bhvfdnfr89dv2jf7tekuesna7gvje4ck6lfheh9rb184q4ddd29vm9mvfm6u1a98kpgditn8vb09durtel67rpof1c62535o#d0", + "tag": "TermReference" }, - "segment": "Nat" + "segment": "C" } ], "tag": "UserObject" }, "typeDocs": [], "typeNames": [ - "AbilityUpdateMe" + "DataDeleteMe" ] }, - "right": { - "bestTypeName": "AbilityUpdateMe", - "defnTypeTag": "Ability", + "shortName": "DataDeleteMe" + }, + "tag": "Removed" + }, + "tag": "Data" + }, + { + "contents": { + "contents": { + "diff": { + "diff": { + "diff": { + "contents": [ + { + "diffTag": "both", + "elements": [ + { + "annotation": { + "tag": "DataTypeKeyword" + }, + "segment": "type" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "DataUpdateMe", + "tag": "HashQualifier" + }, + "segment": "DataUpdateMe" + }, + { + "annotation": { + "tag": "DelimiterChar" + }, + "segment": " = " + } + ] + }, + { + "diffTag": "old", + "elements": [ + { + "annotation": { + "contents": "#a2bvb3g2l1mkijg24ogg0t23h51pnfepnngk6e3bqfijf4l9ms292t006e8faquo66ctn1ho35vtps13m6evbl6bos2guer5j6jcs1o#d0", + "tag": "TermReference" + }, + "segment": "D" + } + ] + }, + { + "diffTag": "new", + "elements": [ + { + "annotation": { + "contents": "#6t7t8lem3bmu3j7bsid4omn8gej2gl57ffmkp0ef6qndhndh2q3q6dd1j9akl653r3vtifsunovvbmbjh0iqc7n6rhp4imnsghhe6go#d0", + "tag": "TermReference" + }, + "segment": "D2" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "##Nat", + "tag": "TypeReference" + }, + "segment": "Nat" + } + ] + } + ], + "tag": "UserObject" + }, + "diffKind": "diff" + }, + "left": { + "bestTypeName": "DataUpdateMe", + "defnTypeTag": "Data", + "typeDefinition": { + "contents": [ + { + "annotation": { + "tag": "DataTypeKeyword" + }, + "segment": "type" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "DataUpdateMe", + "tag": "HashQualifier" + }, + "segment": "DataUpdateMe" + }, + { + "annotation": { + "tag": "DelimiterChar" + }, + "segment": " = " + }, + { + "annotation": { + "contents": "#a2bvb3g2l1mkijg24ogg0t23h51pnfepnngk6e3bqfijf4l9ms292t006e8faquo66ctn1ho35vtps13m6evbl6bos2guer5j6jcs1o#d0", + "tag": "TermReference" + }, + "segment": "D" + } + ], + "tag": "UserObject" + }, + "typeDocs": [], + "typeNames": [ + "DataUpdateMe" + ] + }, + "right": { + "bestTypeName": "DataUpdateMe", + "defnTypeTag": "Data", + "typeDefinition": { + "contents": [ + { + "annotation": { + "tag": "DataTypeKeyword" + }, + "segment": "type" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "DataUpdateMe", + "tag": "HashQualifier" + }, + "segment": "DataUpdateMe" + }, + { + "annotation": { + "tag": "DelimiterChar" + }, + "segment": " = " + }, + { + "annotation": { + "contents": "#6t7t8lem3bmu3j7bsid4omn8gej2gl57ffmkp0ef6qndhndh2q3q6dd1j9akl653r3vtifsunovvbmbjh0iqc7n6rhp4imnsghhe6go#d0", + "tag": "TermReference" + }, + "segment": "D2" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "##Nat", + "tag": "TypeReference" + }, + "segment": "Nat" + } + ], + "tag": "UserObject" + }, + "typeDocs": [], + "typeNames": [ + "DataUpdateMe" + ] + } + }, + "fullName": "DataUpdateMe", + "newHash": "#6t7t8lem3bmu3j7bsid4omn8gej2gl57ffmkp0ef6qndhndh2q3q6dd1j9akl653r3vtifsunovvbmbjh0iqc7n6rhp4imnsghhe6go", + "newTag": "Data", + "oldHash": "#a2bvb3g2l1mkijg24ogg0t23h51pnfepnngk6e3bqfijf4l9ms292t006e8faquo66ctn1ho35vtps13m6evbl6bos2guer5j6jcs1o", + "oldTag": "Data", + "shortName": "DataUpdateMe" + }, + "tag": "Updated" + }, + "tag": "Data" + }, + { + "contents": { + "contents": { + "fullName": "NewType", + "hash": "#rmntisgmjlrtq6kja30at01q04aeq2p17q806li6v509bn117tq9tc3gd3m33lhdgimen1tjdn4tqiu2r11k7ie9oibng1n1i275cdg", + "rendered": { + "bestTypeName": "NewType", + "defnTypeTag": "Data", "typeDefinition": { "contents": [ { "annotation": { "tag": "DataTypeKeyword" }, - "segment": "ability" + "segment": "type" }, { "annotation": null, @@ -715,37 +1062,57 @@ }, { "annotation": { - "contents": "AbilityUpdateMe", + "contents": "NewType", "tag": "HashQualifier" }, - "segment": "AbilityUpdateMe" + "segment": "NewType" }, { "annotation": { - "tag": "ControlKeyword" + "tag": "DelimiterChar" }, - "segment": " where" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": null, - "segment": " " + "segment": " = " }, { "annotation": { - "contents": "#qat72tp0lb43gp5pra5rgobup5r24qrc494crqd5pqjddbneiqdn3hq6puo2344nja1v6cp7aps1p0350ug0f1kvo9cp2gu9l31in18#a0", + "contents": "#rmntisgmjlrtq6kja30at01q04aeq2p17q806li6v509bn117tq9tc3gd3m33lhdgimen1tjdn4tqiu2r11k7ie9oibng1n1i275cdg#d0", "tag": "TermReference" }, - "segment": "abilityUpdateMe" - }, + "segment": "X" + } + ], + "tag": "UserObject" + }, + "typeDocs": [], + "typeNames": [ + "NewType" + ] + }, + "shortName": "NewType" + }, + "tag": "Added" + }, + "tag": "Data" + }, + { + "contents": { + "contents": { + "hash": "#hb2ubbk0c6347s5eqic78f26truhgro1ueh7r8invme3hnalmnv880tgpafpeo5kaaihonoph8o7pmhad8mr2e25m0hhor9lr34skhg", + "newFullName": "RenamedType", + "newShortName": "RenamedType", + "oldNames": [ + "DataRenameMe" + ], + "rendered": { + "bestTypeName": "RenamedType", + "defnTypeTag": "Data", + "typeDefinition": { + "contents": [ { "annotation": { - "tag": "TypeAscriptionColon" + "tag": "DataTypeKeyword" }, - "segment": " :" + "segment": "type" }, { "annotation": null, @@ -753,236 +1120,200 @@ }, { "annotation": { - "tag": "AbilityBraces" - }, - "segment": "{" - }, - { - "annotation": { - "contents": "#qat72tp0lb43gp5pra5rgobup5r24qrc494crqd5pqjddbneiqdn3hq6puo2344nja1v6cp7aps1p0350ug0f1kvo9cp2gu9l31in18", - "tag": "TypeReference" + "contents": "RenamedType", + "tag": "HashQualifier" }, - "segment": "AbilityUpdateMe" + "segment": "RenamedType" }, { "annotation": { - "tag": "AbilityBraces" + "tag": "DelimiterChar" }, - "segment": "}" - }, - { - "annotation": null, - "segment": " " + "segment": " = " }, { "annotation": { - "contents": "##Text", - "tag": "TypeReference" + "contents": "#hb2ubbk0c6347s5eqic78f26truhgro1ueh7r8invme3hnalmnv880tgpafpeo5kaaihonoph8o7pmhad8mr2e25m0hhor9lr34skhg#d0", + "tag": "TermReference" }, - "segment": "Text" + "segment": "E" } ], "tag": "UserObject" }, "typeDocs": [], "typeNames": [ - "AbilityUpdateMe" + "RenamedType" ] } }, - "fullName": "AbilityUpdateMe", - "newHash": "#qat72tp0lb43gp5pra5rgobup5r24qrc494crqd5pqjddbneiqdn3hq6puo2344nja1v6cp7aps1p0350ug0f1kvo9cp2gu9l31in18", - "newTag": "Ability", - "oldHash": "#0d5ej3mann48uffjea4epi8ss486689gsj46cscorhs3d4j7ohvj9t7ghg05tra792umcmgjr6lgqkskoo3odge7jm2ci91dlmpefcg", - "oldTag": "Ability", - "shortName": "AbilityUpdateMe" + "tag": "RenamedFrom" }, - "tag": "Updated" + "tag": "Data" }, - "tag": "Ability" - }, - { - "contents": { + { "contents": { - "fullName": "DataDeleteMe", - "hash": "#keu02n8is0irijd65cvuos41kukj3f4ni18mmnudrbll2epo6ftd03nt9l0vqc4fvg98198tefgoupco4o0d0gvnigqgr1bmo2neo88", - "rendered": { - "bestTypeName": "DataDeleteMe", - "defnTypeTag": "Data", - "typeDefinition": { - "contents": [ - { - "annotation": { - "tag": "DataTypeKeyword" - }, - "segment": "type" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "DataDeleteMe", - "tag": "HashQualifier" - }, - "segment": "DataDeleteMe" - }, - { - "annotation": { - "tag": "DelimiterChar" - }, - "segment": " = " - }, + "contents": { + "fullName": "aDoc", + "hash": "#areni4s9liksvfs3923a4ub81qpu37f964fqhbq832artpff8vm1em45ic0k2hlkv4nn08u712ibvjo9b4fl5u19o65g9medo7645i8", + "rendered": { + "bestTermName": "aDoc", + "defnTermTag": "Doc", + "signature": [ { "annotation": { - "contents": "#keu02n8is0irijd65cvuos41kukj3f4ni18mmnudrbll2epo6ftd03nt9l0vqc4fvg98198tefgoupco4o0d0gvnigqgr1bmo2neo88#d0", - "tag": "TermReference" + "contents": "#ej86si0ur1lsjade71dojr25phk9bbom9rdks6dltolos5tjivakujcriqe02npba53n9gd7tkh8bmv08ttjb9t35lq2ch5heshqcs0", + "tag": "TypeReference" }, - "segment": "C" + "segment": "Doc2" } ], - "tag": "UserObject" - }, - "typeDocs": [], - "typeNames": [ - "DataDeleteMe" - ] - }, - "shortName": "DataDeleteMe" - }, - "tag": "Removed" - }, - "tag": "Data" - }, - { - "contents": { - "contents": { - "diff": { - "diff": { - "diff": { + "termDefinition": { "contents": [ { - "diffTag": "both", - "elements": [ - { - "annotation": { - "tag": "DataTypeKeyword" - }, - "segment": "type" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "DataUpdateMe", - "tag": "HashQualifier" - }, - "segment": "DataUpdateMe" - }, - { - "annotation": { - "tag": "DelimiterChar" - }, - "segment": " = " - } - ] + "annotation": { + "contents": "aDoc", + "tag": "HashQualifier" + }, + "segment": "aDoc" }, { - "diffTag": "old", - "elements": [ - { - "annotation": { - "contents": "#fhc8jn2bhvfdnfr89dv2jf7tekuesna7gvje4ck6lfheh9rb184q4ddd29vm9mvfm6u1a98kpgditn8vb09durtel67rpof1c62535o#d0", - "tag": "TermReference" - }, - "segment": "D" - } - ] + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" }, { - "diffTag": "new", - "elements": [ - { - "annotation": { - "contents": "#qnblpurkqedrq0kae95ep7b8f6uh5b7igefp21r1nvl22agjoup5e7aunua4q8ku8mb532fh3lst4mj3m2bsb3kluchc3fuau5cllr0#d0", - "tag": "TermReference" - }, - "segment": "D2" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "##Nat", - "tag": "TypeReference" - }, - "segment": "Nat" - } - ] - } - ], - "tag": "UserObject" - }, - "diffKind": "diff" - }, - "left": { - "bestTypeName": "DataUpdateMe", - "defnTypeTag": "Data", - "typeDefinition": { - "contents": [ + "annotation": null, + "segment": " " + }, { "annotation": { - "tag": "DataTypeKeyword" + "contents": "#ej86si0ur1lsjade71dojr25phk9bbom9rdks6dltolos5tjivakujcriqe02npba53n9gd7tkh8bmv08ttjb9t35lq2ch5heshqcs0", + "tag": "TypeReference" }, - "segment": "type" + "segment": "Doc2" }, { "annotation": null, - "segment": " " + "segment": "\n" }, { "annotation": { - "contents": "DataUpdateMe", + "contents": "aDoc", "tag": "HashQualifier" }, - "segment": "DataUpdateMe" + "segment": "aDoc" }, { "annotation": { - "tag": "DelimiterChar" + "tag": "BindingEquals" }, - "segment": " = " + "segment": " =" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "DocDelimiter" + }, + "segment": "{{" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": null, + "segment": "Test" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": null, + "segment": "Doc" + }, + { + "annotation": null, + "segment": " " }, { "annotation": { - "contents": "#fhc8jn2bhvfdnfr89dv2jf7tekuesna7gvje4ck6lfheh9rb184q4ddd29vm9mvfm6u1a98kpgditn8vb09durtel67rpof1c62535o#d0", - "tag": "TermReference" + "tag": "DocDelimiter" }, - "segment": "D" + "segment": "}}" } ], "tag": "UserObject" }, - "typeDocs": [], - "typeNames": [ - "DataUpdateMe" + "termDocs": [ + [ + "aDoc", + "#areni4s9liksvfs3923a4ub81qpu37f964fqhbq832artpff8vm1em45ic0k2hlkv4nn08u712ibvjo9b4fl5u19o65g9medo7645i8", + { + "contents": [ + { + "contents": "Test", + "tag": "Word" + }, + { + "contents": "Doc", + "tag": "Word" + } + ], + "tag": "Paragraph" + } + ] + ], + "termNames": [ + "aDoc" ] }, - "right": { - "bestTypeName": "DataUpdateMe", - "defnTypeTag": "Data", - "typeDefinition": { + "shortName": "aDoc" + }, + "tag": "Removed" + }, + "tag": "Doc" + }, + { + "contents": { + "contents": { + "aliasFullName": "aTermAlias", + "aliasShortName": "aTermAlias", + "hash": "#gjmq673r1vrurfotlnirv7vutdhm6sa3s02em5g22kk606mv6duvv8be402dv79312i4a0onepq5bo7citsodvq2g720nttj0ee9p0g", + "otherNames": [ + "termAliasMe" + ], + "rendered": { + "bestTermName": "aTermAlias", + "defnTermTag": "Plain", + "signature": [ + { + "annotation": { + "contents": "##Nat", + "tag": "TypeReference" + }, + "segment": "Nat" + } + ], + "termDefinition": { "contents": [ { "annotation": { - "tag": "DataTypeKeyword" + "contents": "aTermAlias", + "tag": "HashQualifier" }, - "segment": "type" + "segment": "aTermAlias" + }, + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" }, { "annotation": null, @@ -990,23 +1321,27 @@ }, { "annotation": { - "contents": "DataUpdateMe", - "tag": "HashQualifier" + "contents": "##Nat", + "tag": "TypeReference" }, - "segment": "DataUpdateMe" + "segment": "Nat" + }, + { + "annotation": null, + "segment": "\n" }, { "annotation": { - "tag": "DelimiterChar" + "contents": "aTermAlias", + "tag": "HashQualifier" }, - "segment": " = " + "segment": "aTermAlias" }, { "annotation": { - "contents": "#qnblpurkqedrq0kae95ep7b8f6uh5b7igefp21r1nvl22agjoup5e7aunua4q8ku8mb532fh3lst4mj3m2bsb3kluchc3fuau5cllr0#d0", - "tag": "TermReference" + "tag": "BindingEquals" }, - "segment": "D2" + "segment": " =" }, { "annotation": null, @@ -1014,1272 +1349,1352 @@ }, { "annotation": { - "contents": "##Nat", - "tag": "TypeReference" + "tag": "NumericLiteral" }, - "segment": "Nat" + "segment": "1" } ], "tag": "UserObject" }, - "typeDocs": [], - "typeNames": [ - "DataUpdateMe" + "termDocs": [], + "termNames": [ + "aTermAlias", + "termAliasMe" ] } }, - "fullName": "DataUpdateMe", - "newHash": "#qnblpurkqedrq0kae95ep7b8f6uh5b7igefp21r1nvl22agjoup5e7aunua4q8ku8mb532fh3lst4mj3m2bsb3kluchc3fuau5cllr0", - "newTag": "Data", - "oldHash": "#fhc8jn2bhvfdnfr89dv2jf7tekuesna7gvje4ck6lfheh9rb184q4ddd29vm9mvfm6u1a98kpgditn8vb09durtel67rpof1c62535o", - "oldTag": "Data", - "shortName": "DataUpdateMe" - }, - "tag": "Updated" - }, - "tag": "Data" - }, - { - "contents": { - "contents": { - "fullName": "NewType", - "hash": "#sa4ptibggqmbifhfj37gj2lq487q5ucfuojjcblfaas9bunlthhkvhstsrj20fvlpqakb8e9mqds4p32lnh8ohmf1s5omvdhc23jibg", - "rendered": { - "bestTypeName": "NewType", - "defnTypeTag": "Data", - "typeDefinition": { - "contents": [ - { - "annotation": { - "tag": "DataTypeKeyword" - }, - "segment": "type" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "NewType", - "tag": "HashQualifier" - }, - "segment": "NewType" - }, - { - "annotation": { - "tag": "DelimiterChar" - }, - "segment": " = " - }, - { - "annotation": { - "contents": "#sa4ptibggqmbifhfj37gj2lq487q5ucfuojjcblfaas9bunlthhkvhstsrj20fvlpqakb8e9mqds4p32lnh8ohmf1s5omvdhc23jibg#d0", - "tag": "TermReference" - }, - "segment": "X" - } - ], - "tag": "UserObject" - }, - "typeDocs": [], - "typeNames": [ - "NewType" - ] - }, - "shortName": "NewType" + "tag": "Aliased" }, - "tag": "Added" + "tag": "Plain" }, - "tag": "Data" - }, - { - "contents": { + { "contents": { - "hash": "#8s3lsrv3p6ngq2bqotvli1f0gfcf9uvci4trmia6dosl3d8vu6i6kubdi3ic7m22r34m4mkru3hatdbgihj0fngmj7gktlq41ncs1e0", - "newFullName": "RenamedType", - "newShortName": "RenamedType", - "oldNames": [ - "DataRenameMe" - ], - "rendered": { - "bestTypeName": "RenamedType", - "defnTypeTag": "Data", - "typeDefinition": { - "contents": [ - { - "annotation": { - "tag": "DataTypeKeyword" - }, - "segment": "type" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "RenamedType", - "tag": "HashQualifier" - }, - "segment": "RenamedType" - }, + "contents": { + "fullName": "aTest", + "hash": "#qak36j7cshv12m9meuc97ovllqm8k2i305sh4oq5dbo4834t7atugsdpto6mou1tch2b3q9j2hbi23gdf4jpth7m97mannv9noucgl8", + "rendered": { + "bestTermName": "aTest", + "defnTermTag": "Test", + "signature": [ { "annotation": { "tag": "DelimiterChar" }, - "segment": " = " - }, - { - "annotation": { - "contents": "#8s3lsrv3p6ngq2bqotvli1f0gfcf9uvci4trmia6dosl3d8vu6i6kubdi3ic7m22r34m4mkru3hatdbgihj0fngmj7gktlq41ncs1e0#d0", - "tag": "TermReference" - }, - "segment": "E" - } - ], - "tag": "UserObject" - }, - "typeDocs": [], - "typeNames": [ - "RenamedType" - ] - } - }, - "tag": "RenamedFrom" - }, - "tag": "Data" - }, - { - "contents": { - "contents": { - "fullName": "aDoc", - "hash": "#areni4s9liksvfs3923a4ub81qpu37f964fqhbq832artpff8vm1em45ic0k2hlkv4nn08u712ibvjo9b4fl5u19o65g9medo7645i8", - "rendered": { - "bestTermName": "aDoc", - "defnTermTag": "Doc", - "signature": [ - { - "annotation": { - "contents": "#ej86si0ur1lsjade71dojr25phk9bbom9rdks6dltolos5tjivakujcriqe02npba53n9gd7tkh8bmv08ttjb9t35lq2ch5heshqcs0", - "tag": "TypeReference" - }, - "segment": "Doc2" - } - ], - "termDefinition": { - "contents": [ - { - "annotation": { - "contents": "aDoc", - "tag": "HashQualifier" - }, - "segment": "aDoc" - }, - { - "annotation": { - "tag": "TypeAscriptionColon" - }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " + "segment": "[" }, { "annotation": { - "contents": "#ej86si0ur1lsjade71dojr25phk9bbom9rdks6dltolos5tjivakujcriqe02npba53n9gd7tkh8bmv08ttjb9t35lq2ch5heshqcs0", + "contents": "#aql7qk3iud6vs4cvu43aimopoosgk0fnipibdkc3so13adencmibgfn0u5c01r0adei55nkl3ttsjhl8gbj7tr4gnpj63g64ftbq6s0", "tag": "TypeReference" }, - "segment": "Doc2" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": { - "contents": "aDoc", - "tag": "HashQualifier" - }, - "segment": "aDoc" - }, - { - "annotation": { - "tag": "BindingEquals" - }, - "segment": " =" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "tag": "DocDelimiter" - }, - "segment": "{{" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": null, - "segment": "Test" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": null, - "segment": "Doc" - }, - { - "annotation": null, - "segment": " " + "segment": "Result" }, { "annotation": { - "tag": "DocDelimiter" + "tag": "DelimiterChar" }, - "segment": "}}" + "segment": "]" } ], - "tag": "UserObject" - }, - "termDocs": [ - [ - "aDoc", - "#areni4s9liksvfs3923a4ub81qpu37f964fqhbq832artpff8vm1em45ic0k2hlkv4nn08u712ibvjo9b4fl5u19o65g9medo7645i8", - { - "contents": [ - { - "contents": "Test", - "tag": "Word" + "termDefinition": { + "contents": [ + { + "annotation": { + "contents": "aTest", + "tag": "HashQualifier" }, - { - "contents": "Doc", - "tag": "Word" - } - ], - "tag": "Paragraph" - } - ] - ], - "termNames": [ - "aDoc" - ] - }, - "shortName": "aDoc" - }, - "tag": "Removed" - }, - "tag": "Doc" - }, - { - "contents": { - "contents": { - "aliasFullName": "aTermAlias", - "aliasShortName": "aTermAlias", - "hash": "#gjmq673r1vrurfotlnirv7vutdhm6sa3s02em5g22kk606mv6duvv8be402dv79312i4a0onepq5bo7citsodvq2g720nttj0ee9p0g", - "otherNames": [ - "termAliasMe" - ], - "rendered": { - "bestTermName": "aTermAlias", - "defnTermTag": "Plain", - "signature": [ - { - "annotation": { - "contents": "##Nat", - "tag": "TypeReference" - }, - "segment": "Nat" - } - ], - "termDefinition": { - "contents": [ - { - "annotation": { - "contents": "aTermAlias", - "tag": "HashQualifier" - }, - "segment": "aTermAlias" - }, - { - "annotation": { - "tag": "TypeAscriptionColon" - }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "##Nat", - "tag": "TypeReference" - }, - "segment": "Nat" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": { - "contents": "aTermAlias", - "tag": "HashQualifier" + "segment": "aTest" }, - "segment": "aTermAlias" - }, - { - "annotation": { - "tag": "BindingEquals" + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" }, - "segment": " =" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "tag": "NumericLiteral" + { + "annotation": null, + "segment": " " }, - "segment": "1" - } - ], - "tag": "UserObject" - }, - "termDocs": [], - "termNames": [ - "aTermAlias", - "termAliasMe" - ] - } - }, - "tag": "Aliased" - }, - "tag": "Plain" - }, - { - "contents": { - "contents": { - "fullName": "aTest", - "hash": "#qak36j7cshv12m9meuc97ovllqm8k2i305sh4oq5dbo4834t7atugsdpto6mou1tch2b3q9j2hbi23gdf4jpth7m97mannv9noucgl8", - "rendered": { - "bestTermName": "aTest", - "defnTermTag": "Test", - "signature": [ - { - "annotation": { - "tag": "DelimiterChar" - }, - "segment": "[" - }, - { - "annotation": { - "contents": "#aql7qk3iud6vs4cvu43aimopoosgk0fnipibdkc3so13adencmibgfn0u5c01r0adei55nkl3ttsjhl8gbj7tr4gnpj63g64ftbq6s0", - "tag": "TypeReference" - }, - "segment": "Result" - }, - { - "annotation": { - "tag": "DelimiterChar" - }, - "segment": "]" - } - ], - "termDefinition": { - "contents": [ - { - "annotation": { - "contents": "aTest", - "tag": "HashQualifier" + { + "annotation": { + "tag": "DelimiterChar" + }, + "segment": "[" }, - "segment": "aTest" - }, - { - "annotation": { - "tag": "TypeAscriptionColon" + { + "annotation": { + "contents": "#aql7qk3iud6vs4cvu43aimopoosgk0fnipibdkc3so13adencmibgfn0u5c01r0adei55nkl3ttsjhl8gbj7tr4gnpj63g64ftbq6s0", + "tag": "TypeReference" + }, + "segment": "Result" }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "tag": "DelimiterChar" + { + "annotation": { + "tag": "DelimiterChar" + }, + "segment": "]" }, - "segment": "[" - }, - { - "annotation": { - "contents": "#aql7qk3iud6vs4cvu43aimopoosgk0fnipibdkc3so13adencmibgfn0u5c01r0adei55nkl3ttsjhl8gbj7tr4gnpj63g64ftbq6s0", - "tag": "TypeReference" + { + "annotation": null, + "segment": "\n" }, - "segment": "Result" - }, - { - "annotation": { - "tag": "DelimiterChar" + { + "annotation": { + "contents": "aTest", + "tag": "HashQualifier" + }, + "segment": "aTest" }, - "segment": "]" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": { - "contents": "aTest", - "tag": "HashQualifier" + { + "annotation": { + "tag": "BindingEquals" + }, + "segment": " =" }, - "segment": "aTest" - }, - { - "annotation": { - "tag": "BindingEquals" + { + "annotation": null, + "segment": " " }, - "segment": " =" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "##Sequence", - "tag": "TypeReference" + { + "annotation": { + "contents": "##Sequence", + "tag": "TypeReference" + }, + "segment": "[" }, - "segment": "[" - }, - { - "annotation": { - "contents": "#aql7qk3iud6vs4cvu43aimopoosgk0fnipibdkc3so13adencmibgfn0u5c01r0adei55nkl3ttsjhl8gbj7tr4gnpj63g64ftbq6s0#d1", - "tag": "TermReference" + { + "annotation": { + "contents": "#aql7qk3iud6vs4cvu43aimopoosgk0fnipibdkc3so13adencmibgfn0u5c01r0adei55nkl3ttsjhl8gbj7tr4gnpj63g64ftbq6s0#d1", + "tag": "TermReference" + }, + "segment": "Ok" }, - "segment": "Ok" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "tag": "TextLiteral" + { + "annotation": null, + "segment": " " }, - "segment": "\"Done\"" - }, - { - "annotation": { - "contents": "##Sequence", - "tag": "TypeReference" + { + "annotation": { + "tag": "TextLiteral" + }, + "segment": "\"Done\"" }, - "segment": "]" - } - ], - "tag": "UserObject" + { + "annotation": { + "contents": "##Sequence", + "tag": "TypeReference" + }, + "segment": "]" + } + ], + "tag": "UserObject" + }, + "termDocs": [], + "termNames": [ + "aTest" + ] }, - "termDocs": [], - "termNames": [ - "aTest" - ] + "shortName": "aTest" }, - "shortName": "aTest" + "tag": "Removed" }, - "tag": "Removed" + "tag": "Test" }, - "tag": "Test" - }, - { - "contents": { + { "contents": { - "fullName": "newTerm", - "hash": "#u1qsl3nk5t2svl58ifqepem851775qca9p4hc10j3iordu1v7u8e16oodui9kvt2c0j1cbc50avado53bl2vt3pphrfj9mhbut1ipm8", - "rendered": { - "bestTermName": "newTerm", - "defnTermTag": "Plain", - "signature": [ - { - "annotation": { - "contents": "##Nat", - "tag": "TypeReference" - }, - "segment": "Nat" - } - ], - "termDefinition": { - "contents": [ - { - "annotation": { - "contents": "newTerm", - "tag": "HashQualifier" - }, - "segment": "newTerm" - }, - { - "annotation": { - "tag": "TypeAscriptionColon" - }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " - }, + "contents": { + "fullName": "newTerm", + "hash": "#u1qsl3nk5t2svl58ifqepem851775qca9p4hc10j3iordu1v7u8e16oodui9kvt2c0j1cbc50avado53bl2vt3pphrfj9mhbut1ipm8", + "rendered": { + "bestTermName": "newTerm", + "defnTermTag": "Plain", + "signature": [ { "annotation": { "contents": "##Nat", "tag": "TypeReference" }, "segment": "Nat" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": { - "contents": "newTerm", - "tag": "HashQualifier" + } + ], + "termDefinition": { + "contents": [ + { + "annotation": { + "contents": "newTerm", + "tag": "HashQualifier" + }, + "segment": "newTerm" }, - "segment": "newTerm" - }, - { - "annotation": { - "tag": "BindingEquals" + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" }, - "segment": " =" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "tag": "NumericLiteral" + { + "annotation": null, + "segment": " " }, - "segment": "100" - } - ], - "tag": "UserObject" + { + "annotation": { + "contents": "##Nat", + "tag": "TypeReference" + }, + "segment": "Nat" + }, + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": { + "contents": "newTerm", + "tag": "HashQualifier" + }, + "segment": "newTerm" + }, + { + "annotation": { + "tag": "BindingEquals" + }, + "segment": " =" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "NumericLiteral" + }, + "segment": "100" + } + ], + "tag": "UserObject" + }, + "termDocs": [], + "termNames": [ + "newTerm" + ] }, - "termDocs": [], - "termNames": [ - "newTerm" - ] + "shortName": "newTerm" }, - "shortName": "newTerm" + "tag": "Added" }, - "tag": "Added" + "tag": "Plain" }, - "tag": "Plain" - }, - { - "contents": { + { "contents": { - "hash": "#f3lgjvjqoocpt8v6kdgd2bgthh11a7md3qdp9rf5datccmo580btjd5bt5dro3irqs0is7vm7s1dphddjbtufch620te7ef7canmjj8", - "newFullName": "renamedTerm", - "newShortName": "renamedTerm", - "oldNames": [ - "termRenameMe" - ], - "rendered": { - "bestTermName": "renamedTerm", - "defnTermTag": "Plain", - "signature": [ - { - "annotation": { - "contents": "##Nat", - "tag": "TypeReference" - }, - "segment": "Nat" - } + "contents": { + "hash": "#f3lgjvjqoocpt8v6kdgd2bgthh11a7md3qdp9rf5datccmo580btjd5bt5dro3irqs0is7vm7s1dphddjbtufch620te7ef7canmjj8", + "newFullName": "renamedTerm", + "newShortName": "renamedTerm", + "oldNames": [ + "termRenameMe" ], - "termDefinition": { - "contents": [ - { - "annotation": { - "contents": "renamedTerm", - "tag": "HashQualifier" - }, - "segment": "renamedTerm" - }, - { - "annotation": { - "tag": "TypeAscriptionColon" - }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " - }, + "rendered": { + "bestTermName": "renamedTerm", + "defnTermTag": "Plain", + "signature": [ { "annotation": { "contents": "##Nat", "tag": "TypeReference" }, "segment": "Nat" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": { - "contents": "renamedTerm", - "tag": "HashQualifier" + } + ], + "termDefinition": { + "contents": [ + { + "annotation": { + "contents": "renamedTerm", + "tag": "HashQualifier" + }, + "segment": "renamedTerm" }, - "segment": "renamedTerm" - }, - { - "annotation": { - "tag": "BindingEquals" + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" }, - "segment": " =" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "tag": "NumericLiteral" + { + "annotation": null, + "segment": " " }, - "segment": "3" - } - ], - "tag": "UserObject" - }, - "termDocs": [], - "termNames": [ - "renamedTerm" - ] - } + { + "annotation": { + "contents": "##Nat", + "tag": "TypeReference" + }, + "segment": "Nat" + }, + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": { + "contents": "renamedTerm", + "tag": "HashQualifier" + }, + "segment": "renamedTerm" + }, + { + "annotation": { + "tag": "BindingEquals" + }, + "segment": " =" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "NumericLiteral" + }, + "segment": "3" + } + ], + "tag": "UserObject" + }, + "termDocs": [], + "termNames": [ + "renamedTerm" + ] + } + }, + "tag": "RenamedFrom" }, - "tag": "RenamedFrom" + "tag": "Plain" }, - "tag": "Plain" - }, - { - "contents": { + { "contents": { - "fullName": "termDeleteMe", - "hash": "#dcgdua2lj6upd1ah5v0qp09gjsej0d77d87fu6qn8e2qrssnlnmuinoio46hiu53magr7qn8vnqke8ndt0v76700o5u8gcvo7st28jg", - "rendered": { - "bestTermName": "termDeleteMe", - "defnTermTag": "Plain", - "signature": [ - { - "annotation": { - "contents": "##Nat", - "tag": "TypeReference" - }, - "segment": "Nat" - } - ], - "termDefinition": { - "contents": [ - { - "annotation": { - "contents": "termDeleteMe", - "tag": "HashQualifier" - }, - "segment": "termDeleteMe" - }, - { - "annotation": { - "tag": "TypeAscriptionColon" - }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " - }, + "contents": { + "fullName": "termDeleteMe", + "hash": "#dcgdua2lj6upd1ah5v0qp09gjsej0d77d87fu6qn8e2qrssnlnmuinoio46hiu53magr7qn8vnqke8ndt0v76700o5u8gcvo7st28jg", + "rendered": { + "bestTermName": "termDeleteMe", + "defnTermTag": "Plain", + "signature": [ { "annotation": { "contents": "##Nat", "tag": "TypeReference" }, "segment": "Nat" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": { - "contents": "termDeleteMe", - "tag": "HashQualifier" + } + ], + "termDefinition": { + "contents": [ + { + "annotation": { + "contents": "termDeleteMe", + "tag": "HashQualifier" + }, + "segment": "termDeleteMe" }, - "segment": "termDeleteMe" - }, - { - "annotation": { - "tag": "BindingEquals" + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" }, - "segment": " =" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "tag": "NumericLiteral" + { + "annotation": null, + "segment": " " }, - "segment": "2" - } - ], - "tag": "UserObject" + { + "annotation": { + "contents": "##Nat", + "tag": "TypeReference" + }, + "segment": "Nat" + }, + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": { + "contents": "termDeleteMe", + "tag": "HashQualifier" + }, + "segment": "termDeleteMe" + }, + { + "annotation": { + "tag": "BindingEquals" + }, + "segment": " =" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "NumericLiteral" + }, + "segment": "2" + } + ], + "tag": "UserObject" + }, + "termDocs": [], + "termNames": [ + "termDeleteMe" + ] }, - "termDocs": [], - "termNames": [ - "termDeleteMe" - ] + "shortName": "termDeleteMe" }, - "shortName": "termDeleteMe" + "tag": "Removed" }, - "tag": "Removed" + "tag": "Plain" }, - "tag": "Plain" - }, - { - "contents": { + { "contents": { - "diff": { + "contents": { "diff": { "diff": { - "contents": [ - { - "diffTag": "both", - "elements": [ - { - "annotation": { - "contents": "termUpdateMe", - "tag": "HashQualifier" + "diff": { + "contents": [ + { + "diffTag": "both", + "elements": [ + { + "annotation": { + "contents": "termDependsOnUpdateMe", + "tag": "HashQualifier" + }, + "segment": "termDependsOnUpdateMe" }, - "segment": "termUpdateMe" - }, - { - "annotation": { - "tag": "TypeAscriptionColon" + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "##Text", - "tag": "TypeReference" + { + "annotation": null, + "segment": " " }, - "segment": "Text" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": { - "contents": "termUpdateMe", - "tag": "HashQualifier" + { + "annotation": { + "contents": "##Text", + "tag": "TypeReference" + }, + "segment": "Text" }, - "segment": "termUpdateMe" - }, - { - "annotation": { - "tag": "BindingEquals" + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": { + "contents": "termDependsOnUpdateMe", + "tag": "HashQualifier" + }, + "segment": "termDependsOnUpdateMe" + }, + { + "annotation": { + "tag": "BindingEquals" + }, + "segment": " =" }, - "segment": " =" + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "UseKeyword" + }, + "segment": "use " + }, + { + "annotation": { + "tag": "UsePrefix" + }, + "segment": "Text" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "UseSuffix" + }, + "segment": "++" + }, + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": null, + "segment": " " + } + ] + }, + { + "diffTag": "annotationChange", + "fromAnnotation": { + "contents": "#ofktbubbloi1omgpr09e0t90pg0cnf0lsuuopqese9biqvpdafsuhq0b4dfasbk6g3hp5r7crp4t486fc8bava7q7rrreg9j2volam8", + "tag": "TermReference" }, - { - "annotation": null, - "segment": " " + "segment": "termUpdateMe", + "toAnnotation": { + "contents": "#711u1t9cjso4t3rhlq2rp491n2n5n4t9o7701053kpj5ouu3kfs2e2l63i879pnsb6ob9fp0gpj18u6fpcl1qosd704h4doklfo734g", + "tag": "TermReference" } - ] - }, - { - "diffTag": "old", - "elements": [ - { - "annotation": { - "tag": "TextLiteral" + }, + { + "diffTag": "both", + "elements": [ + { + "annotation": null, + "segment": " " }, - "segment": "\"original\"" - } - ] - }, - { - "diffTag": "new", - "elements": [ - { - "annotation": { - "tag": "TextLiteral" + { + "annotation": { + "contents": "##Text.++", + "tag": "TermReference" + }, + "segment": "++" }, - "segment": "\"updated\"" + { + "annotation": null, + "segment": " " + } + ] + }, + { + "diffTag": "annotationChange", + "fromAnnotation": { + "contents": "#ofktbubbloi1omgpr09e0t90pg0cnf0lsuuopqese9biqvpdafsuhq0b4dfasbk6g3hp5r7crp4t486fc8bava7q7rrreg9j2volam8", + "tag": "TermReference" + }, + "segment": "termUpdateMe", + "toAnnotation": { + "contents": "#711u1t9cjso4t3rhlq2rp491n2n5n4t9o7701053kpj5ouu3kfs2e2l63i879pnsb6ob9fp0gpj18u6fpcl1qosd704h4doklfo734g", + "tag": "TermReference" } - ] + } + ], + "tag": "UserObject" + }, + "diffKind": "diff" + }, + "left": { + "bestTermName": "termDependsOnUpdateMe", + "defnTermTag": "Plain", + "signature": [ + { + "annotation": { + "contents": "##Text", + "tag": "TypeReference" + }, + "segment": "Text" } ], - "tag": "UserObject" + "termDefinition": { + "contents": [ + { + "annotation": { + "contents": "termDependsOnUpdateMe", + "tag": "HashQualifier" + }, + "segment": "termDependsOnUpdateMe" + }, + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "##Text", + "tag": "TypeReference" + }, + "segment": "Text" + }, + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": { + "contents": "termDependsOnUpdateMe", + "tag": "HashQualifier" + }, + "segment": "termDependsOnUpdateMe" + }, + { + "annotation": { + "tag": "BindingEquals" + }, + "segment": " =" + }, + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "UseKeyword" + }, + "segment": "use " + }, + { + "annotation": { + "tag": "UsePrefix" + }, + "segment": "Text" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "UseSuffix" + }, + "segment": "++" + }, + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "#ofktbubbloi1omgpr09e0t90pg0cnf0lsuuopqese9biqvpdafsuhq0b4dfasbk6g3hp5r7crp4t486fc8bava7q7rrreg9j2volam8", + "tag": "TermReference" + }, + "segment": "termUpdateMe" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "##Text.++", + "tag": "TermReference" + }, + "segment": "++" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "#ofktbubbloi1omgpr09e0t90pg0cnf0lsuuopqese9biqvpdafsuhq0b4dfasbk6g3hp5r7crp4t486fc8bava7q7rrreg9j2volam8", + "tag": "TermReference" + }, + "segment": "termUpdateMe" + } + ], + "tag": "UserObject" + }, + "termDocs": [], + "termNames": [ + "termDependsOnUpdateMe" + ] }, - "diffKind": "diff" - }, - "left": { - "bestTermName": "termUpdateMe", - "defnTermTag": "Plain", - "signature": [ - { - "annotation": { - "contents": "##Text", - "tag": "TypeReference" - }, - "segment": "Text" - } - ], - "termDefinition": { - "contents": [ + "right": { + "bestTermName": "termDependsOnUpdateMe", + "defnTermTag": "Plain", + "signature": [ { "annotation": { - "contents": "termUpdateMe", - "tag": "HashQualifier" + "contents": "##Text", + "tag": "TypeReference" + }, + "segment": "Text" + } + ], + "termDefinition": { + "contents": [ + { + "annotation": { + "contents": "termDependsOnUpdateMe", + "tag": "HashQualifier" + }, + "segment": "termDependsOnUpdateMe" + }, + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "##Text", + "tag": "TypeReference" + }, + "segment": "Text" + }, + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": { + "contents": "termDependsOnUpdateMe", + "tag": "HashQualifier" + }, + "segment": "termDependsOnUpdateMe" + }, + { + "annotation": { + "tag": "BindingEquals" + }, + "segment": " =" + }, + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "UseKeyword" + }, + "segment": "use " + }, + { + "annotation": { + "tag": "UsePrefix" + }, + "segment": "Text" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "UseSuffix" + }, + "segment": "++" + }, + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "#711u1t9cjso4t3rhlq2rp491n2n5n4t9o7701053kpj5ouu3kfs2e2l63i879pnsb6ob9fp0gpj18u6fpcl1qosd704h4doklfo734g", + "tag": "TermReference" + }, + "segment": "termUpdateMe" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "##Text.++", + "tag": "TermReference" + }, + "segment": "++" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "#711u1t9cjso4t3rhlq2rp491n2n5n4t9o7701053kpj5ouu3kfs2e2l63i879pnsb6ob9fp0gpj18u6fpcl1qosd704h4doklfo734g", + "tag": "TermReference" + }, + "segment": "termUpdateMe" + } + ], + "tag": "UserObject" + }, + "termDocs": [], + "termNames": [ + "termDependsOnUpdateMe" + ] + } + }, + "fullName": "termDependsOnUpdateMe", + "newHash": "#t3u2jnk3eej5hrcrfr80vqiaj7n26grg15n4eb67bd1601jb65ikhbfdk18eeirovmaithk3ipukum6qnhttld43ovitj01kdkd4jrg", + "newTag": "Plain", + "oldHash": "#8imj19nvqqdtl1jd9ns5fksnuh4slku9hoi3sl7dh353k7o209eek4aievkp1sbqq5lqpgqouvf00k5b6t1fkv8omnpsnvmpu0a5lr8", + "oldTag": "Plain", + "shortName": "termDependsOnUpdateMe" + }, + "tag": "Propagated" + }, + "tag": "Plain" + }, + { + "contents": { + "contents": { + "diff": { + "diff": { + "diff": { + "contents": [ + { + "diffTag": "both", + "elements": [ + { + "annotation": { + "contents": "termUpdateMe", + "tag": "HashQualifier" + }, + "segment": "termUpdateMe" + }, + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "##Text", + "tag": "TypeReference" + }, + "segment": "Text" + }, + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": { + "contents": "termUpdateMe", + "tag": "HashQualifier" + }, + "segment": "termUpdateMe" + }, + { + "annotation": { + "tag": "BindingEquals" + }, + "segment": " =" + }, + { + "annotation": null, + "segment": " " + } + ] }, - "segment": "termUpdateMe" - }, - { - "annotation": { - "tag": "TypeAscriptionColon" + { + "diffTag": "old", + "elements": [ + { + "annotation": { + "tag": "TextLiteral" + }, + "segment": "\"original\"" + } + ] }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " - }, + { + "diffTag": "new", + "elements": [ + { + "annotation": { + "tag": "TextLiteral" + }, + "segment": "\"updated\"" + } + ] + } + ], + "tag": "UserObject" + }, + "diffKind": "diff" + }, + "left": { + "bestTermName": "termUpdateMe", + "defnTermTag": "Plain", + "signature": [ { "annotation": { "contents": "##Text", "tag": "TypeReference" }, "segment": "Text" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": { - "contents": "termUpdateMe", - "tag": "HashQualifier" + } + ], + "termDefinition": { + "contents": [ + { + "annotation": { + "contents": "termUpdateMe", + "tag": "HashQualifier" + }, + "segment": "termUpdateMe" }, - "segment": "termUpdateMe" - }, - { - "annotation": { - "tag": "BindingEquals" + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" }, - "segment": " =" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "tag": "TextLiteral" + { + "annotation": null, + "segment": " " }, - "segment": "\"original\"" - } - ], - "tag": "UserObject" - }, - "termDocs": [], - "termNames": [ - "termUpdateMe" - ] - }, - "right": { - "bestTermName": "termUpdateMe", - "defnTermTag": "Plain", - "signature": [ - { - "annotation": { - "contents": "##Text", - "tag": "TypeReference" - }, - "segment": "Text" - } - ], - "termDefinition": { - "contents": [ - { - "annotation": { - "contents": "termUpdateMe", - "tag": "HashQualifier" + { + "annotation": { + "contents": "##Text", + "tag": "TypeReference" + }, + "segment": "Text" }, - "segment": "termUpdateMe" - }, - { - "annotation": { - "tag": "TypeAscriptionColon" + { + "annotation": null, + "segment": "\n" }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " - }, + { + "annotation": { + "contents": "termUpdateMe", + "tag": "HashQualifier" + }, + "segment": "termUpdateMe" + }, + { + "annotation": { + "tag": "BindingEquals" + }, + "segment": " =" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "TextLiteral" + }, + "segment": "\"original\"" + } + ], + "tag": "UserObject" + }, + "termDocs": [], + "termNames": [ + "termUpdateMe" + ] + }, + "right": { + "bestTermName": "termUpdateMe", + "defnTermTag": "Plain", + "signature": [ { "annotation": { "contents": "##Text", "tag": "TypeReference" }, "segment": "Text" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": { - "contents": "termUpdateMe", - "tag": "HashQualifier" + } + ], + "termDefinition": { + "contents": [ + { + "annotation": { + "contents": "termUpdateMe", + "tag": "HashQualifier" + }, + "segment": "termUpdateMe" }, - "segment": "termUpdateMe" - }, - { - "annotation": { - "tag": "BindingEquals" + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" }, - "segment": " =" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "tag": "TextLiteral" + { + "annotation": null, + "segment": " " }, - "segment": "\"updated\"" - } - ], - "tag": "UserObject" - }, - "termDocs": [], - "termNames": [ - "termUpdateMe" - ] - } + { + "annotation": { + "contents": "##Text", + "tag": "TypeReference" + }, + "segment": "Text" + }, + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": { + "contents": "termUpdateMe", + "tag": "HashQualifier" + }, + "segment": "termUpdateMe" + }, + { + "annotation": { + "tag": "BindingEquals" + }, + "segment": " =" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "TextLiteral" + }, + "segment": "\"updated\"" + } + ], + "tag": "UserObject" + }, + "termDocs": [], + "termNames": [ + "termUpdateMe" + ] + } + }, + "fullName": "termUpdateMe", + "newHash": "#711u1t9cjso4t3rhlq2rp491n2n5n4t9o7701053kpj5ouu3kfs2e2l63i879pnsb6ob9fp0gpj18u6fpcl1qosd704h4doklfo734g", + "newTag": "Plain", + "oldHash": "#ofktbubbloi1omgpr09e0t90pg0cnf0lsuuopqese9biqvpdafsuhq0b4dfasbk6g3hp5r7crp4t486fc8bava7q7rrreg9j2volam8", + "oldTag": "Plain", + "shortName": "termUpdateMe" }, - "fullName": "termUpdateMe", - "newHash": "#711u1t9cjso4t3rhlq2rp491n2n5n4t9o7701053kpj5ouu3kfs2e2l63i879pnsb6ob9fp0gpj18u6fpcl1qosd704h4doklfo734g", - "newTag": "Plain", - "oldHash": "#ofktbubbloi1omgpr09e0t90pg0cnf0lsuuopqese9biqvpdafsuhq0b4dfasbk6g3hp5r7crp4t486fc8bava7q7rrreg9j2volam8", - "oldTag": "Plain", - "shortName": "termUpdateMe" + "tag": "Updated" }, - "tag": "Updated" - }, - "tag": "Plain" - } - ], - "children": [ - { - "contents": { - "changes": [], - "children": [ - { - "contents": { - "changes": [ - { - "contents": { + "tag": "Plain" + } + ], + "children": [ + { + "contents": { + "changes": [], + "children": [ + { + "contents": { + "changes": [ + { "contents": { - "fullName": "a.definition.at.path1", - "hash": "#r303avnmdmja3ch96otiglq37214t43acpr1ikq4hrp5hmcibstipa69frbd6177jvbn28ioc5ii80fc54ecogm4n64dhjvkonrihso", - "rendered": { - "bestTermName": "path1", - "defnTermTag": "Plain", - "signature": [ - { - "annotation": { - "contents": "##Text", - "tag": "TypeReference" - }, - "segment": "Text" - } - ], - "termDefinition": { - "contents": [ - { - "annotation": { - "contents": "a.definition.at.path1", - "tag": "HashQualifier" - }, - "segment": "a.definition.at.path1" - }, - { - "annotation": { - "tag": "TypeAscriptionColon" - }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " - }, + "contents": { + "fullName": "a.definition.at.path1", + "hash": "#r303avnmdmja3ch96otiglq37214t43acpr1ikq4hrp5hmcibstipa69frbd6177jvbn28ioc5ii80fc54ecogm4n64dhjvkonrihso", + "rendered": { + "bestTermName": "path1", + "defnTermTag": "Plain", + "signature": [ { "annotation": { "contents": "##Text", "tag": "TypeReference" }, "segment": "Text" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": { - "contents": "a.definition.at.path1", - "tag": "HashQualifier" + } + ], + "termDefinition": { + "contents": [ + { + "annotation": { + "contents": "a.definition.at.path1", + "tag": "HashQualifier" + }, + "segment": "a.definition.at.path1" }, - "segment": "a.definition.at.path1" - }, - { - "annotation": { - "tag": "BindingEquals" + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" }, - "segment": " =" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "tag": "TextLiteral" + { + "annotation": null, + "segment": " " }, - "segment": "\"definition at path\"" - } - ], - "tag": "UserObject" + { + "annotation": { + "contents": "##Text", + "tag": "TypeReference" + }, + "segment": "Text" + }, + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": { + "contents": "a.definition.at.path1", + "tag": "HashQualifier" + }, + "segment": "a.definition.at.path1" + }, + { + "annotation": { + "tag": "BindingEquals" + }, + "segment": " =" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "TextLiteral" + }, + "segment": "\"definition at path\"" + } + ], + "tag": "UserObject" + }, + "termDocs": [], + "termNames": [ + "a.definition.at.path1" + ] }, - "termDocs": [], - "termNames": [ - "a.definition.at.path1" - ] + "shortName": "path1" }, - "shortName": "path1" + "tag": "Removed" }, - "tag": "Removed" + "tag": "Plain" }, - "tag": "Plain" - }, - { - "contents": { + { "contents": { - "fullName": "a.definition.at.path2", - "hash": "#k43vb9rkd3n4i8g8bbfb31erufbmu6v1f99i587oqsje51thrm1ugdqa7gkjbdvkactuql3cmc00b7oev0glqb2rko48atkuo798mno", - "rendered": { - "bestTermName": "path2", - "defnTermTag": "Plain", - "signature": [ - { - "annotation": { - "contents": "##Text", - "tag": "TypeReference" - }, - "segment": "Text" - } - ], - "termDefinition": { - "contents": [ - { - "annotation": { - "contents": "a.definition.at.path2", - "tag": "HashQualifier" - }, - "segment": "a.definition.at.path2" - }, - { - "annotation": { - "tag": "TypeAscriptionColon" - }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " - }, + "contents": { + "fullName": "a.definition.at.path2", + "hash": "#k43vb9rkd3n4i8g8bbfb31erufbmu6v1f99i587oqsje51thrm1ugdqa7gkjbdvkactuql3cmc00b7oev0glqb2rko48atkuo798mno", + "rendered": { + "bestTermName": "path2", + "defnTermTag": "Plain", + "signature": [ { "annotation": { "contents": "##Text", "tag": "TypeReference" }, "segment": "Text" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": { - "contents": "a.definition.at.path2", - "tag": "HashQualifier" + } + ], + "termDefinition": { + "contents": [ + { + "annotation": { + "contents": "a.definition.at.path2", + "tag": "HashQualifier" + }, + "segment": "a.definition.at.path2" }, - "segment": "a.definition.at.path2" - }, - { - "annotation": { - "tag": "BindingEquals" + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" }, - "segment": " =" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "tag": "TextLiteral" + { + "annotation": null, + "segment": " " }, - "segment": "\"definition at path2\"" - } - ], - "tag": "UserObject" + { + "annotation": { + "contents": "##Text", + "tag": "TypeReference" + }, + "segment": "Text" + }, + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": { + "contents": "a.definition.at.path2", + "tag": "HashQualifier" + }, + "segment": "a.definition.at.path2" + }, + { + "annotation": { + "tag": "BindingEquals" + }, + "segment": " =" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "TextLiteral" + }, + "segment": "\"definition at path2\"" + } + ], + "tag": "UserObject" + }, + "termDocs": [], + "termNames": [ + "a.definition.at.path2" + ] }, - "termDocs": [], - "termNames": [ - "a.definition.at.path2" - ] + "shortName": "path2" }, - "shortName": "path2" + "tag": "Removed" }, - "tag": "Removed" - }, - "tag": "Plain" - } - ], - "children": [] + "tag": "Plain" + } + ], + "children": [] + }, + "path": "definition.at" }, - "path": "definition.at" - }, - { - "contents": { - "changes": [ - { - "contents": { + { + "contents": { + "changes": [ + { "contents": { - "fullName": "a.different.path", - "hash": "#83be375arg68mqk26bu12elka6fb6mvq6cec92un1p1t5kulhh6672qlnego952pp7h4lfl7mq3crithvtvo3col9mfc8vurbnb8hvo", - "rendered": { - "bestTermName": "path", - "defnTermTag": "Plain", - "signature": [ - { - "annotation": { - "contents": "##Text", - "tag": "TypeReference" - }, - "segment": "Text" - } - ], - "termDefinition": { - "contents": [ - { - "annotation": { - "contents": "a.different.path", - "tag": "HashQualifier" - }, - "segment": "a.different.path" - }, - { - "annotation": { - "tag": "TypeAscriptionColon" - }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " - }, + "contents": { + "fullName": "a.different.path", + "hash": "#83be375arg68mqk26bu12elka6fb6mvq6cec92un1p1t5kulhh6672qlnego952pp7h4lfl7mq3crithvtvo3col9mfc8vurbnb8hvo", + "rendered": { + "bestTermName": "path", + "defnTermTag": "Plain", + "signature": [ { "annotation": { "contents": "##Text", "tag": "TypeReference" }, "segment": "Text" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": { - "contents": "a.different.path", - "tag": "HashQualifier" + } + ], + "termDefinition": { + "contents": [ + { + "annotation": { + "contents": "a.different.path", + "tag": "HashQualifier" + }, + "segment": "a.different.path" }, - "segment": "a.different.path" - }, - { - "annotation": { - "tag": "BindingEquals" + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" }, - "segment": " =" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "tag": "TextLiteral" + { + "annotation": null, + "segment": " " }, - "segment": "\"definition at different path\"" - } - ], - "tag": "UserObject" + { + "annotation": { + "contents": "##Text", + "tag": "TypeReference" + }, + "segment": "Text" + }, + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": { + "contents": "a.different.path", + "tag": "HashQualifier" + }, + "segment": "a.different.path" + }, + { + "annotation": { + "tag": "BindingEquals" + }, + "segment": " =" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "TextLiteral" + }, + "segment": "\"definition at different path\"" + } + ], + "tag": "UserObject" + }, + "termDocs": [], + "termNames": [ + "a.different.path" + ] }, - "termDocs": [], - "termNames": [ - "a.different.path" - ] + "shortName": "path" }, - "shortName": "path" + "tag": "Removed" }, - "tag": "Removed" - }, - "tag": "Plain" - } - ], - "children": [] - }, - "path": "different" - } - ] - }, - "path": "a" - } - ] + "tag": "Plain" + } + ], + "children": [] + }, + "path": "different" + } + ] + }, + "path": "a" + } + ] + }, + "libdeps": [] }, "newRef": "diff-end", - "newRefHash": "#u8i8k3pujkli3o266tsbl9nh3s6al548121ir0mvm7v0nq3v3lhdntfa2p0np7d20drm0dotbs5tfsggadgrqnkqpnmt6tjm3dd9ig0", + "newRefHash": "#f2bjgi4tm53bf6dcfcukt5a6as3ktlrbiacnqq81nco8i4g7dg6pt14vmc1b7ulsb7rt683qjt2rvg9u92uo5mk1gaqgo8cl30umep8", "oldRef": "diff-start", - "oldRefHash": "#rp780a26gio3v8viaq10oa51r4g5b1ocsokmleuo4bc9sjkhq2rut502tmpmrdb5al5lb7k6u7vhp6dab174a48rjoklf3jddp7o420", + "oldRefHash": "#f8nji6tc2vaorc7gl8kjdmj8ucrht674blmb586iptgsa8v1pm8ovjplc4an2voirvlip91ick9g5mjkncsmr8sadaqqf8810eskbig", "project": "@transcripts/contribution-diff" }, "status": [ diff --git a/transcripts/share-apis/contribution-diffs/namespace-diff.json b/transcripts/share-apis/contribution-diffs/namespace-diff.json index f9ad6141..db781a63 100644 --- a/transcripts/share-apis/contribution-diffs/namespace-diff.json +++ b/transcripts/share-apis/contribution-diffs/namespace-diff.json @@ -1,614 +1,387 @@ { "body": { "diff": { - "changes": [ - { - "contents": { + "defns": { + "changes": [ + { "contents": { - "aliasFullName": "ATypeAlias", - "aliasShortName": "ATypeAlias", - "hash": "#bbsbe7lolqunqrftm9jeg299caa91r2mlviqic54toilse443ljup5eojm1et3lqv6ni5gsu9l9hpldptga3cp5e0qffhg36gv5u2jo", - "otherNames": [ - "DataAliasMe" - ], - "rendered": { - "bestTypeName": "ATypeAlias", - "defnTypeTag": "Data", - "typeDefinition": { - "contents": [ - { - "annotation": { - "tag": "DataTypeKeyword" + "contents": { + "aliasFullName": "ATypeAlias", + "aliasShortName": "ATypeAlias", + "hash": "#keu02n8is0irijd65cvuos41kukj3f4ni18mmnudrbll2epo6ftd03nt9l0vqc4fvg98198tefgoupco4o0d0gvnigqgr1bmo2neo88", + "otherNames": [ + "DataAliasMe" + ], + "rendered": { + "bestTypeName": "ATypeAlias", + "defnTypeTag": "Data", + "typeDefinition": { + "contents": [ + { + "annotation": { + "tag": "DataTypeKeyword" + }, + "segment": "type" }, - "segment": "type" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "ATypeAlias", - "tag": "HashQualifier" + { + "annotation": null, + "segment": " " }, - "segment": "ATypeAlias" - }, - { - "annotation": { - "tag": "DelimiterChar" + { + "annotation": { + "contents": "ATypeAlias", + "tag": "HashQualifier" + }, + "segment": "ATypeAlias" }, - "segment": " = " - }, - { - "annotation": { - "contents": "#bbsbe7lolqunqrftm9jeg299caa91r2mlviqic54toilse443ljup5eojm1et3lqv6ni5gsu9l9hpldptga3cp5e0qffhg36gv5u2jo#d0", - "tag": "TermReference" + { + "annotation": { + "tag": "DelimiterChar" + }, + "segment": " = " }, - "segment": "B" - } - ], - "tag": "UserObject" - }, - "typeDocs": [], - "typeNames": [ - "ATypeAlias", - "DataAliasMe" - ] - } + { + "annotation": { + "contents": "#keu02n8is0irijd65cvuos41kukj3f4ni18mmnudrbll2epo6ftd03nt9l0vqc4fvg98198tefgoupco4o0d0gvnigqgr1bmo2neo88#d0", + "tag": "TermReference" + }, + "segment": "B" + } + ], + "tag": "UserObject" + }, + "typeDocs": [], + "typeNames": [ + "ATypeAlias", + "DataAliasMe" + ] + } + }, + "tag": "Aliased" }, - "tag": "Aliased" + "tag": "Data" }, - "tag": "Data" - }, - { - "contents": { + { "contents": { - "aliasFullName": "AbilityAlias", - "aliasShortName": "AbilityAlias", - "hash": "#qfgn5crplnhh308pepplqtleojiqhlpveimv0htug2mqbvhnia7qjfcravqlfb8ooos56jo5qq6brr99gg5kj0g5bgllvgn1nesv608", - "otherNames": [ - "AbilityAliasMe" - ], - "rendered": { - "bestTypeName": "AbilityAlias", - "defnTypeTag": "Ability", - "typeDefinition": { - "contents": [ - { - "annotation": { - "tag": "DataTypeKeyword" - }, - "segment": "ability" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "AbilityAlias", - "tag": "HashQualifier" - }, - "segment": "AbilityAlias" - }, - { - "annotation": { - "tag": "ControlKeyword" - }, - "segment": " where" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "#qfgn5crplnhh308pepplqtleojiqhlpveimv0htug2mqbvhnia7qjfcravqlfb8ooos56jo5qq6brr99gg5kj0g5bgllvgn1nesv608#a0", - "tag": "TermReference" - }, - "segment": "abilityAliasMe" - }, - { - "annotation": { - "tag": "TypeAscriptionColon" - }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "tag": "AbilityBraces" + "contents": { + "aliasFullName": "AbilityAlias", + "aliasShortName": "AbilityAlias", + "hash": "#u9m3jehjj8mtrhh4i4fuk545k3pdged9r0egph91irldf4lc0rsmtma9eoakvv9hoeesciebuqd7kfm0vdnk48gi7q3s7edn5omb65o", + "otherNames": [ + "AbilityAliasMe" + ], + "rendered": { + "bestTypeName": "AbilityAlias", + "defnTypeTag": "Ability", + "typeDefinition": { + "contents": [ + { + "annotation": { + "tag": "DataTypeKeyword" + }, + "segment": "ability" }, - "segment": "{" - }, - { - "annotation": { - "contents": "#qfgn5crplnhh308pepplqtleojiqhlpveimv0htug2mqbvhnia7qjfcravqlfb8ooos56jo5qq6brr99gg5kj0g5bgllvgn1nesv608", - "tag": "TypeReference" + { + "annotation": null, + "segment": " " }, - "segment": "AbilityAlias" - }, - { - "annotation": { - "tag": "AbilityBraces" + { + "annotation": { + "contents": "AbilityAlias", + "tag": "HashQualifier" + }, + "segment": "AbilityAlias" }, - "segment": "}" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "##Nat", - "tag": "TypeReference" + { + "annotation": { + "tag": "ControlKeyword" + }, + "segment": " where" }, - "segment": "Nat" - } - ], - "tag": "UserObject" - }, - "typeDocs": [], - "typeNames": [ - "AbilityAlias", - "AbilityAliasMe" - ] - } - }, - "tag": "Aliased" - }, - "tag": "Ability" - }, - { - "contents": { - "contents": { - "fullName": "AbilityDeleteMe", - "hash": "#val3i3ikhjc998qh1lfefhh08ad77f1eshera5d0hnbrp6qpgmfelbfa96pvsc18d5qd5qm7lij5el0raipb3mbjgalkh7g3aujej1o", - "rendered": { - "bestTypeName": "AbilityDeleteMe", - "defnTypeTag": "Ability", - "typeDefinition": { - "contents": [ - { - "annotation": { - "tag": "DataTypeKeyword" + { + "annotation": null, + "segment": "\n" }, - "segment": "ability" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "AbilityDeleteMe", - "tag": "HashQualifier" + { + "annotation": null, + "segment": " " }, - "segment": "AbilityDeleteMe" - }, - { - "annotation": { - "tag": "ControlKeyword" + { + "annotation": { + "contents": "#u9m3jehjj8mtrhh4i4fuk545k3pdged9r0egph91irldf4lc0rsmtma9eoakvv9hoeesciebuqd7kfm0vdnk48gi7q3s7edn5omb65o#a0", + "tag": "TermReference" + }, + "segment": "abilityAliasMe" }, - "segment": " where" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "#val3i3ikhjc998qh1lfefhh08ad77f1eshera5d0hnbrp6qpgmfelbfa96pvsc18d5qd5qm7lij5el0raipb3mbjgalkh7g3aujej1o#a0", - "tag": "TermReference" + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" }, - "segment": "abilityDeleteMe" - }, - { - "annotation": { - "tag": "TypeAscriptionColon" + { + "annotation": null, + "segment": " " }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "tag": "AbilityBraces" + { + "annotation": { + "tag": "AbilityBraces" + }, + "segment": "{" }, - "segment": "{" - }, - { - "annotation": { - "contents": "#val3i3ikhjc998qh1lfefhh08ad77f1eshera5d0hnbrp6qpgmfelbfa96pvsc18d5qd5qm7lij5el0raipb3mbjgalkh7g3aujej1o", - "tag": "TypeReference" + { + "annotation": { + "contents": "#u9m3jehjj8mtrhh4i4fuk545k3pdged9r0egph91irldf4lc0rsmtma9eoakvv9hoeesciebuqd7kfm0vdnk48gi7q3s7edn5omb65o", + "tag": "TypeReference" + }, + "segment": "AbilityAlias" }, - "segment": "AbilityDeleteMe" - }, - { - "annotation": { - "tag": "AbilityBraces" + { + "annotation": { + "tag": "AbilityBraces" + }, + "segment": "}" }, - "segment": "}" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "##Nat", - "tag": "TypeReference" + { + "annotation": null, + "segment": " " }, - "segment": "Nat" - } - ], - "tag": "UserObject" - }, - "typeDocs": [], - "typeNames": [ - "AbilityDeleteMe" - ] + { + "annotation": { + "contents": "##Nat", + "tag": "TypeReference" + }, + "segment": "Nat" + } + ], + "tag": "UserObject" + }, + "typeDocs": [], + "typeNames": [ + "AbilityAlias", + "AbilityAliasMe" + ] + } }, - "shortName": "AbilityDeleteMe" + "tag": "Aliased" }, - "tag": "Removed" + "tag": "Ability" }, - "tag": "Ability" - }, - { - "contents": { + { "contents": { - "fullName": "AbilityNew", - "hash": "#t66tvdfo0l4pqj6hgav05tqifbuld8dc22g4rom3olfqj7b6cfpvf15j7307j8m2fpdsvcgv4ourrltpjutgpu3bh08efu2jl2nfqq0", - "rendered": { - "bestTypeName": "AbilityNew", - "defnTypeTag": "Ability", - "typeDefinition": { - "contents": [ - { - "annotation": { - "tag": "DataTypeKeyword" + "contents": { + "fullName": "AbilityDeleteMe", + "hash": "#i201btc2422jlmnric78btv3kl1palljsgc55mvm6rb9ofdos9u8mh2jd70uev381oiun4todb8vhkvvpteieshbfsot4slo9cgrjcg", + "rendered": { + "bestTypeName": "AbilityDeleteMe", + "defnTypeTag": "Ability", + "typeDefinition": { + "contents": [ + { + "annotation": { + "tag": "DataTypeKeyword" + }, + "segment": "ability" }, - "segment": "ability" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "AbilityNew", - "tag": "HashQualifier" + { + "annotation": null, + "segment": " " }, - "segment": "AbilityNew" - }, - { - "annotation": { - "tag": "ControlKeyword" + { + "annotation": { + "contents": "AbilityDeleteMe", + "tag": "HashQualifier" + }, + "segment": "AbilityDeleteMe" }, - "segment": " where" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "#t66tvdfo0l4pqj6hgav05tqifbuld8dc22g4rom3olfqj7b6cfpvf15j7307j8m2fpdsvcgv4ourrltpjutgpu3bh08efu2jl2nfqq0#a0", - "tag": "TermReference" + { + "annotation": { + "tag": "ControlKeyword" + }, + "segment": " where" }, - "segment": "abilityNew" - }, - { - "annotation": { - "tag": "TypeAscriptionColon" + { + "annotation": null, + "segment": "\n" }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "tag": "AbilityBraces" + { + "annotation": null, + "segment": " " }, - "segment": "{" - }, - { - "annotation": { - "contents": "#t66tvdfo0l4pqj6hgav05tqifbuld8dc22g4rom3olfqj7b6cfpvf15j7307j8m2fpdsvcgv4ourrltpjutgpu3bh08efu2jl2nfqq0", - "tag": "TypeReference" + { + "annotation": { + "contents": "#i201btc2422jlmnric78btv3kl1palljsgc55mvm6rb9ofdos9u8mh2jd70uev381oiun4todb8vhkvvpteieshbfsot4slo9cgrjcg#a0", + "tag": "TermReference" + }, + "segment": "abilityDeleteMe" }, - "segment": "AbilityNew" - }, - { - "annotation": { - "tag": "AbilityBraces" + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" }, - "segment": "}" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "##Text", - "tag": "TypeReference" + { + "annotation": null, + "segment": " " }, - "segment": "Text" - } - ], - "tag": "UserObject" + { + "annotation": { + "tag": "AbilityBraces" + }, + "segment": "{" + }, + { + "annotation": { + "contents": "#i201btc2422jlmnric78btv3kl1palljsgc55mvm6rb9ofdos9u8mh2jd70uev381oiun4todb8vhkvvpteieshbfsot4slo9cgrjcg", + "tag": "TypeReference" + }, + "segment": "AbilityDeleteMe" + }, + { + "annotation": { + "tag": "AbilityBraces" + }, + "segment": "}" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "##Nat", + "tag": "TypeReference" + }, + "segment": "Nat" + } + ], + "tag": "UserObject" + }, + "typeDocs": [], + "typeNames": [ + "AbilityDeleteMe" + ] }, - "typeDocs": [], - "typeNames": [ - "AbilityNew" - ] + "shortName": "AbilityDeleteMe" }, - "shortName": "AbilityNew" + "tag": "Removed" }, - "tag": "Added" + "tag": "Ability" }, - "tag": "Ability" - }, - { - "contents": { + { "contents": { - "hash": "#iqmiiehu802p15ssntohl6l5kedd0j266rh7815s1t10rfe2bp207vh8ccngrlkii7i32h1n080dggr3r89osrq450kv6dj5uuc0o0o", - "newFullName": "AbilityRenamed", - "newShortName": "AbilityRenamed", - "oldNames": [ - "AbilityRenameMe" - ], - "rendered": { - "bestTypeName": "AbilityRenamed", - "defnTypeTag": "Ability", - "typeDefinition": { - "contents": [ - { - "annotation": { - "tag": "DataTypeKeyword" - }, - "segment": "ability" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "AbilityRenamed", - "tag": "HashQualifier" - }, - "segment": "AbilityRenamed" - }, - { - "annotation": { - "tag": "ControlKeyword" - }, - "segment": " where" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "#iqmiiehu802p15ssntohl6l5kedd0j266rh7815s1t10rfe2bp207vh8ccngrlkii7i32h1n080dggr3r89osrq450kv6dj5uuc0o0o#a0", - "tag": "TermReference" - }, - "segment": "abilityRenameMe" - }, - { - "annotation": { - "tag": "TypeAscriptionColon" - }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "tag": "AbilityBraces" + "contents": { + "fullName": "AbilityNew", + "hash": "#n7jj1pvi6a8689nggmnlhmn8hvkjiu4j5563kojf57dcf8dribv5suliht31nbpgc4501h26geepfg5o8jiid45h6ccmf8ogqu39am0", + "rendered": { + "bestTypeName": "AbilityNew", + "defnTypeTag": "Ability", + "typeDefinition": { + "contents": [ + { + "annotation": { + "tag": "DataTypeKeyword" + }, + "segment": "ability" }, - "segment": "{" - }, - { - "annotation": { - "contents": "#iqmiiehu802p15ssntohl6l5kedd0j266rh7815s1t10rfe2bp207vh8ccngrlkii7i32h1n080dggr3r89osrq450kv6dj5uuc0o0o", - "tag": "TypeReference" + { + "annotation": null, + "segment": " " }, - "segment": "AbilityRenamed" - }, - { - "annotation": { - "tag": "AbilityBraces" + { + "annotation": { + "contents": "AbilityNew", + "tag": "HashQualifier" + }, + "segment": "AbilityNew" }, - "segment": "}" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "##Nat", - "tag": "TypeReference" + { + "annotation": { + "tag": "ControlKeyword" + }, + "segment": " where" }, - "segment": "Nat" - } - ], - "tag": "UserObject" - }, - "typeDocs": [], - "typeNames": [ - "AbilityRenamed" - ] - } - }, - "tag": "RenamedFrom" - }, - "tag": "Ability" - }, - { - "contents": { - "contents": { - "diff": { - "diff": { - "diff": { - "contents": [ { - "diffTag": "both", - "elements": [ - { - "annotation": { - "tag": "DataTypeKeyword" - }, - "segment": "ability" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "AbilityUpdateMe", - "tag": "HashQualifier" - }, - "segment": "AbilityUpdateMe" - }, - { - "annotation": { - "tag": "ControlKeyword" - }, - "segment": " where" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": null, - "segment": " " - } - ] + "annotation": null, + "segment": "\n" + }, + { + "annotation": null, + "segment": " " }, { - "diffTag": "annotationChange", - "fromAnnotation": { - "contents": "#0d5ej3mann48uffjea4epi8ss486689gsj46cscorhs3d4j7ohvj9t7ghg05tra792umcmgjr6lgqkskoo3odge7jm2ci91dlmpefcg#a0", + "annotation": { + "contents": "#n7jj1pvi6a8689nggmnlhmn8hvkjiu4j5563kojf57dcf8dribv5suliht31nbpgc4501h26geepfg5o8jiid45h6ccmf8ogqu39am0#a0", "tag": "TermReference" }, - "segment": "abilityUpdateMe", - "toAnnotation": { - "contents": "#qat72tp0lb43gp5pra5rgobup5r24qrc494crqd5pqjddbneiqdn3hq6puo2344nja1v6cp7aps1p0350ug0f1kvo9cp2gu9l31in18#a0", - "tag": "TermReference" - } + "segment": "abilityNew" }, { - "diffTag": "both", - "elements": [ - { - "annotation": { - "tag": "TypeAscriptionColon" - }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "tag": "AbilityBraces" - }, - "segment": "{" - } - ] + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" }, { - "diffTag": "annotationChange", - "fromAnnotation": { - "contents": "#0d5ej3mann48uffjea4epi8ss486689gsj46cscorhs3d4j7ohvj9t7ghg05tra792umcmgjr6lgqkskoo3odge7jm2ci91dlmpefcg", - "tag": "TypeReference" + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "AbilityBraces" }, - "segment": "AbilityUpdateMe", - "toAnnotation": { - "contents": "#qat72tp0lb43gp5pra5rgobup5r24qrc494crqd5pqjddbneiqdn3hq6puo2344nja1v6cp7aps1p0350ug0f1kvo9cp2gu9l31in18", + "segment": "{" + }, + { + "annotation": { + "contents": "#n7jj1pvi6a8689nggmnlhmn8hvkjiu4j5563kojf57dcf8dribv5suliht31nbpgc4501h26geepfg5o8jiid45h6ccmf8ogqu39am0", "tag": "TypeReference" - } + }, + "segment": "AbilityNew" }, { - "diffTag": "both", - "elements": [ - { - "annotation": { - "tag": "AbilityBraces" - }, - "segment": "}" - }, - { - "annotation": null, - "segment": " " - } - ] + "annotation": { + "tag": "AbilityBraces" + }, + "segment": "}" }, { - "diffTag": "old", - "elements": [ - { - "annotation": { - "contents": "##Nat", - "tag": "TypeReference" - }, - "segment": "Nat" - } - ] + "annotation": null, + "segment": " " }, { - "diffTag": "new", - "elements": [ - { - "annotation": { - "contents": "##Text", - "tag": "TypeReference" - }, - "segment": "Text" - } - ] + "annotation": { + "contents": "##Text", + "tag": "TypeReference" + }, + "segment": "Text" } ], "tag": "UserObject" }, - "diffKind": "diff" + "typeDocs": [], + "typeNames": [ + "AbilityNew" + ] }, - "left": { - "bestTypeName": "AbilityUpdateMe", + "shortName": "AbilityNew" + }, + "tag": "Added" + }, + "tag": "Ability" + }, + { + "contents": { + "contents": { + "hash": "#lh3ufh51cghv5sn14ckq9f2urei00i6adqj3d0vovc51c6f18bhauqfjhkm34227ediga6mc5dp58inn4j714rhenig2jsps9ima7do", + "newFullName": "AbilityRenamed", + "newShortName": "AbilityRenamed", + "oldNames": [ + "AbilityRenameMe" + ], + "rendered": { + "bestTypeName": "AbilityRenamed", "defnTypeTag": "Ability", "typeDefinition": { "contents": [ @@ -624,10 +397,10 @@ }, { "annotation": { - "contents": "AbilityUpdateMe", + "contents": "AbilityRenamed", "tag": "HashQualifier" }, - "segment": "AbilityUpdateMe" + "segment": "AbilityRenamed" }, { "annotation": { @@ -645,16 +418,405 @@ }, { "annotation": { - "contents": "#0d5ej3mann48uffjea4epi8ss486689gsj46cscorhs3d4j7ohvj9t7ghg05tra792umcmgjr6lgqkskoo3odge7jm2ci91dlmpefcg#a0", + "contents": "#lh3ufh51cghv5sn14ckq9f2urei00i6adqj3d0vovc51c6f18bhauqfjhkm34227ediga6mc5dp58inn4j714rhenig2jsps9ima7do#a0", "tag": "TermReference" }, - "segment": "abilityUpdateMe" + "segment": "abilityRenameMe" + }, + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "AbilityBraces" + }, + "segment": "{" + }, + { + "annotation": { + "contents": "#lh3ufh51cghv5sn14ckq9f2urei00i6adqj3d0vovc51c6f18bhauqfjhkm34227ediga6mc5dp58inn4j714rhenig2jsps9ima7do", + "tag": "TypeReference" + }, + "segment": "AbilityRenamed" + }, + { + "annotation": { + "tag": "AbilityBraces" + }, + "segment": "}" + }, + { + "annotation": null, + "segment": " " }, { "annotation": { - "tag": "TypeAscriptionColon" + "contents": "##Nat", + "tag": "TypeReference" + }, + "segment": "Nat" + } + ], + "tag": "UserObject" + }, + "typeDocs": [], + "typeNames": [ + "AbilityRenamed" + ] + } + }, + "tag": "RenamedFrom" + }, + "tag": "Ability" + }, + { + "contents": { + "contents": { + "diff": { + "diff": { + "diff": { + "contents": [ + { + "diffTag": "both", + "elements": [ + { + "annotation": { + "tag": "DataTypeKeyword" + }, + "segment": "ability" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "AbilityUpdateMe", + "tag": "HashQualifier" + }, + "segment": "AbilityUpdateMe" + }, + { + "annotation": { + "tag": "ControlKeyword" + }, + "segment": " where" + }, + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": null, + "segment": " " + } + ] + }, + { + "diffTag": "annotationChange", + "fromAnnotation": { + "contents": "#8u70g0vaddp9jm3egoq434qialp8hdnjfh8ah8mqjau0i5lmdikt9qbe491ss53i71976fftb2o90ii6gckvs0i2lhovs1n6h0huhb0#a0", + "tag": "TermReference" + }, + "segment": "abilityUpdateMe", + "toAnnotation": { + "contents": "#nnulmopbjndcs4si1mop30dm01nlum2k7m6j4mmd1df2e63m09lchh2j1gkqd4gua3bl0g3j6hgn76rmc495au8cpr0t83oqoho0sng#a0", + "tag": "TermReference" + } + }, + { + "diffTag": "both", + "elements": [ + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "AbilityBraces" + }, + "segment": "{" + } + ] + }, + { + "diffTag": "annotationChange", + "fromAnnotation": { + "contents": "#8u70g0vaddp9jm3egoq434qialp8hdnjfh8ah8mqjau0i5lmdikt9qbe491ss53i71976fftb2o90ii6gckvs0i2lhovs1n6h0huhb0", + "tag": "TypeReference" + }, + "segment": "AbilityUpdateMe", + "toAnnotation": { + "contents": "#nnulmopbjndcs4si1mop30dm01nlum2k7m6j4mmd1df2e63m09lchh2j1gkqd4gua3bl0g3j6hgn76rmc495au8cpr0t83oqoho0sng", + "tag": "TypeReference" + } + }, + { + "diffTag": "both", + "elements": [ + { + "annotation": { + "tag": "AbilityBraces" + }, + "segment": "}" + }, + { + "annotation": null, + "segment": " " + } + ] + }, + { + "diffTag": "old", + "elements": [ + { + "annotation": { + "contents": "##Nat", + "tag": "TypeReference" + }, + "segment": "Nat" + } + ] + }, + { + "diffTag": "new", + "elements": [ + { + "annotation": { + "contents": "##Text", + "tag": "TypeReference" + }, + "segment": "Text" + } + ] + } + ], + "tag": "UserObject" + }, + "diffKind": "diff" + }, + "left": { + "bestTypeName": "AbilityUpdateMe", + "defnTypeTag": "Ability", + "typeDefinition": { + "contents": [ + { + "annotation": { + "tag": "DataTypeKeyword" + }, + "segment": "ability" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "AbilityUpdateMe", + "tag": "HashQualifier" + }, + "segment": "AbilityUpdateMe" + }, + { + "annotation": { + "tag": "ControlKeyword" + }, + "segment": " where" + }, + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "#8u70g0vaddp9jm3egoq434qialp8hdnjfh8ah8mqjau0i5lmdikt9qbe491ss53i71976fftb2o90ii6gckvs0i2lhovs1n6h0huhb0#a0", + "tag": "TermReference" + }, + "segment": "abilityUpdateMe" + }, + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "AbilityBraces" + }, + "segment": "{" + }, + { + "annotation": { + "contents": "#8u70g0vaddp9jm3egoq434qialp8hdnjfh8ah8mqjau0i5lmdikt9qbe491ss53i71976fftb2o90ii6gckvs0i2lhovs1n6h0huhb0", + "tag": "TypeReference" + }, + "segment": "AbilityUpdateMe" + }, + { + "annotation": { + "tag": "AbilityBraces" + }, + "segment": "}" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "##Nat", + "tag": "TypeReference" + }, + "segment": "Nat" + } + ], + "tag": "UserObject" + }, + "typeDocs": [], + "typeNames": [ + "AbilityUpdateMe" + ] + }, + "right": { + "bestTypeName": "AbilityUpdateMe", + "defnTypeTag": "Ability", + "typeDefinition": { + "contents": [ + { + "annotation": { + "tag": "DataTypeKeyword" + }, + "segment": "ability" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "AbilityUpdateMe", + "tag": "HashQualifier" + }, + "segment": "AbilityUpdateMe" + }, + { + "annotation": { + "tag": "ControlKeyword" + }, + "segment": " where" + }, + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "#nnulmopbjndcs4si1mop30dm01nlum2k7m6j4mmd1df2e63m09lchh2j1gkqd4gua3bl0g3j6hgn76rmc495au8cpr0t83oqoho0sng#a0", + "tag": "TermReference" + }, + "segment": "abilityUpdateMe" + }, + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "AbilityBraces" + }, + "segment": "{" + }, + { + "annotation": { + "contents": "#nnulmopbjndcs4si1mop30dm01nlum2k7m6j4mmd1df2e63m09lchh2j1gkqd4gua3bl0g3j6hgn76rmc495au8cpr0t83oqoho0sng", + "tag": "TypeReference" + }, + "segment": "AbilityUpdateMe" + }, + { + "annotation": { + "tag": "AbilityBraces" + }, + "segment": "}" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "##Text", + "tag": "TypeReference" + }, + "segment": "Text" + } + ], + "tag": "UserObject" + }, + "typeDocs": [], + "typeNames": [ + "AbilityUpdateMe" + ] + } + }, + "fullName": "AbilityUpdateMe", + "newHash": "#nnulmopbjndcs4si1mop30dm01nlum2k7m6j4mmd1df2e63m09lchh2j1gkqd4gua3bl0g3j6hgn76rmc495au8cpr0t83oqoho0sng", + "newTag": "Ability", + "oldHash": "#8u70g0vaddp9jm3egoq434qialp8hdnjfh8ah8mqjau0i5lmdikt9qbe491ss53i71976fftb2o90ii6gckvs0i2lhovs1n6h0huhb0", + "oldTag": "Ability", + "shortName": "AbilityUpdateMe" + }, + "tag": "Updated" + }, + "tag": "Ability" + }, + { + "contents": { + "contents": { + "fullName": "DataDeleteMe", + "hash": "#fhc8jn2bhvfdnfr89dv2jf7tekuesna7gvje4ck6lfheh9rb184q4ddd29vm9mvfm6u1a98kpgditn8vb09durtel67rpof1c62535o", + "rendered": { + "bestTypeName": "DataDeleteMe", + "defnTypeTag": "Data", + "typeDefinition": { + "contents": [ + { + "annotation": { + "tag": "DataTypeKeyword" }, - "segment": " :" + "segment": "type" }, { "annotation": null, @@ -662,52 +824,237 @@ }, { "annotation": { - "tag": "AbilityBraces" - }, - "segment": "{" - }, - { - "annotation": { - "contents": "#0d5ej3mann48uffjea4epi8ss486689gsj46cscorhs3d4j7ohvj9t7ghg05tra792umcmgjr6lgqkskoo3odge7jm2ci91dlmpefcg", - "tag": "TypeReference" + "contents": "DataDeleteMe", + "tag": "HashQualifier" }, - "segment": "AbilityUpdateMe" + "segment": "DataDeleteMe" }, { "annotation": { - "tag": "AbilityBraces" + "tag": "DelimiterChar" }, - "segment": "}" - }, - { - "annotation": null, - "segment": " " + "segment": " = " }, { "annotation": { - "contents": "##Nat", - "tag": "TypeReference" + "contents": "#fhc8jn2bhvfdnfr89dv2jf7tekuesna7gvje4ck6lfheh9rb184q4ddd29vm9mvfm6u1a98kpgditn8vb09durtel67rpof1c62535o#d0", + "tag": "TermReference" }, - "segment": "Nat" + "segment": "C" } ], "tag": "UserObject" }, "typeDocs": [], "typeNames": [ - "AbilityUpdateMe" + "DataDeleteMe" ] }, - "right": { - "bestTypeName": "AbilityUpdateMe", - "defnTypeTag": "Ability", + "shortName": "DataDeleteMe" + }, + "tag": "Removed" + }, + "tag": "Data" + }, + { + "contents": { + "contents": { + "diff": { + "diff": { + "diff": { + "contents": [ + { + "diffTag": "both", + "elements": [ + { + "annotation": { + "tag": "DataTypeKeyword" + }, + "segment": "type" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "DataUpdateMe", + "tag": "HashQualifier" + }, + "segment": "DataUpdateMe" + }, + { + "annotation": { + "tag": "DelimiterChar" + }, + "segment": " = " + } + ] + }, + { + "diffTag": "old", + "elements": [ + { + "annotation": { + "contents": "#a2bvb3g2l1mkijg24ogg0t23h51pnfepnngk6e3bqfijf4l9ms292t006e8faquo66ctn1ho35vtps13m6evbl6bos2guer5j6jcs1o#d0", + "tag": "TermReference" + }, + "segment": "D" + } + ] + }, + { + "diffTag": "new", + "elements": [ + { + "annotation": { + "contents": "#6t7t8lem3bmu3j7bsid4omn8gej2gl57ffmkp0ef6qndhndh2q3q6dd1j9akl653r3vtifsunovvbmbjh0iqc7n6rhp4imnsghhe6go#d0", + "tag": "TermReference" + }, + "segment": "D2" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "##Nat", + "tag": "TypeReference" + }, + "segment": "Nat" + } + ] + } + ], + "tag": "UserObject" + }, + "diffKind": "diff" + }, + "left": { + "bestTypeName": "DataUpdateMe", + "defnTypeTag": "Data", + "typeDefinition": { + "contents": [ + { + "annotation": { + "tag": "DataTypeKeyword" + }, + "segment": "type" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "DataUpdateMe", + "tag": "HashQualifier" + }, + "segment": "DataUpdateMe" + }, + { + "annotation": { + "tag": "DelimiterChar" + }, + "segment": " = " + }, + { + "annotation": { + "contents": "#a2bvb3g2l1mkijg24ogg0t23h51pnfepnngk6e3bqfijf4l9ms292t006e8faquo66ctn1ho35vtps13m6evbl6bos2guer5j6jcs1o#d0", + "tag": "TermReference" + }, + "segment": "D" + } + ], + "tag": "UserObject" + }, + "typeDocs": [], + "typeNames": [ + "DataUpdateMe" + ] + }, + "right": { + "bestTypeName": "DataUpdateMe", + "defnTypeTag": "Data", + "typeDefinition": { + "contents": [ + { + "annotation": { + "tag": "DataTypeKeyword" + }, + "segment": "type" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "DataUpdateMe", + "tag": "HashQualifier" + }, + "segment": "DataUpdateMe" + }, + { + "annotation": { + "tag": "DelimiterChar" + }, + "segment": " = " + }, + { + "annotation": { + "contents": "#6t7t8lem3bmu3j7bsid4omn8gej2gl57ffmkp0ef6qndhndh2q3q6dd1j9akl653r3vtifsunovvbmbjh0iqc7n6rhp4imnsghhe6go#d0", + "tag": "TermReference" + }, + "segment": "D2" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "##Nat", + "tag": "TypeReference" + }, + "segment": "Nat" + } + ], + "tag": "UserObject" + }, + "typeDocs": [], + "typeNames": [ + "DataUpdateMe" + ] + } + }, + "fullName": "DataUpdateMe", + "newHash": "#6t7t8lem3bmu3j7bsid4omn8gej2gl57ffmkp0ef6qndhndh2q3q6dd1j9akl653r3vtifsunovvbmbjh0iqc7n6rhp4imnsghhe6go", + "newTag": "Data", + "oldHash": "#a2bvb3g2l1mkijg24ogg0t23h51pnfepnngk6e3bqfijf4l9ms292t006e8faquo66ctn1ho35vtps13m6evbl6bos2guer5j6jcs1o", + "oldTag": "Data", + "shortName": "DataUpdateMe" + }, + "tag": "Updated" + }, + "tag": "Data" + }, + { + "contents": { + "contents": { + "fullName": "NewType", + "hash": "#rmntisgmjlrtq6kja30at01q04aeq2p17q806li6v509bn117tq9tc3gd3m33lhdgimen1tjdn4tqiu2r11k7ie9oibng1n1i275cdg", + "rendered": { + "bestTypeName": "NewType", + "defnTypeTag": "Data", "typeDefinition": { "contents": [ { "annotation": { "tag": "DataTypeKeyword" }, - "segment": "ability" + "segment": "type" }, { "annotation": null, @@ -715,37 +1062,57 @@ }, { "annotation": { - "contents": "AbilityUpdateMe", + "contents": "NewType", "tag": "HashQualifier" }, - "segment": "AbilityUpdateMe" + "segment": "NewType" }, { "annotation": { - "tag": "ControlKeyword" + "tag": "DelimiterChar" }, - "segment": " where" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": null, - "segment": " " + "segment": " = " }, { "annotation": { - "contents": "#qat72tp0lb43gp5pra5rgobup5r24qrc494crqd5pqjddbneiqdn3hq6puo2344nja1v6cp7aps1p0350ug0f1kvo9cp2gu9l31in18#a0", + "contents": "#rmntisgmjlrtq6kja30at01q04aeq2p17q806li6v509bn117tq9tc3gd3m33lhdgimen1tjdn4tqiu2r11k7ie9oibng1n1i275cdg#d0", "tag": "TermReference" }, - "segment": "abilityUpdateMe" - }, + "segment": "X" + } + ], + "tag": "UserObject" + }, + "typeDocs": [], + "typeNames": [ + "NewType" + ] + }, + "shortName": "NewType" + }, + "tag": "Added" + }, + "tag": "Data" + }, + { + "contents": { + "contents": { + "hash": "#hb2ubbk0c6347s5eqic78f26truhgro1ueh7r8invme3hnalmnv880tgpafpeo5kaaihonoph8o7pmhad8mr2e25m0hhor9lr34skhg", + "newFullName": "RenamedType", + "newShortName": "RenamedType", + "oldNames": [ + "DataRenameMe" + ], + "rendered": { + "bestTypeName": "RenamedType", + "defnTypeTag": "Data", + "typeDefinition": { + "contents": [ { "annotation": { - "tag": "TypeAscriptionColon" + "tag": "DataTypeKeyword" }, - "segment": " :" + "segment": "type" }, { "annotation": null, @@ -753,236 +1120,200 @@ }, { "annotation": { - "tag": "AbilityBraces" - }, - "segment": "{" - }, - { - "annotation": { - "contents": "#qat72tp0lb43gp5pra5rgobup5r24qrc494crqd5pqjddbneiqdn3hq6puo2344nja1v6cp7aps1p0350ug0f1kvo9cp2gu9l31in18", - "tag": "TypeReference" + "contents": "RenamedType", + "tag": "HashQualifier" }, - "segment": "AbilityUpdateMe" + "segment": "RenamedType" }, { "annotation": { - "tag": "AbilityBraces" + "tag": "DelimiterChar" }, - "segment": "}" - }, - { - "annotation": null, - "segment": " " + "segment": " = " }, { "annotation": { - "contents": "##Text", - "tag": "TypeReference" + "contents": "#hb2ubbk0c6347s5eqic78f26truhgro1ueh7r8invme3hnalmnv880tgpafpeo5kaaihonoph8o7pmhad8mr2e25m0hhor9lr34skhg#d0", + "tag": "TermReference" }, - "segment": "Text" + "segment": "E" } ], "tag": "UserObject" }, "typeDocs": [], "typeNames": [ - "AbilityUpdateMe" + "RenamedType" ] } }, - "fullName": "AbilityUpdateMe", - "newHash": "#qat72tp0lb43gp5pra5rgobup5r24qrc494crqd5pqjddbneiqdn3hq6puo2344nja1v6cp7aps1p0350ug0f1kvo9cp2gu9l31in18", - "newTag": "Ability", - "oldHash": "#0d5ej3mann48uffjea4epi8ss486689gsj46cscorhs3d4j7ohvj9t7ghg05tra792umcmgjr6lgqkskoo3odge7jm2ci91dlmpefcg", - "oldTag": "Ability", - "shortName": "AbilityUpdateMe" + "tag": "RenamedFrom" }, - "tag": "Updated" + "tag": "Data" }, - "tag": "Ability" - }, - { - "contents": { + { "contents": { - "fullName": "DataDeleteMe", - "hash": "#keu02n8is0irijd65cvuos41kukj3f4ni18mmnudrbll2epo6ftd03nt9l0vqc4fvg98198tefgoupco4o0d0gvnigqgr1bmo2neo88", - "rendered": { - "bestTypeName": "DataDeleteMe", - "defnTypeTag": "Data", - "typeDefinition": { - "contents": [ - { - "annotation": { - "tag": "DataTypeKeyword" - }, - "segment": "type" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "DataDeleteMe", - "tag": "HashQualifier" - }, - "segment": "DataDeleteMe" - }, - { - "annotation": { - "tag": "DelimiterChar" - }, - "segment": " = " - }, + "contents": { + "fullName": "aDoc", + "hash": "#areni4s9liksvfs3923a4ub81qpu37f964fqhbq832artpff8vm1em45ic0k2hlkv4nn08u712ibvjo9b4fl5u19o65g9medo7645i8", + "rendered": { + "bestTermName": "aDoc", + "defnTermTag": "Doc", + "signature": [ { "annotation": { - "contents": "#keu02n8is0irijd65cvuos41kukj3f4ni18mmnudrbll2epo6ftd03nt9l0vqc4fvg98198tefgoupco4o0d0gvnigqgr1bmo2neo88#d0", - "tag": "TermReference" + "contents": "#ej86si0ur1lsjade71dojr25phk9bbom9rdks6dltolos5tjivakujcriqe02npba53n9gd7tkh8bmv08ttjb9t35lq2ch5heshqcs0", + "tag": "TypeReference" }, - "segment": "C" + "segment": "Doc2" } ], - "tag": "UserObject" - }, - "typeDocs": [], - "typeNames": [ - "DataDeleteMe" - ] - }, - "shortName": "DataDeleteMe" - }, - "tag": "Removed" - }, - "tag": "Data" - }, - { - "contents": { - "contents": { - "diff": { - "diff": { - "diff": { + "termDefinition": { "contents": [ { - "diffTag": "both", - "elements": [ - { - "annotation": { - "tag": "DataTypeKeyword" - }, - "segment": "type" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "DataUpdateMe", - "tag": "HashQualifier" - }, - "segment": "DataUpdateMe" - }, - { - "annotation": { - "tag": "DelimiterChar" - }, - "segment": " = " - } - ] + "annotation": { + "contents": "aDoc", + "tag": "HashQualifier" + }, + "segment": "aDoc" }, { - "diffTag": "old", - "elements": [ - { - "annotation": { - "contents": "#fhc8jn2bhvfdnfr89dv2jf7tekuesna7gvje4ck6lfheh9rb184q4ddd29vm9mvfm6u1a98kpgditn8vb09durtel67rpof1c62535o#d0", - "tag": "TermReference" - }, - "segment": "D" - } - ] + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" }, { - "diffTag": "new", - "elements": [ - { - "annotation": { - "contents": "#qnblpurkqedrq0kae95ep7b8f6uh5b7igefp21r1nvl22agjoup5e7aunua4q8ku8mb532fh3lst4mj3m2bsb3kluchc3fuau5cllr0#d0", - "tag": "TermReference" - }, - "segment": "D2" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "##Nat", - "tag": "TypeReference" - }, - "segment": "Nat" - } - ] - } - ], - "tag": "UserObject" - }, - "diffKind": "diff" - }, - "left": { - "bestTypeName": "DataUpdateMe", - "defnTypeTag": "Data", - "typeDefinition": { - "contents": [ + "annotation": null, + "segment": " " + }, { "annotation": { - "tag": "DataTypeKeyword" + "contents": "#ej86si0ur1lsjade71dojr25phk9bbom9rdks6dltolos5tjivakujcriqe02npba53n9gd7tkh8bmv08ttjb9t35lq2ch5heshqcs0", + "tag": "TypeReference" }, - "segment": "type" + "segment": "Doc2" }, { "annotation": null, - "segment": " " + "segment": "\n" }, { "annotation": { - "contents": "DataUpdateMe", + "contents": "aDoc", "tag": "HashQualifier" }, - "segment": "DataUpdateMe" + "segment": "aDoc" }, { "annotation": { - "tag": "DelimiterChar" + "tag": "BindingEquals" }, - "segment": " = " + "segment": " =" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "DocDelimiter" + }, + "segment": "{{" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": null, + "segment": "Test" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": null, + "segment": "Doc" + }, + { + "annotation": null, + "segment": " " }, { "annotation": { - "contents": "#fhc8jn2bhvfdnfr89dv2jf7tekuesna7gvje4ck6lfheh9rb184q4ddd29vm9mvfm6u1a98kpgditn8vb09durtel67rpof1c62535o#d0", - "tag": "TermReference" + "tag": "DocDelimiter" }, - "segment": "D" + "segment": "}}" } ], "tag": "UserObject" }, - "typeDocs": [], - "typeNames": [ - "DataUpdateMe" + "termDocs": [ + [ + "aDoc", + "#areni4s9liksvfs3923a4ub81qpu37f964fqhbq832artpff8vm1em45ic0k2hlkv4nn08u712ibvjo9b4fl5u19o65g9medo7645i8", + { + "contents": [ + { + "contents": "Test", + "tag": "Word" + }, + { + "contents": "Doc", + "tag": "Word" + } + ], + "tag": "Paragraph" + } + ] + ], + "termNames": [ + "aDoc" ] }, - "right": { - "bestTypeName": "DataUpdateMe", - "defnTypeTag": "Data", - "typeDefinition": { + "shortName": "aDoc" + }, + "tag": "Removed" + }, + "tag": "Doc" + }, + { + "contents": { + "contents": { + "aliasFullName": "aTermAlias", + "aliasShortName": "aTermAlias", + "hash": "#gjmq673r1vrurfotlnirv7vutdhm6sa3s02em5g22kk606mv6duvv8be402dv79312i4a0onepq5bo7citsodvq2g720nttj0ee9p0g", + "otherNames": [ + "termAliasMe" + ], + "rendered": { + "bestTermName": "aTermAlias", + "defnTermTag": "Plain", + "signature": [ + { + "annotation": { + "contents": "##Nat", + "tag": "TypeReference" + }, + "segment": "Nat" + } + ], + "termDefinition": { "contents": [ { "annotation": { - "tag": "DataTypeKeyword" + "contents": "aTermAlias", + "tag": "HashQualifier" }, - "segment": "type" + "segment": "aTermAlias" + }, + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" }, { "annotation": null, @@ -990,23 +1321,27 @@ }, { "annotation": { - "contents": "DataUpdateMe", - "tag": "HashQualifier" + "contents": "##Nat", + "tag": "TypeReference" }, - "segment": "DataUpdateMe" + "segment": "Nat" + }, + { + "annotation": null, + "segment": "\n" }, { "annotation": { - "tag": "DelimiterChar" + "contents": "aTermAlias", + "tag": "HashQualifier" }, - "segment": " = " + "segment": "aTermAlias" }, { "annotation": { - "contents": "#qnblpurkqedrq0kae95ep7b8f6uh5b7igefp21r1nvl22agjoup5e7aunua4q8ku8mb532fh3lst4mj3m2bsb3kluchc3fuau5cllr0#d0", - "tag": "TermReference" + "tag": "BindingEquals" }, - "segment": "D2" + "segment": " =" }, { "annotation": null, @@ -1014,1272 +1349,1352 @@ }, { "annotation": { - "contents": "##Nat", - "tag": "TypeReference" + "tag": "NumericLiteral" }, - "segment": "Nat" + "segment": "1" } ], "tag": "UserObject" }, - "typeDocs": [], - "typeNames": [ - "DataUpdateMe" + "termDocs": [], + "termNames": [ + "aTermAlias", + "termAliasMe" ] } }, - "fullName": "DataUpdateMe", - "newHash": "#qnblpurkqedrq0kae95ep7b8f6uh5b7igefp21r1nvl22agjoup5e7aunua4q8ku8mb532fh3lst4mj3m2bsb3kluchc3fuau5cllr0", - "newTag": "Data", - "oldHash": "#fhc8jn2bhvfdnfr89dv2jf7tekuesna7gvje4ck6lfheh9rb184q4ddd29vm9mvfm6u1a98kpgditn8vb09durtel67rpof1c62535o", - "oldTag": "Data", - "shortName": "DataUpdateMe" - }, - "tag": "Updated" - }, - "tag": "Data" - }, - { - "contents": { - "contents": { - "fullName": "NewType", - "hash": "#sa4ptibggqmbifhfj37gj2lq487q5ucfuojjcblfaas9bunlthhkvhstsrj20fvlpqakb8e9mqds4p32lnh8ohmf1s5omvdhc23jibg", - "rendered": { - "bestTypeName": "NewType", - "defnTypeTag": "Data", - "typeDefinition": { - "contents": [ - { - "annotation": { - "tag": "DataTypeKeyword" - }, - "segment": "type" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "NewType", - "tag": "HashQualifier" - }, - "segment": "NewType" - }, - { - "annotation": { - "tag": "DelimiterChar" - }, - "segment": " = " - }, - { - "annotation": { - "contents": "#sa4ptibggqmbifhfj37gj2lq487q5ucfuojjcblfaas9bunlthhkvhstsrj20fvlpqakb8e9mqds4p32lnh8ohmf1s5omvdhc23jibg#d0", - "tag": "TermReference" - }, - "segment": "X" - } - ], - "tag": "UserObject" - }, - "typeDocs": [], - "typeNames": [ - "NewType" - ] - }, - "shortName": "NewType" + "tag": "Aliased" }, - "tag": "Added" + "tag": "Plain" }, - "tag": "Data" - }, - { - "contents": { + { "contents": { - "hash": "#8s3lsrv3p6ngq2bqotvli1f0gfcf9uvci4trmia6dosl3d8vu6i6kubdi3ic7m22r34m4mkru3hatdbgihj0fngmj7gktlq41ncs1e0", - "newFullName": "RenamedType", - "newShortName": "RenamedType", - "oldNames": [ - "DataRenameMe" - ], - "rendered": { - "bestTypeName": "RenamedType", - "defnTypeTag": "Data", - "typeDefinition": { - "contents": [ - { - "annotation": { - "tag": "DataTypeKeyword" - }, - "segment": "type" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "RenamedType", - "tag": "HashQualifier" - }, - "segment": "RenamedType" - }, + "contents": { + "fullName": "aTest", + "hash": "#qak36j7cshv12m9meuc97ovllqm8k2i305sh4oq5dbo4834t7atugsdpto6mou1tch2b3q9j2hbi23gdf4jpth7m97mannv9noucgl8", + "rendered": { + "bestTermName": "aTest", + "defnTermTag": "Test", + "signature": [ { "annotation": { "tag": "DelimiterChar" }, - "segment": " = " - }, - { - "annotation": { - "contents": "#8s3lsrv3p6ngq2bqotvli1f0gfcf9uvci4trmia6dosl3d8vu6i6kubdi3ic7m22r34m4mkru3hatdbgihj0fngmj7gktlq41ncs1e0#d0", - "tag": "TermReference" - }, - "segment": "E" - } - ], - "tag": "UserObject" - }, - "typeDocs": [], - "typeNames": [ - "RenamedType" - ] - } - }, - "tag": "RenamedFrom" - }, - "tag": "Data" - }, - { - "contents": { - "contents": { - "fullName": "aDoc", - "hash": "#areni4s9liksvfs3923a4ub81qpu37f964fqhbq832artpff8vm1em45ic0k2hlkv4nn08u712ibvjo9b4fl5u19o65g9medo7645i8", - "rendered": { - "bestTermName": "aDoc", - "defnTermTag": "Doc", - "signature": [ - { - "annotation": { - "contents": "#ej86si0ur1lsjade71dojr25phk9bbom9rdks6dltolos5tjivakujcriqe02npba53n9gd7tkh8bmv08ttjb9t35lq2ch5heshqcs0", - "tag": "TypeReference" - }, - "segment": "Doc2" - } - ], - "termDefinition": { - "contents": [ - { - "annotation": { - "contents": "aDoc", - "tag": "HashQualifier" - }, - "segment": "aDoc" - }, - { - "annotation": { - "tag": "TypeAscriptionColon" - }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " + "segment": "[" }, { "annotation": { - "contents": "#ej86si0ur1lsjade71dojr25phk9bbom9rdks6dltolos5tjivakujcriqe02npba53n9gd7tkh8bmv08ttjb9t35lq2ch5heshqcs0", + "contents": "#aql7qk3iud6vs4cvu43aimopoosgk0fnipibdkc3so13adencmibgfn0u5c01r0adei55nkl3ttsjhl8gbj7tr4gnpj63g64ftbq6s0", "tag": "TypeReference" }, - "segment": "Doc2" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": { - "contents": "aDoc", - "tag": "HashQualifier" - }, - "segment": "aDoc" - }, - { - "annotation": { - "tag": "BindingEquals" - }, - "segment": " =" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "tag": "DocDelimiter" - }, - "segment": "{{" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": null, - "segment": "Test" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": null, - "segment": "Doc" - }, - { - "annotation": null, - "segment": " " + "segment": "Result" }, { "annotation": { - "tag": "DocDelimiter" + "tag": "DelimiterChar" }, - "segment": "}}" + "segment": "]" } ], - "tag": "UserObject" - }, - "termDocs": [ - [ - "aDoc", - "#areni4s9liksvfs3923a4ub81qpu37f964fqhbq832artpff8vm1em45ic0k2hlkv4nn08u712ibvjo9b4fl5u19o65g9medo7645i8", - { - "contents": [ - { - "contents": "Test", - "tag": "Word" + "termDefinition": { + "contents": [ + { + "annotation": { + "contents": "aTest", + "tag": "HashQualifier" }, - { - "contents": "Doc", - "tag": "Word" - } - ], - "tag": "Paragraph" - } - ] - ], - "termNames": [ - "aDoc" - ] - }, - "shortName": "aDoc" - }, - "tag": "Removed" - }, - "tag": "Doc" - }, - { - "contents": { - "contents": { - "aliasFullName": "aTermAlias", - "aliasShortName": "aTermAlias", - "hash": "#gjmq673r1vrurfotlnirv7vutdhm6sa3s02em5g22kk606mv6duvv8be402dv79312i4a0onepq5bo7citsodvq2g720nttj0ee9p0g", - "otherNames": [ - "termAliasMe" - ], - "rendered": { - "bestTermName": "aTermAlias", - "defnTermTag": "Plain", - "signature": [ - { - "annotation": { - "contents": "##Nat", - "tag": "TypeReference" - }, - "segment": "Nat" - } - ], - "termDefinition": { - "contents": [ - { - "annotation": { - "contents": "aTermAlias", - "tag": "HashQualifier" - }, - "segment": "aTermAlias" - }, - { - "annotation": { - "tag": "TypeAscriptionColon" - }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "##Nat", - "tag": "TypeReference" - }, - "segment": "Nat" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": { - "contents": "aTermAlias", - "tag": "HashQualifier" + "segment": "aTest" }, - "segment": "aTermAlias" - }, - { - "annotation": { - "tag": "BindingEquals" + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" }, - "segment": " =" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "tag": "NumericLiteral" + { + "annotation": null, + "segment": " " }, - "segment": "1" - } - ], - "tag": "UserObject" - }, - "termDocs": [], - "termNames": [ - "aTermAlias", - "termAliasMe" - ] - } - }, - "tag": "Aliased" - }, - "tag": "Plain" - }, - { - "contents": { - "contents": { - "fullName": "aTest", - "hash": "#qak36j7cshv12m9meuc97ovllqm8k2i305sh4oq5dbo4834t7atugsdpto6mou1tch2b3q9j2hbi23gdf4jpth7m97mannv9noucgl8", - "rendered": { - "bestTermName": "aTest", - "defnTermTag": "Test", - "signature": [ - { - "annotation": { - "tag": "DelimiterChar" - }, - "segment": "[" - }, - { - "annotation": { - "contents": "#aql7qk3iud6vs4cvu43aimopoosgk0fnipibdkc3so13adencmibgfn0u5c01r0adei55nkl3ttsjhl8gbj7tr4gnpj63g64ftbq6s0", - "tag": "TypeReference" - }, - "segment": "Result" - }, - { - "annotation": { - "tag": "DelimiterChar" - }, - "segment": "]" - } - ], - "termDefinition": { - "contents": [ - { - "annotation": { - "contents": "aTest", - "tag": "HashQualifier" + { + "annotation": { + "tag": "DelimiterChar" + }, + "segment": "[" }, - "segment": "aTest" - }, - { - "annotation": { - "tag": "TypeAscriptionColon" + { + "annotation": { + "contents": "#aql7qk3iud6vs4cvu43aimopoosgk0fnipibdkc3so13adencmibgfn0u5c01r0adei55nkl3ttsjhl8gbj7tr4gnpj63g64ftbq6s0", + "tag": "TypeReference" + }, + "segment": "Result" }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "tag": "DelimiterChar" + { + "annotation": { + "tag": "DelimiterChar" + }, + "segment": "]" }, - "segment": "[" - }, - { - "annotation": { - "contents": "#aql7qk3iud6vs4cvu43aimopoosgk0fnipibdkc3so13adencmibgfn0u5c01r0adei55nkl3ttsjhl8gbj7tr4gnpj63g64ftbq6s0", - "tag": "TypeReference" + { + "annotation": null, + "segment": "\n" }, - "segment": "Result" - }, - { - "annotation": { - "tag": "DelimiterChar" + { + "annotation": { + "contents": "aTest", + "tag": "HashQualifier" + }, + "segment": "aTest" }, - "segment": "]" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": { - "contents": "aTest", - "tag": "HashQualifier" + { + "annotation": { + "tag": "BindingEquals" + }, + "segment": " =" }, - "segment": "aTest" - }, - { - "annotation": { - "tag": "BindingEquals" + { + "annotation": null, + "segment": " " }, - "segment": " =" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "##Sequence", - "tag": "TypeReference" + { + "annotation": { + "contents": "##Sequence", + "tag": "TypeReference" + }, + "segment": "[" }, - "segment": "[" - }, - { - "annotation": { - "contents": "#aql7qk3iud6vs4cvu43aimopoosgk0fnipibdkc3so13adencmibgfn0u5c01r0adei55nkl3ttsjhl8gbj7tr4gnpj63g64ftbq6s0#d1", - "tag": "TermReference" + { + "annotation": { + "contents": "#aql7qk3iud6vs4cvu43aimopoosgk0fnipibdkc3so13adencmibgfn0u5c01r0adei55nkl3ttsjhl8gbj7tr4gnpj63g64ftbq6s0#d1", + "tag": "TermReference" + }, + "segment": "Ok" }, - "segment": "Ok" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "tag": "TextLiteral" + { + "annotation": null, + "segment": " " }, - "segment": "\"Done\"" - }, - { - "annotation": { - "contents": "##Sequence", - "tag": "TypeReference" + { + "annotation": { + "tag": "TextLiteral" + }, + "segment": "\"Done\"" }, - "segment": "]" - } - ], - "tag": "UserObject" + { + "annotation": { + "contents": "##Sequence", + "tag": "TypeReference" + }, + "segment": "]" + } + ], + "tag": "UserObject" + }, + "termDocs": [], + "termNames": [ + "aTest" + ] }, - "termDocs": [], - "termNames": [ - "aTest" - ] + "shortName": "aTest" }, - "shortName": "aTest" + "tag": "Removed" }, - "tag": "Removed" + "tag": "Test" }, - "tag": "Test" - }, - { - "contents": { + { "contents": { - "fullName": "newTerm", - "hash": "#u1qsl3nk5t2svl58ifqepem851775qca9p4hc10j3iordu1v7u8e16oodui9kvt2c0j1cbc50avado53bl2vt3pphrfj9mhbut1ipm8", - "rendered": { - "bestTermName": "newTerm", - "defnTermTag": "Plain", - "signature": [ - { - "annotation": { - "contents": "##Nat", - "tag": "TypeReference" - }, - "segment": "Nat" - } - ], - "termDefinition": { - "contents": [ - { - "annotation": { - "contents": "newTerm", - "tag": "HashQualifier" - }, - "segment": "newTerm" - }, - { - "annotation": { - "tag": "TypeAscriptionColon" - }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " - }, + "contents": { + "fullName": "newTerm", + "hash": "#u1qsl3nk5t2svl58ifqepem851775qca9p4hc10j3iordu1v7u8e16oodui9kvt2c0j1cbc50avado53bl2vt3pphrfj9mhbut1ipm8", + "rendered": { + "bestTermName": "newTerm", + "defnTermTag": "Plain", + "signature": [ { "annotation": { "contents": "##Nat", "tag": "TypeReference" }, "segment": "Nat" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": { - "contents": "newTerm", - "tag": "HashQualifier" + } + ], + "termDefinition": { + "contents": [ + { + "annotation": { + "contents": "newTerm", + "tag": "HashQualifier" + }, + "segment": "newTerm" }, - "segment": "newTerm" - }, - { - "annotation": { - "tag": "BindingEquals" + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" }, - "segment": " =" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "tag": "NumericLiteral" + { + "annotation": null, + "segment": " " }, - "segment": "100" - } - ], - "tag": "UserObject" + { + "annotation": { + "contents": "##Nat", + "tag": "TypeReference" + }, + "segment": "Nat" + }, + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": { + "contents": "newTerm", + "tag": "HashQualifier" + }, + "segment": "newTerm" + }, + { + "annotation": { + "tag": "BindingEquals" + }, + "segment": " =" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "NumericLiteral" + }, + "segment": "100" + } + ], + "tag": "UserObject" + }, + "termDocs": [], + "termNames": [ + "newTerm" + ] }, - "termDocs": [], - "termNames": [ - "newTerm" - ] + "shortName": "newTerm" }, - "shortName": "newTerm" + "tag": "Added" }, - "tag": "Added" + "tag": "Plain" }, - "tag": "Plain" - }, - { - "contents": { + { "contents": { - "hash": "#f3lgjvjqoocpt8v6kdgd2bgthh11a7md3qdp9rf5datccmo580btjd5bt5dro3irqs0is7vm7s1dphddjbtufch620te7ef7canmjj8", - "newFullName": "renamedTerm", - "newShortName": "renamedTerm", - "oldNames": [ - "termRenameMe" - ], - "rendered": { - "bestTermName": "renamedTerm", - "defnTermTag": "Plain", - "signature": [ - { - "annotation": { - "contents": "##Nat", - "tag": "TypeReference" - }, - "segment": "Nat" - } + "contents": { + "hash": "#f3lgjvjqoocpt8v6kdgd2bgthh11a7md3qdp9rf5datccmo580btjd5bt5dro3irqs0is7vm7s1dphddjbtufch620te7ef7canmjj8", + "newFullName": "renamedTerm", + "newShortName": "renamedTerm", + "oldNames": [ + "termRenameMe" ], - "termDefinition": { - "contents": [ - { - "annotation": { - "contents": "renamedTerm", - "tag": "HashQualifier" - }, - "segment": "renamedTerm" - }, - { - "annotation": { - "tag": "TypeAscriptionColon" - }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " - }, + "rendered": { + "bestTermName": "renamedTerm", + "defnTermTag": "Plain", + "signature": [ { "annotation": { "contents": "##Nat", "tag": "TypeReference" }, "segment": "Nat" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": { - "contents": "renamedTerm", - "tag": "HashQualifier" + } + ], + "termDefinition": { + "contents": [ + { + "annotation": { + "contents": "renamedTerm", + "tag": "HashQualifier" + }, + "segment": "renamedTerm" }, - "segment": "renamedTerm" - }, - { - "annotation": { - "tag": "BindingEquals" + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" }, - "segment": " =" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "tag": "NumericLiteral" + { + "annotation": null, + "segment": " " }, - "segment": "3" - } - ], - "tag": "UserObject" - }, - "termDocs": [], - "termNames": [ - "renamedTerm" - ] - } + { + "annotation": { + "contents": "##Nat", + "tag": "TypeReference" + }, + "segment": "Nat" + }, + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": { + "contents": "renamedTerm", + "tag": "HashQualifier" + }, + "segment": "renamedTerm" + }, + { + "annotation": { + "tag": "BindingEquals" + }, + "segment": " =" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "NumericLiteral" + }, + "segment": "3" + } + ], + "tag": "UserObject" + }, + "termDocs": [], + "termNames": [ + "renamedTerm" + ] + } + }, + "tag": "RenamedFrom" }, - "tag": "RenamedFrom" + "tag": "Plain" }, - "tag": "Plain" - }, - { - "contents": { + { "contents": { - "fullName": "termDeleteMe", - "hash": "#dcgdua2lj6upd1ah5v0qp09gjsej0d77d87fu6qn8e2qrssnlnmuinoio46hiu53magr7qn8vnqke8ndt0v76700o5u8gcvo7st28jg", - "rendered": { - "bestTermName": "termDeleteMe", - "defnTermTag": "Plain", - "signature": [ - { - "annotation": { - "contents": "##Nat", - "tag": "TypeReference" - }, - "segment": "Nat" - } - ], - "termDefinition": { - "contents": [ - { - "annotation": { - "contents": "termDeleteMe", - "tag": "HashQualifier" - }, - "segment": "termDeleteMe" - }, - { - "annotation": { - "tag": "TypeAscriptionColon" - }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " - }, + "contents": { + "fullName": "termDeleteMe", + "hash": "#dcgdua2lj6upd1ah5v0qp09gjsej0d77d87fu6qn8e2qrssnlnmuinoio46hiu53magr7qn8vnqke8ndt0v76700o5u8gcvo7st28jg", + "rendered": { + "bestTermName": "termDeleteMe", + "defnTermTag": "Plain", + "signature": [ { "annotation": { "contents": "##Nat", "tag": "TypeReference" }, "segment": "Nat" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": { - "contents": "termDeleteMe", - "tag": "HashQualifier" + } + ], + "termDefinition": { + "contents": [ + { + "annotation": { + "contents": "termDeleteMe", + "tag": "HashQualifier" + }, + "segment": "termDeleteMe" }, - "segment": "termDeleteMe" - }, - { - "annotation": { - "tag": "BindingEquals" + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" }, - "segment": " =" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "tag": "NumericLiteral" + { + "annotation": null, + "segment": " " }, - "segment": "2" - } - ], - "tag": "UserObject" + { + "annotation": { + "contents": "##Nat", + "tag": "TypeReference" + }, + "segment": "Nat" + }, + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": { + "contents": "termDeleteMe", + "tag": "HashQualifier" + }, + "segment": "termDeleteMe" + }, + { + "annotation": { + "tag": "BindingEquals" + }, + "segment": " =" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "NumericLiteral" + }, + "segment": "2" + } + ], + "tag": "UserObject" + }, + "termDocs": [], + "termNames": [ + "termDeleteMe" + ] }, - "termDocs": [], - "termNames": [ - "termDeleteMe" - ] + "shortName": "termDeleteMe" }, - "shortName": "termDeleteMe" + "tag": "Removed" }, - "tag": "Removed" + "tag": "Plain" }, - "tag": "Plain" - }, - { - "contents": { + { "contents": { - "diff": { + "contents": { "diff": { "diff": { - "contents": [ - { - "diffTag": "both", - "elements": [ - { - "annotation": { - "contents": "termUpdateMe", - "tag": "HashQualifier" + "diff": { + "contents": [ + { + "diffTag": "both", + "elements": [ + { + "annotation": { + "contents": "termDependsOnUpdateMe", + "tag": "HashQualifier" + }, + "segment": "termDependsOnUpdateMe" }, - "segment": "termUpdateMe" - }, - { - "annotation": { - "tag": "TypeAscriptionColon" + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "##Text", - "tag": "TypeReference" + { + "annotation": null, + "segment": " " }, - "segment": "Text" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": { - "contents": "termUpdateMe", - "tag": "HashQualifier" + { + "annotation": { + "contents": "##Text", + "tag": "TypeReference" + }, + "segment": "Text" }, - "segment": "termUpdateMe" - }, - { - "annotation": { - "tag": "BindingEquals" + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": { + "contents": "termDependsOnUpdateMe", + "tag": "HashQualifier" + }, + "segment": "termDependsOnUpdateMe" + }, + { + "annotation": { + "tag": "BindingEquals" + }, + "segment": " =" }, - "segment": " =" + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "UseKeyword" + }, + "segment": "use " + }, + { + "annotation": { + "tag": "UsePrefix" + }, + "segment": "Text" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "UseSuffix" + }, + "segment": "++" + }, + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": null, + "segment": " " + } + ] + }, + { + "diffTag": "annotationChange", + "fromAnnotation": { + "contents": "#ofktbubbloi1omgpr09e0t90pg0cnf0lsuuopqese9biqvpdafsuhq0b4dfasbk6g3hp5r7crp4t486fc8bava7q7rrreg9j2volam8", + "tag": "TermReference" }, - { - "annotation": null, - "segment": " " + "segment": "termUpdateMe", + "toAnnotation": { + "contents": "#711u1t9cjso4t3rhlq2rp491n2n5n4t9o7701053kpj5ouu3kfs2e2l63i879pnsb6ob9fp0gpj18u6fpcl1qosd704h4doklfo734g", + "tag": "TermReference" } - ] - }, - { - "diffTag": "old", - "elements": [ - { - "annotation": { - "tag": "TextLiteral" + }, + { + "diffTag": "both", + "elements": [ + { + "annotation": null, + "segment": " " }, - "segment": "\"original\"" - } - ] - }, - { - "diffTag": "new", - "elements": [ - { - "annotation": { - "tag": "TextLiteral" + { + "annotation": { + "contents": "##Text.++", + "tag": "TermReference" + }, + "segment": "++" }, - "segment": "\"updated\"" + { + "annotation": null, + "segment": " " + } + ] + }, + { + "diffTag": "annotationChange", + "fromAnnotation": { + "contents": "#ofktbubbloi1omgpr09e0t90pg0cnf0lsuuopqese9biqvpdafsuhq0b4dfasbk6g3hp5r7crp4t486fc8bava7q7rrreg9j2volam8", + "tag": "TermReference" + }, + "segment": "termUpdateMe", + "toAnnotation": { + "contents": "#711u1t9cjso4t3rhlq2rp491n2n5n4t9o7701053kpj5ouu3kfs2e2l63i879pnsb6ob9fp0gpj18u6fpcl1qosd704h4doklfo734g", + "tag": "TermReference" } - ] + } + ], + "tag": "UserObject" + }, + "diffKind": "diff" + }, + "left": { + "bestTermName": "termDependsOnUpdateMe", + "defnTermTag": "Plain", + "signature": [ + { + "annotation": { + "contents": "##Text", + "tag": "TypeReference" + }, + "segment": "Text" } ], - "tag": "UserObject" + "termDefinition": { + "contents": [ + { + "annotation": { + "contents": "termDependsOnUpdateMe", + "tag": "HashQualifier" + }, + "segment": "termDependsOnUpdateMe" + }, + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "##Text", + "tag": "TypeReference" + }, + "segment": "Text" + }, + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": { + "contents": "termDependsOnUpdateMe", + "tag": "HashQualifier" + }, + "segment": "termDependsOnUpdateMe" + }, + { + "annotation": { + "tag": "BindingEquals" + }, + "segment": " =" + }, + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "UseKeyword" + }, + "segment": "use " + }, + { + "annotation": { + "tag": "UsePrefix" + }, + "segment": "Text" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "UseSuffix" + }, + "segment": "++" + }, + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "#ofktbubbloi1omgpr09e0t90pg0cnf0lsuuopqese9biqvpdafsuhq0b4dfasbk6g3hp5r7crp4t486fc8bava7q7rrreg9j2volam8", + "tag": "TermReference" + }, + "segment": "termUpdateMe" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "##Text.++", + "tag": "TermReference" + }, + "segment": "++" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "#ofktbubbloi1omgpr09e0t90pg0cnf0lsuuopqese9biqvpdafsuhq0b4dfasbk6g3hp5r7crp4t486fc8bava7q7rrreg9j2volam8", + "tag": "TermReference" + }, + "segment": "termUpdateMe" + } + ], + "tag": "UserObject" + }, + "termDocs": [], + "termNames": [ + "termDependsOnUpdateMe" + ] }, - "diffKind": "diff" - }, - "left": { - "bestTermName": "termUpdateMe", - "defnTermTag": "Plain", - "signature": [ - { - "annotation": { - "contents": "##Text", - "tag": "TypeReference" - }, - "segment": "Text" - } - ], - "termDefinition": { - "contents": [ + "right": { + "bestTermName": "termDependsOnUpdateMe", + "defnTermTag": "Plain", + "signature": [ { "annotation": { - "contents": "termUpdateMe", - "tag": "HashQualifier" + "contents": "##Text", + "tag": "TypeReference" + }, + "segment": "Text" + } + ], + "termDefinition": { + "contents": [ + { + "annotation": { + "contents": "termDependsOnUpdateMe", + "tag": "HashQualifier" + }, + "segment": "termDependsOnUpdateMe" + }, + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "##Text", + "tag": "TypeReference" + }, + "segment": "Text" + }, + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": { + "contents": "termDependsOnUpdateMe", + "tag": "HashQualifier" + }, + "segment": "termDependsOnUpdateMe" + }, + { + "annotation": { + "tag": "BindingEquals" + }, + "segment": " =" + }, + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "UseKeyword" + }, + "segment": "use " + }, + { + "annotation": { + "tag": "UsePrefix" + }, + "segment": "Text" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "UseSuffix" + }, + "segment": "++" + }, + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "#711u1t9cjso4t3rhlq2rp491n2n5n4t9o7701053kpj5ouu3kfs2e2l63i879pnsb6ob9fp0gpj18u6fpcl1qosd704h4doklfo734g", + "tag": "TermReference" + }, + "segment": "termUpdateMe" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "##Text.++", + "tag": "TermReference" + }, + "segment": "++" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "#711u1t9cjso4t3rhlq2rp491n2n5n4t9o7701053kpj5ouu3kfs2e2l63i879pnsb6ob9fp0gpj18u6fpcl1qosd704h4doklfo734g", + "tag": "TermReference" + }, + "segment": "termUpdateMe" + } + ], + "tag": "UserObject" + }, + "termDocs": [], + "termNames": [ + "termDependsOnUpdateMe" + ] + } + }, + "fullName": "termDependsOnUpdateMe", + "newHash": "#t3u2jnk3eej5hrcrfr80vqiaj7n26grg15n4eb67bd1601jb65ikhbfdk18eeirovmaithk3ipukum6qnhttld43ovitj01kdkd4jrg", + "newTag": "Plain", + "oldHash": "#8imj19nvqqdtl1jd9ns5fksnuh4slku9hoi3sl7dh353k7o209eek4aievkp1sbqq5lqpgqouvf00k5b6t1fkv8omnpsnvmpu0a5lr8", + "oldTag": "Plain", + "shortName": "termDependsOnUpdateMe" + }, + "tag": "Propagated" + }, + "tag": "Plain" + }, + { + "contents": { + "contents": { + "diff": { + "diff": { + "diff": { + "contents": [ + { + "diffTag": "both", + "elements": [ + { + "annotation": { + "contents": "termUpdateMe", + "tag": "HashQualifier" + }, + "segment": "termUpdateMe" + }, + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "contents": "##Text", + "tag": "TypeReference" + }, + "segment": "Text" + }, + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": { + "contents": "termUpdateMe", + "tag": "HashQualifier" + }, + "segment": "termUpdateMe" + }, + { + "annotation": { + "tag": "BindingEquals" + }, + "segment": " =" + }, + { + "annotation": null, + "segment": " " + } + ] }, - "segment": "termUpdateMe" - }, - { - "annotation": { - "tag": "TypeAscriptionColon" + { + "diffTag": "old", + "elements": [ + { + "annotation": { + "tag": "TextLiteral" + }, + "segment": "\"original\"" + } + ] }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " - }, + { + "diffTag": "new", + "elements": [ + { + "annotation": { + "tag": "TextLiteral" + }, + "segment": "\"updated\"" + } + ] + } + ], + "tag": "UserObject" + }, + "diffKind": "diff" + }, + "left": { + "bestTermName": "termUpdateMe", + "defnTermTag": "Plain", + "signature": [ { "annotation": { "contents": "##Text", "tag": "TypeReference" }, "segment": "Text" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": { - "contents": "termUpdateMe", - "tag": "HashQualifier" + } + ], + "termDefinition": { + "contents": [ + { + "annotation": { + "contents": "termUpdateMe", + "tag": "HashQualifier" + }, + "segment": "termUpdateMe" }, - "segment": "termUpdateMe" - }, - { - "annotation": { - "tag": "BindingEquals" + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" }, - "segment": " =" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "tag": "TextLiteral" + { + "annotation": null, + "segment": " " }, - "segment": "\"original\"" - } - ], - "tag": "UserObject" - }, - "termDocs": [], - "termNames": [ - "termUpdateMe" - ] - }, - "right": { - "bestTermName": "termUpdateMe", - "defnTermTag": "Plain", - "signature": [ - { - "annotation": { - "contents": "##Text", - "tag": "TypeReference" - }, - "segment": "Text" - } - ], - "termDefinition": { - "contents": [ - { - "annotation": { - "contents": "termUpdateMe", - "tag": "HashQualifier" + { + "annotation": { + "contents": "##Text", + "tag": "TypeReference" + }, + "segment": "Text" }, - "segment": "termUpdateMe" - }, - { - "annotation": { - "tag": "TypeAscriptionColon" + { + "annotation": null, + "segment": "\n" }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " - }, + { + "annotation": { + "contents": "termUpdateMe", + "tag": "HashQualifier" + }, + "segment": "termUpdateMe" + }, + { + "annotation": { + "tag": "BindingEquals" + }, + "segment": " =" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "TextLiteral" + }, + "segment": "\"original\"" + } + ], + "tag": "UserObject" + }, + "termDocs": [], + "termNames": [ + "termUpdateMe" + ] + }, + "right": { + "bestTermName": "termUpdateMe", + "defnTermTag": "Plain", + "signature": [ { "annotation": { "contents": "##Text", "tag": "TypeReference" }, "segment": "Text" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": { - "contents": "termUpdateMe", - "tag": "HashQualifier" + } + ], + "termDefinition": { + "contents": [ + { + "annotation": { + "contents": "termUpdateMe", + "tag": "HashQualifier" + }, + "segment": "termUpdateMe" }, - "segment": "termUpdateMe" - }, - { - "annotation": { - "tag": "BindingEquals" + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" }, - "segment": " =" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "tag": "TextLiteral" + { + "annotation": null, + "segment": " " }, - "segment": "\"updated\"" - } - ], - "tag": "UserObject" - }, - "termDocs": [], - "termNames": [ - "termUpdateMe" - ] - } + { + "annotation": { + "contents": "##Text", + "tag": "TypeReference" + }, + "segment": "Text" + }, + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": { + "contents": "termUpdateMe", + "tag": "HashQualifier" + }, + "segment": "termUpdateMe" + }, + { + "annotation": { + "tag": "BindingEquals" + }, + "segment": " =" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "TextLiteral" + }, + "segment": "\"updated\"" + } + ], + "tag": "UserObject" + }, + "termDocs": [], + "termNames": [ + "termUpdateMe" + ] + } + }, + "fullName": "termUpdateMe", + "newHash": "#711u1t9cjso4t3rhlq2rp491n2n5n4t9o7701053kpj5ouu3kfs2e2l63i879pnsb6ob9fp0gpj18u6fpcl1qosd704h4doklfo734g", + "newTag": "Plain", + "oldHash": "#ofktbubbloi1omgpr09e0t90pg0cnf0lsuuopqese9biqvpdafsuhq0b4dfasbk6g3hp5r7crp4t486fc8bava7q7rrreg9j2volam8", + "oldTag": "Plain", + "shortName": "termUpdateMe" }, - "fullName": "termUpdateMe", - "newHash": "#711u1t9cjso4t3rhlq2rp491n2n5n4t9o7701053kpj5ouu3kfs2e2l63i879pnsb6ob9fp0gpj18u6fpcl1qosd704h4doklfo734g", - "newTag": "Plain", - "oldHash": "#ofktbubbloi1omgpr09e0t90pg0cnf0lsuuopqese9biqvpdafsuhq0b4dfasbk6g3hp5r7crp4t486fc8bava7q7rrreg9j2volam8", - "oldTag": "Plain", - "shortName": "termUpdateMe" + "tag": "Updated" }, - "tag": "Updated" - }, - "tag": "Plain" - } - ], - "children": [ - { - "contents": { - "changes": [], - "children": [ - { - "contents": { - "changes": [ - { - "contents": { + "tag": "Plain" + } + ], + "children": [ + { + "contents": { + "changes": [], + "children": [ + { + "contents": { + "changes": [ + { "contents": { - "fullName": "a.definition.at.path1", - "hash": "#r303avnmdmja3ch96otiglq37214t43acpr1ikq4hrp5hmcibstipa69frbd6177jvbn28ioc5ii80fc54ecogm4n64dhjvkonrihso", - "rendered": { - "bestTermName": "path1", - "defnTermTag": "Plain", - "signature": [ - { - "annotation": { - "contents": "##Text", - "tag": "TypeReference" - }, - "segment": "Text" - } - ], - "termDefinition": { - "contents": [ - { - "annotation": { - "contents": "a.definition.at.path1", - "tag": "HashQualifier" - }, - "segment": "a.definition.at.path1" - }, - { - "annotation": { - "tag": "TypeAscriptionColon" - }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " - }, + "contents": { + "fullName": "a.definition.at.path1", + "hash": "#r303avnmdmja3ch96otiglq37214t43acpr1ikq4hrp5hmcibstipa69frbd6177jvbn28ioc5ii80fc54ecogm4n64dhjvkonrihso", + "rendered": { + "bestTermName": "path1", + "defnTermTag": "Plain", + "signature": [ { "annotation": { "contents": "##Text", "tag": "TypeReference" }, "segment": "Text" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": { - "contents": "a.definition.at.path1", - "tag": "HashQualifier" + } + ], + "termDefinition": { + "contents": [ + { + "annotation": { + "contents": "a.definition.at.path1", + "tag": "HashQualifier" + }, + "segment": "a.definition.at.path1" }, - "segment": "a.definition.at.path1" - }, - { - "annotation": { - "tag": "BindingEquals" + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" }, - "segment": " =" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "tag": "TextLiteral" + { + "annotation": null, + "segment": " " }, - "segment": "\"definition at path\"" - } - ], - "tag": "UserObject" + { + "annotation": { + "contents": "##Text", + "tag": "TypeReference" + }, + "segment": "Text" + }, + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": { + "contents": "a.definition.at.path1", + "tag": "HashQualifier" + }, + "segment": "a.definition.at.path1" + }, + { + "annotation": { + "tag": "BindingEquals" + }, + "segment": " =" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "TextLiteral" + }, + "segment": "\"definition at path\"" + } + ], + "tag": "UserObject" + }, + "termDocs": [], + "termNames": [ + "a.definition.at.path1" + ] }, - "termDocs": [], - "termNames": [ - "a.definition.at.path1" - ] + "shortName": "path1" }, - "shortName": "path1" + "tag": "Removed" }, - "tag": "Removed" + "tag": "Plain" }, - "tag": "Plain" - }, - { - "contents": { + { "contents": { - "fullName": "a.definition.at.path2", - "hash": "#k43vb9rkd3n4i8g8bbfb31erufbmu6v1f99i587oqsje51thrm1ugdqa7gkjbdvkactuql3cmc00b7oev0glqb2rko48atkuo798mno", - "rendered": { - "bestTermName": "path2", - "defnTermTag": "Plain", - "signature": [ - { - "annotation": { - "contents": "##Text", - "tag": "TypeReference" - }, - "segment": "Text" - } - ], - "termDefinition": { - "contents": [ - { - "annotation": { - "contents": "a.definition.at.path2", - "tag": "HashQualifier" - }, - "segment": "a.definition.at.path2" - }, - { - "annotation": { - "tag": "TypeAscriptionColon" - }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " - }, + "contents": { + "fullName": "a.definition.at.path2", + "hash": "#k43vb9rkd3n4i8g8bbfb31erufbmu6v1f99i587oqsje51thrm1ugdqa7gkjbdvkactuql3cmc00b7oev0glqb2rko48atkuo798mno", + "rendered": { + "bestTermName": "path2", + "defnTermTag": "Plain", + "signature": [ { "annotation": { "contents": "##Text", "tag": "TypeReference" }, "segment": "Text" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": { - "contents": "a.definition.at.path2", - "tag": "HashQualifier" + } + ], + "termDefinition": { + "contents": [ + { + "annotation": { + "contents": "a.definition.at.path2", + "tag": "HashQualifier" + }, + "segment": "a.definition.at.path2" }, - "segment": "a.definition.at.path2" - }, - { - "annotation": { - "tag": "BindingEquals" + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" }, - "segment": " =" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "tag": "TextLiteral" + { + "annotation": null, + "segment": " " }, - "segment": "\"definition at path2\"" - } - ], - "tag": "UserObject" + { + "annotation": { + "contents": "##Text", + "tag": "TypeReference" + }, + "segment": "Text" + }, + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": { + "contents": "a.definition.at.path2", + "tag": "HashQualifier" + }, + "segment": "a.definition.at.path2" + }, + { + "annotation": { + "tag": "BindingEquals" + }, + "segment": " =" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "TextLiteral" + }, + "segment": "\"definition at path2\"" + } + ], + "tag": "UserObject" + }, + "termDocs": [], + "termNames": [ + "a.definition.at.path2" + ] }, - "termDocs": [], - "termNames": [ - "a.definition.at.path2" - ] + "shortName": "path2" }, - "shortName": "path2" + "tag": "Removed" }, - "tag": "Removed" - }, - "tag": "Plain" - } - ], - "children": [] + "tag": "Plain" + } + ], + "children": [] + }, + "path": "definition.at" }, - "path": "definition.at" - }, - { - "contents": { - "changes": [ - { - "contents": { + { + "contents": { + "changes": [ + { "contents": { - "fullName": "a.different.path", - "hash": "#83be375arg68mqk26bu12elka6fb6mvq6cec92un1p1t5kulhh6672qlnego952pp7h4lfl7mq3crithvtvo3col9mfc8vurbnb8hvo", - "rendered": { - "bestTermName": "path", - "defnTermTag": "Plain", - "signature": [ - { - "annotation": { - "contents": "##Text", - "tag": "TypeReference" - }, - "segment": "Text" - } - ], - "termDefinition": { - "contents": [ - { - "annotation": { - "contents": "a.different.path", - "tag": "HashQualifier" - }, - "segment": "a.different.path" - }, - { - "annotation": { - "tag": "TypeAscriptionColon" - }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " - }, + "contents": { + "fullName": "a.different.path", + "hash": "#83be375arg68mqk26bu12elka6fb6mvq6cec92un1p1t5kulhh6672qlnego952pp7h4lfl7mq3crithvtvo3col9mfc8vurbnb8hvo", + "rendered": { + "bestTermName": "path", + "defnTermTag": "Plain", + "signature": [ { "annotation": { "contents": "##Text", "tag": "TypeReference" }, "segment": "Text" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": { - "contents": "a.different.path", - "tag": "HashQualifier" + } + ], + "termDefinition": { + "contents": [ + { + "annotation": { + "contents": "a.different.path", + "tag": "HashQualifier" + }, + "segment": "a.different.path" }, - "segment": "a.different.path" - }, - { - "annotation": { - "tag": "BindingEquals" + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" }, - "segment": " =" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "tag": "TextLiteral" + { + "annotation": null, + "segment": " " }, - "segment": "\"definition at different path\"" - } - ], - "tag": "UserObject" + { + "annotation": { + "contents": "##Text", + "tag": "TypeReference" + }, + "segment": "Text" + }, + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": { + "contents": "a.different.path", + "tag": "HashQualifier" + }, + "segment": "a.different.path" + }, + { + "annotation": { + "tag": "BindingEquals" + }, + "segment": " =" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "TextLiteral" + }, + "segment": "\"definition at different path\"" + } + ], + "tag": "UserObject" + }, + "termDocs": [], + "termNames": [ + "a.different.path" + ] }, - "termDocs": [], - "termNames": [ - "a.different.path" - ] + "shortName": "path" }, - "shortName": "path" + "tag": "Removed" }, - "tag": "Removed" - }, - "tag": "Plain" - } - ], - "children": [] - }, - "path": "different" - } - ] - }, - "path": "a" - } - ] + "tag": "Plain" + } + ], + "children": [] + }, + "path": "different" + } + ] + }, + "path": "a" + } + ] + }, + "libdeps": [] }, "newRef": "diff-end", - "newRefHash": "#u8i8k3pujkli3o266tsbl9nh3s6al548121ir0mvm7v0nq3v3lhdntfa2p0np7d20drm0dotbs5tfsggadgrqnkqpnmt6tjm3dd9ig0", + "newRefHash": "#f2bjgi4tm53bf6dcfcukt5a6as3ktlrbiacnqq81nco8i4g7dg6pt14vmc1b7ulsb7rt683qjt2rvg9u92uo5mk1gaqgo8cl30umep8", "oldRef": "diff-start", - "oldRefHash": "#rp780a26gio3v8viaq10oa51r4g5b1ocsokmleuo4bc9sjkhq2rut502tmpmrdb5al5lb7k6u7vhp6dab174a48rjoklf3jddp7o420", + "oldRefHash": "#f8nji6tc2vaorc7gl8kjdmj8ucrht674blmb586iptgsa8v1pm8ovjplc4an2voirvlip91ick9g5mjkncsmr8sadaqqf8810eskbig", "project": "@transcripts/contribution-diff" }, "status": [ diff --git a/transcripts/share-apis/contribution-diffs/prelude.md b/transcripts/share-apis/contribution-diffs/prelude.md index 28e2b3e1..379af7bc 100644 --- a/transcripts/share-apis/contribution-diffs/prelude.md +++ b/transcripts/share-apis/contribution-diffs/prelude.md @@ -10,6 +10,7 @@ termAliasMe = 1 termDeleteMe = 2 termRenameMe = 3 termUpdateMe = "original" +termDependsOnUpdateMe = termUpdateMe ++ termUpdateMe type DataLeaveMeAlone = A type DataAliasMe = B @@ -94,7 +95,7 @@ contribution-diff/diff-end> rename.namespace AbilityRenameMe AbilityRenamed contribution-diff/diff-end> push @transcripts/contribution-diff/diff-end ``` -Now we go back to the `diff-start` branch and make some more commits to test that +Now we go back to the `diff-start` branch and make some more commits to test that diffing uses the best common ancestor. ```unison diff --git a/transcripts/share-apis/contribution-diffs/standard-type-diff.json b/transcripts/share-apis/contribution-diffs/standard-type-diff.json index a313a984..e21c40b4 100644 --- a/transcripts/share-apis/contribution-diffs/standard-type-diff.json +++ b/transcripts/share-apis/contribution-diffs/standard-type-diff.json @@ -35,7 +35,7 @@ "elements": [ { "annotation": { - "contents": "#fhc8jn2bhvfdnfr89dv2jf7tekuesna7gvje4ck6lfheh9rb184q4ddd29vm9mvfm6u1a98kpgditn8vb09durtel67rpof1c62535o#d0", + "contents": "#a2bvb3g2l1mkijg24ogg0t23h51pnfepnngk6e3bqfijf4l9ms292t006e8faquo66ctn1ho35vtps13m6evbl6bos2guer5j6jcs1o#d0", "tag": "TermReference" }, "segment": "D" @@ -47,7 +47,7 @@ "elements": [ { "annotation": { - "contents": "#qnblpurkqedrq0kae95ep7b8f6uh5b7igefp21r1nvl22agjoup5e7aunua4q8ku8mb532fh3lst4mj3m2bsb3kluchc3fuau5cllr0#d0", + "contents": "#6t7t8lem3bmu3j7bsid4omn8gej2gl57ffmkp0ef6qndhndh2q3q6dd1j9akl653r3vtifsunovvbmbjh0iqc7n6rhp4imnsghhe6go#d0", "tag": "TermReference" }, "segment": "D2" @@ -100,7 +100,7 @@ }, { "annotation": { - "contents": "#qnblpurkqedrq0kae95ep7b8f6uh5b7igefp21r1nvl22agjoup5e7aunua4q8ku8mb532fh3lst4mj3m2bsb3kluchc3fuau5cllr0#d0", + "contents": "#6t7t8lem3bmu3j7bsid4omn8gej2gl57ffmkp0ef6qndhndh2q3q6dd1j9akl653r3vtifsunovvbmbjh0iqc7n6rhp4imnsghhe6go#d0", "tag": "TermReference" }, "segment": "D2" @@ -155,7 +155,7 @@ }, { "annotation": { - "contents": "#fhc8jn2bhvfdnfr89dv2jf7tekuesna7gvje4ck6lfheh9rb184q4ddd29vm9mvfm6u1a98kpgditn8vb09durtel67rpof1c62535o#d0", + "contents": "#a2bvb3g2l1mkijg24ogg0t23h51pnfepnngk6e3bqfijf4l9ms292t006e8faquo66ctn1ho35vtps13m6evbl6bos2guer5j6jcs1o#d0", "tag": "TermReference" }, "segment": "D" diff --git a/transcripts/share-apis/contributions/merged-contribution-diff.json b/transcripts/share-apis/contributions/merged-contribution-diff.json index 34ba83b6..c0422147 100644 --- a/transcripts/share-apis/contributions/merged-contribution-diff.json +++ b/transcripts/share-apis/contributions/merged-contribution-diff.json @@ -1,256 +1,259 @@ { "body": { "diff": { - "changes": [ - { - "contents": { + "defns": { + "changes": [ + { "contents": { - "diff": { + "contents": { "diff": { "diff": { - "contents": [ - { - "diffTag": "both", - "elements": [ - { - "annotation": { - "contents": "term", - "tag": "HashQualifier" + "diff": { + "contents": [ + { + "diffTag": "both", + "elements": [ + { + "annotation": { + "contents": "term", + "tag": "HashQualifier" + }, + "segment": "term" }, - "segment": "term" - }, - { - "annotation": { - "tag": "TypeAscriptionColon" + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "##Text", - "tag": "HashQualifier" + { + "annotation": null, + "segment": " " }, - "segment": "##Text" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": { - "contents": "term", - "tag": "HashQualifier" + { + "annotation": { + "contents": "##Text", + "tag": "HashQualifier" + }, + "segment": "##Text" }, - "segment": "term" - }, - { - "annotation": { - "tag": "BindingEquals" + { + "annotation": null, + "segment": "\n" }, - "segment": " =" - }, - { - "annotation": null, - "segment": " " - } - ] - }, - { - "diffTag": "old", - "elements": [ - { - "annotation": { - "tag": "TextLiteral" + { + "annotation": { + "contents": "term", + "tag": "HashQualifier" + }, + "segment": "term" }, - "segment": "\"start\"" - } - ] - }, - { - "diffTag": "new", - "elements": [ - { - "annotation": { - "tag": "TextLiteral" + { + "annotation": { + "tag": "BindingEquals" + }, + "segment": " =" }, - "segment": "\"feature-one\"" - } - ] - } - ], - "tag": "UserObject" - }, - "diffKind": "diff" - }, - "left": { - "bestTermName": "term", - "defnTermTag": "Plain", - "signature": [ - { - "annotation": { - "contents": "##Text", - "tag": "HashQualifier" - }, - "segment": "##Text" - } - ], - "termDefinition": { - "contents": [ - { - "annotation": { - "contents": "term", - "tag": "HashQualifier" + { + "annotation": null, + "segment": " " + } + ] }, - "segment": "term" - }, - { - "annotation": { - "tag": "TypeAscriptionColon" + { + "diffTag": "old", + "elements": [ + { + "annotation": { + "tag": "TextLiteral" + }, + "segment": "\"start\"" + } + ] }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " - }, + { + "diffTag": "new", + "elements": [ + { + "annotation": { + "tag": "TextLiteral" + }, + "segment": "\"feature-one\"" + } + ] + } + ], + "tag": "UserObject" + }, + "diffKind": "diff" + }, + "left": { + "bestTermName": "term", + "defnTermTag": "Plain", + "signature": [ { "annotation": { "contents": "##Text", "tag": "HashQualifier" }, "segment": "##Text" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": { - "contents": "term", - "tag": "HashQualifier" + } + ], + "termDefinition": { + "contents": [ + { + "annotation": { + "contents": "term", + "tag": "HashQualifier" + }, + "segment": "term" }, - "segment": "term" - }, - { - "annotation": { - "tag": "BindingEquals" + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" }, - "segment": " =" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "tag": "TextLiteral" + { + "annotation": null, + "segment": " " }, - "segment": "\"start\"" - } - ], - "tag": "UserObject" - }, - "termDocs": [], - "termNames": [ - "term" - ] - }, - "right": { - "bestTermName": "term", - "defnTermTag": "Plain", - "signature": [ - { - "annotation": { - "contents": "##Text", - "tag": "HashQualifier" - }, - "segment": "##Text" - } - ], - "termDefinition": { - "contents": [ - { - "annotation": { - "contents": "term", - "tag": "HashQualifier" + { + "annotation": { + "contents": "##Text", + "tag": "HashQualifier" + }, + "segment": "##Text" }, - "segment": "term" - }, - { - "annotation": { - "tag": "TypeAscriptionColon" + { + "annotation": null, + "segment": "\n" }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " - }, + { + "annotation": { + "contents": "term", + "tag": "HashQualifier" + }, + "segment": "term" + }, + { + "annotation": { + "tag": "BindingEquals" + }, + "segment": " =" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "TextLiteral" + }, + "segment": "\"start\"" + } + ], + "tag": "UserObject" + }, + "termDocs": [], + "termNames": [ + "term" + ] + }, + "right": { + "bestTermName": "term", + "defnTermTag": "Plain", + "signature": [ { "annotation": { "contents": "##Text", "tag": "HashQualifier" }, "segment": "##Text" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": { - "contents": "term", - "tag": "HashQualifier" + } + ], + "termDefinition": { + "contents": [ + { + "annotation": { + "contents": "term", + "tag": "HashQualifier" + }, + "segment": "term" }, - "segment": "term" - }, - { - "annotation": { - "tag": "BindingEquals" + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" }, - "segment": " =" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "tag": "TextLiteral" + { + "annotation": null, + "segment": " " }, - "segment": "\"feature-one\"" - } - ], - "tag": "UserObject" - }, - "termDocs": [], - "termNames": [ - "term" - ] - } + { + "annotation": { + "contents": "##Text", + "tag": "HashQualifier" + }, + "segment": "##Text" + }, + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": { + "contents": "term", + "tag": "HashQualifier" + }, + "segment": "term" + }, + { + "annotation": { + "tag": "BindingEquals" + }, + "segment": " =" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "TextLiteral" + }, + "segment": "\"feature-one\"" + } + ], + "tag": "UserObject" + }, + "termDocs": [], + "termNames": [ + "term" + ] + } + }, + "fullName": "term", + "newHash": "#t8aquv2oldk8euc6uveu227hiv76tlic78h607s2nr47mruvocg1oq147b4jf8l850qj2jl37n37ohned32c4ag97mq22cvhl0sbbfo", + "newTag": "Plain", + "oldHash": "#rhaja5f1cv52a3h2sook0mnagjn62dvm0e66auh1o741bn1qc0fefjlsqqc8mgar0nlui5fdia8ji7j3fbpejdv4dgb3vlh6bq4q4b8", + "oldTag": "Plain", + "shortName": "term" }, - "fullName": "term", - "newHash": "#t8aquv2oldk8euc6uveu227hiv76tlic78h607s2nr47mruvocg1oq147b4jf8l850qj2jl37n37ohned32c4ag97mq22cvhl0sbbfo", - "newTag": "Plain", - "oldHash": "#rhaja5f1cv52a3h2sook0mnagjn62dvm0e66auh1o741bn1qc0fefjlsqqc8mgar0nlui5fdia8ji7j3fbpejdv4dgb3vlh6bq4q4b8", - "oldTag": "Plain", - "shortName": "term" + "tag": "Updated" }, - "tag": "Updated" - }, - "tag": "Plain" - } - ], - "children": [] + "tag": "Plain" + } + ], + "children": [] + }, + "libdeps": [] }, "newRef": "feature-one", "newRefHash": "#7shvkj0gn9mfne1pemp3oudmo23vio4d8ualvbah6avr7m5471rssu9cd4o6i4pn91bgc62vgnm0oper0itgtmopqmff7c0b40ui1s0", "oldRef": "main", - "oldRefHash": "#rl08e4s9jm58fhj7uslg0qlndg2qhlp6gdd2thjicgpakqbkeumgeo220hgrh27jcd3kqh1o9b24dimpssr9eq2pe2icdu7nffkabsg", + "oldRefHash": "#7shvkj0gn9mfne1pemp3oudmo23vio4d8ualvbah6avr7m5471rssu9cd4o6i4pn91bgc62vgnm0oper0itgtmopqmff7c0b40ui1s0", "project": "@transcripts/bca-updates" }, "status": [ diff --git a/transcripts/share-apis/contributions/transitive-contribution-diff.json b/transcripts/share-apis/contributions/transitive-contribution-diff.json index 861ae60a..e96edaba 100644 --- a/transcripts/share-apis/contributions/transitive-contribution-diff.json +++ b/transcripts/share-apis/contributions/transitive-contribution-diff.json @@ -1,251 +1,254 @@ { "body": { "diff": { - "changes": [ - { - "contents": { + "defns": { + "changes": [ + { "contents": { - "diff": { + "contents": { "diff": { "diff": { - "contents": [ - { - "diffTag": "both", - "elements": [ - { - "annotation": { - "contents": "term", - "tag": "HashQualifier" + "diff": { + "contents": [ + { + "diffTag": "both", + "elements": [ + { + "annotation": { + "contents": "term", + "tag": "HashQualifier" + }, + "segment": "term" }, - "segment": "term" - }, - { - "annotation": { - "tag": "TypeAscriptionColon" + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "contents": "##Text", - "tag": "HashQualifier" + { + "annotation": null, + "segment": " " }, - "segment": "##Text" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": { - "contents": "term", - "tag": "HashQualifier" + { + "annotation": { + "contents": "##Text", + "tag": "HashQualifier" + }, + "segment": "##Text" }, - "segment": "term" - }, - { - "annotation": { - "tag": "BindingEquals" + { + "annotation": null, + "segment": "\n" }, - "segment": " =" - }, - { - "annotation": null, - "segment": " " - } - ] - }, - { - "diffTag": "old", - "elements": [ - { - "annotation": { - "tag": "TextLiteral" + { + "annotation": { + "contents": "term", + "tag": "HashQualifier" + }, + "segment": "term" }, - "segment": "\"feature-one\"" - } - ] - }, - { - "diffTag": "new", - "elements": [ - { - "annotation": { - "tag": "TextLiteral" + { + "annotation": { + "tag": "BindingEquals" + }, + "segment": " =" }, - "segment": "\"feature-two\"" - } - ] - } - ], - "tag": "UserObject" - }, - "diffKind": "diff" - }, - "left": { - "bestTermName": "term", - "defnTermTag": "Plain", - "signature": [ - { - "annotation": { - "contents": "##Text", - "tag": "HashQualifier" - }, - "segment": "##Text" - } - ], - "termDefinition": { - "contents": [ - { - "annotation": { - "contents": "term", - "tag": "HashQualifier" + { + "annotation": null, + "segment": " " + } + ] }, - "segment": "term" - }, - { - "annotation": { - "tag": "TypeAscriptionColon" + { + "diffTag": "old", + "elements": [ + { + "annotation": { + "tag": "TextLiteral" + }, + "segment": "\"feature-one\"" + } + ] }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " - }, + { + "diffTag": "new", + "elements": [ + { + "annotation": { + "tag": "TextLiteral" + }, + "segment": "\"feature-two\"" + } + ] + } + ], + "tag": "UserObject" + }, + "diffKind": "diff" + }, + "left": { + "bestTermName": "term", + "defnTermTag": "Plain", + "signature": [ { "annotation": { "contents": "##Text", "tag": "HashQualifier" }, "segment": "##Text" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": { - "contents": "term", - "tag": "HashQualifier" + } + ], + "termDefinition": { + "contents": [ + { + "annotation": { + "contents": "term", + "tag": "HashQualifier" + }, + "segment": "term" }, - "segment": "term" - }, - { - "annotation": { - "tag": "BindingEquals" + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" }, - "segment": " =" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "tag": "TextLiteral" + { + "annotation": null, + "segment": " " }, - "segment": "\"feature-one\"" - } - ], - "tag": "UserObject" - }, - "termDocs": [], - "termNames": [ - "term" - ] - }, - "right": { - "bestTermName": "term", - "defnTermTag": "Plain", - "signature": [ - { - "annotation": { - "contents": "##Text", - "tag": "HashQualifier" - }, - "segment": "##Text" - } - ], - "termDefinition": { - "contents": [ - { - "annotation": { - "contents": "term", - "tag": "HashQualifier" + { + "annotation": { + "contents": "##Text", + "tag": "HashQualifier" + }, + "segment": "##Text" }, - "segment": "term" - }, - { - "annotation": { - "tag": "TypeAscriptionColon" + { + "annotation": null, + "segment": "\n" }, - "segment": " :" - }, - { - "annotation": null, - "segment": " " - }, + { + "annotation": { + "contents": "term", + "tag": "HashQualifier" + }, + "segment": "term" + }, + { + "annotation": { + "tag": "BindingEquals" + }, + "segment": " =" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "TextLiteral" + }, + "segment": "\"feature-one\"" + } + ], + "tag": "UserObject" + }, + "termDocs": [], + "termNames": [ + "term" + ] + }, + "right": { + "bestTermName": "term", + "defnTermTag": "Plain", + "signature": [ { "annotation": { "contents": "##Text", "tag": "HashQualifier" }, "segment": "##Text" - }, - { - "annotation": null, - "segment": "\n" - }, - { - "annotation": { - "contents": "term", - "tag": "HashQualifier" + } + ], + "termDefinition": { + "contents": [ + { + "annotation": { + "contents": "term", + "tag": "HashQualifier" + }, + "segment": "term" }, - "segment": "term" - }, - { - "annotation": { - "tag": "BindingEquals" + { + "annotation": { + "tag": "TypeAscriptionColon" + }, + "segment": " :" }, - "segment": " =" - }, - { - "annotation": null, - "segment": " " - }, - { - "annotation": { - "tag": "TextLiteral" + { + "annotation": null, + "segment": " " }, - "segment": "\"feature-two\"" - } - ], - "tag": "UserObject" - }, - "termDocs": [], - "termNames": [ - "term" - ] - } + { + "annotation": { + "contents": "##Text", + "tag": "HashQualifier" + }, + "segment": "##Text" + }, + { + "annotation": null, + "segment": "\n" + }, + { + "annotation": { + "contents": "term", + "tag": "HashQualifier" + }, + "segment": "term" + }, + { + "annotation": { + "tag": "BindingEquals" + }, + "segment": " =" + }, + { + "annotation": null, + "segment": " " + }, + { + "annotation": { + "tag": "TextLiteral" + }, + "segment": "\"feature-two\"" + } + ], + "tag": "UserObject" + }, + "termDocs": [], + "termNames": [ + "term" + ] + } + }, + "fullName": "term", + "newHash": "#918iukm79ii0jll0m3qtsrcqjp1sqe5rdpf1kochqp52a52s9ciil7mu6m3t4l39pdk60imhj5be1d9rat2lgdmr6u0jn93v7v8o6rg", + "newTag": "Plain", + "oldHash": "#t8aquv2oldk8euc6uveu227hiv76tlic78h607s2nr47mruvocg1oq147b4jf8l850qj2jl37n37ohned32c4ag97mq22cvhl0sbbfo", + "oldTag": "Plain", + "shortName": "term" }, - "fullName": "term", - "newHash": "#918iukm79ii0jll0m3qtsrcqjp1sqe5rdpf1kochqp52a52s9ciil7mu6m3t4l39pdk60imhj5be1d9rat2lgdmr6u0jn93v7v8o6rg", - "newTag": "Plain", - "oldHash": "#t8aquv2oldk8euc6uveu227hiv76tlic78h607s2nr47mruvocg1oq147b4jf8l850qj2jl37n37ohned32c4ag97mq22cvhl0sbbfo", - "oldTag": "Plain", - "shortName": "term" + "tag": "Updated" }, - "tag": "Updated" - }, - "tag": "Plain" - } - ], - "children": [] + "tag": "Plain" + } + ], + "children": [] + }, + "libdeps": [] }, "newRef": "feature-two", "newRefHash": "#ktjspqi8s5ngg129a6lt7i9kd488isfoq8hqmsv54f327de28dq9u0n1dp1vlbgs8jdc6bqss3h46ep9241405ml19nr0gekel56pig",