-
Notifications
You must be signed in to change notification settings - Fork 274
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
Merge pull request #4535 from unisonweb/cp/edit-namespace
Add `edit.namespace` command
- Loading branch information
Showing
9 changed files
with
337 additions
and
46 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
67 changes: 67 additions & 0 deletions
67
unison-cli/src/Unison/Codebase/Editor/HandleInput/EditNamespace.hs
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,67 @@ | ||
module Unison.Codebase.Editor.HandleInput.EditNamespace (handleEditNamespace) where | ||
|
||
import Control.Monad.Reader | ||
import Data.List.Extra qualified as List | ||
import Data.Map qualified as Map | ||
import Unison.Cli.Monad (Cli) | ||
import Unison.Cli.Monad qualified as Cli | ||
import Unison.Cli.MonadUtils qualified as Cli | ||
import Unison.Cli.PrettyPrintUtils qualified as NamesUtils | ||
import Unison.Codebase qualified as Codebase | ||
import Unison.Codebase.Branch qualified as Branch | ||
import Unison.Codebase.Branch.Names qualified as Branch | ||
import Unison.Codebase.Editor.HandleInput.ShowDefinition (showDefinitions) | ||
import Unison.Codebase.Editor.Input (OutputLocation (..)) | ||
import Unison.Codebase.Path (Path) | ||
import Unison.Codebase.Path qualified as Path | ||
import Unison.Names qualified as Names | ||
import Unison.Prelude | ||
import Unison.Server.Backend qualified as Backend | ||
import Unison.Util.Monoid (foldMapM) | ||
|
||
handleEditNamespace :: OutputLocation -> [Path] -> Cli () | ||
handleEditNamespace outputLoc inputPaths = do | ||
Cli.Env {codebase} <- ask | ||
currentBranch <- Cli.getCurrentBranch0 | ||
ppe <- NamesUtils.currentPrettyPrintEnvDecl | ||
let paths = | ||
if null inputPaths | ||
then [Path.empty] | ||
else inputPaths | ||
let allNamesToEdit = | ||
(List.nubOrd paths) & foldMap \path -> | ||
let b = Branch.withoutLib $ Branch.getAt0 path currentBranch | ||
names = (Branch.toNames b) | ||
prefixedNames = case Path.toName path of | ||
Nothing -> names | ||
Just pathPrefix -> Names.prefix0 pathPrefix names | ||
in prefixedNames | ||
let termRefs = Names.termReferences allNamesToEdit | ||
-- We only need to (optionally) include cycles for type references, not term references, | ||
-- because 'update' is smart enough to patch-up cycles as expected for terms. | ||
let typeRefsWithoutCycles = Names.typeReferences allNamesToEdit | ||
typeRefs <- Cli.runTransaction $ | ||
case includeCycles of | ||
Backend.IncludeCycles -> foldMapM Codebase.componentReferencesForReference typeRefsWithoutCycles | ||
Backend.DontIncludeCycles -> pure typeRefsWithoutCycles | ||
|
||
terms <- | ||
termRefs | ||
& foldMapM \ref -> | ||
Map.singleton ref <$> Backend.displayTerm codebase ref | ||
& Cli.runTransaction | ||
|
||
types <- | ||
typeRefs | ||
& foldMapM \ref -> | ||
Map.singleton ref <$> Backend.displayType codebase ref | ||
& Cli.runTransaction | ||
let misses = [] | ||
showDefinitions outputLoc ppe terms types misses | ||
where | ||
-- `view`: don't include cycles; `edit`: include cycles | ||
includeCycles = | ||
case outputLoc of | ||
ConsoleLocation -> Backend.DontIncludeCycles | ||
FileLocation _ -> Backend.IncludeCycles | ||
LatestFileLocation -> Backend.IncludeCycles |
86 changes: 86 additions & 0 deletions
86
unison-cli/src/Unison/Codebase/Editor/HandleInput/ShowDefinition.hs
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,86 @@ | ||
module Unison.Codebase.Editor.HandleInput.ShowDefinition (showDefinitions) where | ||
|
||
import Control.Lens | ||
import Control.Monad.Reader (ask) | ||
import Control.Monad.State qualified as State | ||
import Data.Map qualified as Map | ||
import Data.Set qualified as Set | ||
import Data.Text qualified as Text | ||
import Unison.Builtin.Decls qualified as DD | ||
import Unison.Cli.Monad (Cli) | ||
import Unison.Cli.Monad qualified as Cli | ||
import Unison.Cli.Pretty qualified as Pretty | ||
import Unison.Codebase qualified as Codebase | ||
import Unison.Codebase.Editor.DisplayObject (DisplayObject) | ||
import Unison.Codebase.Editor.Input | ||
import Unison.Codebase.Editor.Output | ||
import Unison.DataDeclaration (Decl) | ||
import Unison.HashQualified qualified as HQ | ||
import Unison.Name (Name) | ||
import Unison.Parser.Ann (Ann) | ||
import Unison.Prelude | ||
import Unison.PrettyPrintEnvDecl qualified as PPED | ||
import Unison.Reference qualified as Reference | ||
import Unison.Symbol (Symbol) | ||
import Unison.Term (Term) | ||
import Unison.Type (Type) | ||
import Unison.Util.Pretty qualified as Pretty | ||
import Unison.Util.Set qualified as Set | ||
|
||
-- | Show the provided definitions to console or scratch file. | ||
-- The caller is responsible for ensuring that the definitions include cycles if that's | ||
-- the desired behavior. | ||
showDefinitions :: | ||
OutputLocation -> | ||
PPED.PrettyPrintEnvDecl -> | ||
(Map Reference.Reference (DisplayObject (Type Symbol Ann) (Term Symbol Ann))) -> | ||
( Map | ||
Reference.Reference | ||
(DisplayObject () (Decl Symbol Ann)) | ||
) -> | ||
[HQ.HashQualified Name] -> | ||
Cli () | ||
showDefinitions outputLoc pped terms types misses = do | ||
Cli.Env {codebase, writeSource} <- ask | ||
outputPath <- getOutputPath | ||
case outputPath of | ||
_ | null terms && null types -> pure () | ||
Nothing -> do | ||
-- If we're writing to console we don't add test-watch syntax | ||
let isTest _ = False | ||
let isSourceFile = False | ||
-- No filepath, render code to console. | ||
let renderedCodePretty = renderCodePretty pped isSourceFile isTest terms types | ||
Cli.respond $ DisplayDefinitions renderedCodePretty | ||
Just fp -> do | ||
-- We build an 'isTest' check to prepend "test>" to tests in a scratch file. | ||
testRefs <- Cli.runTransaction (Codebase.filterTermsByReferenceIdHavingType codebase (DD.testResultType mempty) (Map.keysSet terms & Set.mapMaybe Reference.toId)) | ||
let isTest r = Set.member r testRefs | ||
let isSourceFile = True | ||
let renderedCodePretty = renderCodePretty pped isSourceFile isTest terms types | ||
let renderedCodeText = Text.pack $ Pretty.toPlain 80 renderedCodePretty | ||
|
||
-- We set latestFile to be programmatically generated, if we | ||
-- are viewing these definitions to a file - this will skip the | ||
-- next update for that file (which will happen immediately) | ||
#latestFile ?= (fp, True) | ||
liftIO $ writeSource (Text.pack fp) renderedCodeText | ||
let numDefinitions = Map.size terms + Map.size types | ||
Cli.respond $ LoadedDefinitionsToSourceFile fp numDefinitions | ||
when (not (null misses)) (Cli.respond (SearchTermsNotFound misses)) | ||
where | ||
-- Get the file path to send the definition(s) to. `Nothing` means the terminal. | ||
getOutputPath :: Cli (Maybe FilePath) | ||
getOutputPath = | ||
case outputLoc of | ||
ConsoleLocation -> pure Nothing | ||
FileLocation path -> pure (Just path) | ||
LatestFileLocation -> do | ||
loopState <- State.get | ||
pure case loopState ^. #latestFile of | ||
Nothing -> Just "scratch.u" | ||
Just (path, _) -> Just path | ||
|
||
renderCodePretty pped isSourceFile isTest terms types = | ||
Pretty.syntaxToColor . Pretty.sep "\n\n" $ | ||
Pretty.prettyTypeDisplayObjects pped types <> Pretty.prettyTermDisplayObjects pped isSourceFile isTest terms |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,41 @@ | ||
```ucm:hide | ||
.lib> builtins.mergeio | ||
``` | ||
|
||
```unison:hide | ||
{{ ping doc }} | ||
nested.cycle.ping n = n Nat.+ pong n | ||
{{ pong doc }} | ||
nested.cycle.pong n = n Nat.+ ping n | ||
toplevel = "hi" | ||
simple.x = 10 | ||
simple.y = 20 | ||
-- Shouldn't edit things in lib | ||
lib.project.ignoreMe = 30 | ||
``` | ||
|
||
```ucm:hide | ||
.> add | ||
``` | ||
|
||
Edit current namespace | ||
|
||
```ucm | ||
.simple> edit.namespace | ||
``` | ||
|
||
Edit should hit things recursively | ||
|
||
```ucm | ||
.> edit.namespace | ||
``` | ||
|
||
Edit should handle multiple explicit paths at once. | ||
|
||
```ucm | ||
.> edit.namespace nested.cycle simple | ||
``` |
Oops, something went wrong.