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