<div dir="ltr"><div><div><div><div>Hi, everyone, I have a question about `compileToCoreModule` function from the GHC module.<br><br></div>I noticed that the following code not just outputs the Core code, but also produces object files and a linked executable (in case when &#39;test.hs&#39; is a program):<br>
<br>---------------------------<br>module Main where<br><br>import DynFlags<br>import GHC<br>import GHC.Paths<br>import MonadUtils<br>import Outputable<br><br>main = defaultErrorHandler defaultFatalMessager defaultFlushOut $ do<br>
    runGhc (Just libdir) $ do<br>        dflags &lt;- getSessionDynFlags<br>        setSessionDynFlags  dflags<br>        cm &lt;- compileToCoreModule &quot;test.hs&quot;<br>        output cm<br><br>-- | Outputs any value that can be pretty-printed using the default style<br>
output :: (GhcMonad m, MonadIO m) =&gt; Outputable a =&gt; a -&gt; m ()<br>output a = do<br>    dfs &lt;- getSessionDynFlags<br>    let style = defaultUserStyle<br>    let cntx = initSDocContext dfs style<br>    liftIO $ print $ runSDoc (ppr a) cntx<br>
-----------------------------<br><br><br></div>I thought this was strange and looked up the source of &#39;compileToCoreModule&#39;, and indeed, it calls &#39;load LoadAllTargets&#39;. So my question is, why is it necessary to do so? I had the impression that compiling Haskell to Core is a step that precedes compiling to the actual binary.<br>
<br></div>NB: I tried setting `ghcLink&#39; and `hscTarget&#39; options in dynflags to `NoLink&#39; and `HscNothing&#39; respectively, but that resulted in somewhat weird Core:<br><br></div>$ cat test.hs<br clear="all"><div>
<div><div><div><div><div>module Test (test) where<br><br>test :: Int<br>test = 123<br><br>test2 :: String<br>test2 = &quot;Hi&quot;<br><br>$ ./testcore<br>%module main:Test (Safe-Inferred) [(reF, Identifier `Test.test&#39;)]<br>
Test.test :: <a href="http://GHC.Types.Int">GHC.Types.Int</a><br>[LclIdX]<br>Test.test = GHC.Types.I# 123<br><br></div><div>$ ./testcore-nolinknothing<br></div><div>%module main:Test (Safe-Inferred) []<br><br><br></div><div>
Thanks.<br><br></div><div>-- <br>Sincerely yours,<br>-- Daniil Frumin<br>
</div></div></div></div></div></div></div>