@@ -5,13 +5,11 @@ module Wingman.Machinery where
5
5
6
6
import Control.Applicative (empty )
7
7
import Control.Lens ((<>~) )
8
- import Control.Monad.Error.Class
9
8
import Control.Monad.Reader
10
9
import Control.Monad.State.Class (gets , modify , MonadState )
11
10
import Control.Monad.State.Strict (StateT (.. ), execStateT )
12
11
import Control.Monad.Trans.Maybe
13
12
import Data.Coerce
14
- import Data.Either
15
13
import Data.Foldable
16
14
import Data.Functor ((<&>) )
17
15
import Data.Generics (everything , gcount , mkQ )
@@ -96,20 +94,20 @@ runTactic ctx jdg t = do
96
94
res <- flip runReaderT ctx
97
95
. unExtractM
98
96
$ 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
102
100
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
105
103
case sorted of
106
- ((syn, (_, subgoals) ) : _) ->
104
+ ((Proof syn _ subgoals) : _) ->
107
105
Right $
108
106
RunTacticResults
109
107
{ rtr_trace = syn_trace syn
110
108
, 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
113
111
, rtr_jdg = jdg
114
112
, rtr_ctx = ctx
115
113
}
@@ -154,7 +152,7 @@ mappingExtract
154
152
-> TacticT jdg ext err s m a
155
153
mappingExtract f (TacticT m)
156
154
= TacticT $ StateT $ \ jdg ->
157
- mapExtract' f $ runStateT m jdg
155
+ mapExtract id f $ runStateT m jdg
158
156
159
157
160
158
------------------------------------------------------------------------------
@@ -227,7 +225,10 @@ unify goal inst = do
227
225
case tryUnifyUnivarsButNotSkolems skolems goal inst of
228
226
Just subst ->
229
227
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
231
232
232
233
233
234
------------------------------------------------------------------------------
@@ -254,26 +255,6 @@ attemptWhen _ t2 False = t2
254
255
attemptWhen t1 t2 True = commit t1 t2
255
256
256
257
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
-
277
258
------------------------------------------------------------------------------
278
259
-- | Run the given tactic iff the current hole contains no univars. Skolems and
279
260
-- already decided univars are OK though.
@@ -284,7 +265,7 @@ requireConcreteHole m = do
284
265
let vars = S. fromList $ tyCoVarsOfTypeWellScoped $ unCType $ jGoal jdg
285
266
case S. size $ vars S. \\ skolems of
286
267
0 -> m
287
- _ -> throwError TooPolymorphic
268
+ _ -> failure TooPolymorphic
288
269
289
270
290
271
------------------------------------------------------------------------------
@@ -317,7 +298,7 @@ useNameFromHypothesis f name = do
317
298
hy <- jHypothesis <$> goal
318
299
case M. lookup name $ hyByName hy of
319
300
Just hi -> f hi
320
- Nothing -> throwError $ NotInScope name
301
+ Nothing -> failure $ NotInScope name
321
302
322
303
------------------------------------------------------------------------------
323
304
-- | 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
326
307
useNameFromContext f name = do
327
308
lookupNameInContext name >>= \ case
328
309
Just ty -> f $ createImportedHyInfo name ty
329
- Nothing -> throwError $ NotInScope name
310
+ Nothing -> failure $ NotInScope name
330
311
331
312
332
313
------------------------------------------------------------------------------
@@ -340,12 +321,11 @@ lookupNameInContext name = do
340
321
341
322
342
323
getDefiningType
343
- :: (MonadError TacticError m , MonadReader Context m )
344
- => m CType
324
+ :: TacticsM CType
345
325
getDefiningType = do
346
326
calling_fun_name <- fst . head <$> asks ctxDefiningFuncs
347
327
maybe
348
- (throwError $ NotInScope calling_fun_name)
328
+ (failure $ NotInScope calling_fun_name)
349
329
pure
350
330
=<< lookupNameInContext calling_fun_name
351
331
@@ -403,7 +383,7 @@ getOccNameType
403
383
getOccNameType occ = do
404
384
getTyThing occ >>= \ case
405
385
Just (AnId v) -> pure $ varType v
406
- _ -> throwError $ NotInScope occ
386
+ _ -> failure $ NotInScope occ
407
387
408
388
409
389
getCurrentDefinitions :: TacticsM [(OccName , CType )]
0 commit comments