Skip to content

Commit

Permalink
feat(cli): names command can search for multiple names
Browse files Browse the repository at this point in the history
  • Loading branch information
xmbhasin committed Jan 3, 2025
1 parent b7b3439 commit 6950fc1
Show file tree
Hide file tree
Showing 15 changed files with 273 additions and 122 deletions.
28 changes: 4 additions & 24 deletions unison-cli/src/Unison/Codebase/Editor/HandleInput.hs
Original file line number Diff line number Diff line change
Expand Up @@ -59,8 +59,8 @@ import Unison.Codebase.Editor.HandleInput.DeleteBranch (handleDeleteBranch)
import Unison.Codebase.Editor.HandleInput.DeleteNamespace (getEndangeredDependents, handleDeleteNamespace)
import Unison.Codebase.Editor.HandleInput.DeleteProject (handleDeleteProject)
import Unison.Codebase.Editor.HandleInput.Dependents (handleDependents)
import Unison.Codebase.Editor.HandleInput.EditNamespace (handleEditNamespace)
import Unison.Codebase.Editor.HandleInput.EditDependents (handleEditDependents)
import Unison.Codebase.Editor.HandleInput.EditNamespace (handleEditNamespace)
import Unison.Codebase.Editor.HandleInput.FindAndReplace (handleStructuredFindI, handleStructuredFindReplaceI, handleTextFindI)
import Unison.Codebase.Editor.HandleInput.FormatFile qualified as Format
import Unison.Codebase.Editor.HandleInput.Global qualified as Global
Expand All @@ -73,6 +73,7 @@ import Unison.Codebase.Editor.HandleInput.MoveAll (handleMoveAll)
import Unison.Codebase.Editor.HandleInput.MoveBranch (doMoveBranch)
import Unison.Codebase.Editor.HandleInput.MoveTerm (doMoveTerm)
import Unison.Codebase.Editor.HandleInput.MoveType (doMoveType)
import Unison.Codebase.Editor.HandleInput.Names (handleNames)
import Unison.Codebase.Editor.HandleInput.NamespaceDependencies (handleNamespaceDependencies)
import Unison.Codebase.Editor.HandleInput.NamespaceDiffUtils (diffHelper)
import Unison.Codebase.Editor.HandleInput.ProjectClone (handleClone)
Expand Down Expand Up @@ -497,29 +498,8 @@ loop e = do

fixupOutput :: Path.HQSplit -> HQ.HashQualified Name
fixupOutput = HQ'.toHQ . Path.nameFromHQSplit
NamesI global query -> do
hqLength <- Cli.runTransaction Codebase.hashLength
let searchNames names = do
let pped = PPED.makePPED (PPE.hqNamer 10 names) (PPE.suffixifyByHash names)
unsuffixifiedPPE = PPED.unsuffixifiedPPE pped
terms = Names.lookupHQTerm Names.IncludeSuffixes query names
types = Names.lookupHQType Names.IncludeSuffixes query names
terms' :: [(Referent, [HQ'.HashQualified Name])]
terms' = map (\r -> (r, PPE.allTermNames unsuffixifiedPPE r)) (Set.toList terms)
types' :: [(Reference, [HQ'.HashQualified Name])]
types' = map (\r -> (r, PPE.allTypeNames unsuffixifiedPPE r)) (Set.toList types)
pure (terms', types')
if global
then do
Global.forAllProjectBranches \(projBranchNames, _ids) branch -> do
let names = Branch.toNames . Branch.head $ branch
(terms, types) <- searchNames names
when (not (null terms) || not (null types)) do
Cli.respond $ GlobalListNames projBranchNames hqLength types terms
else do
names <- Cli.currentNames
(terms, types) <- searchNames names
Cli.respond $ ListNames hqLength types terms
NamesI global queries -> do
mapM_ (handleNames global) queries
DocsI srcs -> do
for_ srcs docsI
CreateAuthorI authorNameSegment authorFullName -> do
Expand Down
70 changes: 70 additions & 0 deletions unison-cli/src/Unison/Codebase/Editor/HandleInput/Names.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,70 @@
module Unison.Codebase.Editor.HandleInput.Names (handleNames) where

