7
7
8
8
module Development.IDE.GHC.ExactPrint
9
9
( Graft (.. ),
10
- graft ,
11
- graftWithoutParentheses ,
12
10
graftDecls ,
13
11
graftDeclsWithM ,
14
12
annotate ,
@@ -65,6 +63,7 @@ import Parser (parseIdentifier)
65
63
import Data.Traversable (for )
66
64
import Data.Foldable (Foldable (fold ))
67
65
import Data.Bool (bool )
66
+ import Data.Monoid (All (All ))
68
67
#if __GLASGOW_HASKELL__ == 808
69
68
import Control.Arrow
70
69
#endif
@@ -178,30 +177,57 @@ transformM dflags ccs uri f a = runExceptT $
178
177
let res = printA a'
179
178
pure $ diffText ccs (uri, T. pack src) (T. pack res) IncludeDeletions
180
179
180
+
181
+ -- | Returns whether or not this node requires its immediate children to have
182
+ -- be parenthesized and have a leading space.
183
+ --
184
+ -- A more natural type for this function would be to return @(Bool, Bool)@, but
185
+ -- we use 'All' instead for its monoid instance.
186
+ needsParensSpace ::
187
+ HsExpr GhcPs ->
188
+ -- | (Needs parens, needs space)
189
+ (All , All )
190
+ needsParensSpace HsLam {} = (All False , All False )
191
+ needsParensSpace HsLamCase {} = (All False , All False )
192
+ needsParensSpace HsApp {} = mempty
193
+ needsParensSpace HsAppType {} = mempty
194
+ needsParensSpace OpApp {} = mempty
195
+ needsParensSpace HsPar {} = (All False , All False )
196
+ needsParensSpace SectionL {} = (All False , All False )
197
+ needsParensSpace SectionR {} = (All False , All False )
198
+ needsParensSpace ExplicitTuple {} = (All False , All False )
199
+ needsParensSpace ExplicitSum {} = (All False , All False )
200
+ needsParensSpace HsCase {} = (All False , All False )
201
+ needsParensSpace HsIf {} = (All False , All False )
202
+ needsParensSpace HsMultiIf {} = (All False , All False )
203
+ needsParensSpace HsLet {} = (All False , All False )
204
+ needsParensSpace HsDo {} = (All False , All False )
205
+ needsParensSpace ExplicitList {} = (All False , All False )
206
+ needsParensSpace RecordCon {} = (All False , All False )
207
+ needsParensSpace RecordUpd {} = mempty
208
+ needsParensSpace _ = mempty
209
+
210
+
181
211
------------------------------------------------------------------------------
182
212
183
213
{- | Construct a 'Graft', replacing the node at the given 'SrcSpan' with the
184
- given 'LHSExpr' . The node at that position must already be a 'LHsExpr', or
185
- this is a no-op.
214
+ given @Located ast@ . The node at that position must already be a @Located
215
+ ast@, or this is a no-op.
186
216
-}
187
- graft ::
217
+ graft' ::
188
218
forall ast a .
189
219
(Data a , ASTElement ast ) =>
220
+ -- | Do we need to insert a space before this grafting? In do blocks, the
221
+ -- answer is no, or we will break layout. But in function applications,
222
+ -- the answer is yes, or the function call won't get its argument. Yikes!
223
+ --
224
+ -- More often the answer is yes, so when in doubt, use that.
225
+ Bool ->
190
226
SrcSpan ->
191
227
Located ast ->
192
228
Graft (Either String ) a
193
- graft dst = graftWithoutParentheses dst . maybeParensAST
194
-
195
- -- | Like 'graft', but trusts that you have correctly inserted the parentheses
196
- -- yourself. If you haven't, the resulting AST will not be valid!
197
- graftWithoutParentheses ::
198
- forall ast a .
199
- (Data a , ASTElement ast ) =>
200
- SrcSpan ->
201
- Located ast ->
202
- Graft (Either String ) a
203
- graftWithoutParentheses dst val = Graft $ \ dflags a -> do
204
- (anns, val') <- annotate dflags val
229
+ graft' needs_space dst val = Graft $ \ dflags a -> do
230
+ (anns, val') <- annotate dflags needs_space val
205
231
modifyAnnsT $ mappend anns
206
232
pure $
207
233
everywhere'
@@ -212,6 +238,31 @@ graftWithoutParentheses dst val = Graft $ \dflags a -> do
212
238
)
213
239
a
214
240
241
+ -- | Like 'graft', but specialized to 'LHsExpr', and intelligently inserts
242
+ -- parentheses if they're necessary.
243
+ graftExpr ::
244
+ forall a .
245
+ (Data a ) =>
246
+ SrcSpan ->
247
+ LHsExpr GhcPs ->
248
+ Graft (Either String ) a
249
+ graftExpr dst val = Graft $ \ dflags a -> do
250
+ -- Traverse the tree, looking for our replacement node. But keep track of
251
+ -- the context (parent HsExpr constructor) we're in while we do it. This
252
+ -- lets us determine wehther or not we need parentheses.
253
+ let (All needs_parens, All needs_space) =
254
+ everythingWithContext (All True , All True ) (<>)
255
+ ( mkQ (mempty , ) $ \ x s -> case x of
256
+ (L src _ :: LHsExpr GhcPs ) | src == dst ->
257
+ (s, s)
258
+ L _ x' -> (mempty , needsParensSpace x')
259
+ ) a
260
+
261
+ runGraft
262
+ (graft' needs_space dst $ bool id maybeParensAST needs_parens val)
263
+ dflags
264
+ a
265
+
215
266
216
267
------------------------------------------------------------------------------
217
268
@@ -232,7 +283,7 @@ graftWithM dst trans = Graft $ \dflags a -> do
232
283
Just val' -> do
233
284
(anns, val'') <-
234
285
hoistTransform (either Fail. fail pure ) $
235
- annotate dflags $ maybeParensAST val'
286
+ annotate dflags True $ maybeParensAST val'
236
287
modifyAnnsT $ mappend anns
237
288
pure val''
238
289
Nothing -> pure val
@@ -257,7 +308,7 @@ graftWithSmallestM dst trans = Graft $ \dflags a -> do
257
308
Just val' -> do
258
309
(anns, val'') <-
259
310
hoistTransform (either Fail. fail pure ) $
260
- annotate dflags $ maybeParensAST val'
311
+ annotate dflags True $ maybeParensAST val'
261
312
modifyAnnsT $ mappend anns
262
313
pure val''
263
314
Nothing -> pure val
@@ -352,10 +403,22 @@ everywhereM' f = go
352
403
class (Data ast , Outputable ast ) => ASTElement ast where
353
404
parseAST :: Parser (Located ast )
354
405
maybeParensAST :: Located ast -> Located ast
406
+ {- | Construct a 'Graft', replacing the node at the given 'SrcSpan' with
407
+ the given @Located ast@. The node at that position must already be
408
+ a @Located ast@, or this is a no-op.
409
+ -}
410
+ graft ::
411
+ forall a .
412
+ (Data a ) =>
413
+ SrcSpan ->
414
+ Located ast ->
415
+ Graft (Either String ) a
416
+ graft dst = graft' True dst . maybeParensAST
355
417
356
418
instance p ~ GhcPs => ASTElement (HsExpr p ) where
357
419
parseAST = parseExpr
358
420
maybeParensAST = parenthesize
421
+ graft = graftExpr
359
422
360
423
instance p ~ GhcPs => ASTElement (Pat p ) where
361
424
#if __GLASGOW_HASKELL__ == 808
@@ -394,12 +457,12 @@ fixAnns ParsedModule {..} =
394
457
395
458
-- | Given an 'LHSExpr', compute its exactprint annotations.
396
459
-- Note that this function will throw away any existing annotations (and format)
397
- annotate :: ASTElement ast => DynFlags -> Located ast -> TransformT (Either String ) (Anns , Located ast )
398
- annotate dflags ast = do
460
+ annotate :: ASTElement ast => DynFlags -> Bool -> Located ast -> TransformT (Either String ) (Anns , Located ast )
461
+ annotate dflags needs_space ast = do
399
462
uniq <- show <$> uniqueSrcSpanT
400
463
let rendered = render dflags ast
401
464
(anns, expr') <- lift $ mapLeft show $ parseAST dflags uniq rendered
402
- let anns' = setPrecedingLines expr' 0 1 anns
465
+ let anns' = setPrecedingLines expr' 0 (bool 0 1 needs_space) anns
403
466
pure (anns', expr')
404
467
405
468
-- | Given an 'LHsDecl', compute its exactprint annotations.
0 commit comments