Skip to content

Commit

Permalink
Use annotations from Abs instead
Browse files Browse the repository at this point in the history
  • Loading branch information
ChrisPenner committed Jul 9, 2024
1 parent 60bb91a commit da449fb
Show file tree
Hide file tree
Showing 2 changed files with 10 additions and 19 deletions.
27 changes: 9 additions & 18 deletions unison-cli/src/Unison/LSP/FileAnalysis/UnusedBindings.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,32 +10,23 @@ import U.Core.ABT (ABT (..))
import U.Core.ABT qualified as ABT
import Unison.LSP.Conversions qualified as Cv
import Unison.LSP.Diagnostics qualified as Diagnostic
import Unison.Lexer.Pos qualified as Pos
import Unison.Parser.Ann (Ann)
import Unison.Prelude
import Unison.Symbol (Symbol (..))
import Unison.Term (Term)
import Unison.Util.Monoid qualified as Monoid
import Unison.Util.Range qualified as Range
import Unison.Var qualified as Var

analyseTerm :: Lsp.Uri -> Ann -> Term Symbol Ann -> [Diagnostic]
analyseTerm fileUri topLevelTermAnn tm =
analyseTerm :: Lsp.Uri -> Term Symbol Ann -> [Diagnostic]
analyseTerm fileUri tm =
let (unusedVars, _) = ABT.cata alg tm
-- Unfortunately we don't capture the annotation of the actual binding when parsing :'(, for now the least
-- annoying thing to do is just highlight the top of the binding.
mayRange =
Cv.annToURange topLevelTermAnn
<&> (\(Range.Range start@(Pos.Pos line _col) _end) -> Range.Range start (Pos.Pos line 9999))
<&> Cv.uToLspRange
vars =
Map.toList unusedVars & mapMaybe \(v, _ann) -> do
getRelevantVarName v
in case mayRange of
Nothing -> []
Just lspRange ->
let bindings = Text.intercalate ", " (tShow <$> vars)
in Monoid.whenM (not $ null vars) [Diagnostic.mkDiagnostic fileUri lspRange Diagnostic.DiagnosticSeverity_Warning ("Unused binding(s) " <> bindings <> " inside this term.\nUse the binding(s), or prefix them with an _ to dismiss this warning.") []]
Map.toList unusedVars & mapMaybe \(v, ann) -> do
(,ann) <$> getRelevantVarName v
diagnostics =
vars & mapMaybe \(varName, ann) -> do
lspRange <- Cv.annToRange ann
pure $ Diagnostic.mkDiagnostic fileUri lspRange Diagnostic.DiagnosticSeverity_Warning ("Unused binding " <> varName <> ". Use the binding, or prefix it with an _ to dismiss this warning.") []
in diagnostics
where
getRelevantVarName :: Symbol -> Maybe Text
getRelevantVarName = \case
Expand Down
2 changes: 1 addition & 1 deletion unison-core/src/Unison/Term.hs
Original file line number Diff line number Diff line change
Expand Up @@ -947,7 +947,7 @@ letRec isTop blockAnn bindings e =
(foldr addAbs body bindings)
where
addAbs :: ((a, v), b) -> ABT.Term f v a -> ABT.Term f v a
addAbs ((_a, v), _b) t = ABT.abs' blockAnn v t
addAbs ((a, v), _b) t = ABT.abs' a v t
body :: Term' vt v a
body = ABT.tm' blockAnn (LetRec isTop (map snd bindings) e)

Expand Down

0 comments on commit da449fb

Please sign in to comment.