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