@@ -9,9 +9,10 @@ module Wingman.Tactics
99import Control.Applicative (Alternative (empty ), (<|>) )
1010import Control.Lens ((&) , (%~) , (<>~) )
1111import Control.Monad (filterM , unless )
12+ import Control.Monad (when )
1213import Control.Monad.Extra (anyM )
1314import Control.Monad.Reader.Class (MonadReader (ask ))
14- import Control.Monad.State.Strict (StateT (.. ), runStateT )
15+ import Control.Monad.State.Strict (StateT (.. ), runStateT , execStateT )
1516import Data.Bool (bool )
1617import Data.Foldable
1718import Data.Functor ((<&>) )
@@ -640,3 +641,51 @@ hyDiff m = do
640641 g' <- unHypothesis . jEntireHypothesis <$> goal
641642 pure $ Hypothesis $ take (length g' - g_len) g'
642643
644+
645+ ------------------------------------------------------------------------------
646+ -- | Attempt to run the given tactic in "idiom bracket" mode. For example, if
647+ -- the current goal is
648+ --
649+ -- (_ :: [r])
650+ --
651+ -- then @idiom apply@ will remove the applicative context, resulting in a hole:
652+ --
653+ -- (_ :: r)
654+ --
655+ -- and then use @apply@ to solve it. Let's say this results in:
656+ --
657+ -- (f (_ :: a) (_ :: b))
658+ --
659+ -- Finally, @idiom@ lifts this back into the original applicative:
660+ --
661+ -- (f <$> (_ :: [a]) <*> (_ :: [b]))
662+ --
663+ -- Idiom will fail fast if the current goal doesn't have an applicative
664+ -- instance.
665+ idiom :: TacticsM () -> TacticsM ()
666+ idiom m = do
667+ jdg <- goal
668+ let hole = unCType $ jGoal jdg
669+ when (isFunction hole) $
670+ failure $ GoalMismatch " idiom" $ jGoal jdg
671+ case splitAppTy_maybe hole of
672+ Just (applic, ty) -> do
673+ minst <- getKnownInstance (mkClsOcc " Applicative" )
674+ . pure
675+ $ applic
676+ case minst of
677+ Nothing -> failure $ GoalMismatch " idiom" $ CType applic
678+ Just (_, _) -> do
679+ rule $ \ jdg -> do
680+ expr <- subgoalWith (withNewGoal (CType ty) jdg) m
681+ case unLoc $ syn_val expr of
682+ HsApp {} -> pure $ fmap idiomize expr
683+ RecordCon {} -> pure $ fmap idiomize expr
684+ _ -> unsolvable $ GoalMismatch " idiom" $ jGoal jdg
685+ rule $ newSubgoal . withModifiedGoal (CType . mkAppTy applic . unCType)
686+ Nothing ->
687+ failure $ GoalMismatch " idiom" $ jGoal jdg
688+
689+ subgoalWith :: Judgement -> TacticsM () -> RuleM (Synthesized (LHsExpr GhcPs ))
690+ subgoalWith jdg t = RuleT $ flip execStateT jdg $ unTacticT t
691+
0 commit comments