8.8.x change in lookupModule / findModule semantics?

Daniel Gröber dxld at darkboxed.org
Thu Feb 27 23:20:47 UTC 2020


Hi,

On Thu, Feb 27, 2020 at 08:37:12PM +0000, Tseen She wrote:
>       setTargets [Target (TargetFile "Main.hs" (Just $ Hsc HsSrcFile))
> False (Just (stringToStringBuffer buffer, t))]
>
> i.e. an explicit phase.
>
> I will just use Nothing in my TargetFile. Was this an intended change?

I found the reason for the change, my commit 0f9ec9d1ff ("Allow using
tagetContents for modules needing preprocessing") removes the special
casing in `preprocessFile` for in-memory buffers:

    -preprocessFile hsc_env src_fn mb_phase (Just (buf, _time))
    -  = do
    -        let dflags = hsc_dflags hsc_env
    -        let local_opts = getOptions dflags buf src_fn
    -
    -        (dflags', leftovers, warns)
    -            <- parseDynamicFilePragma dflags local_opts

It used to do a `parseDynamicFilePragma` which parses the LANGUAGE and
OPTIONS pragmas.

I think this change is actually for the better though, as this dflags
modification does not occur with a regular file, so we're actually being
more consistent.

I just tested this out and when setting the phase but not passing a buffer
8.6 will also fail to get the pragma in the ModSummary. When not giving an
explicit phase it works for 8.6, 8.8, with and without in-memory buffers
though. So I think that is the proper solution here, unless you can think
of a reason running the rest of the pipeline is a problem in this case?

On Thu, Feb 27, 2020 at 08:49:43PM +0000, Tseen She wrote:
> 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.

I would still like to reproduce your problem but I'm again not sure how
you're triggering it, this is what I have so far:

    -- $ ghc -package ghc -package ghc-paths FindModule.hs
    module Main where

    import GHC
    import GHC.Paths (libdir)
    import MonadUtils
    import DynFlags
    import Module

    main :: IO ()
    main = do
      defaultErrorHandler defaultFatalMessager defaultFlushOut $ do
        runGhc (Just libdir) $ do
          dflags0 <- getSessionDynFlags
          (dflags1, _, _)
              <- parseDynamicFlags dflags0 $ map noLoc ["-package", "base"]
          _ <- setSessionDynFlags dflags1

          setTargets [Target (TargetFile "Main.hs" Nothing) False Nothing]

          _ <- load LoadAllTargets

          m <- findModule (mkModuleName "Main") Nothing
          liftIO $ print $ (unitIdFS (moduleUnitId m), moduleNameFS (moduleName m))

Running it with 8.8 and 8.4 i get the same results:

    $ ghc-$ver -package ghc -package ghc-paths FindModule.hs
    $ echo 'main = return()' > Main.hs # a working file
    $ ./FindModule
    ("main","Main")

    $ echo '=' > Main.hs  # a syntax error
    $ ./FindModule
    Main.hs:1:1: error:
        parse error on input ‘=’
        Perhaps you need a 'let' in a 'do' block?
        e.g. 'let x = 5' instead of 'x = 5'
      |
    1 | =
      | ^
    <command line>: module is not loaded: ‘Main’ (Main.hs)

so this seems to be consistent?

--Daniel
-------------- next part --------------
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 833 bytes
Desc: not available
URL: <http://mail.haskell.org/pipermail/ghc-devs/attachments/20200228/9d0fd5d9/attachment.sig>


More information about the ghc-devs mailing list