79305fcccb68c0af0011e84e08beb4dd4d82a184
[ghc-hetmet.git] / 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 {-# OPTIONS -w #-}
8 -- The above warning supression flag is a temporary kludge.
9 -- While working on this module you are encouraged to remove it and fix
10 -- any warnings in the module. See
11 --     http://hackage.haskell.org/trac/ghc/wiki/CodingStyle#Warnings
12 -- for details
13
14 module CodeOutput( codeOutput, outputForeignStubs ) where
15
16 #include "HsVersions.h"
17
18 #ifndef OMIT_NATIVE_CODEGEN
19 import UniqSupply       ( mkSplitUniqSupply )
20 import AsmCodeGen       ( nativeCodeGen )
21 #endif
22
23 #ifdef JAVA
24 import JavaGen          ( javaGen )
25 import qualified PrintJava
26 import OccurAnal        ( occurAnalyseBinds )
27 #endif
28
29 import Finder           ( mkStubPaths )
30 import PprC             ( writeCs )
31 import CmmLint          ( cmmLint )
32 import Packages
33 import PackageConfig    ( rtsPackageId )
34 import Util
35 import FastString       ( unpackFS )
36 import Cmm              ( RawCmm )
37 import HscTypes
38 import DynFlags
39
40 import ErrUtils         ( dumpIfSet_dyn, showPass, ghcExit )
41 import Outputable
42 import Pretty           ( Mode(..), printDoc )
43 import Module           ( Module, ModLocation(..), moduleName )
44 import List             ( nub )
45 import Maybes           ( firstJust )
46
47 import Distribution.Package     ( showPackageId )
48 import Directory        ( doesFileExist )
49 import Monad            ( when )
50 import IO
51 \end{code}
52
53 %************************************************************************
54 %*                                                                      *
55 \subsection{Steering}
56 %*                                                                      *
57 %************************************************************************
58
59 \begin{code}
60 codeOutput :: DynFlags
61            -> Module
62            -> ModLocation
63            -> ForeignStubs
64            -> [PackageId]
65            -> [RawCmm]                  -- Compiled C--
66            -> IO (Bool{-stub_h_exists-}, Bool{-stub_c_exists-})
67
68 codeOutput dflags this_mod location foreign_stubs pkg_deps flat_abstractC
69   = 
70     -- You can have C (c_output) or assembly-language (ncg_output),
71     -- but not both.  [Allowing for both gives a space leak on
72     -- flat_abstractC.  WDP 94/10]
73
74     -- Dunno if the above comment is still meaningful now.  JRS 001024.
75
76     do  { when (dopt Opt_DoCmmLinting dflags) $ do
77                 { showPass dflags "CmmLint"
78                 ; let lints = map cmmLint flat_abstractC
79                 ; case firstJust lints of
80                         Just err -> do { printDump err
81                                        ; ghcExit dflags 1
82                                        }
83                         Nothing  -> return ()
84                 }
85
86         ; showPass dflags "CodeOutput"
87         ; let filenm = hscOutName dflags 
88         ; stubs_exist <- outputForeignStubs dflags this_mod location foreign_stubs
89         ; case hscTarget dflags of {
90              HscInterpreted -> return ();
91              HscAsm         -> outputAsm dflags filenm flat_abstractC;
92              HscC           -> outputC dflags filenm this_mod location 
93                                  flat_abstractC stubs_exist pkg_deps
94                                  foreign_stubs;
95              HscJava        -> 
96 #ifdef JAVA
97                                outputJava dflags filenm mod_name tycons core_binds;
98 #else
99                                panic "Java support not compiled into this ghc";
100 #endif
101           }
102         ; return stubs_exist
103         }
104
105 doOutput :: String -> (Handle -> IO ()) -> IO ()
106 doOutput filenm io_action = bracket (openFile filenm WriteMode) hClose io_action
107 \end{code}
108
109
110 %************************************************************************
111 %*                                                                      *
112 \subsection{C}
113 %*                                                                      *
114 %************************************************************************
115
116 \begin{code}
117 outputC dflags filenm mod location flat_absC 
118         (stub_h_exists, _) packages foreign_stubs
119   = do 
120        -- figure out which header files to #include in the generated .hc file:
121        --
122        --   * extra_includes from packages
123        --   * -#include options from the cmdline and OPTIONS pragmas
124        --   * the _stub.h file, if there is one.
125        --
126        pkg_configs <- getPreloadPackagesAnd 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 (nub 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 stub_h) ++ "\"")
155           writeCs dflags h flat_absC
156   where
157     (_, stub_h) = mkStubPaths dflags (moduleName mod) location
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
174        {-# SCC "OutputAsm" #-} doOutput filenm $
175            \f -> {-# SCC "NativeCodeGen" #-}
176                  nativeCodeGen dflags f ncg_uniqs flat_absC
177   where
178
179 #else /* OMIT_NATIVE_CODEGEN */
180
181   = pprPanic "This compiler was built without a native code generator"
182              (text "Use -fvia-C instead")
183
184 #endif
185 \end{code}
186
187
188 %************************************************************************
189 %*                                                                      *
190 \subsection{Java}
191 %*                                                                      *
192 %************************************************************************
193
194 \begin{code}
195 #ifdef JAVA
196 outputJava dflags filenm mod tycons core_binds
197   = doOutput filenm (\ f -> printForUser f alwaysQualify pp_java)
198         -- User style printing for now to keep indentation
199   where
200     occ_anal_binds = occurAnalyseBinds core_binds
201         -- Make sure we have up to date dead-var information
202     java_code = javaGen mod [{- Should be imports-}] tycons occ_anal_binds
203     pp_java   = PrintJava.compilationUnit java_code
204 #endif
205 \end{code}
206
207
208 %************************************************************************
209 %*                                                                      *
210 \subsection{Foreign import/export}
211 %*                                                                      *
212 %************************************************************************
213
214 \begin{code}
215 outputForeignStubs :: DynFlags -> Module -> ModLocation -> ForeignStubs
216                    -> IO (Bool,         -- Header file created
217                           Bool)         -- C file created
218 outputForeignStubs dflags mod location stubs
219   | NoStubs <- stubs = do
220         -- When compiling External Core files, may need to use stub
221         -- files from a previous compilation
222         stub_c_exists <- doesFileExist stub_c
223         stub_h_exists <- doesFileExist stub_h
224         return (stub_h_exists, stub_c_exists)
225
226   | ForeignStubs h_code c_code _ <- stubs
227   = do
228         let
229             stub_c_output_d = pprCode CStyle c_code
230             stub_c_output_w = showSDoc stub_c_output_d
231         
232             -- Header file protos for "foreign export"ed functions.
233             stub_h_output_d = pprCode CStyle h_code
234             stub_h_output_w = showSDoc stub_h_output_d
235         -- in
236
237         createDirectoryHierarchy (directoryOf stub_c)
238
239         dumpIfSet_dyn dflags Opt_D_dump_foreign
240                       "Foreign export header file" stub_h_output_d
241
242         -- we need the #includes from the rts package for the stub files
243         let rts_includes = 
244                let rts_pkg = getPackageDetails (pkgState dflags) rtsPackageId in
245                concatMap mk_include (includes rts_pkg)
246             mk_include i = "#include \"" ++ i ++ "\"\n"
247
248         stub_h_file_exists
249            <- outputForeignStubs_help stub_h stub_h_output_w
250                 ("#include \"HsFFI.h\"\n" ++ cplusplus_hdr) cplusplus_ftr
251
252         dumpIfSet_dyn dflags Opt_D_dump_foreign
253                       "Foreign export stubs" stub_c_output_d
254
255         stub_c_file_exists
256            <- outputForeignStubs_help stub_c stub_c_output_w
257                 ("#define IN_STG_CODE 0\n" ++ 
258                  "#include \"Rts.h\"\n" ++
259                  rts_includes ++
260                  cplusplus_hdr)
261                  cplusplus_ftr
262            -- We're adding the default hc_header to the stub file, but this
263            -- isn't really HC code, so we need to define IN_STG_CODE==0 to
264            -- avoid the register variables etc. being enabled.
265
266         return (stub_h_file_exists, stub_c_file_exists)
267   where
268    (stub_c, stub_h) = mkStubPaths dflags (moduleName mod) location
269
270 cplusplus_hdr = "#ifdef __cplusplus\nextern \"C\" {\n#endif\n"
271 cplusplus_ftr = "#ifdef __cplusplus\n}\n#endif\n"
272
273 -- Don't use doOutput for dumping the f. export stubs
274 -- since it is more than likely that the stubs file will
275 -- turn out to be empty, in which case no file should be created.
276 outputForeignStubs_help fname ""      header footer = return False
277 outputForeignStubs_help fname doc_str header footer
278    = do writeFile fname (header ++ doc_str ++ '\n':footer ++ "\n")
279         return True
280 \end{code}
281