[project @ 2005-03-07 16:46:08 by simonpj]
[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 DriverUtil       ( filenameOf )
31 import FastString       ( unpackFS )
32 import Cmm              ( Cmm )
33 import HscTypes
34 import CmdLineOpts
35 import ErrUtils         ( dumpIfSet_dyn, showPass, ghcExit )
36 import Outputable
37 import Pretty           ( Mode(..), printDoc )
38 import Module           ( Module )
39 import ListSetOps       ( removeDupsEq )
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            -> Dependencies
58            -> [Cmm]                     -- Compiled C--
59            -> IO (Bool{-stub_h_exists-}, Bool{-stub_c_exists-})
60
61 codeOutput dflags this_mod foreign_stubs 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 1
75                                        }
76                         Nothing  -> return ()
77                 }
78
79         ; showPass dflags "CodeOutput"
80         ; let filenm = dopt_OutName dflags 
81         ; stubs_exist <- outputForeignStubs dflags foreign_stubs
82         ; case dopt_HscTarget dflags of {
83              HscInterpreted -> return ();
84              HscAsm         -> outputAsm dflags filenm flat_abstractC;
85              HscC           -> outputC dflags filenm flat_abstractC stubs_exist
86                                         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, _) dependencies 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        let packages = dep_pkgs dependencies
126        pkg_configs <- getExplicitPackagesAnd dflags packages
127        let pkg_names = map (showPackageId.package) pkg_configs
128
129        c_includes <- getPackageCIncludes pkg_configs
130        let cmdline_includes = cmdlineHcIncludes dflags -- -#include options
131        
132            ffi_decl_headers 
133               = case foreign_stubs of
134                   NoStubs                 -> []
135                   ForeignStubs _ _ fdhs _ -> map unpackFS (fst (removeDupsEq fdhs))
136                         -- Remove duplicates, because distinct foreign import decls
137                         -- may cite the same #include.  Order doesn't matter.
138
139            all_headers =  c_includes
140                        ++ reverse cmdline_includes
141                        ++ ffi_decl_headers
142
143        let cc_injects = unlines (map mk_include all_headers)
144            mk_include h_file = 
145             case h_file of 
146                '"':_{-"-} -> "#include "++h_file
147                '<':_      -> "#include "++h_file
148                _          -> "#include \""++h_file++"\""
149
150        doOutput filenm $ \ h -> do
151           hPutStr h ("/* GHC_PACKAGES " ++ unwords pkg_names ++ "\n*/\n")
152           hPutStr h cc_injects
153           when stub_h_exists $ 
154              hPutStrLn h ("#include \"" ++ (filenameOf (hscStubHOutName dflags)) ++ "\"")
155           writeCs h flat_absC
156 \end{code}
157
158
159 %************************************************************************
160 %*                                                                      *
161 \subsection{Assembler}
162 %*                                                                      *
163 %************************************************************************
164
165 \begin{code}
166 outputAsm dflags filenm flat_absC
167
168 #ifndef OMIT_NATIVE_CODEGEN
169
170   = do ncg_uniqs <- mkSplitUniqSupply 'n'
171        ncg_output_d <- _scc_ "NativeCodeGen" 
172                           nativeCodeGen dflags flat_absC ncg_uniqs
173        dumpIfSet_dyn dflags Opt_D_dump_asm "Asm code" (docToSDoc ncg_output_d)
174        _scc_ "OutputAsm" doOutput filenm $
175            \f -> printDoc LeftMode f ncg_output_d
176   where
177
178 #else /* OMIT_NATIVE_CODEGEN */
179
180   = pprPanic "This compiler was built without a native code generator"
181              (text "Use -fvia-C instead")
182
183 #endif
184 \end{code}
185
186
187 %************************************************************************
188 %*                                                                      *
189 \subsection{Java}
190 %*                                                                      *
191 %************************************************************************
192
193 \begin{code}
194 #ifdef JAVA
195 outputJava dflags filenm mod tycons core_binds
196   = doOutput filenm (\ f -> printForUser f alwaysQualify pp_java)
197         -- User style printing for now to keep indentation
198   where
199     occ_anal_binds = occurAnalyseBinds core_binds
200         -- Make sure we have up to date dead-var information
201     java_code = javaGen mod [{- Should be imports-}] tycons occ_anal_binds
202     pp_java   = PrintJava.compilationUnit java_code
203 #endif
204 \end{code}
205
206
207 %************************************************************************
208 %*                                                                      *
209 \subsection{Ilx}
210 %*                                                                      *
211 %************************************************************************
212
213 \begin{code}
214 #ifdef ILX
215 outputIlx dflags filename mod tycons stg_binds
216   =  doOutput filename (\ f -> printForC f pp_ilx)
217   where
218     pp_ilx = ilxGen mod tycons stg_binds
219 #endif
220 \end{code}
221
222
223 %************************************************************************
224 %*                                                                      *
225 \subsection{Foreign import/export}
226 %*                                                                      *
227 %************************************************************************
228
229 \begin{code}
230 outputForeignStubs :: DynFlags -> ForeignStubs
231                    -> IO (Bool,         -- Header file created
232                           Bool)         -- C file created
233 outputForeignStubs dflags NoStubs = do
234 -- When compiling External Core files, may need to use stub files from a 
235 -- previous compilation
236    hFileExists <- doesFileExist (hscStubHOutName dflags)
237    cFileExists <- doesFileExist (hscStubCOutName dflags)
238    return (hFileExists, cFileExists)
239 outputForeignStubs dflags (ForeignStubs h_code c_code _ _)
240   = do
241         dumpIfSet_dyn dflags Opt_D_dump_foreign
242                       "Foreign export header file" stub_h_output_d
243
244         -- we need the #includes from the rts package for the stub files
245         let rtsid = rtsPackageId (pkgState dflags)
246             rts_includes 
247                 | ExtPackage pid <- rtsid = 
248                         let rts_pkg = getPackageDetails (pkgState dflags) pid in
249                         concatMap mk_include (includes rts_pkg)
250                 | otherwise = []
251             mk_include i = "#include \"" ++ i ++ "\"\n"
252
253         stub_h_file_exists
254            <- outputForeignStubs_help (hscStubHOutName dflags) stub_h_output_w
255                 ("#include \"HsFFI.h\"\n" ++ cplusplus_hdr) cplusplus_ftr
256
257         dumpIfSet_dyn dflags Opt_D_dump_foreign
258                       "Foreign export stubs" stub_c_output_d
259
260         stub_c_file_exists
261            <- outputForeignStubs_help (hscStubCOutName dflags) stub_c_output_w
262                 ("#define IN_STG_CODE 0\n" ++ 
263                  "#include \"Rts.h\"\n" ++
264                  rts_includes ++
265                  cplusplus_hdr)
266                  cplusplus_ftr
267            -- We're adding the default hc_header to the stub file, but this
268            -- isn't really HC code, so we need to define IN_STG_CODE==0 to
269            -- avoid the register variables etc. being enabled.
270
271         return (stub_h_file_exists, stub_c_file_exists)
272   where
273     -- C stubs for "foreign export"ed functions.
274     stub_c_output_d = pprCode CStyle c_code
275     stub_c_output_w = showSDoc stub_c_output_d
276
277     -- Header file protos for "foreign export"ed functions.
278     stub_h_output_d = pprCode CStyle h_code
279     stub_h_output_w = showSDoc stub_h_output_d
280
281 cplusplus_hdr = "#ifdef __cplusplus\nextern \"C\" {\n#endif\n"
282 cplusplus_ftr = "#ifdef __cplusplus\n}\n#endif\n"
283
284 -- Don't use doOutput for dumping the f. export stubs
285 -- since it is more than likely that the stubs file will
286 -- turn out to be empty, in which case no file should be created.
287 outputForeignStubs_help fname ""      header footer = return False
288 outputForeignStubs_help fname doc_str header footer
289    = do writeFile fname (header ++ doc_str ++ '\n':footer ++ "\n")
290         return True
291 \end{code}
292