Skip to content

Multiple code action for (at least) explicit record fields #3574

@joyfulmantis

Description

@joyfulmantis

Any time that expansion is used, for example, because of a dot record, the renamed ast includes an HsExpanded expression that contains both the original and generated expressions. This is problematic because an ordinary syb traversal of the ast usually traverses both sets of expressions, causing duplicate returns. In explicit record fields, this causes duplicate codeActions, for example.

Steps to reproduce

This small modification of one of explicit record fields tests was able to trigger the issue

{-# LANGUAGE Haskell2010 #-}
{-# LANGUAGE RecordWildCards #-}
{-# Language OverloadedRecordDot #-}
module Construction where

data MyRec = MyRec
  { foo :: Int
  , bar :: Int
  , baz :: Char
  }

convertMe :: () -> Int
convertMe _ =
  let foo = 3
      bar = 5
      baz = 'a'
  in MyRec {..}.foo

Expected behavior

In this case, instead of the expected one codeAction offering to rewrite the wildcard when clicking upon MyRec, there were two completely identical ones.

If using everything, this can be fixed with using everythingBut, manually starting traversal on one of the branches when HsExpanded is found, and at the same time returning True, which keeps the first everything from traversing any more on that branch.
For example, this is how I did it on the overloaded-record-dot-plugin

-- It's important that we use everthingBut here, because if we used everything we would
-- get duplicates for every case that occurs inside a HsExpanded expression.
collectRecordSelectors :: GenericQ [RecordSelectorExpr]
collectRecordSelectors = everythingBut (<>) (([], False) `mkQ` getRecSels)
-- | We want to return a list here, because on the occasion that we encounter a HsExpanded expression,
-- | we want to return all the results from recursing on one branch, which could be multiple matches
getRecSels :: LHsExpr (GhcPass 'Renamed) -> ([RecordSelectorExpr], Bool)
-- When we stumble upon an occurrence of HsExpanded, we only want to follow one branch
-- we do this here, by explicitly returning occurrences from traversing the original branch,
-- and returning True, which keeps syb from implicitly continuing to traverse.
getRecSels (unLoc -> XExpr (HsExpanded a _)) = (collectRecordSelectors a, True)

I, unfortunately, opened a pull request on the main branch of my fork of hls, so until that closes, I won't be able to submit a fix for explicit record fields. This bug may also affect other plugins, but probably only if they used the Renamed or TypeChecked ast.

Metadata

Metadata

Assignees

Labels

type: bugSomething isn't right: doesn't work as intended, documentation is missing/outdated, etc..

Type

No type

Projects

No projects

Milestone

No milestone

Relationships

None yet

Development

No branches or pull requests

Issue actions