5f7f395a29bc3f03f2fd6dfc2c45948ebe7b993c
[ghc-hetmet.git] / ghc / compiler / main / CodeOutput.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1993-1998
3 %
4 \section{Code output phase}
5
6 \begin{code}
7 module CodeOutput( codeOutput, outputForeignStubs ) where
8
9 #include "HsVersions.h"
10
11 #ifndef OMIT_NATIVE_CODEGEN
12 import UniqSupply       ( mkSplitUniqSupply )
13 import AsmCodeGen       ( nativeCodeGen )
14 #endif
15
16 #ifdef ILX
17 import IlxGen           ( ilxGen )
18 #endif
19
20 #ifdef JAVA
21 import JavaGen          ( javaGen )
22 import OccurAnal        ( occurAnalyseBinds )
23 import qualified PrintJava
24 import OccurAnal        ( occurAnalyseBinds )
25 #endif
26
27 import Distribution.Package     ( showPackageId )
28 import PprC             ( writeCs )
29 import CmmLint          ( cmmLint )
30 import Packages
31 import DriverUtil       ( filenameOf )
32 import FastString       ( unpackFS )
33 import Cmm              ( Cmm )
34 import HscTypes
35 import CmdLineOpts
36 import ErrUtils         ( dumpIfSet_dyn, showPass, ghcExit )
37 import Outputable
38 import Pretty           ( Mode(..), printDoc )
39 import Module           ( Module )
40 import ListSetOps       ( removeDupsEq )
41 import Maybes           ( firstJust )
42
43 import Directory        ( doesFileExist )
44 import Monad            ( when )
45 import IO
46 \end{code}
47
48 %************************************************************************
49 %*                                                                      *
50 \subsection{Steering}
51 %*                                                                      *
52 %************************************************************************
53
54 \begin{code}
55 codeOutput :: DynFlags
56            -> Module
57            -> ForeignStubs
58            -> Dependencies
59            -> [Cmm]                     -- Compiled C--
60            -> IO (Bool{-stub_h_exists-}, Bool{-stub_c_exists-})
61
62 codeOutput dflags this_mod foreign_stubs deps flat_abstractC
63   = 
64     -- You can have C (c_output) or assembly-language (ncg_output),
65     -- but not both.  [Allowing for both gives a space leak on
66     -- flat_abstractC.  WDP 94/10]
67
68     -- Dunno if the above comment is still meaningful now.  JRS 001024.
69
70     do  { when (dopt Opt_DoCmmLinting dflags) $ do
71                 { showPass dflags "CmmLint"
72                 ; let lints = map cmmLint flat_abstractC
73                 ; case firstJust lints of
74                         Just err -> do { printDump err
75                                        ; ghcExit 1
76                                        }
77                         Nothing  -> return ()
78                 }
79
80         ; showPass dflags "CodeOutput"
81         ; let filenm = dopt_OutName dflags 
82         ; stubs_exist <- outputForeignStubs dflags foreign_stubs
83         ; case dopt_HscTarget dflags of {
84              HscInterpreted -> return ();
85              HscAsm         -> outputAsm dflags filenm flat_abstractC;
86              HscC           -> outputC dflags filenm flat_abstractC stubs_exist
87                                         deps foreign_stubs;
88              HscJava        -> 
89 #ifdef JAVA
90                                outputJava dflags filenm mod_name tycons core_binds;
91 #else
92                                panic "Java support not compiled into this ghc";
93 #endif
94              HscILX         -> 
95 #ifdef ILX
96                                let tycons = typeEnvTyCons type_env in
97                                outputIlx dflags filenm mod_name tycons stg_binds;
98 #else
99                                panic "ILX support not compiled into this ghc";
100 #endif
101           }
102         ; return stubs_exist
103         }
104
105 doOutput :: String -> (Handle -> IO ()) -> IO ()
106 doOutput filenm io_action = bracket (openFile filenm WriteMode) hClose io_action
107 \end{code}
108
109
110 %************************************************************************
111 %*                                                                      *
112 \subsection{C}
113 %*                                                                      *
114 %************************************************************************
115
116 \begin{code}
117 outputC dflags filenm flat_absC 
118         (stub_h_exists, _) dependencies foreign_stubs
119   = do 
120        -- figure out which header files to #include in the generated .hc file:
121        --
122        --   * extra_includes from packages
123        --   * -#include options from the cmdline and OPTIONS pragmas
124        --   * the _stub.h file, if there is one.
125        --
126        let packages = dep_pkgs dependencies
127        pkg_configs <- getExplicitPackagesAnd dflags packages
128        let pkg_names = map (showPackageId.package) pkg_configs
129
130        c_includes <- getPackageCIncludes pkg_configs
131        let cmdline_includes = cmdlineHcIncludes dflags -- -#include options
132        
133            ffi_decl_headers 
134               = case foreign_stubs of
135                   NoStubs                 -> []
136                   ForeignStubs _ _ fdhs _ -> map unpackFS (fst (removeDupsEq fdhs))
137                         -- Remove duplicates, because distinct foreign import decls
138                         -- may cite the same #include.  Order doesn't matter.
139
140            all_headers =  c_includes
141                        ++ reverse cmdline_includes
142                        ++ ffi_decl_headers
143
144        let cc_injects = unlines (map mk_include all_headers)
145            mk_include h_file = 
146             case h_file of 
147                '"':_{-"-} -> "#include "++h_file
148                '<':_      -> "#include "++h_file
149                _          -> "#include \""++h_file++"\""
150
151        doOutput filenm $ \ h -> do
152           hPutStr h ("/* GHC_PACKAGES " ++ unwords pkg_names ++ "\n*/\n")
153           hPutStr h cc_injects
154           when stub_h_exists $ 
155              hPutStrLn h ("#include \"" ++ (filenameOf (hscStubHOutName dflags)) ++ "\"")
156           writeCs h flat_absC
157 \end{code}
158
159
160 %************************************************************************
161 %*                                                                      *
162 \subsection{Assembler}
163 %*                                                                      *
164 %************************************************************************
165
166 \begin{code}
167 outputAsm dflags filenm flat_absC
168
169 #ifndef OMIT_NATIVE_CODEGEN
170
171   = do ncg_uniqs <- mkSplitUniqSupply 'n'
172        ncg_output_d <- _scc_ "NativeCodeGen" 
173                           nativeCodeGen dflags flat_absC ncg_uniqs
174        dumpIfSet_dyn dflags Opt_D_dump_asm "Asm code" (docToSDoc ncg_output_d)
175        _scc_ "OutputAsm" doOutput filenm $
176            \f -> printDoc LeftMode f ncg_output_d
177   where
178
179 #else /* OMIT_NATIVE_CODEGEN */
180
181   = pprPanic "This compiler was built without a native code generator"
182              (text "Use -fvia-C instead")
183
184 #endif
185 \end{code}
186
187
188 %************************************************************************
189 %*                                                                      *
190 \subsection{Java}
191 %*                                                                      *
192 %************************************************************************
193
194 \begin{code}
195 #ifdef JAVA
196 outputJava dflags filenm mod tycons core_binds
197   = doOutput filenm (\ f -> printForUser f alwaysQualify pp_java)
198         -- User style printing for now to keep indentation
199   where
200     occ_anal_binds = occurAnalyseBinds core_binds
201         -- Make sure we have up to date dead-var information
202     java_code = javaGen mod [{- Should be imports-}] tycons occ_anal_binds
203     pp_java   = PrintJava.compilationUnit java_code
204 #endif
205 \end{code}
206
207
208 %************************************************************************
209 %*                                                                      *
210 \subsection{Ilx}
211 %*                                                                      *
212 %************************************************************************
213
214 \begin{code}
215 #ifdef ILX
216 outputIlx dflags filename mod tycons stg_binds
217   =  doOutput filename (\ f -> printForC f pp_ilx)
218   where
219     pp_ilx = ilxGen mod tycons stg_binds
220 #endif
221 \end{code}
222
223
224 %************************************************************************
225 %*                                                                      *
226 \subsection{Foreign import/export}
227 %*                                                                      *
228 %************************************************************************
229
230 \begin{code}
231 outputForeignStubs :: DynFlags -> ForeignStubs
232                    -> IO (Bool,         -- Header file created
233                           Bool)         -- C file created
234 outputForeignStubs dflags NoStubs = do
235 -- When compiling External Core files, may need to use stub files from a 
236 -- previous compilation
237    hFileExists <- doesFileExist (hscStubHOutName dflags)
238    cFileExists <- doesFileExist (hscStubCOutName dflags)
239    return (hFileExists, cFileExists)
240 outputForeignStubs dflags (ForeignStubs h_code c_code _ _)
241   = do
242         dumpIfSet_dyn dflags Opt_D_dump_foreign
243                       "Foreign export header file" stub_h_output_d
244
245         -- we need the #includes from the rts package for the stub files
246         let rtsid = rtsPackageId (pkgState dflags)
247             rts_includes 
248                 | ExtPackage pid <- rtsid = 
249                         let rts_pkg = getPackageDetails (pkgState dflags) pid in
250                         concatMap mk_include (includes rts_pkg)
251                 | otherwise = []
252             mk_include i = "#include \"" ++ i ++ "\"\n"
253
254         stub_h_file_exists
255            <- outputForeignStubs_help (hscStubHOutName dflags) stub_h_output_w
256                 ("#include \"HsFFI.h\"\n" ++ cplusplus_hdr) cplusplus_ftr
257
258         dumpIfSet_dyn dflags Opt_D_dump_foreign
259                       "Foreign export stubs" stub_c_output_d
260
261         stub_c_file_exists
262            <- outputForeignStubs_help (hscStubCOutName dflags) stub_c_output_w
263                 ("#define IN_STG_CODE 0\n" ++ 
264                  "#include \"Rts.h\"\n" ++
265                  rts_includes ++
266                  cplusplus_hdr)
267                  cplusplus_ftr
268            -- We're adding the default hc_header to the stub file, but this
269            -- isn't really HC code, so we need to define IN_STG_CODE==0 to
270            -- avoid the register variables etc. being enabled.
271
272         return (stub_h_file_exists, stub_c_file_exists)
273   where
274     -- C stubs for "foreign export"ed functions.
275     stub_c_output_d = pprCode CStyle c_code
276     stub_c_output_w = showSDoc stub_c_output_d
277
278     -- Header file protos for "foreign export"ed functions.
279     stub_h_output_d = pprCode CStyle h_code
280     stub_h_output_w = showSDoc stub_h_output_d
281
282 cplusplus_hdr = "#ifdef __cplusplus\nextern \"C\" {\n#endif\n"
283 cplusplus_ftr = "#ifdef __cplusplus\n}\n#endif\n"
284
285 -- Don't use doOutput for dumping the f. export stubs
286 -- since it is more than likely that the stubs file will
287 -- turn out to be empty, in which case no file should be created.
288 outputForeignStubs_help fname ""      header footer = return False
289 outputForeignStubs_help fname doc_str header footer
290    = do writeFile fname (header ++ doc_str ++ '\n':footer ++ "\n")
291         return True
292 \end{code}
293