1
1
module Stg.GHC.Backend where
2
2
3
3
-- Compiler
4
- import GHC
4
+ import GHC hiding ( Backend )
5
5
import GHC.Paths ( libdir )
6
6
import GHC.Platform ( platformOS , osSubsectionsViaSymbols )
7
7
import GHC.Driver.CodeOutput
@@ -10,11 +10,12 @@ import GHC.Driver.Main
10
10
import GHC.Driver.Phases
11
11
import GHC.Driver.Pipeline
12
12
import GHC.Driver.Session
13
- -- import GHC.Driver.Types
14
13
import GHC.Utils.Error
15
14
import GHC.Utils.Outputable
16
15
import GHC.Builtin.Names (rOOT_MAIN )
17
16
import GHC.Unit.State
17
+ import GHC.Types.Basic
18
+ import GHC.Types.HpcInfo
18
19
19
20
-- Stg Types
20
21
import GHC.Data.FastString
@@ -33,7 +34,7 @@ import GHC.Cmm
33
34
import GHC.Cmm.Info (cmmToRawCmm )
34
35
import GHC.StgToCmm (codeGen )
35
36
import GHC.Types.Unique.Supply ( mkSplitUniqSupply , initUs_ )
36
- import GHC.StgToCmm.Types ( CgInfos ( .. ))
37
+ import GHC.StgToCmm.Types
37
38
38
39
import Control.Monad.Trans
39
40
import Control.Monad
@@ -61,11 +62,11 @@ modl = rOOT_MAIN
61
62
data Backend = NCG | LLVM
62
63
63
64
64
- compileToObject :: Backend -> Unit -> ModuleName -> ForeignStubs -> [TyCon ] -> [StgTopBinding ] -> FilePath -> IO ()
65
+ compileToObject :: Backend -> Unit -> ModuleName -> C. ForeignStubs -> [TyCon ] -> [StgTopBinding ] -> FilePath -> IO ()
65
66
compileToObject backend unitId modName stubs tyCons topBinds_simple outputName = do
66
67
runGhc (Just libdir) $ compileToObjectM backend unitId modName stubs tyCons topBinds_simple outputName
67
68
68
- compileToObjectM :: Backend -> Unit -> ModuleName -> ForeignStubs -> [TyCon ] -> [StgTopBinding ] -> FilePath -> Ghc ()
69
+ compileToObjectM :: Backend -> Unit -> ModuleName -> C. ForeignStubs -> [TyCon ] -> [StgTopBinding ] -> FilePath -> Ghc ()
69
70
compileToObjectM backend unitId modName stubs tyCons topBinds_simple outputName = do
70
71
dflags <- getSessionDynFlags
71
72
@@ -103,7 +104,7 @@ compileToObjectM backend unitId modName stubs tyCons topBinds_simple outputName
103
104
-- Compile
104
105
dflags <- getSessionDynFlags
105
106
pkgs <- setSessionDynFlags $
106
- dflags { hscTarget = target, ghcLink = NoLink }
107
+ dflags { targetPlatform = target, ghcLink = NoLink }
107
108
`gopt_set` Opt_KeepSFiles
108
109
`gopt_set` Opt_KeepLlvmFiles
109
110
-- `dopt_set` Opt_D_dump_cmm
@@ -125,7 +126,7 @@ compileToObjectM backend unitId modName stubs tyCons topBinds_simple outputName
125
126
pure ()
126
127
127
128
128
- compileProgram :: Backend -> Bool -> [String ] -> [String ] -> [String ] -> [String ] -> ForeignStubs -> [TyCon ] -> [StgTopBinding ] -> IO ()
129
+ compileProgram :: Backend -> Bool -> [String ] -> [String ] -> [String ] -> [String ] -> C. ForeignStubs -> [TyCon ] -> [StgTopBinding ] -> IO ()
129
130
compileProgram backend noHsMain incPaths libPaths ldOpts clikeFiles stubs tyCons topBinds_simple = runGhc (Just libdir) $ do
130
131
dflags <- getSessionDynFlags
131
132
@@ -176,7 +177,7 @@ type CollectedCCs
176
177
setSessionDynFlags $
177
178
(if noHsMain then flip gopt_set Opt_NoHsMain else id ) $
178
179
dflags
179
- { hscTarget = target
180
+ { targetPlatform = target
180
181
, ghcLink = LinkBinary
181
182
, libraryPaths = libraryPaths dflags ++ libPaths
182
183
, ldInputs = ldInputs dflags ++ map Option ldOpts
@@ -220,12 +221,12 @@ newGen :: DynFlags
220
221
-> HscEnv
221
222
-> FilePath
222
223
-> Module
223
- -> ForeignStubs
224
+ -> C. ForeignStubs
224
225
-> [TyCon ]
225
226
-> CollectedCCs
226
227
-> [StgTopBinding ]
227
228
-> HpcInfo
228
- -> IO (FilePath , Maybe FilePath , [(ForeignSrcLang , FilePath )], CgInfos )
229
+ -> IO (FilePath , Maybe FilePath , [(ForeignSrcLang , FilePath )], CmmCgInfos )
229
230
newGen dflags hsc_env output_filename this_mod foreign_stubs data_tycons cost_centre_info stg_binds hpc_info = do
230
231
-- TODO: add these to parameters
231
232
let location = ModLocation
0 commit comments