<div dir="ltr"><div>Additionally, now that importsOnly is working for me on 8.8.x I can use lookupModule on *that* instead of the original module file, and then I can make use of the newly exposed modInfoRdrEnv thus answering my second thread's question too.<br></div><div><br></div><div>It is, however, a shame that lookupModule seems to require the entire file to parse / typecheck. That also smells like a regression, but not one that impacts me anymore.</div><div><br></div></div><br><div class="gmail_quote"><div dir="ltr" class="gmail_attr">On Thu, 27 Feb 2020 at 20:37, Tseen She <<a href="mailto:ts33n.sh3@gmail.com">ts33n.sh3@gmail.com</a>> wrote:<br></div><blockquote class="gmail_quote" style="margin:0px 0px 0px 0.8ex;border-left:1px solid rgb(204,204,204);padding-left:1ex"><div dir="ltr"><div dir="ltr"><div>Bingo!</div><div><br></div><div>      setTargets [Target (TargetFile "Main.hs" (Just $ Hsc HsSrcFile)) False (Just (stringToStringBuffer buffer, t))]<br></div><div><br></div><div>i.e. an explicit phase.</div><div><br></div><div>I will just use Nothing in my TargetFile. Was this an intended change?<br></div></div><br><div class="gmail_quote"><div dir="ltr" class="gmail_attr">On Thu, 27 Feb 2020 at 18:13, Daniel Gröber <<a href="mailto:dxld@darkboxed.org" target="_blank">dxld@darkboxed.org</a>> wrote:<br></div><blockquote class="gmail_quote" style="margin:0px 0px 0px 0.8ex;border-left:1px solid rgb(204,204,204);padding-left:1ex">Hi,<br>
<br>
On Thu, Feb 27, 2020 at 03:43:35PM +0000, Tseen She wrote:<br>
> Sorry for the spam, but I think this is definitely a bug/regression in<br>
> ghc-8.8.1 (still present in 8.8.3).<br>
<br>
No worries<br>
<br>
> I don't know which commit introduced the problem, but it seems that<br>
> getModSummary is no longer reporting the correct ms_hspp_opts, at least for<br>
> an in-memory file but it could also be for a file on disk as well (I<br>
> haven't excluded that as a possibility).<br>
<br>
On a quick testcase I cannot reproduce this behaviour:<br>
<br>
    -- $ ghc -package ghc -package ghc-paths TargetContents.hs<br>
    module Main where<br>
<br>
    import GHC<br>
    import GHC.Paths (libdir)<br>
    import MonadUtils<br>
    import DynFlags<br>
    import StringBuffer<br>
    import Data.Time.Clock<br>
<br>
    main :: IO ()<br>
    main = do<br>
      defaultErrorHandler defaultFatalMessager defaultFlushOut $ do<br>
        runGhc (Just libdir) $ do<br>
          dflags0 <- getSessionDynFlags<br>
          (dflags1, _, _)<br>
              <- parseDynamicFlags dflags0 $ map noLoc ["-package", "base"]<br>
          _ <- setSessionDynFlags dflags1<br>
<br>
          t <- liftIO getCurrentTime<br>
          setTargets [Target (TargetFile "Main.hs" Nothing) False (Just (stringToStringBuffer buffer, t)) ]<br>
<br>
          _ <- depanal [] False<br>
<br>
          ms <- getModSummary (mkModuleName "Main")<br>
          pm <- parseModule ms<br>
<br>
          liftIO $ print $ extensions $ ms_hspp_opts ms<br>
<br>
          _ <- typecheckModule pm<br>
<br>
          return ()<br>
<br>
    buffer = "{-# LANGUAGE PackageImports #-}\nimport \"base\" Data.List\nmain = return ()"<br>
<br>
Running it it prints the PackageImports ext from the in-memory buffer just<br>
fine:<br>
<br>
    $ ghc-8.8.1 -package ghc -package ghc-paths TargetContents.hs<br>
    $ ./TargetContents<br>
    [On PackageImports]<br>
<br>
One change in behaviour to note is that when doing this with <8.8 we first<br>
need to create the Main.hs file so GHC doesn't complain about it missing.<br>
<br>
Maybe you can fiddle with the test case until it reflects what you're<br>
doing?<br>
<br>
--Daniel<br>
</blockquote></div></div>
</blockquote></div>