refactoring only: use the parameterised InstalledPackageInfo
[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/Commentary/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 Util
34 import FastString       ( unpackFS )
35 import Cmm              ( RawCmm )
36 import HscTypes
37 import DynFlags
38
39 import ErrUtils         ( dumpIfSet_dyn, showPass, ghcExit )
40 import Outputable
41 import Pretty           ( Mode(..), printDoc )
42 import Module
43 import List             ( nub )
44 import Maybes           ( firstJust )
45
46 import Distribution.Package     ( showPackageId )
47 import Directory        ( doesFileExist )
48 import Monad            ( when )
49 import IO
50 \end{code}
51
52 %************************************************************************
53 %*                                                                      *
54 \subsection{Steering}
55 %*                                                                      *
56 %************************************************************************
57
58 \begin{code}
59 codeOutput :: DynFlags
60            -> Module
61            -> ModLocation
62            -> ForeignStubs
63            -> [PackageId]
64            -> [RawCmm]                  -- Compiled C--
65            -> IO (Bool{-stub_h_exists-}, Bool{-stub_c_exists-})
66
67 codeOutput dflags this_mod location foreign_stubs pkg_deps flat_abstractC
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           }
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 mod location flat_absC 
117         (stub_h_exists, _) packages 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        pkg_configs <- getPreloadPackagesAnd dflags packages
126        let pkg_names = map (showPackageId.package) pkg_configs
127
128        c_includes <- getPackageCIncludes pkg_configs
129        let cmdline_includes = cmdlineHcIncludes dflags -- -#include options
130        
131            ffi_decl_headers 
132               = case foreign_stubs of
133                   NoStubs               -> []
134                   ForeignStubs _ _ fdhs -> map unpackFS (nub fdhs)
135                         -- Remove duplicates, because distinct foreign import decls
136                         -- may cite the same #include.  Order doesn't matter.
137
138            all_headers =  c_includes
139                        ++ reverse cmdline_includes
140                        ++ ffi_decl_headers
141                        
142        let cc_injects = unlines (map mk_include all_headers)
143            mk_include h_file = 
144             case h_file of 
145                '"':_{-"-} -> "#include "++h_file
146                '<':_      -> "#include "++h_file
147                _          -> "#include \""++h_file++"\""
148
149        doOutput filenm $ \ h -> do
150           hPutStr h ("/* GHC_PACKAGES " ++ unwords pkg_names ++ "\n*/\n")
151           hPutStr h cc_injects
152           when stub_h_exists $ 
153              hPutStrLn h ("#include \"" ++ inc_stub_h ++ "\"")
154           writeCs dflags h flat_absC
155   where
156     (_, _, inc_stub_h) = mkStubPaths dflags (moduleName mod) location
157 \end{code}
158
159
160 %************************************************************************
161 %*                                                                      *
162 \subsection{Assembler}
163 %*                                                                      *
164 %************************************************************************
165
166 \begin{code}
167 outputAsm dflags filenm flat_absC
168
169 #ifndef OMIT_NATIVE_CODEGEN
170
171   = do ncg_uniqs <- mkSplitUniqSupply 'n'
172
173        {-# SCC "OutputAsm" #-} doOutput filenm $
174            \f -> {-# SCC "NativeCodeGen" #-}
175                  nativeCodeGen dflags f ncg_uniqs flat_absC
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{Foreign import/export}
210 %*                                                                      *
211 %************************************************************************
212
213 \begin{code}
214 outputForeignStubs :: DynFlags -> Module -> ModLocation -> ForeignStubs
215                    -> IO (Bool,         -- Header file created
216                           Bool)         -- C file created
217 outputForeignStubs dflags mod location stubs
218   | NoStubs <- stubs = do
219         -- When compiling External Core files, may need to use stub
220         -- files from a previous compilation
221         stub_c_exists <- doesFileExist stub_c
222         stub_h_exists <- doesFileExist stub_h
223         return (stub_h_exists, stub_c_exists)
224
225   | ForeignStubs h_code c_code _ <- stubs
226   = do
227         let
228             stub_c_output_d = pprCode CStyle c_code
229             stub_c_output_w = showSDoc stub_c_output_d
230         
231             -- Header file protos for "foreign export"ed functions.
232             stub_h_output_d = pprCode CStyle h_code
233             stub_h_output_w = showSDoc stub_h_output_d
234         -- in
235
236         createDirectoryHierarchy (directoryOf stub_c)
237
238         dumpIfSet_dyn dflags Opt_D_dump_foreign
239                       "Foreign export header file" stub_h_output_d
240
241         -- we need the #includes from the rts package for the stub files
242         let rts_includes = 
243                let rts_pkg = getPackageDetails (pkgState dflags) rtsPackageId in
244                concatMap mk_include (includes rts_pkg)
245             mk_include i = "#include \"" ++ i ++ "\"\n"
246
247         stub_h_file_exists
248            <- outputForeignStubs_help stub_h stub_h_output_w
249                 ("#include \"HsFFI.h\"\n" ++ cplusplus_hdr) cplusplus_ftr
250
251         dumpIfSet_dyn dflags Opt_D_dump_foreign
252                       "Foreign export stubs" stub_c_output_d
253
254         stub_c_file_exists
255            <- outputForeignStubs_help stub_c stub_c_output_w
256                 ("#define IN_STG_CODE 0\n" ++ 
257                  "#include \"Rts.h\"\n" ++
258                  rts_includes ++
259                  cplusplus_hdr)
260                  cplusplus_ftr
261            -- We're adding the default hc_header to the stub file, but this
262            -- isn't really HC code, so we need to define IN_STG_CODE==0 to
263            -- avoid the register variables etc. being enabled.
264
265         return (stub_h_file_exists, stub_c_file_exists)
266   where
267    (stub_c, stub_h, _) = mkStubPaths dflags (moduleName mod) location
268
269 cplusplus_hdr = "#ifdef __cplusplus\nextern \"C\" {\n#endif\n"
270 cplusplus_ftr = "#ifdef __cplusplus\n}\n#endif\n"
271
272 -- Don't use doOutput for dumping the f. export stubs
273 -- since it is more than likely that the stubs file will
274 -- turn out to be empty, in which case no file should be created.
275 outputForeignStubs_help fname ""      header footer = return False
276 outputForeignStubs_help fname doc_str header footer
277    = do writeFile fname (header ++ doc_str ++ '\n':footer ++ "\n")
278         return True
279 \end{code}
280