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