Skip to content

Commit 430ba2d

Browse files
Agda-style case splitting for tactics (#1379)
* Agda splitting machinery * Expand decls! * Only very top-level lambda to args * Preserve top-level args (but it doesnt work very well) * Preserve existing patterns and matches when agdasplitting * Add traceFX debug function * Force a few iterations of splitAgda * Cleanup imports * Put wildcard patterns in for unused variables * Update tests * Agda-unfold on instance deps * wildify at the very end of simplifying * Haddock for top-level functions * Move case splitting stuff into its own module * Exactprint comments * Haddock for casesplit * Use PatCompat * Remove HsDumpAst * Use Pat, not LPat * More massaging Pats * Only unXPat on 8.0.8 * Haddock and cleanup -Wall * Cleanup sus errors * Fix parse errors in GHC > 8.8 * Update comment around unXPat * Cleanup ExactPrint to split FunBind matches * Minor haddock tweak * Bad suggest, hlint * I hate hlint with so much passion Co-authored-by: Pepe Iborra <[email protected]>
1 parent f73b936 commit 430ba2d

31 files changed

+515
-140
lines changed

ghcide/src/Development/IDE/GHC/ExactPrint.hs

Lines changed: 81 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,11 @@
1-
{-# LANGUAGE CPP #-}
1+
{-# LANGUAGE CPP #-}
22
{-# LANGUAGE DerivingStrategies #-}
3-
{-# LANGUAGE GADTs #-}
4-
{-# LANGUAGE OverloadedStrings #-}
5-
{-# LANGUAGE RankNTypes #-}
6-
{-# LANGUAGE TypeFamilies #-}
3+
{-# LANGUAGE GADTs #-}
4+
{-# LANGUAGE OverloadedStrings #-}
5+
{-# LANGUAGE RankNTypes #-}
6+
{-# LANGUAGE TypeFamilies #-}
7+
8+
{- HLINT ignore "Use zipFrom" -}
79

810
module Development.IDE.GHC.ExactPrint
911
( Graft(..),
@@ -15,6 +17,8 @@ module Development.IDE.GHC.ExactPrint
1517
hoistGraft,
1618
graftWithM,
1719
graftWithSmallestM,
20+
graftSmallestDecls,
21+
graftSmallestDeclsWithM,
1822
transform,
1923
transformM,
2024
useAnnotatedSource,
@@ -60,9 +64,17 @@ import Language.LSP.Types.Capabilities (ClientCapabilities)
6064
import Outputable (Outputable, ppr, showSDoc)
6165
import Retrie.ExactPrint hiding (parseDecl, parseExpr, parsePattern, parseType)
6266
import Parser (parseIdentifier)
67+
import Data.Traversable (for)
68+
import Data.Foldable (Foldable(fold))
69+
import Data.Bool (bool)
6370
#if __GLASGOW_HASKELL__ == 808
6471
import Control.Arrow
6572
#endif
73+
#if __GLASGOW_HASKELL__ > 808
74+
import Bag (listToBag)
75+
import ErrUtils (mkErrMsg)
76+
import Outputable (text, neverQualify)
77+
#endif
6678

6779

6880
------------------------------------------------------------------------------
@@ -202,6 +214,7 @@ graftWithoutParentheses dst val = Graft $ \dflags a -> do
202214
)
203215
a
204216

217+
205218
------------------------------------------------------------------------------
206219

207220
graftWithM ::
@@ -271,6 +284,44 @@ graftDecls dst decs0 = Graft $ \dflags a -> do
271284
| otherwise = DL.singleton (L src e) <> go rest
272285
modifyDeclsT (pure . DL.toList . go) a
273286

287+
graftSmallestDecls ::
288+
forall a.
289+
(HasDecls a) =>
290+
SrcSpan ->
291+
[LHsDecl GhcPs] ->
292+
Graft (Either String) a
293+
graftSmallestDecls dst decs0 = Graft $ \dflags a -> do
294+
decs <- forM decs0 $ \decl -> do
295+
(anns, decl') <- annotateDecl dflags decl
296+
modifyAnnsT $ mappend anns
297+
pure decl'
298+
let go [] = DL.empty
299+
go (L src e : rest)
300+
| dst `isSubspanOf` src = DL.fromList decs <> DL.fromList rest
301+
| otherwise = DL.singleton (L src e) <> go rest
302+
modifyDeclsT (pure . DL.toList . go) a
303+
304+
graftSmallestDeclsWithM ::
305+
forall a.
306+
(HasDecls a) =>
307+
SrcSpan ->
308+
(LHsDecl GhcPs -> TransformT (Either String) (Maybe [LHsDecl GhcPs])) ->
309+
Graft (Either String) a
310+
graftSmallestDeclsWithM dst toDecls = Graft $ \dflags a -> do
311+
let go [] = pure DL.empty
312+
go (e@(L src _) : rest)
313+
| dst `isSubspanOf` src = toDecls e >>= \case
314+
Just decs0 -> do
315+
decs <- forM decs0 $ \decl -> do
316+
(anns, decl') <-
317+
annotateDecl dflags decl
318+
modifyAnnsT $ mappend anns
319+
pure decl'
320+
pure $ DL.fromList decs <> DL.fromList rest
321+
Nothing -> (DL.singleton e <>) <$> go rest
322+
| otherwise = (DL.singleton e <>) <$> go rest
323+
modifyDeclsT (fmap DL.toList . go) a
324+
274325
graftDeclsWithM ::
275326
forall a m.
276327
(HasDecls a, Fail.MonadFail m) =>
@@ -355,12 +406,37 @@ annotate dflags ast = do
355406

356407
-- | Given an 'LHsDecl', compute its exactprint annotations.
357408
annotateDecl :: DynFlags -> LHsDecl GhcPs -> TransformT (Either String) (Anns, LHsDecl GhcPs)
409+
-- The 'parseDecl' function fails to parse 'FunBind' 'ValD's which contain
410+
-- multiple matches. To work around this, we split the single
411+
-- 'FunBind'-of-multiple-'Match'es into multiple 'FunBind's-of-one-'Match',
412+
-- and then merge them all back together.
413+
annotateDecl dflags
414+
(L src (
415+
ValD ext fb@FunBind
416+
{ fun_matches = mg@MG { mg_alts = L alt_src alts@(_:_)}
417+
})) = do
418+
let set_matches matches =
419+
ValD ext fb { fun_matches = mg { mg_alts = L alt_src matches }}
420+
421+
(anns', alts') <- fmap unzip $ for (zip [0..] alts) $ \(ix :: Int, alt) -> do
422+
uniq <- show <$> uniqueSrcSpanT
423+
let rendered = render dflags $ set_matches [alt]
424+
lift (mapLeft show $ parseDecl dflags uniq rendered) >>= \case
425+
(ann, L _ (ValD _ FunBind { fun_matches = MG { mg_alts = L _ [alt']}}))
426+
-> pure (bool id (setPrecedingLines alt' 1 0) (ix /= 0) ann, alt')
427+
_ -> lift $ Left "annotateDecl: didn't parse a single FunBind match"
428+
429+
let expr' = L src $ set_matches alts'
430+
anns'' = setPrecedingLines expr' 1 0 $ fold anns'
431+
432+
pure (anns'', expr')
358433
annotateDecl dflags ast = do
359434
uniq <- show <$> uniqueSrcSpanT
360435
let rendered = render dflags ast
361436
(anns, expr') <- lift $ mapLeft show $ parseDecl dflags uniq rendered
362437
let anns' = setPrecedingLines expr' 1 0 anns
363438
pure (anns', expr')
439+
364440
------------------------------------------------------------------------------
365441

366442
-- | Print out something 'Outputable'.

plugins/hls-tactics-plugin/hls-tactics-plugin.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -24,6 +24,7 @@ library
2424
exposed-modules:
2525
Ide.Plugin.Tactic
2626
Ide.Plugin.Tactic.Auto
27+
Ide.Plugin.Tactic.CaseSplit
2728
Ide.Plugin.Tactic.CodeGen
2829
Ide.Plugin.Tactic.CodeGen.Utils
2930
Ide.Plugin.Tactic.Context

0 commit comments

Comments
 (0)