Skip to content

Commit 3190da3

Browse files
authored
Only expand positional records if the DataCon application is fully saturated (#4586)
* Add issue reproducer as test * Generate the CA only for fully saturated DataCon applications
1 parent 8dd8ffc commit 3190da3

File tree

3 files changed

+44
-8
lines changed

3 files changed

+44
-8
lines changed

plugins/hls-explicit-record-fields-plugin/src/Ide/Plugin/ExplicitFields.hs

Lines changed: 35 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -151,10 +151,17 @@ descriptor recorder plId =
151151
codeActionProvider :: PluginMethodHandler IdeState 'Method_TextDocumentCodeAction
152152
codeActionProvider ideState _ (CodeActionParams _ _ docId range _) = do
153153
nfp <- getNormalizedFilePathE (docId ^. L.uri)
154-
CRR {crCodeActions, enabledExtensions} <- runActionE "ExplicitFields.CollectRecords" ideState $ useE CollectRecords nfp
154+
CRR {crCodeActions, crCodeActionResolve, enabledExtensions} <- runActionE "ExplicitFields.CollectRecords" ideState $ useE CollectRecords nfp
155155
-- All we need to build a code action is the list of extensions, and a int to
156156
-- allow us to resolve it later.
157-
let actions = map (mkCodeAction enabledExtensions) (RangeMap.filterByRange range crCodeActions)
157+
let recordUids = [ uid
158+
| uid <- RangeMap.filterByRange range crCodeActions
159+
, Just record <- [IntMap.lookup uid crCodeActionResolve]
160+
-- Only fully saturated constructor applications can be
161+
-- converted to the record syntax through the code action
162+
, isConvertible record
163+
]
164+
let actions = map (mkCodeAction enabledExtensions) recordUids
158165
pure $ InL actions
159166
where
160167
mkCodeAction :: [Extension] -> Int -> Command |? CodeAction
@@ -169,6 +176,11 @@ codeActionProvider ideState _ (CodeActionParams _ _ docId range _) = do
169176
, _data_ = Just $ toJSON uid
170177
}
171178

179+
isConvertible :: RecordInfo -> Bool
180+
isConvertible = \case
181+
RecordInfoApp _ (RecordAppExpr Unsaturated _ _) -> False
182+
_ -> True
183+
172184
codeActionResolveProvider :: ResolveFunction IdeState Int 'Method_CodeActionResolve
173185
codeActionResolveProvider ideState pId ca uri uid = do
174186
nfp <- getNormalizedFilePathE uri
@@ -253,7 +265,7 @@ inlayHintPosRecProvider _ state _pId InlayHintParams {_textDocument = TextDocume
253265
pure $ InL (concatMap (mkInlayHints nameMap pm) records)
254266
where
255267
mkInlayHints :: UniqFM Name [Name] -> PositionMapping -> RecordInfo -> [InlayHint]
256-
mkInlayHints nameMap pm record@(RecordInfoApp _ (RecordAppExpr _ fla)) =
268+
mkInlayHints nameMap pm record@(RecordInfoApp _ (RecordAppExpr _ _ fla)) =
257269
let textEdits = renderRecordInfoAsTextEdit nameMap record
258270
in mapMaybe (mkInlayHint textEdits pm) fla
259271
mkInlayHints _ _ _ = []
@@ -379,7 +391,16 @@ instance Show CollectNamesResult where
379391

380392
type instance RuleResult CollectNames = CollectNamesResult
381393

382-
data RecordAppExpr = RecordAppExpr (LHsExpr GhcTc) [(Located FieldLabel, HsExpr GhcTc)]
394+
data Saturated = Saturated | Unsaturated
395+
deriving (Generic)
396+
397+
instance NFData Saturated
398+
399+
data RecordAppExpr
400+
= RecordAppExpr
401+
Saturated -- ^ Is the DataCon application fully saturated or partially applied?
402+
(LHsExpr GhcTc)
403+
[(Located FieldLabel, HsExpr GhcTc)]
383404
deriving (Generic)
384405

385406
data RecordInfo
@@ -391,7 +412,7 @@ data RecordInfo
391412
instance Pretty RecordInfo where
392413
pretty (RecordInfoPat ss p) = pretty (printOutputable ss) <> ":" <+> pretty (printOutputable p)
393414
pretty (RecordInfoCon ss e) = pretty (printOutputable ss) <> ":" <+> pretty (printOutputable e)
394-
pretty (RecordInfoApp ss (RecordAppExpr _ fla))
415+
pretty (RecordInfoApp ss (RecordAppExpr _ _ fla))
395416
= pretty (printOutputable ss) <> ":" <+> hsep (map (pretty . printOutputable) fla)
396417

397418
recordInfoToRange :: RecordInfo -> Range
@@ -536,7 +557,7 @@ showRecordConFlds (RecordCon _ _ flds) =
536557
showRecordConFlds _ = Nothing
537558

538559
showRecordApp :: RecordAppExpr -> Maybe Text
539-
showRecordApp (RecordAppExpr recConstr fla)
560+
showRecordApp (RecordAppExpr _ recConstr fla)
540561
= Just $ printOutputable recConstr <> " { "
541562
<> T.intercalate ", " (showFieldWithArg <$> fla)
542563
<> " }"
@@ -588,8 +609,14 @@ getRecCons expr@(unLoc -> app@(HsApp _ _ _)) =
588609

589610
getFields :: HsExpr GhcTc -> [LHsExpr GhcTc] -> Maybe RecordAppExpr
590611
getFields (HsApp _ constr@(unLoc -> expr) arg) args
591-
| not (null fls)
592-
= Just (RecordAppExpr constr labelWithArgs)
612+
| not (null fls) = Just $
613+
-- Code action is only valid if the constructor application is fully
614+
-- saturated, but we still want to display the inlay hints for partially
615+
-- applied constructors
616+
RecordAppExpr
617+
(if length fls <= length args + 1 then Saturated else Unsaturated)
618+
constr
619+
labelWithArgs
593620
where fls = getExprFields expr
594621
labelWithArgs = zipWith mkLabelWithArg fls (arg : args)
595622
mkLabelWithArg label arg = (L (getLoc arg) label, unLoc arg)

plugins/hls-explicit-record-fields-plugin/test/Main.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -36,6 +36,7 @@ test = testGroup "explicit-fields"
3636
, mkTestNoAction "Puns" "Puns" 12 10 12 31
3737
, mkTestNoAction "Infix" "Infix" 11 11 11 31
3838
, mkTestNoAction "Prefix" "Prefix" 10 11 10 28
39+
, mkTestNoAction "PartiallyAppliedCon" "PartiallyAppliedCon" 7 8 7 12
3940
, mkTest "PolymorphicRecordConstruction" "PolymorphicRecordConstruction" 15 5 15 15
4041
]
4142
, testGroup "inlay hints"
Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,8 @@
1+
{-# LANGUAGE Haskell2010 #-}
2+
3+
module PartiallyAppliedCon where
4+
5+
data T = MkT { fa :: Int, fb :: Char }
6+
7+
foo :: Int -> Char -> T
8+
foo x = MkT x

0 commit comments

Comments
 (0)