diff --git a/parser-typechecker/src/Unison/DataDeclaration/Dependencies.hs b/parser-typechecker/src/Unison/DataDeclaration/Dependencies.hs index 0958aaf9c4..e16190f9a8 100644 --- a/parser-typechecker/src/Unison/DataDeclaration/Dependencies.hs +++ b/parser-typechecker/src/Unison/DataDeclaration/Dependencies.hs @@ -122,5 +122,6 @@ hashFieldAccessors ppe declName vars declRef dd = do effectDecls = mempty }, termsByShortname = mempty, + freeNameToFuzzyTermsByShortName = Map.empty, topLevelComponents = Map.empty } diff --git a/parser-typechecker/src/Unison/FileParsers.hs b/parser-typechecker/src/Unison/FileParsers.hs index f1c352aea8..bb69274460 100644 --- a/parser-typechecker/src/Unison/FileParsers.hs +++ b/parser-typechecker/src/Unison/FileParsers.hs @@ -10,14 +10,19 @@ import Control.Monad.State (evalStateT) import Data.Foldable qualified as Foldable import Data.List (partition) import Data.List qualified as List +import Data.List.NonEmpty qualified as NonEmpty import Data.Map qualified as Map +import Data.Ord (clamp) import Data.Sequence qualified as Seq import Data.Set qualified as Set +import Data.Text qualified as Text import Unison.ABT qualified as ABT import Unison.Blank qualified as Blank import Unison.Builtin qualified as Builtin import Unison.ConstructorReference qualified as ConstructorReference import Unison.Name (Name) +import Unison.Name qualified as Name +import Unison.NameSegment qualified as NameSegment import Unison.Names qualified as Names import Unison.Names.ResolvesTo (ResolvesTo (..)) import Unison.Parser.Ann (Ann) @@ -28,7 +33,7 @@ import Unison.Referent (Referent) import Unison.Referent qualified as Referent import Unison.Result (CompilerBug (..), Note (..), ResultT, pattern Result) import Unison.Result qualified as Result -import Unison.Syntax.Name qualified as Name (unsafeParseVar) +import Unison.Syntax.Name qualified as Name (toText, unsafeParseText, unsafeParseVar) import Unison.Syntax.Parser qualified as Parser import Unison.Term qualified as Term import Unison.Type qualified as Type @@ -94,21 +99,50 @@ computeTypecheckingEnvironment shouldUseTndr ambientAbilities typeLookupf uf = { ambientAbilities = ambientAbilities, typeLookup = tl, termsByShortname = Map.empty, + freeNameToFuzzyTermsByShortName = Map.empty, topLevelComponents = Map.empty } ShouldUseTndr'Yes parsingEnv -> do - let tm = UF.typecheckingTerm uf - resolveName :: Name -> Relation Name (ResolvesTo Referent) + let resolveName :: Name -> Relation Name (ResolvesTo Referent) resolveName = Names.resolveNameIncludingNames (Names.shadowing1 (Names.terms (UF.toNames uf)) (Names.terms (Parser.names parsingEnv))) - (Set.map Name.unsafeParseVar (UF.toTermAndWatchNames uf)) - possibleDeps = do - v <- Set.toList (Term.freeVars tm) - let shortname = Name.unsafeParseVar v - (name, ref) <- Rel.toList (resolveName shortname) - [(name, shortname, ref)] - possibleRefs = + localNames + + localNames = Set.map Name.unsafeParseVar (UF.toTermAndWatchNames uf) + globalNamesShadowed = Names.shadowing (UF.toNames uf) (Parser.names parsingEnv) + + freeNames :: [Name] + freeNames = + Name.unsafeParseVar <$> Set.toList (Term.freeVars $ UF.typecheckingTerm uf) + + possibleDepsExact :: [(Name, Name, ResolvesTo Referent)] + possibleDepsExact = do + freeName <- freeNames + (name, ref) <- Rel.toList (resolveName freeName) + [(name, freeName, ref)] + + getFreeNameDepsFuzzy :: Name -> [(Name, Name, ResolvesTo Referent)] + getFreeNameDepsFuzzy freeName = do + let wantedTopNFuzzyMatches = 3 + -- We use fuzzy matching by edit distance here because it is usually more appropriate + -- than FZF-style fuzzy finding for offering suggestions for typos or other user errors. + let fuzzyMatches = + take wantedTopNFuzzyMatches $ + fuzzyFindByEditDistanceRanked globalNamesShadowed localNames freeName + + let names = fuzzyMatches ^.. each . _2 + let resolvedNames = Rel.toList . resolveName =<< names + let getShortName longname = Name.unsafeParseText (NameSegment.toUnescapedText $ Name.lastSegment longname) + + map (\(longname, ref) -> (longname, getShortName longname, ref)) resolvedNames + + freeNameDepsFuzzy :: Map Name [(Name, Name, ResolvesTo Referent)] + freeNameDepsFuzzy = + Map.fromList [(freeName, getFreeNameDepsFuzzy freeName) | freeName <- freeNames] + + getPossibleRefs :: [(Name, Name, ResolvesTo Referent)] -> Defns (Set TermReference) (Set TypeReference) + getPossibleRefs = List.foldl' ( \acc -> \case (_, _, ResolvesToNamespace ref0) -> @@ -118,30 +152,106 @@ computeTypecheckingEnvironment shouldUseTndr ambientAbilities typeLookupf uf = (_, _, ResolvesToLocal _) -> acc ) (Defns Set.empty Set.empty) - possibleDeps - tl <- fmap (UF.declsToTypeLookup uf <>) (typeLookupf (UF.dependencies uf <> possibleRefs)) - let termsByShortname :: Map Name [Either Name (Typechecker.NamedReference v Ann)] - termsByShortname = + + typeLookup <- + fmap + (UF.declsToTypeLookup uf <>) + ( typeLookupf + ( UF.dependencies uf + <> getPossibleRefs possibleDepsExact + <> getPossibleRefs (join $ Map.elems freeNameDepsFuzzy) + ) + ) + + let getTermsByShortname :: [(Name, Name, ResolvesTo Referent)] -> Map Name [Either Name (Typechecker.NamedReference v Ann)] + getTermsByShortname = List.foldl' ( \acc -> \case (name, shortname, ResolvesToLocal _) -> let v = Left name in Map.upsert (maybe [v] (v :)) shortname acc (name, shortname, ResolvesToNamespace ref) -> - case TL.typeOfReferent tl ref of + case TL.typeOfReferent typeLookup ref of Just ty -> let v = Right (Typechecker.NamedReference name ty (Context.ReplacementRef ref)) in Map.upsert (maybe [v] (v :)) shortname acc Nothing -> acc ) Map.empty - possibleDeps + + let termsByShortname = getTermsByShortname possibleDepsExact + let freeNameToFuzzyTermsByShortName = Map.mapWithKey (\_ v -> getTermsByShortname v) freeNameDepsFuzzy + pure Typechecker.Env { ambientAbilities, - typeLookup = tl, + typeLookup = typeLookup, termsByShortname, + freeNameToFuzzyTermsByShortName, topLevelComponents = Map.empty } +-- | 'fuzzyFindByEditDistanceRanked' finds matches for the given 'name' within 'names' by edit distance. +-- +-- Returns a list of 3-tuples composed of an edit-distance Score, a Name, and a List of term and type references). +-- +-- Adapted from Unison.Server.Backend.fuzzyFind +-- +-- TODO: Consider moving to Unison.Names +-- +-- TODO: Take type similarity into account when ranking matches +fuzzyFindByEditDistanceRanked :: + Names.Names -> + Set Name -> + Name -> + [(Int, Name)] +fuzzyFindByEditDistanceRanked globalNames localNames name = + let query = + (Text.unpack . nameToText) name + + -- Use 'nameToTextFromLastNSegments' so edit distance is not biased towards shorter fully-qualified names + -- and the name being queried is only partially qualified. + fzfGlobalNames = + Names.queryEditDistances nameToTextFromLastNSegments query globalNames + fzfLocalNames = + Names.queryEditDistances' nameToTextFromLastNSegments query localNames + fzfNames = fzfGlobalNames ++ fzfLocalNames + + -- Keep only matches with a sufficiently low edit-distance score + filterByScore = filter (\(score, _, _) -> score < maxScore) + + -- Prefer lower edit distances and then prefer shorter names by segment count + rank (score, name, _) = (score, length $ Name.segments name) + + -- Remove dupes based on refs + dedupe = + List.nubOrdOn (\(_, _, refs) -> refs) + + dropRef = map (\(x, y, _) -> (x, y)) + + refine = + dropRef . dedupe . sortOn rank . filterByScore + in refine fzfNames + where + nNameSegments = max 1 $ NonEmpty.length $ Name.segments name + + takeLast :: Int -> NonEmpty.NonEmpty a -> [a] + takeLast n xs = NonEmpty.drop (NonEmpty.length xs - n) xs + nameFromLastNSegments = + Name.fromSegments + . NonEmpty.fromList + . takeLast nNameSegments + . Name.segments + + -- Convert to lowercase for case-insensitive fuzzy matching + nameToText = Text.toLower . Name.toText + nameToTextFromLastNSegments = nameToText . nameFromLastNSegments + + ceilingDiv :: Int -> Int -> Int + ceilingDiv x y = (x + 1) `div` y + -- Expect edit distances (number of typos) to be about half the length of the name being queried + -- But clamp max edit distance to work well with very short names + -- and keep ranking reasonably fast when a verbose name is queried + maxScore = clamp (3, 16) $ Text.length (nameToText name) `ceilingDiv` 2 + synthesizeFile :: forall m v. (Monad m, Var v) => diff --git a/parser-typechecker/src/Unison/PrintError.hs b/parser-typechecker/src/Unison/PrintError.hs index 9d5dd0cf84..e0086ec871 100644 --- a/parser-typechecker/src/Unison/PrintError.hs +++ b/parser-typechecker/src/Unison/PrintError.hs @@ -14,7 +14,7 @@ module Unison.PrintError ) where -import Control.Lens.Tuple (_1, _2, _3) +import Control.Lens.Tuple (_1, _2, _3, _4, _5) import Data.Foldable qualified as Foldable import Data.Function (on) import Data.List (find, intersperse, sortBy) @@ -628,17 +628,19 @@ renderTypeError e env src = case e of Type.Var' (TypeVar.Existential {}) -> mempty _ -> Pr.wrap $ "It should be of type " <> Pr.group (style Type1 (renderType' env expectedType) <> ".") UnknownTerm {..} -> - let (correct, wrongTypes, wrongNames) = + let (correct, rightNameWrongTypes, wrongNameRightTypes, similarNameRightTypes, similarNameWrongTypes) = foldr sep id (sortBy (comparing length <> compare `on` (Name.segments . C.suggestionName)) suggestions) - ([], [], []) + ([], [], [], [], []) sep s@(C.Suggestion _ _ _ match) r = case match of C.Exact -> (_1 %~ (s :)) . r - C.WrongType -> (_2 %~ (s :)) . r - C.WrongName -> (_3 %~ (s :)) . r + C.RightNameWrongType -> (_2 %~ (s :)) . r + C.WrongNameRightType -> (_3 %~ (s :)) . r + C.SimilarNameRightType -> (_4 %~ (s :)) . r + C.SimilarNameWrongType -> (_5 %~ (s :)) . r undefinedSymbolHelp = mconcat [ ( case expectedType of @@ -668,11 +670,24 @@ renderTypeError e env src = case e of annotatedAsErrorSite src termSite, "\n", case correct of - [] -> case wrongTypes of - [] -> case wrongNames of - [] -> undefinedSymbolHelp - wrongs -> formatWrongs wrongNameText wrongs - wrongs -> + [] -> case rightNameWrongTypes of + [] -> case similarNameRightTypes of + [] -> + -- If available, show any 'WrongNameRightType' or 'SimilarNameWrongType' suggestions + -- Otherwise if no suggestions are available show 'undefinedSymbolHelp' + if null wrongNameRightTypes && null similarNameWrongTypes + then undefinedSymbolHelp + else + mconcat + [ if null similarNameWrongTypes + then "" + else formatWrongs similarNameWrongTypeText similarNameWrongTypes, + if null wrongNameRightTypes + then "" + else formatWrongs wrongNameRightTypeText wrongNameRightTypes + ] + similarNameRightTypes -> formatWrongs similarNameRightTypeText similarNameRightTypes + rightNameWrongTypes -> let helpMeOut = Pr.wrap ( mconcat @@ -709,7 +724,7 @@ renderTypeError e env src = case e of ) ] <> "\n\n" - <> formatWrongs wrongTypeText wrongs + <> formatWrongs rightNameWrongTypeText rightNameWrongTypes suggs -> mconcat [ Pr.wrap @@ -790,45 +805,46 @@ renderTypeError e env src = case e of summary note ] where - wrongTypeText pl = - Pr.paragraphyText - ( mconcat - [ "I found ", - pl "a term" "some terms", - " in scope with ", - pl "a " "", - "matching name", - pl "" "s", - " but ", - pl "a " "", - "different type", - pl "" "s", - ". ", - "If ", - pl "this" "one of these", - " is what you meant, try using its full name:" - ] - ) - <> "\n\n" - wrongNameText pl = - Pr.paragraphyText - ( mconcat - [ "I found ", - pl "a term" "some terms", - " in scope with ", - pl "a " "", - "matching type", - pl "" "s", - " but ", - pl "a " "", - "different name", - pl "" "s", - ". ", - "Maybe you meant ", - pl "this" "one of these", - ":\n\n" - ] - ) + rightNameWrongTypeText _ = + mconcat + [ "I found one or more terms in scope with the ", + Pr.bold "right names ", + "but the ", + Pr.bold "wrong types.", + "\n", + "If you meant to use one of these, try using it with its full name and then adjusting types", + ":\n\n" + ] + similarNameRightTypeText _ = + mconcat + [ "I found one or more terms in scope with ", + Pr.bold "similar names ", + "and the ", + Pr.bold "right types.", + "\n", + "If you meant to use one of these, try using it instead", + ":\n\n" + ] + similarNameWrongTypeText _ = + mconcat + [ "I found one or more terms in scope with ", + Pr.bold "similar names ", + "but the ", + Pr.bold "wrong types.", + "\n", + "If you meant to use one of these, try using it instead and then adjusting types", + ":\n\n" + ] + wrongNameRightTypeText _ = + mconcat + [ "I found one or more terms in scope with the ", + Pr.bold "wrong names ", + "but the ", + Pr.bold "right types.", + "\n", + "If you meant to use one of these, try using it instead", + ":\n\n" + ] formatWrongs txt wrongs = let sz = length wrongs pl a b = if sz == 1 then a else b diff --git a/parser-typechecker/src/Unison/Typechecker.hs b/parser-typechecker/src/Unison/Typechecker.hs index 20b4fe8918..0f2797086e 100644 --- a/parser-typechecker/src/Unison/Typechecker.hs +++ b/parser-typechecker/src/Unison/Typechecker.hs @@ -91,6 +91,7 @@ data Env v loc = Env -- - Right means a term/constructor in the namespace, or a constructor in the file (for which we do have a type -- before typechecking) termsByShortname :: Map Name.Name [Either Name.Name (NamedReference v loc)], + freeNameToFuzzyTermsByShortName :: Map Name.Name (Map Name.Name [Either Name.Name (NamedReference v loc)]), topLevelComponents :: Map Name.Name (NamedReference v loc) } deriving stock (Generic) @@ -253,6 +254,10 @@ typeDirectedNameResolution ppe oldNotes oldType env = do Var.MissingResult -> v _ -> Var.named name + dedupe :: [Context.Suggestion v loc] -> [Context.Suggestion v loc] + dedupe = + uniqueBy Context.suggestionReplacement + extractSubstitution :: [Context.Suggestion v loc] -> Maybe (Context.Replacement v) extractSubstitution suggestions = let groupedByName :: [([Name.Name], Context.Replacement v)] = @@ -301,20 +306,23 @@ typeDirectedNameResolution ppe oldNotes oldType env = do Context.InfoNote v loc -> Result (Notes v loc) (Maybe (Resolution v loc)) resolveNote env = \case - Context.SolvedBlank (B.Resolve loc str) v it -> do - let shortname = Name.unsafeParseText (Text.pack str) - matches = - env.termsByShortname - & Map.findWithDefault [] shortname - & mapMaybe \case - Left longname -> Map.lookup longname env.topLevelComponents - Right namedRef -> Just namedRef - suggestions <- wither (resolve it) matches + Context.SolvedBlank (B.Resolve loc str) v inferredType -> do + let resolvedName = Text.pack str + let shortname = Name.unsafeParseText resolvedName + + let matches = findExactMatches env shortname + suggestionsExact <- wither (resolveExact inferredType) matches + + let fuzzyMatches = findFuzzyMatches env shortname + suggestionsFuzzy <- wither (resolveFuzzy inferredType) fuzzyMatches + + let suggestions = suggestionsExact ++ suggestionsFuzzy + pure $ Just Resolution - { resolvedName = Text.pack str, - inferredType = it, + { resolvedName, + inferredType, resolvedLoc = loc, v, suggestions @@ -326,27 +334,51 @@ typeDirectedNameResolution ppe oldNotes oldType env = do note -> do btw note pure Nothing - - dedupe :: [Context.Suggestion v loc] -> [Context.Suggestion v loc] - dedupe = - uniqueBy Context.suggestionReplacement - - resolve :: - Context.Type v loc -> - NamedReference v loc -> - Result (Notes v loc) (Maybe (Context.Suggestion v loc)) - resolve inferredType (NamedReference fqn foundType replace) = - -- We found a name that matches. See if the type matches too. - case Context.isSubtype (TypeVar.liftType foundType) (Context.relax inferredType) of - Left bug -> Nothing <$ compilerBug bug - -- Suggest the import if the type matches. - Right b -> - pure . Just $ - Context.Suggestion - fqn - (TypeVar.liftType foundType) - replace - (if b then Context.Exact else Context.WrongType) + where + findExactMatches :: Env v loc -> Name.Name -> [NamedReference v loc] + findExactMatches env name = do + env.termsByShortname + & Map.findWithDefault [] name + & lookupName + + findFuzzyMatches :: Env v loc -> Name.Name -> [NamedReference v loc] + findFuzzyMatches env name = do + env.freeNameToFuzzyTermsByShortName + & Map.findWithDefault Map.empty name + -- Keep only names that are not exact matches, assuming they are instead fuzzy matches. + & Map.filterWithKey (\key _ -> key /= name) + & Map.elems + & join + & lookupName + + lookupName = mapMaybe \case + Left longname -> Map.lookup longname env.topLevelComponents + Right namedRef -> Just namedRef + + resolveExact = resolve False + resolveFuzzy = resolve True + + resolve :: + Bool -> + Context.Type v loc -> + NamedReference v loc -> + Result (Notes v loc) (Maybe (Context.Suggestion v loc)) + resolve fuzzyNameMatch inferredType (NamedReference fqn foundType replace) = + -- We found a name that matches or is similar. Check the type matches too. + case Context.isSubtype (TypeVar.liftType foundType) (Context.relax inferredType) of + Left bug -> Nothing <$ compilerBug bug + -- Create a suggestion based on name and type similarity. + Right typeMatches -> + pure . Just $ + Context.Suggestion + fqn + (TypeVar.liftType foundType) + replace + if not fuzzyNameMatch + then + if typeMatches then Context.Exact else Context.RightNameWrongType + else + if typeMatches then Context.SimilarNameRightType else Context.SimilarNameWrongType -- | Check whether a term matches a type, using a -- function to resolve the type of @Ref@ constructors diff --git a/parser-typechecker/src/Unison/Typechecker/Context.hs b/parser-typechecker/src/Unison/Typechecker/Context.hs index 767fa37316..913e33940f 100644 --- a/parser-typechecker/src/Unison/Typechecker/Context.hs +++ b/parser-typechecker/src/Unison/Typechecker/Context.hs @@ -327,7 +327,12 @@ type ExpectedArgCount = Int type ActualArgCount = Int -data SuggestionMatch = Exact | WrongType | WrongName +data SuggestionMatch + = Exact + | RightNameWrongType + | WrongNameRightType + | SimilarNameRightType + | SimilarNameWrongType deriving (Ord, Eq, Show) data Suggestion v loc = Suggestion diff --git a/parser-typechecker/src/Unison/UnisonFile.hs b/parser-typechecker/src/Unison/UnisonFile.hs index b3b8a12e1d..d5416dd5b6 100644 --- a/parser-typechecker/src/Unison/UnisonFile.hs +++ b/parser-typechecker/src/Unison/UnisonFile.hs @@ -139,7 +139,7 @@ definitionLocation v uf = <|> dataDeclarations uf ^? ix v . _2 . to DD.annotation <|> effectDeclarations uf ^? ix v . _2 . to (DD.annotation . DD.toDataDecl) --- Converts a file to a single let rec with a body of `()`, for +-- | Converts a file to a single let rec with a body of `()`, for -- purposes of typechecking. typecheckingTerm :: (Var v, Monoid a) => UnisonFile v a -> Term v a typecheckingTerm uf = diff --git a/parser-typechecker/tests/Unison/Test/Typechecker/TypeError.hs b/parser-typechecker/tests/Unison/Test/Typechecker/TypeError.hs index de466722c3..cc4a5ca3a2 100644 --- a/parser-typechecker/tests/Unison/Test/Typechecker/TypeError.hs +++ b/parser-typechecker/tests/Unison/Test/Typechecker/TypeError.hs @@ -17,7 +17,7 @@ import Unison.Typechecker.TypeError qualified as Err test :: Test () test = - scope "> extractor" . tests $ + scope "extractor" . tests $ [ y "> true && 3" Err.and, y "> true || 3" Err.or, y "> if 3 then 1 else 2" Err.cond, @@ -54,7 +54,7 @@ noYieldsError s ex = not $ yieldsError s ex yieldsError :: forall a. String -> ErrorExtractor Symbol Ann a -> Bool yieldsError s ex = - case Common.parseAndSynthesizeAsFile [] "> test" s of + case Common.parseAndSynthesizeAsFile [] "> test_path" s of Result notes (Just _) -> let notes' :: [C.ErrorNote Symbol Ann] notes' = [n | Result.TypeError n <- toList notes] diff --git a/parser-typechecker/unison-parser-typechecker.cabal b/parser-typechecker/unison-parser-typechecker.cabal index 0e8691bbb2..1627a1cf5f 100644 --- a/parser-typechecker/unison-parser-typechecker.cabal +++ b/parser-typechecker/unison-parser-typechecker.cabal @@ -1,6 +1,6 @@ cabal-version: 1.12 --- This file has been generated from package.yaml by hpack version 0.36.0. +-- This file has been generated from package.yaml by hpack version 0.37.0. -- -- see: https://github.com/sol/hpack diff --git a/unison-cli/src/Unison/Cli/TypeCheck.hs b/unison-cli/src/Unison/Cli/TypeCheck.hs index b7e74a231f..f3b6bdf433 100644 --- a/unison-cli/src/Unison/Cli/TypeCheck.hs +++ b/unison-cli/src/Unison/Cli/TypeCheck.hs @@ -50,6 +50,7 @@ typecheckTerm codebase tm = do { ambientAbilities = [], typeLookup, termsByShortname = Map.empty, + freeNameToFuzzyTermsByShortName = Map.empty, topLevelComponents = Map.empty } pure $ fmap extract $ FileParsers.synthesizeFile typecheckingEnv file diff --git a/unison-cli/src/Unison/Codebase/Editor/HandleInput/Run.hs b/unison-cli/src/Unison/Codebase/Editor/HandleInput/Run.hs index 91d0329c6c..22b643dd3e 100644 --- a/unison-cli/src/Unison/Codebase/Editor/HandleInput/Run.hs +++ b/unison-cli/src/Unison/Codebase/Editor/HandleInput/Run.hs @@ -171,6 +171,7 @@ synthesizeForce tl typeOfFunc = do { ambientAbilities = [DD.exceptionType External, Type.builtinIO External], typeLookup = mempty {TypeLookup.typeOfTerms = Map.singleton ref typeOfFunc} <> tl, termsByShortname = Map.empty, + freeNameToFuzzyTermsByShortName = Map.empty, topLevelComponents = Map.empty } case Result.runResultT diff --git a/unison-cli/src/Unison/LSP/FileAnalysis.hs b/unison-cli/src/Unison/LSP/FileAnalysis.hs index 2b5363c7ff..f68370b3b3 100644 --- a/unison-cli/src/Unison/LSP/FileAnalysis.hs +++ b/unison-cli/src/Unison/LSP/FileAnalysis.hs @@ -354,8 +354,10 @@ analyseNotes fileUri ppe src notes = do nameResolutionSuggestionPriority (Context.Suggestion {suggestionMatch, suggestionName}) = case suggestionMatch of Context.Exact -> (0 :: Int, suggestionName) - Context.WrongType -> (1, suggestionName) - Context.WrongName -> (2, suggestionName) + Context.RightNameWrongType -> (1, suggestionName) + Context.SimilarNameRightType -> (2, suggestionName) + Context.SimilarNameWrongType -> (3, suggestionName) + Context.WrongNameRightType -> (4, suggestionName) -- typeHoleReplacementCodeActions :: Symbol -> _ -> Lsp [a] typeHoleReplacementCodeActions diags v typ diff --git a/unison-core/package.yaml b/unison-core/package.yaml index 1b9f2d996e..bc16dba23e 100644 --- a/unison-core/package.yaml +++ b/unison-core/package.yaml @@ -9,6 +9,7 @@ library: source-dirs: src ghc-options: -Wall -fno-warn-name-shadowing -fno-warn-missing-pattern-synonym-signatures -funbox-strict-fields dependencies: + - edit-distance - base - bytestring - containers >= 0.6.3 diff --git a/unison-core/src/Unison/Names.hs b/unison-core/src/Unison/Names.hs index d0613f1411..1f4554992f 100644 --- a/unison-core/src/Unison/Names.hs +++ b/unison-core/src/Unison/Names.hs @@ -19,6 +19,8 @@ module Unison.Names makeAbsolute, makeRelative, fuzzyFind, + queryEditDistances, + queryEditDistances', hqName, hqTermName, hqTypeName, @@ -65,6 +67,7 @@ import Data.Semialign (alignWith) import Data.Set qualified as Set import Data.Text qualified as Text import Data.These (These (..)) +import Text.EditDistance import Text.FuzzyFind qualified as FZF import Unison.ConstructorReference (GConstructorReference (..)) import Unison.ConstructorType qualified as CT @@ -139,7 +142,7 @@ makeAbsolute = map Name.makeAbsolute makeRelative :: Names -> Names makeRelative = map Name.makeRelative --- Finds names that are supersequences of all the given strings, ordered by +-- | Finds names that are supersequences of all the given strings, ordered by -- score and grouped by name. fuzzyFind :: (Name -> Text) -> @@ -163,11 +166,13 @@ fuzzyFind nameToText query names = -- Special cases here just to help optimizer, since -- not sure if `all` will get sufficiently unrolled for -- Text fusion to work out. - [q] -> q `Text.isInfixOf` lowername - [q1, q2] -> q1 `Text.isInfixOf` lowername && q2 `Text.isInfixOf` lowername - query -> all (`Text.isInfixOf` lowername) query + [q] -> q `prefilterTest` lowername + [q1, q2] -> q1 `prefilterTest` lowername && q2 `prefilterTest` lowername + query -> all (`prefilterTest` lowername) query where lowername = Text.toLower name + isBiInfixOf a b = (a `Text.isInfixOf` b) || (b `Text.isInfixOf` a) + prefilterTest a b = (a `isBiInfixOf` b) || (Text.length a == Text.length b) flatten (a, (b, c)) = (a, b, c) fuzzyFinds :: (a -> String) -> [String] -> [a] -> [(FZF.Alignment, a)] fuzzyFinds f query d = @@ -181,6 +186,51 @@ fuzzyFind nameToText query names = query ) +-- | Computes edit distances between a name query and each name in names. +-- +-- Searches both terms and types in names. +queryEditDistances :: + (Name -> Text) -> + String -> + Names -> + [(Int, Name, Maybe (Set (Either Referent TypeReference)))] +queryEditDistances nameToText query names = do + let namedReferences = + (Set.mapMonotonic Left <$> R.toMultimap names.terms) + <> (Set.mapMonotonic Right <$> R.toMultimap names.types) + & Map.toList + let nameToString = Text.unpack . nameToText + let fuzzyMatches = + fmap + ( \(name, reference) -> + (editDistance query (nameToString name), name, Just reference) + ) + namedReferences + + fuzzyMatches + +-- | Computes edit distances between a name query and each name in names. +-- +-- Searches over a set of names. +queryEditDistances' :: + (Name -> Text) -> + String -> + Set Name -> + [(Int, Name, Maybe (Set (Either Referent TypeReference)))] +queryEditDistances' nameToText query names = do + let nameToString = Text.unpack . nameToText + let fuzzyMatches = + Set.map + ( \name -> + (editDistance query (nameToString name), name, Nothing) + ) + names + + Set.toList fuzzyMatches + +editDistance :: String -> String -> Int +editDistance = restrictedDamerauLevenshteinDistance defaultEditCosts + -- | Get all (untagged) term/type references ids in a @Names@. referenceIds :: Names -> Set Reference.Id referenceIds Names {terms, types} = diff --git a/unison-core/unison-core1.cabal b/unison-core/unison-core1.cabal index 91d1b40b27..57f0800859 100644 --- a/unison-core/unison-core1.cabal +++ b/unison-core/unison-core1.cabal @@ -98,6 +98,7 @@ library , bytestring , containers >=0.6.3 , cryptonite + , edit-distance , extra , fuzzyfind , generic-lens diff --git a/unison-merge/src/Unison/Merge/Mergeblob5.hs b/unison-merge/src/Unison/Merge/Mergeblob5.hs index 4390c74838..be65cd0f9d 100644 --- a/unison-merge/src/Unison/Merge/Mergeblob5.hs +++ b/unison-merge/src/Unison/Merge/Mergeblob5.hs @@ -26,6 +26,7 @@ makeMergeblob5 blob typeLookup = { ambientAbilities = [], termsByShortname = Map.empty, typeLookup, + freeNameToFuzzyTermsByShortName = Map.empty, topLevelComponents = Map.empty } in case runIdentity (Result.runResultT (FileParsers.synthesizeFile typecheckingEnv blob.file)) of diff --git a/unison-src/transcripts-manual/rewrites.output.md b/unison-src/transcripts-manual/rewrites.output.md index d591c74597..5ecd303323 100644 --- a/unison-src/transcripts-manual/rewrites.output.md +++ b/unison-src/transcripts-manual/rewrites.output.md @@ -336,14 +336,10 @@ scratch/main> load 19 | bar21 - I also don't know what type it should be. - - Some common causes of this error include: - * Your current namespace is too deep to contain the - definition in its subtree - * The definition is part of a library which hasn't been - added to this project - * You have a typo in the name + I found one or more terms in scope with similar names and the right types. + If you meant to use one of these, try using it instead: + + bar1 : Nat ``` In this example, the `a` is locally bound by the rule, so it shouldn't capture the `a = 39494` binding which is in scope at the point of the replacement: @@ -393,14 +389,12 @@ scratch/main> load 6 | a1 - I also don't know what type it should be. + I found one or more terms in scope with similar names and the right types. + If you meant to use one of these, try using it instead: - Some common causes of this error include: - * Your current namespace is too deep to contain the - definition in its subtree - * The definition is part of a library which hasn't been - added to this project - * You have a typo in the name + (<|) : (i ->{g} o) -> i ->{g} o + Bytes.at : Nat -> Bytes -> Optional Nat + List.at : Nat -> [a] -> Optional a ``` ## Structural find diff --git a/unison-src/transcripts/idempotent/destructuring-binds.md b/unison-src/transcripts/idempotent/destructuring-binds.md index e18e80649a..d2f8e72c94 100644 --- a/unison-src/transcripts/idempotent/destructuring-binds.md +++ b/unison-src/transcripts/idempotent/destructuring-binds.md @@ -91,16 +91,12 @@ ex4 = 2 | (a,b) = (a Nat.+ b, 19) - I think its type should be: + I found one or more terms in scope with similar names but the wrong types. + If you meant to use one of these, try using it instead and then adjusting types: - Nat - - Some common causes of this error include: - * Your current namespace is too deep to contain the - definition in its subtree - * The definition is part of a library which hasn't been - added to this project - * You have a typo in the name + (Float.*) : Float -> Float -> Float + (Int.*) : Int -> Int -> Int + (Nat.*) : Nat -> Nat -> Nat ``` Even though the parser accepts any pattern on the LHS of a bind, it looks pretty weird to see things like `12 = x`, so we avoid showing a destructuring bind when the LHS is a "literal" pattern (like `42` or "hi"). Again these examples wouldn't compile with coverage checking. diff --git a/unison-src/transcripts/idempotent/fix845.md b/unison-src/transcripts/idempotent/fix845.md index 57c5dc7fcd..9e1c1f0978 100644 --- a/unison-src/transcripts/idempotent/fix845.md +++ b/unison-src/transcripts/idempotent/fix845.md @@ -43,16 +43,10 @@ Now, typecheck a file with a reference to `Blah.zonk` (which doesn't exist in th 2 | > Blah.zonk [1,2,3] - I think its type should be: + I found one or more terms in scope with similar names and the right types. + If you meant to use one of these, try using it instead: - [Nat] -> o - - Some common causes of this error include: - * Your current namespace is too deep to contain the - definition in its subtree - * The definition is part of a library which hasn't been - added to this project - * You have a typo in the name + List.zonk : [a] -> [a] ``` Here's another example, just checking that TDNR works for definitions in the same file: diff --git a/unison-src/transcripts/idempotent/formatter.md b/unison-src/transcripts/idempotent/formatter.md index ac170b1b5e..d3a6755ac6 100644 --- a/unison-src/transcripts/idempotent/formatter.md +++ b/unison-src/transcripts/idempotent/formatter.md @@ -193,9 +193,8 @@ brokenDoc = {{ hello }} + 1 Help me out by using a more specific name here or adding a type annotation. - I found some terms in scope with matching names but different - types. If one of these is what you meant, try using its full - name: + I found one or more terms in scope with the right names but the wrong types. + If you meant to use one of these, try using it with its full name and then adjusting types: (Float.+) : Float -> Float -> Float (Int.+) : Int -> Int -> Int diff --git a/unison-src/transcripts/idempotent/name-resolution-fuzzy.md b/unison-src/transcripts/idempotent/name-resolution-fuzzy.md new file mode 100644 index 0000000000..4c595ca699 --- /dev/null +++ b/unison-src/transcripts/idempotent/name-resolution-fuzzy.md @@ -0,0 +1,247 @@ +# Check outputs produced during fuzzy name resolution failures + +## Setup + +``` ucm :hide +scratch/main> builtins.merge +``` + +## When given a term with the right name and the right type + +### Then I successfully typecheck the term and allow it to be added + +``` unison +myFunction : Float -> Int +myFunction = truncate +``` + +``` ucm :added-by-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`: + + myFunction : Float -> Int +``` + +## When given a term with the right name but wrong type + +### Then I get a type mismatch error + +``` unison :error +-- TODO: Can we exercise suggestions for right name wrong type without encountering type mismatch errors? +myFunction : Float -> Nat +myFunction = truncate +``` + +``` ucm :added-by-ucm + Loading changes detected in scratch.u. + + I found a value of type: Int + where I expected to find: Nat + + 2 | myFunction : Float -> Nat + 3 | myFunction = truncate +``` + +## When given a term that matches with terms with similar names and the right type + +### Then I get a name resolution error with suggestions to use one of the similar names + +``` unison :error +-- This should be Float -> Float but it seems the stdlib is old +-- should match only truncate +myFunction : Float -> Int +myFunction = TRuncate +``` + +``` ucm :added-by-ucm + Loading changes detected in scratch.u. + + I couldn't figure out what TRuncate refers to here: + + 4 | myFunction = TRuncate + + I found one or more terms in scope with similar names and the right types. + If you meant to use one of these, try using it instead: + + truncate : Float -> Int +``` + +``` unison :error +-- Works with fully-qualified names +-- should match only builtin.io2.Ref.cas +myFunction : Ref {IO} a1 -> Ticket a1 -> a1 ->{IO} Boolean +myFunction = builtin.io2.Ref.ca1 +``` + +``` ucm :added-by-ucm + Loading changes detected in scratch.u. + + I couldn't figure out what builtin.io2.Ref.ca1 refers to here: + + 4 | myFunction = builtin.io2.Ref.ca1 + + I found one or more terms in scope with similar names and the right types. + If you meant to use one of these, try using it instead: + + cas : Ref {IO} a -> Ticket a -> a ->{IO} Boolean +``` + +``` unison :hide +-- Works with definitions added to the code base interactively +List.zonk : [a] -> [a] +List.zonk xs = xs +``` + +``` ucm :hide +scratch/main> add +``` + +``` unison :error +> Blah.zonk [1,2,3] +``` + +``` ucm :added-by-ucm + Loading changes detected in scratch.u. + + I couldn't figure out what Blah.zonk refers to here: + + 1 | > Blah.zonk [1,2,3] + + I found one or more terms in scope with similar names and the right types. + If you meant to use one of these, try using it instead: + + zonk : [a] -> [a] +``` + +## When given a term that matches with terms with similar names but the wrong type + +### Then I get a name resolution error with suggestions to use one of the similar names and adjust the type + +``` unison :error +-- Should match truncate and truncate0 though they have different types +myFunction : Float -> Nat +myFunction = Flat.TRuncate2x4 +``` + +``` ucm :added-by-ucm + Loading changes detected in scratch.u. + + I couldn't figure out what Flat.TRuncate2x4 refers to here: + + 3 | myFunction = Flat.TRuncate2x4 + + I found one or more terms in scope with similar names but the wrong types. + If you meant to use one of these, try using it instead and then adjusting types: + + truncate : Float -> Int + truncate0 : Int -> Nat +``` + +``` unison :error +-- Works with short names +-- Should match short name * in Float/Int/Nat +myFunction : Int -> Int -> Boolean +myFunction = X +``` + +``` ucm :added-by-ucm + Loading changes detected in scratch.u. + + I couldn't figure out what X refers to here: + + 4 | myFunction = X + + I found one or more terms in scope with similar names but the wrong types. + If you meant to use one of these, try using it instead and then adjusting types: + + (Float.*) : Float -> Float -> Float + (Int.*) : Int -> Int -> Int + (Nat.*) : Nat -> Nat -> Nat +``` + +``` unison :error +-- Works with qualified short names +-- Should only match short names Int +myFunction : Int -> Int -> Boolean +myFunction = In.X +``` + +``` ucm :added-by-ucm + Loading changes detected in scratch.u. + + I couldn't figure out what In.X refers to here: + + 4 | myFunction = In.X + + I found one or more terms in scope with similar names but the wrong types. + If you meant to use one of these, try using it instead and then adjusting types: + + (Int.*) : Int -> Int -> Int + (Int.+) : Int -> Int -> Int + (Int.-) : Int -> Int -> Int +``` + +## When given a term that matches local terms not yet added to the code base + +### Then I get a name resolution error with suggestions to use a similar name + +``` unison :error +a : Boolean +a = 1 == 2 + +xyzlmno : Boolean +xyzlmno = 1 == 2 + +-- Should only match with local name a with the right type Boolean +f : () +f = + if A then xYzlmno else () +``` + +``` ucm :added-by-ucm + Loading changes detected in scratch.u. + + I couldn't figure out what A refers to here: + + 10 | if A then xYzlmno else () + + I found one or more terms in scope with similar names and the right types. + If you meant to use one of these, try using it instead: + + a : Boolean +``` + +``` unison :error +a : Boolean +a = 1 == 2 + +L.xyzlmno : Int +L.xyzlmno = +1 + +-- Should only match with local name L.xyzlmno although the type doesn't match +f : () +f = + if R.xYzlmno then A else () +``` + +``` ucm :added-by-ucm + Loading changes detected in scratch.u. + + I couldn't figure out what R.xYzlmno refers to here: + + 10 | if R.xYzlmno then A else () + + I found one or more terms in scope with similar names but the wrong types. + If you meant to use one of these, try using it instead and then adjusting types: + + L.xyzlmno : Int +``` + +## Notes + +There is another case where the term matches with terms with the wrong name but the right type. This case was not added here because it is unclear how to produce a concrete example. This kind of suggestion does not seem to be produced in the code paths in Unison.TypeChecker