Skip to content

Commit f4a9671

Browse files
Simplify tactics state structure (#1449)
* Store total number of arguments in TopLevelArgPrv * Re-enable tracing other solutions * Document a bug I ran into while trying to dogfood * Replace the janky (Trace,) extract with something more principled * Add explicit constructors for introducing hypotheses * Split apart creation of hypothesis from introduction of it * Produce better debug output for other solns * Track all the bindings that get generated in Synthesized * Remove ts_intro_vals; use synthesized bindings instead * Track used variables in the Synthesis * Remove a debug trace * Add some documentation about what's happening here. * Minor tidying Co-authored-by: mergify[bot] <37929162+mergify[bot]@users.noreply.github.com>
1 parent 7d416f0 commit f4a9671

File tree

8 files changed

+212
-206
lines changed

8 files changed

+212
-206
lines changed

plugins/hls-tactics-plugin/src/Ide/Plugin/Tactic.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -23,6 +23,7 @@ import Data.Aeson
2323
import Data.Bifunctor (Bifunctor (bimap))
2424
import Data.Bool (bool)
2525
import Data.Data (Data)
26+
import Data.Foldable (for_)
2627
import Data.Generics.Aliases (mkQ)
2728
import Data.Generics.Schemes (everything)
2829
import Data.Maybe
@@ -144,6 +145,7 @@ mkWorkspaceEdits
144145
-> RunTacticResults
145146
-> Either ResponseError (Maybe WorkspaceEdit)
146147
mkWorkspaceEdits span dflags ccs uri pm rtr = do
148+
for_ (rtr_other_solns rtr) $ traceMX "other solution"
147149
let g = graftHole (RealSrcSpan span) rtr
148150
response = transform dflags ccs uri g pm
149151
in case response of

plugins/hls-tactics-plugin/src/Ide/Plugin/Tactic/CodeGen.hs

Lines changed: 31 additions & 44 deletions
Original file line numberDiff line numberDiff line change
@@ -7,14 +7,11 @@ module Ide.Plugin.Tactic.CodeGen
77
, module Ide.Plugin.Tactic.CodeGen.Utils
88
) where
99

10-
import Control.Lens ((%~), (+~), (<>~))
10+
import Control.Lens ((+~))
1111
import Control.Monad.Except
12-
import Control.Monad.State (MonadState)
13-
import Control.Monad.State.Class (modify)
14-
import Data.Generics.Product (field)
12+
import Data.Generics.Product (field)
1513
import Data.List
16-
import qualified Data.Map as M
17-
import qualified Data.Set as S
14+
import qualified Data.Set as S
1815
import Data.Traversable
1916
import DataCon
2017
import Development.IDE.GHC.Compat
@@ -29,32 +26,16 @@ import Ide.Plugin.Tactic.Judgements
2926
import Ide.Plugin.Tactic.Machinery
3027
import Ide.Plugin.Tactic.Naming
3128
import Ide.Plugin.Tactic.Types
32-
import Type hiding (Var)
29+
import Type hiding (Var)
3330

3431

35-
useOccName :: MonadState TacticState m => Judgement -> OccName -> m ()
36-
useOccName jdg name =
37-
-- Only score points if this is in the local hypothesis
38-
case M.lookup name $ hyByName $ jLocalHypothesis jdg of
39-
Just{} -> modify
40-
$ (withUsedVals $ S.insert name)
41-
. (field @"ts_unused_top_vals" %~ S.delete name)
42-
Nothing -> pure ()
43-
4432

4533
------------------------------------------------------------------------------
4634
-- | Doing recursion incurs a small penalty in the score.
4735
countRecursiveCall :: TacticState -> TacticState
4836
countRecursiveCall = field @"ts_recursion_count" +~ 1
4937

5038