import Control.Monad (when)
import Data.Set qualified as Set
import Unison.Cli.Monad (Cli)
import Unison.Cli.Monad qualified as Cli
import Unison.Cli.NamesUtils qualified as Cli
import Unison.Codebase qualified as Codebase
import Unison.Codebase.Branch qualified as Branch
import Unison.Codebase.Branch.Names qualified as Branch
import Unison.Codebase.Editor.HandleInput.Global qualified as Global
import Unison.Codebase.Editor.Input (ErrorMessageOrName, RawQuery)
import Unison.Codebase.Editor.Output (Output (..))
import Unison.HashQualifiedPrime qualified as HQ'
import Unison.Name (Name)
import Unison.NamesWithHistory qualified as Names
import Unison.PrettyPrintEnv qualified as PPE
import Unison.PrettyPrintEnv.Names qualified as PPE
import Unison.PrettyPrintEnvDecl qualified as PPED
import Unison.PrettyPrintEnvDecl.Names qualified as PPED
import Unison.Reference (Reference)
import Unison.Referent (Referent)
import Unison.Util.Pretty qualified as P

-- | Handles a single @NamesI@ input query returning terms that match a given name.
--
-- Parameters:
--
-- * @global :: Bool@
-- ** If @True@, search all projects and branches.
-- ** If @False@, search only the current branch.
--
-- * @query :: (RawQuery, ErrorMessageOrName)@
-- ** The first member is the raw @nameQuery@ being handled.
-- ** The second member is the parsed @nameQuery@ that is either an error message
-- to be printed or a name that can be looked up in the codebase.
handleNames ::
Bool ->
(RawQuery, ErrorMessageOrName) ->
Cli ()
handleNames _ (nameQuery, Left errMsg) = do
Cli.respond $
PrintMessage $
P.indentAfterNewline " " (P.sepNonEmpty "\n" [P.red $ P.bold $ P.string (nameQuery <> ":"), errMsg])
handleNames global (nameQuery, Right query) = do
hqLength <- Cli.runTransaction Codebase.hashLength
let searchNames names = do
let pped = PPED.makePPED (PPE.hqNamer 10 names) (PPE.suffixifyByHash names)
unsuffixifiedPPE = PPED.unsuffixifiedPPE pped
terms = Names.lookupHQTerm Names.IncludeSuffixes query names
types = Names.lookupHQType Names.IncludeSuffixes query names
terms' :: [(Referent, [HQ'.HashQualified Name])]
terms' = map (\r -> (r, PPE.allTermNames unsuffixifiedPPE r)) (Set.toList terms)
types' :: [(Reference, [HQ'.HashQualified Name])]
types' = map (\r -> (r, PPE.allTypeNames unsuffixifiedPPE r)) (Set.toList types)
pure (terms', types')
let prettyNameQuery =
PrintMessage $
P.green (P.bold $ P.string nameQuery) <> ":\n"
if global
then do
Global.forAllProjectBranches \(projBranchNames, _ids) branch -> do
let names = Branch.toNames . Branch.head $ branch
(terms, types) <- searchNames names
when (not (null terms) || not (null types)) do
Cli.respond $ BatchedOutput [prettyNameQuery, IndentedOutput 2 $ GlobalListNames projBranchNames hqLength types terms]
else do
names <- Cli.currentNames
(terms, types) <- searchNames names
Cli.respond $ BatchedOutput [prettyNameQuery, IndentedOutput 2 $ ListNames hqLength types terms]
13 changes: 12 additions & 1 deletion unison-cli/src/Unison/Codebase/Editor/Input.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,10 @@ module Unison.Codebase.Editor.Input
IsGlobal,
DeleteOutput (..),
DeleteTarget (..),

-- * Type aliases
ErrorMessageOrName,
RawQuery,
)
where

Expand Down Expand Up @@ -61,6 +65,12 @@ type SourceName = Text -- "foo.u" or "buffer 7"

type PatchPath = Path.Split'

type ErrorMessageOrValue a = Either (P.Pretty P.ColorText) a

type ErrorMessageOrName = ErrorMessageOrValue (HQ.HashQualified Name)

type RawQuery = String

data OptionalPatch = NoPatch | DefaultPatch | UsePatch PatchPath
deriving (Eq, Ord, Show)

Expand Down Expand Up @@ -141,7 +151,8 @@ data Input
-- > names .foo.bar
-- > names .foo.bar#asdflkjsdf
-- > names #sdflkjsdfhsdf
NamesI IsGlobal (HQ.HashQualified Name)
-- > names foo.bar foo.baz #sdflkjsdfhsdf
NamesI IsGlobal [(RawQuery, ErrorMessageOrName)]
| AliasTermI !Bool HashOrHQSplit' Path.Split' -- bool = force?
| AliasTypeI !Bool HashOrHQSplit' Path.Split' -- bool = force?
| AliasManyI [Path.HQSplit] Path'
Expand Down
8 changes: 7 additions & 1 deletion unison-cli/src/Unison/Codebase/Editor/Output.hs
Original file line number Diff line number Diff line change
Expand Up @@ -189,7 +189,11 @@ data AmbiguousReset'Argument
-- | ShowDiff

