@@ -31,6 +31,7 @@ import Wingman.Judgements
31
31
import Wingman.Machinery
32
32
import Wingman.Naming
33
33
import Wingman.Types
34
+ import GHC (EpAnn (.. ), emptyComments )
34
35
35
36
36
37
destructMatches
@@ -84,14 +85,13 @@ destructionFor hy t = do
84
85
args = conLikeInstOrigArgTys' con apps
85
86
names = mkManyGoodNames (hyNamesInScope hy) args
86
87
pure
87
- . noLoc
88
+ . noLocA
88
89
. Match
89
- noExtField
90
+ EpAnnNotUsed
90
91
CaseAlt
91
92
[toPatCompat $ snd $ mkDestructPat Nothing con names]
92
- . GRHSs noExtField (pure $ noLoc $ GRHS noExtField [] $ noLoc $ var " _" )
93
- . noLoc
94
- $ EmptyLocalBinds noExtField
93
+ . GRHSs emptyComments (pure $ noLoc $ GRHS EpAnnNotUsed [] $ noLocA $ var " _" )
94
+ $ EmptyLocalBinds NoExtField
95
95
96
96
97
97
@@ -110,17 +110,19 @@ mkDestructPat already_in_scope con names
110
110
case S. member label_occ in_scope of
111
111
-- We have a shadow, so use the generated name instead
112
112
True ->
113
- (name,) $ noLoc $
113
+ (name,) $ noLocA $
114
114
HsRecField
115
- (noLoc $ mkFieldOcc $ noLoc $ Unqual label_occ)
116
- (noLoc $ bvar' name)
115
+ EpAnnNotUsed
116
+ (noLoc $ mkFieldOcc $ noLocA $ Unqual label_occ)
117
+ (noLocA $ bvar' name)
117
118
False
118
119
-- No shadow, safe to use a pun
119
120
False ->
120
- (label_occ,) $ noLoc $
121
+ (label_occ,) $ noLocA $
121
122
HsRecField
122
- (noLoc $ mkFieldOcc $ noLoc $ Unqual label_occ)
123
- (noLoc $ bvar' label_occ)
123
+ EpAnnNotUsed
124
+ (noLoc $ mkFieldOcc $ noLocA $ Unqual label_occ)
125
+ (noLocA $ bvar' label_occ)
124
126
True
125
127
126
128
in (names', )
@@ -140,7 +142,7 @@ infixifyPatIfNecessary :: ConLike -> Pat GhcPs -> Pat GhcPs
140
142
infixifyPatIfNecessary dcon x
141
143
| conLikeIsInfix dcon =
142
144
case x of
143
- ConPatIn op (PrefixCon [lhs, rhs]) ->
145
+ ConPatIn op (PrefixCon _ [lhs, rhs]) ->
144
146
ConPatIn op $ InfixCon lhs rhs
145
147
y -> y
146
148
| otherwise = x
@@ -201,7 +203,7 @@ destruct' use_field_puns f hi jdg = do
201
203
(hi_type hi)
202
204
$ disallowing AlreadyDestructed (S. singleton term) jdg
203
205
pure $ ext
204
- & # syn_val %~ noLoc . case' (var' term)
206
+ & # syn_val %~ noLocA . case' (var' term)
205
207
206
208
207
209
------------------------------------------------------------------------------
@@ -216,7 +218,7 @@ destructLambdaCase' use_field_puns f jdg = do
216
218
#else
217
219
Just (arg, _) | isAlgType arg ->
218
220
#endif
219
- fmap (fmap noLoc lambdaCase) <$>
221
+ fmap (fmap noLocA lambdaCase) <$>
220
222
destructMatches use_field_puns f Nothing (CType arg) jdg
221
223
_ -> cut -- throwError $ GoalMismatch "destructLambdaCase'" g
222
224
@@ -259,8 +261,8 @@ buildDataCon jdg dc tyapps = do
259
261
mkApply :: OccName -> [HsExpr GhcPs ] -> LHsExpr GhcPs
260
262
mkApply occ (lhs : rhs : more)
261
263
| isSymOcc occ
262
- = noLoc $ foldl' (@@) (op lhs (coerceName occ) rhs) more
263
- mkApply occ args = noLoc $ foldl' (@@) (var' occ) args
264
+ = noLocA $ foldl' (@@) (op lhs (coerceName occ) rhs) more
265
+ mkApply occ args = noLocA $ foldl' (@@) (var' occ) args
264
266
265
267
266
268
------------------------------------------------------------------------------
@@ -285,7 +287,7 @@ letForEach rename solve (unHypothesis -> hy) jdg = do
285
287
let hy' = fmap (g <$ ) $ syn_val terms
286
288
matches = fmap (fmap (\ (occ, expr) -> valBind (occNameToStr occ) expr)) terms
287
289
g <- fmap (fmap unLoc) $ newSubgoal $ introduce (userHypothesis hy') jdg
288
- pure $ fmap noLoc $ let' <$> matches <*> g
290
+ pure $ fmap noLocA $ let' <$> matches <*> g
289
291
290
292
291
293
------------------------------------------------------------------------------
@@ -298,7 +300,7 @@ nonrecLet occjdgs jdg = do
298
300
occexts <- traverse newSubgoal $ fmap snd occjdgs
299
301
ext <- newSubgoal
300
302
$ introduce (userHypothesis $ fmap (second jGoal) occjdgs) jdg
301
- pure $ fmap noLoc $
303
+ pure $ fmap noLocA $
302
304
let'
303
305
<$> traverse
304
306
(\ (occ, ext) -> valBind (occNameToStr occ) <$> fmap unLoc ext)
@@ -309,12 +311,12 @@ nonrecLet occjdgs jdg = do
309
311
------------------------------------------------------------------------------
310
312
-- | Converts a function application into applicative form
311
313
idiomize :: LHsExpr GhcPs -> LHsExpr GhcPs
312
- idiomize x = noLoc $ case unLoc x of
314
+ idiomize x = noLocA $ case unLoc x of
313
315
HsApp _ (L _ (HsVar _ (L _ x))) gshgp3 ->
314
316
op (bvar' $ occName x) " <$>" (unLoc gshgp3)
315
317
HsApp _ gsigp gshgp3 ->
316
318
op (unLoc $ idiomize gsigp) " <*>" (unLoc gshgp3)
317
- RecordCon _ con flds ->
318
- unLoc $ idiomize $ noLoc $ foldl' (@@) (HsVar noExtField con) $ fmap unLoc flds
319
+ RecordCon _ con ( HsRecFields flds _) ->
320
+ unLoc $ idiomize $ noLocA $ foldl' (@@) (HsVar noExtField con) $ fmap ( unLoc . hsRecFieldArg . unLoc) flds
319
321
y -> y
320
322
0 commit comments