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