Skip to content

Commit

Permalink
add failing transcript
Browse files Browse the repository at this point in the history
  • Loading branch information
mitchellwrosen committed Nov 7, 2024
1 parent 2c11caa commit 78cbe72
Show file tree
Hide file tree
Showing 4 changed files with 100 additions and 21 deletions.
4 changes: 2 additions & 2 deletions unison-cli/src/Unison/Codebase/Editor/HandleInput.hs
Original file line number Diff line number Diff line change
Expand Up @@ -572,7 +572,7 @@ loop e = do
delete input doutput getTerms getTypes hqs
DeleteTarget'Type doutput hqs -> delete input doutput (const (pure Set.empty)) getTypes hqs
DeleteTarget'Term doutput hqs -> delete input doutput getTerms (const (pure Set.empty)) hqs
DeleteTarget'Namespace insistence path -> handleDeleteNamespace input inputDescription insistence path
DeleteTarget'Namespace insistence path -> handleDeleteNamespace input insistence path
DeleteTarget'ProjectBranch name -> handleDeleteBranch name
DeleteTarget'Project name -> handleDeleteProject name
DisplayI outputLoc namesToDisplay -> do
Expand Down Expand Up @@ -1457,7 +1457,7 @@ checkDeletes typesTermsTuples doutput inputs = do
Cli.runTransaction $
traverse
( \targetToDelete ->
getEndangeredDependents targetToDelete (allTermsToDelete) projectNames
getEndangeredDependents targetToDelete allTermsToDelete projectNames
)
toDelete
-- If the overall dependency map is not completely empty, abort deletion
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@ module Unison.Codebase.Editor.HandleInput.DeleteNamespace
where

import Control.Lens hiding (from)
import Control.Lens qualified as Lens
import Control.Monad.State qualified as State
import Data.Map qualified as Map
import Data.Set qualified as Set
Expand All @@ -22,6 +23,7 @@ import Unison.Codebase.Editor.Input
import Unison.Codebase.Editor.Output
import Unison.Codebase.Path (Path)
import Unison.Codebase.Path qualified as Path
import Unison.Codebase.ProjectPath qualified as ProjectPath
import Unison.LabeledDependency (LabeledDependency)
import Unison.LabeledDependency qualified as LD
import Unison.NameSegment qualified as NameSegment
Expand All @@ -33,25 +35,18 @@ import Unison.PrettyPrintEnvDecl.Names qualified as PPED
import Unison.Referent qualified as Referent
import Unison.Sqlite qualified as Sqlite

handleDeleteNamespace ::
Input ->
(Input -> Cli Text) ->
Insistence ->
Maybe (Path, NameSegment.NameSegment) ->
Cli ()
handleDeleteNamespace input inputDescription insistence = \case
handleDeleteNamespace :: Input -> Insistence -> Maybe (Path, NameSegment.NameSegment) -> Cli ()
handleDeleteNamespace input insistence = \case
Nothing -> do
hasConfirmed <- confirmedCommand input
if hasConfirmed || insistence == Force
loopState <- State.get
if loopState.lastInput == Just input || insistence == Force
then do
description <- inputDescription input
pp <- Cli.getCurrentProjectPath
_ <- Cli.updateAt description pp (const Branch.empty)
_ <- Cli.updateAt (commandName <> " .") pp (const Branch.empty)
Cli.respond DeletedEverything
else Cli.respond DeleteEverythingConfirmation
Just p@(parentPath, childName) -> do
branch <- Cli.expectBranchAtPath (Path.unsplit p)
description <- inputDescription input
let toDelete =
Names.prefix0
(Path.nameFromSplit' $ first (Path.RelativePath' . Path.Relative) p)
Expand All @@ -71,17 +66,23 @@ handleDeleteNamespace input inputDescription insistence = \case
Cli.respondNumbered $ CantDeleteNamespace ppeDecl endangerments
Cli.returnEarlyWithoutOutput
parentPathAbs <- Cli.resolvePath parentPath
let description = commandName <> " " <> into @Text (parentPathAbs & ProjectPath.absPath_ %~ (`Lens.snoc` childName))
-- We have to modify the parent in order to also wipe out the history at the
-- child.
Cli.updateAt description parentPathAbs \parentBranch ->
parentBranch
& Branch.modifyAt (Path.singleton childName) \_ -> Branch.empty
Cli.updateAt description parentPathAbs (Branch.modifyAt (Path.singleton childName) \_ -> Branch.empty)
afterDelete
where
commandName :: Text
commandName =
case insistence of
Try -> "delete.namespace"
Force -> "delete.namespace.force"

confirmedCommand :: Input -> Cli Bool
confirmedCommand i = do
loopState <- State.get
pure $ Just i == (loopState ^. #lastInput)
-- How I might do it (is this any better than the current algorithm?)
--
-- 1. Get all direct dependents of the deleted things in the current namespace.
-- 2. For each direct dependent, check a Names built from the deleted namespace – is it there? If not it's the last
-- name.

-- | Goal: When deleting, we might be removing the last name of a given definition (i.e. the
-- definition is going "extinct"). In this case we may wish to take some action or warn the
Expand Down
18 changes: 18 additions & 0 deletions unison-src/transcripts/fix-5446.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,18 @@
Previously `delete.namespace` would refuse to delete a namespace if it would leave any nameless references in `lib`.

```ucm:hide
scratch/main> builtins.merge lib.builtin
```

```unison
lib.one.foo = 17
lib.two.bar = foo Nat.+ foo
```

```ucm
scratch/main> add
```

```ucm:error
scratch/main> delete.namespace lib.one
```
60 changes: 60 additions & 0 deletions unison-src/transcripts/fix-5446.output.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,60 @@
``` unison
lib.one.foo = 17
lib.two.bar = foo Nat.+ foo
```

``` ucm
Loading changes detected in scratch.u.
I found and typechecked these definitions in scratch.u. If you
do an `add` or `update`, here's how your codebase would
change:
⍟ These new definitions are ok to `add`:
lib.one.foo : Nat
lib.two.bar : Nat
```
``` ucm
scratch/main> add
⍟ I've added these definitions:
lib.one.foo : Nat
lib.two.bar : Nat
scratch/main> delete.namespace lib.one
⚠️
I didn't delete the namespace because the following
definitions are still in use.
Dependency Referenced In
foo 1. lib.two.bar
If you want to proceed anyways and leave those definitions
without names, use delete.namespace.force
```



🛑

The transcript failed due to an error in the stanza above. The error is:


⚠️

I didn't delete the namespace because the following
definitions are still in use.

Dependency Referenced In
foo 1. lib.two.bar

If you want to proceed anyways and leave those definitions
without names, use delete.namespace.force

0 comments on commit 78cbe72

Please sign in to comment.