data Output
= -- Generic Success response; we might consider deleting this.
= -- | Output that should be indented by some amount before printing.
IndentedOutput Int Output
| -- | A list of outputs that should be handled together in sequence.
BatchedOutput [Output]
| -- Generic Success response; we might consider deleting this.
Success
| -- User did `add` or `update` before typechecking a file?
NoUnisonFile
Expand Down Expand Up @@ -496,6 +500,8 @@ type SourceFileContents = Text

isFailure :: Output -> Bool
isFailure o = case o of
BatchedOutput os -> any isFailure os
IndentedOutput _ o -> isFailure o
UpdateTypecheckingFailure {} -> True
UpdateIncompleteConstructorSet {} -> True
AmbiguousCloneLocal {} -> True
Expand Down
29 changes: 21 additions & 8 deletions unison-cli/src/Unison/CommandLine/InputPatterns.hs
Original file line number Diff line number Diff line change
Expand Up @@ -281,9 +281,13 @@ formatStructuredArgument schLength = \case
else "." <> s
pathArgStr = Text.pack $ show pathArg

-- | Converts an arbitrary argument to a `String`. This is for cases where the
-- | Converts an arbitrary argument to a `String`.
--
-- This is for cases where the
-- command /should/ accept a structured argument of some type, but currently
-- wants a `String`.
--
-- This can also be used where the input argument needs to be included in the output.
unifyArgument :: I.Argument -> String
unifyArgument = either id (Text.unpack . formatStructuredArgument Nothing)

Expand Down Expand Up @@ -2687,16 +2691,25 @@ names isGlobal =
cmdName
[]
I.Visible
[("name or hash", Required, definitionQueryArg)]
(P.wrap $ makeExample (names isGlobal) ["foo"] <> description)
[("name or hash", OnePlus, definitionQueryArg)]
description
$ \case
[thing] -> Input.NamesI isGlobal <$> handleHashQualifiedNameArg thing
args -> wrongArgsLength "exactly one argument" args
[] -> wrongArgsLength "at least one argument" []
args -> do
let answers = handleArg <$> args
pure $ Input.NamesI isGlobal answers
where
description
| isGlobal = "Iteratively search across all projects and branches for names matching `foo`. Note that this is expected to be quite slow and is primarily for debugging issues with your codebase."
| otherwise = "List all known names for `foo` in the current branch."
isGlobalPreamble = "Iteratively search names or hashes across all projects and branches."
isNotGlobalPreamble = "Search names or hashes in the current branch."
cmdName = if isGlobal then "debug.names.global" else "names"
description =
P.lines
[ if isGlobal then isGlobalPreamble else isNotGlobalPreamble,
P.wrap $ makeExample (names isGlobal) ["foo"] <> "List all known names for `foo`.",
P.wrap $ makeExample (names isGlobal) ["foo", "#bar"] <> "List all known names for the name `foo` and for the hash `#bar`.",
P.wrap $ makeExample (names isGlobal) [] <> "without arguments invokes a search to select names/hashes to list, which requires that `fzf` can be found within your PATH."
]
handleArg arg = (unifyArgument arg, handleHashQualifiedNameArg arg)

dependents, dependencies :: InputPattern
dependents =
Expand Down
15 changes: 14 additions & 1 deletion unison-cli/src/Unison/CommandLine/OutputMessages.hs
Original file line number Diff line number Diff line change
Expand Up @@ -572,6 +572,16 @@ undoTip =

notifyUser :: FilePath -> Output -> IO Pretty
notifyUser dir = \case
-- Recursively handle BatchedOutput
BatchedOutput [] -> pure ""
BatchedOutput (o : os) -> do
combine [notifyUser dir o, notifyUser dir (BatchedOutput os)]
where
combine :: (Foldable t, Monad m1, Monoid m2) => t (m1 m2) -> m1 m2
combine = foldr (liftA2 (<>)) (pure mempty)
IndentedOutput indent o -> do
let indented = P.indentN (P.Width indent)
indented <$> notifyUser dir o
SaveTermNameConflict name ->
pure
. P.warnCallout
Expand Down Expand Up @@ -2765,6 +2775,9 @@ handleTodoOutput todo
if todo.defnsInLib
then
P.wrap $
-- Note [DefnsInLibMessage] If you change this, also change the other similar one
-- Note [DefnsInLibMessage] If you change this, also change the other similar one

