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