Skip to content

Commit 92e4bad

Browse files
authored
Upgrade to refinery-0.4.0.0 (#2021)
* Upgrade refinery versions * Get everything compiling against refinery v4 * Don't use UnderlyingState * Every test is fucked * Update tests
1 parent e190a0e commit 92e4bad

File tree

69 files changed

+295
-237
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

69 files changed

+295
-237
lines changed

Diff for: plugins/hls-tactics-plugin/hls-tactics-plugin.cabal

+1-1
Original file line numberDiff line numberDiff line change
@@ -87,7 +87,7 @@ library
8787
, mtl
8888
, parser-combinators
8989
, prettyprinter
90-
, refinery ^>=0.3
90+
, refinery ^>=0.4
9191
, retrie >=0.1.1.0
9292
, syb
9393
, text

Diff for: plugins/hls-tactics-plugin/src/Wingman/CodeGen.hs

+5-5
Original file line numberDiff line numberDiff line change
@@ -59,7 +59,7 @@ destructMatches use_field_puns f scrut t jdg = do
5959
let hy = jEntireHypothesis jdg
6060
g = jGoal jdg
6161
case tacticsGetDataCons $ unCType t of
62-
Nothing -> throwError $ GoalMismatch "destruct" g
62+
Nothing -> cut -- throwError $ GoalMismatch "destruct" g
6363
Just (dcs, apps) ->
6464
fmap unzipTrace $ for dcs $ \dc -> do
6565
let con = RealDataCon dc
@@ -214,7 +214,7 @@ patSynExTys ps = patSynExTyVars ps
214214

215215
destruct' :: Bool -> (ConLike -> Judgement -> Rule) -> HyInfo CType -> Judgement -> Rule
216216
destruct' use_field_puns f hi jdg = do
217-
when (isDestructBlacklisted jdg) $ throwError NoApplicableTactic
217+
when (isDestructBlacklisted jdg) $ cut -- throwError NoApplicableTactic
218218
let term = hi_name hi
219219
ext
220220
<- destructMatches
@@ -234,13 +234,13 @@ destruct' use_field_puns f hi jdg = do
234234
-- resulting matches.
235235
destructLambdaCase' :: Bool -> (ConLike -> Judgement -> Rule) -> Judgement -> Rule
236236
destructLambdaCase' use_field_puns f jdg = do
237-
when (isDestructBlacklisted jdg) $ throwError NoApplicableTactic
237+
when (isDestructBlacklisted jdg) $ cut -- throwError NoApplicableTactic
238238
let g = jGoal jdg
239239
case splitFunTy_maybe (unCType g) of
240240
Just (arg, _) | isAlgType arg ->
241241
fmap (fmap noLoc lambdaCase) <$>
242242
destructMatches use_field_puns f Nothing (CType arg) jdg
243-
_ -> throwError $ GoalMismatch "destructLambdaCase'" g
243+
_ -> cut -- throwError $ GoalMismatch "destructLambdaCase'" g
244244

245245

246246
------------------------------------------------------------------------------
@@ -267,7 +267,7 @@ buildDataCon should_blacklist jdg dc tyapps = do
267267
--
268268
-- Fortunately, this isn't an issue in practice, since 'PatSyn's are
269269
-- never in the hypothesis.
270-
throwError $ TacticPanic "Can't build Pattern constructors yet"
270+
cut -- throwError $ TacticPanic "Can't build Pattern constructors yet"
271271
ext
272272
<- fmap unzipTrace
273273
$ traverse ( \(arg, n) ->

Diff for: plugins/hls-tactics-plugin/src/Wingman/KnownStrategies.hs

+1-2
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,5 @@
11
module Wingman.KnownStrategies where
22

3-
import Control.Monad.Error.Class
43
import Data.Foldable (for_)
54
import OccName (mkVarOcc, mkClsOcc)
65
import Refinery.Tactic
@@ -26,7 +25,7 @@ known name t = do
2625
getCurrentDefinitions >>= \case
2726
[(def, _)] | def == mkVarOcc name ->
2827
tracing ("known " <> name) t
29-
_ -> throwError NoApplicableTactic
28+
_ -> failure NoApplicableTactic
3029

3130

3231
deriveFmap :: TacticsM ()

Diff for: plugins/hls-tactics-plugin/src/Wingman/KnownStrategies/QuickCheck.hs

+2-3
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,6 @@
11
module Wingman.KnownStrategies.QuickCheck where
22

33
import ConLike (ConLike(RealDataCon))
4-
import Control.Monad.Except (MonadError (throwError))
54
import Data.Bool (bool)
65
import Data.Generics (everything, mkQ)
76
import Data.List (partition)
@@ -15,7 +14,7 @@ import GHC.SourceGen.Expr (case', lambda, let')
1514
import GHC.SourceGen.Overloaded (App ((@@)), HasList (list))
1615
import GHC.SourceGen.Pat (conP)
1716
import OccName (HasOccName (occName), mkVarOcc, occNameString)
18-
import Refinery.Tactic (goal, rule)
17+
import Refinery.Tactic (goal, rule, failure)
1918
import TyCon (TyCon, tyConDataCons, tyConName)
2019
import Type (splitTyConApp_maybe)
2120
import Wingman.CodeGen
@@ -61,7 +60,7 @@ deriveArbitrary = do
6160
(list $ fmap genExpr big)
6261
terminal_expr
6362
]
64-
_ -> throwError $ GoalMismatch "deriveArbitrary" ty
63+
_ -> failure $ GoalMismatch "deriveArbitrary" ty
6564

6665

6766
------------------------------------------------------------------------------

Diff for: plugins/hls-tactics-plugin/src/Wingman/Machinery.hs

+19-39
Original file line numberDiff line numberDiff line change
@@ -5,13 +5,11 @@ module Wingman.Machinery where
55

66
import Control.Applicative (empty)
77
import Control.Lens ((<>~))
8-
import Control.Monad.Error.Class
98
import Control.Monad.Reader
109
import Control.Monad.State.Class (gets, modify, MonadState)
1110
import Control.Monad.State.Strict (StateT (..), execStateT)
1211
import Control.Monad.Trans.Maybe
1312
import Data.Coerce
14-
import Data.Either
1513
import Data.Foldable
1614
import Data.Functor ((<&>))
1715
import Data.Generics (everything, gcount, mkQ)
@@ -96,20 +94,20 @@ runTactic ctx jdg t = do
9694
res <- flip runReaderT ctx
9795
. unExtractM
9896
$ runTacticT t jdg tacticState
99-
pure $ case partitionEithers res of
100-
(errs, []) -> Left $ take 50 errs
101-
(_, fmap assoc23 -> solns) -> do
97+
pure $ case res of
98+
(Left errs) -> Left $ take 50 errs
99+
(Right solns) -> do
102100
let sorted =
103-
flip sortBy solns $ comparing $ \(ext, (_, holes)) ->
104-
Down $ scoreSolution ext jdg holes
101+
flip sortBy solns $ comparing $ \(Proof ext _ holes) ->
102+
Down $ scoreSolution ext jdg $ fmap snd holes
105103
case sorted of
106-
((syn, (_, subgoals)) : _) ->
104+
((Proof syn _ subgoals) : _) ->
107105
Right $
108106
RunTacticResults
109107
{ rtr_trace = syn_trace syn
110108
, rtr_extract = simplify $ syn_val syn
111-
, rtr_subgoals = subgoals
112-
, rtr_other_solns = reverse . fmap fst $ sorted
109+
, rtr_subgoals = fmap snd subgoals
110+
, rtr_other_solns = reverse . fmap pf_extract $ sorted
113111
, rtr_jdg = jdg
114112
, rtr_ctx = ctx
115113
}
@@ -154,7 +152,7 @@ mappingExtract
154152
-> TacticT jdg ext err s m a
155153
mappingExtract f (TacticT m)
156154
= TacticT $ StateT $ \jdg ->
157-
mapExtract' f $ runStateT m jdg
155+
mapExtract id f $ runStateT m jdg
158156

159157

160158
------------------------------------------------------------------------------
@@ -227,7 +225,10 @@ unify goal inst = do
227225
case tryUnifyUnivarsButNotSkolems skolems goal inst of
228226
Just subst ->
229227
modify $ updateSubst subst
230-
Nothing -> throwError (UnificationError inst goal)
228+
Nothing -> cut -- failure (UnificationError inst goal)
229+
230+
cut :: RuleT jdg ext err s m a
231+
cut = RuleT Empty
231232

232233

233234
------------------------------------------------------------------------------
@@ -254,26 +255,6 @@ attemptWhen _ t2 False = t2
254255
attemptWhen t1 t2 True = commit t1 t2
255256

256257

257-
------------------------------------------------------------------------------
258-
-- | Mystical time-traveling combinator for inspecting the extracts produced by
259-
-- a tactic. We can use it to guard that extracts match certain predicates, for
260-
-- example.
261-
--
262-
-- Note, that this thing is WEIRD. To illustrate:
263-
--
264-
-- @@
265-
-- peek f
266-
-- blah
267-
-- @@
268-
--
269-
-- Here, @f@ can inspect the extract _produced by @blah@,_ which means the
270-
-- causality appears to go backwards.
271-
--
272-
-- 'peek' should be exposed directly by @refinery@ in the next release.
273-
peek :: (ext -> TacticT jdg ext err s m ()) -> TacticT jdg ext err s m ()
274-
peek k = tactic $ \j -> Subgoal ((), j) $ \e -> proofState (k e) j
275-
276-
277258
------------------------------------------------------------------------------
278259
-- | Run the given tactic iff the current hole contains no univars. Skolems and
279260
-- already decided univars are OK though.
@@ -284,7 +265,7 @@ requireConcreteHole m = do
284265
let vars = S.fromList $ tyCoVarsOfTypeWellScoped $ unCType $ jGoal jdg
285266
case S.size $ vars S.\\ skolems of
286267
0 -> m
287-
_ -> throwError TooPolymorphic
268+
_ -> failure TooPolymorphic
288269

289270

290271
------------------------------------------------------------------------------
@@ -317,7 +298,7 @@ useNameFromHypothesis f name = do
317298
hy <- jHypothesis <$> goal
318299
case M.lookup name $ hyByName hy of
319300
Just hi -> f hi
320-
Nothing -> throwError $ NotInScope name
301+
Nothing -> failure $ NotInScope name
321302

322303
------------------------------------------------------------------------------
323304
-- | Lift a function over 'HyInfo's to one that takes an 'OccName' and tries to
@@ -326,7 +307,7 @@ useNameFromContext :: (HyInfo CType -> TacticsM a) -> OccName -> TacticsM a
326307
useNameFromContext f name = do
327308
lookupNameInContext name >>= \case
328309
Just ty -> f $ createImportedHyInfo name ty
329-
Nothing -> throwError $ NotInScope name
310+
Nothing -> failure $ NotInScope name
330311

331312

332313
------------------------------------------------------------------------------
@@ -340,12 +321,11 @@ lookupNameInContext name = do
340321

341322

342323
getDefiningType
343-
:: (MonadError TacticError m, MonadReader Context m)
344-
=> m CType
324+
:: TacticsM CType
345325
getDefiningType = do
346326
calling_fun_name <- fst . head <$> asks ctxDefiningFuncs
347327
maybe
348-
(throwError $ NotInScope calling_fun_name)
328+
(failure $ NotInScope calling_fun_name)
349329
pure
350330
=<< lookupNameInContext calling_fun_name
351331

@@ -403,7 +383,7 @@ getOccNameType
403383
getOccNameType occ = do
404384
getTyThing occ >>= \case
405385
Just (AnId v) -> pure $ varType v
406-
_ -> throwError $ NotInScope occ
386+
_ -> failure $ NotInScope occ
407387

408388

409389
getCurrentDefinitions :: TacticsM [(OccName, CType)]

Diff for: plugins/hls-tactics-plugin/src/Wingman/Metaprogramming/Parser.hs

+4-4
Original file line numberDiff line numberDiff line change
@@ -7,10 +7,12 @@
77
module Wingman.Metaprogramming.Parser where
88

99
import qualified Control.Monad.Combinators.Expr as P
10-
import qualified Control.Monad.Error.Class as E
1110
import Data.Functor
1211
import Data.Maybe (listToMaybe)
1312
import qualified Data.Text as T
13+
import Development.IDE.GHC.Compat (RealSrcLoc, srcLocLine, srcLocCol, srcLocFile)
14+
import FastString (unpackFS)
15+
import Refinery.Tactic (failure)
1416
import qualified Refinery.Tactic as R
1517
import qualified Text.Megaparsec as P
1618
import Wingman.Auto
@@ -20,8 +22,6 @@ import Wingman.Metaprogramming.Parser.Documentation
2022
import Wingman.Metaprogramming.ProofState (proofState, layout)
2123
import Wingman.Tactics
2224
import Wingman.Types
23-
import Development.IDE.GHC.Compat (RealSrcLoc, srcLocLine, srcLocCol, srcLocFile)
24-
import FastString (unpackFS)
2525

2626

2727
nullary :: T.Text -> TacticsM () -> Parser (TacticsM ())
@@ -296,7 +296,7 @@ commands =
296296
( pure $
297297
fmap listToMaybe getCurrentDefinitions >>= \case
298298
Just (self, _) -> useNameFromContext (apply Saturated) self
299-
Nothing -> E.throwError $ TacticPanic "no defining function"
299+
Nothing -> failure $ TacticPanic "no defining function"
300300
)
301301
[ Example
302302
(Just "In the context of `foo (a :: Int) (b :: b) = _`:")

0 commit comments

Comments
 (0)