51-
------------------------------------------------------------------------------
52-
-- | Insert some values into the unused top values field. These are
53-
-- subsequently removed via 'useOccName'.
54-
addUnusedTopVals :: MonadState TacticState m => S.Set OccName -> m ()
55-
addUnusedTopVals vals = modify $ field @"ts_unused_top_vals" <>~ vals
56-
57-
5839
destructMatches
5940
:: (DataCon -> Judgement -> Rule)
6041
-- ^ How to construct each match
@@ -63,7 +44,7 @@ destructMatches
6344
-> CType
6445
-- ^ Type being destructed
6546
-> Judgement
66-
-> RuleM (Trace, [RawMatch])
47+
-> RuleM (Synthesized [RawMatch])
6748
destructMatches f scrut t jdg = do
6849
let hy = jEntireHypothesis jdg
6950
g = jGoal jdg
@@ -76,16 +57,21 @@ destructMatches f scrut t jdg = do
7657
_ -> fmap unzipTrace $ for dcs $ \dc -> do
7758
let args = dataConInstOrigArgTys' dc apps
7859
names <- mkManyGoodNames (hyNamesInScope hy) args
79-
let hy' = zip names $ coerce args
80-
j = introducingPat scrut dc hy'
60+
let hy' = patternHypothesis scrut dc jdg
61+
$ zip names
62+
$ coerce args
63+
j = introduce hy'
8164
$ withNewGoal g jdg
82-
(tr, sg) <- f dc j
83-
modify $ withIntroducedVals $ mappend $ S.fromList names
84-
pure ( rose ("match " <> show dc <> " {" <>
65+
Synthesized tr sc uv sg <- f dc j
66+
pure
67+
$ Synthesized
68+
( rose ("match " <> show dc <> " {" <>
8569
intercalate ", " (fmap show names) <> "}")
86-
$ pure tr
87-
, match [mkDestructPat dc names] $ unLoc sg
88-
)
70+
$ pure tr)
71+
(sc <> hy')
72+
uv
73+
$ match [mkDestructPat dc names]
74+
$ unLoc sg
8975

9076

9177
------------------------------------------------------------------------------
@@ -114,10 +100,8 @@ infixifyPatIfNecessary dcon x
114100

115101

116102

117-
unzipTrace :: [(Trace, a)] -> (Trace, [a])
118-
unzipTrace l =
119-
let (trs, as) = unzip l
120-
in (rose mempty trs, as)
103+
unzipTrace :: [Synthesized a] -> Synthesized [a]
104+
unzipTrace = sequenceA
121105

122106

123107
-- | Essentially same as 'dataConInstOrigArgTys' in GHC,
@@ -154,16 +138,19 @@ destruct' :: (DataCon -> Judgement -> Rule) -> HyInfo CType -> Judgement -> Rule
154138
destruct' f hi jdg = do
155139
when (isDestructBlacklisted jdg) $ throwError NoApplicableTactic
156140
let term = hi_name hi
157-
useOccName jdg term
158-
(tr, ms)
141+
Synthesized tr sc uv ms
159142
<- destructMatches
160143
f
161144
(Just term)
162145
(hi_type hi)
163146
$ disallowing AlreadyDestructed [term] jdg
164-
pure ( rose ("destruct " <> show term) $ pure tr
165-
, noLoc $ case' (var' term) ms
166-
)
147+
pure
148+
$ Synthesized
149+
(rose ("destruct " <> show term) $ pure tr)
150+
sc
151+
(S.insert term uv)
152+
$ noLoc
153+
$ case' (var' term) ms
167154

168155

169156
------------------------------------------------------------------------------
@@ -186,10 +173,10 @@ buildDataCon
186173
:: Judgement
187174
-> DataCon -- ^ The data con to build
188175
-> [Type] -- ^ Type arguments for the data con
189-
-> RuleM (Trace, LHsExpr GhcPs)
176+
-> RuleM (Synthesized (LHsExpr GhcPs))
190177
buildDataCon jdg dc tyapps = do
191178
let args = dataConInstOrigArgTys' dc tyapps
192-
(tr, sgs)
179+
Synthesized tr sc uv sgs
193180
<- fmap unzipTrace
194181
$ traverse ( \(arg, n) ->
195182
newSubgoal
@@ -199,6 +186,6 @@ buildDataCon jdg dc tyapps = do
199186
$ CType arg
200187
) $ zip args [0..]
201188
pure
202-
. (rose (show dc) $ pure tr,)
189+
$ Synthesized (rose (show dc) $ pure tr) sc uv
203190
$ mkCon dc sgs
204191

