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