-- Note [DefnsInLibMessage] If you change this, also change the other similar one
"There's a type or term at the top level of the `lib` namespace, where I only expect to find"
<> "subnamespaces representing library dependencies. Please move or remove it."
Expand Down Expand Up @@ -2931,7 +2944,7 @@ listOfNames len types terms = do
]
where
formatTerms tms =
P.lines . P.nonEmpty $ P.plural tms (P.blue "Term") : List.intersperse "" (go <$> tms)
P.lines . P.nonEmpty $ P.blue (P.plural tms "Term") : List.intersperse "" (go <$> tms)
where
go (ref, hqs) =
P.column2
Expand Down
1 change: 1 addition & 0 deletions unison-cli/unison-cli.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -74,6 +74,7 @@ library
Unison.Codebase.Editor.HandleInput.MoveBranch
Unison.Codebase.Editor.HandleInput.MoveTerm
Unison.Codebase.Editor.HandleInput.MoveType
Unison.Codebase.Editor.HandleInput.Names
Unison.Codebase.Editor.HandleInput.NamespaceDependencies
Unison.Codebase.Editor.HandleInput.NamespaceDiffUtils
Unison.Codebase.Editor.HandleInput.ProjectClone
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,8 @@ scratch/main> add
scratch/main> names term1
Term
Hash: #42m1ui9g56
Names: term1 term2
term1:
Term
Hash: #42m1ui9g56
Names: term1 term2
```
28 changes: 16 additions & 12 deletions unison-src/transcripts/idempotent/deep-names.md
Original file line number Diff line number Diff line change
Expand Up @@ -53,15 +53,17 @@ As such, we see two copies of `a` and two copies of `x` via these direct depende
``` ucm
scratch/app1> names a
Term
Hash: #gjmq673r1v
Names: lib.text_v1.a lib.text_v2.a
a:
Term
Hash: #gjmq673r1v
Names: lib.text_v1.a lib.text_v2.a
scratch/app1> names x
Term
Hash: #nsmc4p1ra4
Names: lib.http_v3.x lib.http_v4.x
x:
Term
Hash: #nsmc4p1ra4
Names: lib.http_v3.x lib.http_v4.x
```

Our `app2` project includes the `http` library twice as direct dependencies, and once as an indirect dependency via `webutil`.
Expand Down Expand Up @@ -103,13 +105,15 @@ We see neither the second indirect copy of `a` nor the indirect copy of `x` via
``` ucm
scratch/app2> names a
Term
Hash: #gjmq673r1v
Names: lib.webutil.lib.text_v1.a
a:
Term
Hash: #gjmq673r1v
Names: lib.webutil.lib.text_v1.a
scratch/app2> names x
Term
Hash: #nsmc4p1ra4
Names: lib.http_v1.x lib.http_v2.x
x:
Term
Hash: #nsmc4p1ra4
Names: lib.http_v1.x lib.http_v2.x
```
20 changes: 14 additions & 6 deletions unison-src/transcripts/idempotent/help.md
Original file line number Diff line number Diff line change
Expand Up @@ -152,10 +152,13 @@ scratch/main> help
operation.
debug.names.global
`debug.names.global foo` Iteratively search across all
projects and branches for names matching `foo`. Note that this
is expected to be quite slow and is primarily for debugging
issues with your codebase.
Iteratively search names or hashes across all projects and branches.
`debug.names.global foo` List all known names for `foo`.
`debug.names.global foo #bar` List all known names for the
name `foo` and for the hash `#bar`.
`debug.names.global` without arguments invokes a search to
select names/hashes to list, which requires that `fzf` can be
found within your PATH.
debug.numberedArgs
Dump the contents of the numbered args state.
Expand Down Expand Up @@ -553,8 +556,13 @@ scratch/main> help
`move.type foo bar` renames `foo` to `bar`.
names
`names foo` List all known names for `foo` in the current
branch.
Search names or hashes in the current branch.
`names foo` List all known names for `foo`.
`names foo #bar` List all known names for the name `foo` and
for the hash `#bar`.
`names` without arguments invokes a search to select
names/hashes to list, which requires that `fzf` can be found
within your PATH.
namespace.dependencies
List the external dependencies of the specified namespace.
Expand Down
Loading

0 comments on commit 6950fc1

Please sign in to comment.