11{-# LANGUAGE CPP #-}
22{-# LANGUAGE OverloadedStrings #-}
33{-# LANGUAGE RankNTypes #-}
4+ {-# LANGUAGE TupleSections #-}
45{-# LANGUAGE TypeFamilies #-}
56
67{-# LANGUAGE NoMonoLocalBinds #-}
@@ -43,6 +44,7 @@ import Development.IDE.Spans.LocalBindings (Bindings, getDefiningBindi
4344import qualified FastString
4445import GHC.Generics (Generic )
4546import Generics.SYB hiding (Generic )
47+ import GhcPlugins (extractModule )
4648import GhcPlugins (tupleDataCon , consDataCon , substTyAddInScope , ExternalPackageState , HscEnv (hsc_EPS ), unpackFS )
4749import qualified Ide.Plugin.Config as Plugin
4850import Ide.Plugin.Properties
@@ -57,13 +59,14 @@ import OccName
5759import Prelude hiding (span )
5860import Retrie (transformA )
5961import SrcLoc (containsSpan )
60- import TcRnTypes (tcg_binds , TcGblEnv )
62+ import TcRnTypes (tcg_binds , TcGblEnv ( tcg_rdr_env ) )
6163import Wingman.Context
6264import Wingman.FeatureSet
6365import Wingman.GHC
6466import Wingman.Judgements
6567import Wingman.Judgements.SYB (everythingContaining , metaprogramQ )
6668import Wingman.Judgements.Theta
69+ import Wingman.Metaprogramming.Lexer (ParserContext (.. ))
6770import Wingman.Range
6871import Wingman.StaticPlugin (pattern WingmanMetaprogram , pattern MetaprogramSyntax )
6972import Wingman.Types
@@ -576,6 +579,10 @@ mkWorkspaceEdits dflags ccs uri pm g = do
576579 in first (InfrastructureError . T. pack) response
577580
578581
582+ ------------------------------------------------------------------------------
583+ -- | Add ExactPrint annotations to every metaprogram in the source tree.
584+ -- Usually the ExactPrint module can do this for us, but we've enabled
585+ -- QuasiQuotes, so the round-trip print/parse journey will crash.
579586annotateMetaprograms :: Data a => a -> Transform a
580587annotateMetaprograms = everywhereM $ mkM $ \ case
581588 L ss (WingmanMetaprogram mp) -> do
@@ -585,6 +592,9 @@ annotateMetaprograms = everywhereM $ mkM $ \case
585592 pure x
586593 (x :: LHsExpr GhcPs ) -> pure x
587594
595+
596+ ------------------------------------------------------------------------------
597+ -- | Find the source of a tactic metaprogram at the given span.
588598getMetaprogramAtSpan
589599 :: Tracked age SrcSpan
590600 -> Tracked age TcGblEnv
@@ -596,3 +606,25 @@ getMetaprogramAtSpan (unTrack -> ss)
596606 . tcg_binds
597607 . unTrack
598608
609+
610+ ------------------------------------------------------------------------------
611+ -- | The metaprogram parser needs the ability to lookup terms from the module
612+ -- and imports. The 'ParserContext' contains everything we need to find that
613+ -- stuff.
614+ getParserState
615+ :: IdeState
616+ -> NormalizedFilePath
617+ -> Context
618+ -> MaybeT IO ParserContext
619+ getParserState state nfp ctx = do
620+ let stale a = runStaleIde " getParserState" state nfp a
621+
622+ TrackedStale (unTrack -> tcmod) _ <- stale TypeCheck
623+ TrackedStale (unTrack -> hscenv) _ <- stale GhcSessionDeps
624+
625+ let tcgblenv = tmrTypechecked tcmod
626+ modul = extractModule tcgblenv
627+ rdrenv = tcg_rdr_env tcgblenv
628+
629+ pure $ ParserContext (hscEnv hscenv) rdrenv modul ctx
630+
0 commit comments