Question about `compileToCoreModule`

Daniel F difrumin at gmail.com
Mon Aug 19 09:47:40 CEST 2013


Hi, everyone, I have a question about `compileToCoreModule` function from
the GHC module.

I noticed that the following code not just outputs the Core code, but also
produces object files and a linked executable (in case when 'test.hs' is a
program):

---------------------------
module Main where

import DynFlags
import GHC
import GHC.Paths
import MonadUtils
import Outputable

main = defaultErrorHandler defaultFatalMessager defaultFlushOut $ do
    runGhc (Just libdir) $ do
        dflags <- getSessionDynFlags
        setSessionDynFlags  dflags
        cm <- compileToCoreModule "test.hs"
        output cm

-- | Outputs any value that can be pretty-printed using the default style
output :: (GhcMonad m, MonadIO m) => Outputable a => a -> m ()
output a = do
    dfs <- getSessionDynFlags
    let style = defaultUserStyle
    let cntx = initSDocContext dfs style
    liftIO $ print $ runSDoc (ppr a) cntx
-----------------------------


I thought this was strange and looked up the source of
'compileToCoreModule', and indeed, it calls 'load LoadAllTargets'. 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.

NB: I tried setting `ghcLink' and `hscTarget' options in dynflags to
`NoLink' and `HscNothing' respectively, but that resulted in somewhat weird
Core:

$ cat test.hs
module Test (test) where

test :: Int
test = 123

test2 :: String
test2 = "Hi"

$ ./testcore
%module main:Test (Safe-Inferred) [(reF, Identifier `Test.test')]
Test.test :: GHC.Types.Int
[LclIdX]
Test.test = GHC.Types.I# 123

$ ./testcore-nolinknothing
%module main:Test (Safe-Inferred) []


Thanks.

-- 
Sincerely yours,
-- Daniil Frumin
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/ghc-devs/attachments/20130819/95d42b7a/attachment.htm>


More information about the ghc-devs mailing list