plugins/hls-tactics-plugin/src/Ide/Plugin/Tactic/Judgements.hs

Lines changed: 32 additions & 58 deletions
Original file line numberDiff line numberDiff line change
@@ -1,33 +1,7 @@
11
{-# LANGUAGE TypeApplications #-}
22
{-# LANGUAGE ViewPatterns #-}
33

4-
module Ide.Plugin.Tactic.Judgements
5-
( blacklistingDestruct
6-
, unwhitelistingSplit
7-
, introducingLambda
8-
, introducingRecursively
9-
, introducingPat
10-
, jGoal
11-
, jHypothesis
12-
, jEntireHypothesis
13-
, jPatHypothesis
14-
, substJdg
15-
, unsetIsTopHole
16-
, filterSameTypeFromOtherPositions
17-
, isDestructBlacklisted
18-
, withNewGoal
19-
, jLocalHypothesis
20-
, isSplitWhitelisted
21-
, isPatternMatch
22-
, filterPosition
23-
, isTopHole
24-
, disallowing
25-
, mkFirstJudgement
26-
, hypothesisFromBindings
27-
, isTopLevel
28-
, hyNamesInScope
29-
, hyByName
30-
) where
4+
module Ide.Plugin.Tactic.Judgements where
315

326
import Control.Arrow
337
import Control.Lens hiding (Context)
@@ -89,35 +63,39 @@ withNewGoal :: a -> Judgement' a -> Judgement' a
8963
withNewGoal t = field @"_jGoal" .~ t
9064

9165

66+
introduce :: Hypothesis a -> Judgement' a -> Judgement' a
67+
introduce hy = field @"_jHypothesis" <>~ hy
68+
69+
9270
------------------------------------------------------------------------------
9371
-- | Helper function for implementing functions which introduce new hypotheses.
94-
introducing
95-
:: (Int -> Provenance) -- ^ A function from the position of the arg to its
96-
-- provenance.
72+
introduceHypothesis
73+
:: (Int -> Int -> Provenance)
74+
-- ^ A function from the total number of args and position of this arg
75+
-- to its provenance.
9776
-> [(OccName, a)]
98-
-> Judgement' a
99-
-> Judgement' a
100-
introducing f ns =
101-
field @"_jHypothesis" <>~ (Hypothesis $ zip [0..] ns <&>
102-
\(pos, (name, ty)) -> HyInfo name (f pos) ty)
77+
-> Hypothesis a
78+
introduceHypothesis f ns =
79+
Hypothesis $ zip [0..] ns <&> \(pos, (name, ty)) ->
80+
HyInfo name (f (length ns) pos) ty
10381

10482

10583
------------------------------------------------------------------------------
10684
-- | Introduce bindings in the context of a lamba.
107-
introducingLambda
85+
lambdaHypothesis
10886
:: Maybe OccName -- ^ The name of the top level function. For any other
10987
-- function, this should be 'Nothing'.
11088
-> [(OccName, a)]
111-
-> Judgement' a
112-
-> Judgement' a
113-
introducingLambda func = introducing $ \pos ->
114-
maybe UserPrv (\x -> TopLevelArgPrv x pos) func
89+
-> Hypothesis a
90+
lambdaHypothesis func =
91+
introduceHypothesis $ \count pos ->
92+
maybe UserPrv (\x -> TopLevelArgPrv x pos count) func
11593

11694

11795
------------------------------------------------------------------------------
11896
-- | Introduce a binding in a recursive context.
119-
introducingRecursively :: [(OccName, a)] -> Judgement' a -> Judgement' a
120-
introducingRecursively = introducing $ const RecursivePrv
97+
recursiveHypothesis :: [(OccName, a)] -> Hypothesis a
98+
recursiveHypothesis = introduceHypothesis $ const $ const RecursivePrv
12199

122100

123101
------------------------------------------------------------------------------
@@ -176,7 +154,7 @@ findPositionVal jdg defn pos = listToMaybe $ do
176154
-- ancstry through potentially disallowed terms in the hypothesis.
177155
(name, hi) <- M.toList $ M.map (overProvenance expandDisallowed) $ hyByName $ jEntireHypothesis jdg
178156
case hi_provenance hi of
179-
TopLevelArgPrv defn' pos'
157+
TopLevelArgPrv defn' pos' _
180158
| defn == defn'
181159
, pos == pos' -> pure name
182160
PatternMatchPrv pv
@@ -243,26 +221,22 @@ extremelyStupid__definingFunction =
243221
fst . head . ctxDefiningFuncs
244222

245223

246-
------------------------------------------------------------------------------
247-
-- | Pattern vals are currently tracked in jHypothesis, with an extra piece of
248-
-- data sitting around in jPatternVals.
249-
introducingPat
224+
patternHypothesis
250225
:: Maybe OccName
251226
-> DataCon
252-
-> [(OccName, a)]
253227
-> Judgement' a
254-
-> Judgement' a
255-
introducingPat scrutinee dc ns jdg
256-
= introducing (\pos ->
228+
-> [(OccName, a)]
229+
-> Hypothesis a
230+
patternHypothesis scrutinee dc jdg
231+
= introduceHypothesis $ \_ pos ->
257232
PatternMatchPrv $
258233
PatVal
259-
scrutinee
260-
(maybe mempty
261-
(\scrut -> S.singleton scrut <> getAncestry jdg scrut)
262-
scrutinee)
263-
(Uniquely dc)
264-
pos
265-
) ns jdg
234+
scrutinee
235+
(maybe mempty
236+
(\scrut -> S.singleton scrut <> getAncestry jdg scrut)
237+
scrutinee)
238+
(Uniquely dc)
239+
pos
266240

267241

268242
------------------------------------------------------------------------------

plugins/hls-tactics-plugin/src/Ide/Plugin/Tactic/KnownStrategies/QuickCheck.hs

Lines changed: 7 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -44,8 +44,13 @@ deriveArbitrary = do
4444
terminal_expr = mkVal "terminal"
4545
oneof_expr = mkVal "oneof"
4646
pure
47-
( tracePrim "deriveArbitrary"
48-
, noLoc $
47+
$ Synthesized (tracePrim "deriveArbitrary")
48+
-- TODO(sandy): This thing is not actually empty! We produced
49+
-- a bespoke binding "terminal", and a not-so-bespoke "n".
50+
-- But maybe it's fine for known rules?
51+
mempty
52+
mempty
53+
$ noLoc $
4954
let' [valBind (fromString "terminal") $ list $ fmap genExpr terminal] $
5055
appDollar (mkFunc "sized") $ lambda [bvar' (mkVarOcc "n")] $
5156
case' (infixCall "<=" (mkVal "n") (int 1))
@@ -57,7 +62,6 @@ deriveArbitrary = do
5762
(list $ fmap genExpr big)
5863
terminal_expr
5964
]
60-
)
6165
_ -> throwError $ GoalMismatch "deriveArbitrary" ty
6266

6367

plugins/hls-tactics-plugin/src/Ide/Plugin/Tactic/LanguageServer.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -197,7 +197,8 @@ getRhsPosVals rss tcs
197197
, isHole $ occName hole -- and the span is a hole
198198
-> First $ do
199199
patnames <- traverse getPatName ps
200-
pure $ zip patnames $ [0..] <&> TopLevelArgPrv name
200+
pure $ zip patnames $ [0..] <&> \n ->
201+
TopLevelArgPrv name n (length patnames)
201202
_ -> mempty
202203
) tcs
203204

0 commit comments

Comments
 (0)