merge GHC HEAD
[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 module CodeOutput( codeOutput, outputForeignStubs ) where
8
9 #include "HsVersions.h"
10
11 import AsmCodeGen ( nativeCodeGen )
12 import LlvmCodeGen ( llvmCodeGen )
13
14 import UniqSupply       ( mkSplitUniqSupply )
15
16 #ifdef JAVA
17 import JavaGen          ( javaGen )
18 import qualified PrintJava
19 import OccurAnal        ( occurAnalyseBinds )
20 #endif
21
22 import Finder           ( mkStubPaths )
23 import PprC             ( writeCs )
24 import CmmLint          ( cmmLint )
25 import Packages
26 import Util
27 import OldCmm           ( RawCmm )
28 import HscTypes
29 import DynFlags
30 import Config
31 import SysTools
32
33 import ErrUtils         ( dumpIfSet_dyn, showPass, ghcExit )
34 import Outputable
35 import Module
36 import Maybes           ( firstJusts )
37
38 import Control.Exception
39 import Control.Monad
40 import System.Directory
41 import System.FilePath
42 import System.IO
43 \end{code}
44
45 %************************************************************************
46 %*                                                                      *
47 \subsection{Steering}
48 %*                                                                      *
49 %************************************************************************
50
51 \begin{code}
52 codeOutput :: DynFlags
53            -> Module
54            -> ModLocation
55            -> ForeignStubs
56            -> [PackageId]
57            -> [RawCmm]                  -- Compiled C--
58            -> IO (Bool{-stub_h_exists-}, Maybe FilePath{-stub_c_exists-})
59
60 codeOutput dflags this_mod location foreign_stubs pkg_deps flat_abstractC
61   = 
62     -- You can have C (c_output) or assembly-language (ncg_output),
63     -- but not both.  [Allowing for both gives a space leak on
64     -- flat_abstractC.  WDP 94/10]
65
66     -- Dunno if the above comment is still meaningful now.  JRS 001024.
67
68     do  { when (dopt Opt_DoCmmLinting dflags) $ do
69                 { showPass dflags "CmmLint"
70                 ; let lints = map cmmLint flat_abstractC
71                 ; case firstJusts lints of
72                         Just err -> do { printDump err
73                                        ; ghcExit dflags 1
74                                        }
75                         Nothing  -> return ()
76                 }
77
78         ; showPass dflags "CodeOutput"
79         ; let filenm = hscOutName dflags 
80         ; stubs_exist <- outputForeignStubs dflags this_mod location foreign_stubs
81         ; case hscTarget dflags of {
82              HscInterpreted -> return ();
83              HscAsm         -> outputAsm dflags filenm flat_abstractC;
84              HscC           -> outputC dflags filenm flat_abstractC pkg_deps;
85              HscLlvm        -> outputLlvm dflags filenm flat_abstractC;
86              HscJava        -> 
87 #ifdef JAVA
88                                outputJava dflags filenm mod_name tycons core_binds;
89 #else
90                                panic "Java support not compiled into this ghc";
91 #endif
92              HscNothing     -> panic "codeOutput: HscNothing"
93           }
94         ; return stubs_exist
95         }
96
97 doOutput :: String -> (Handle -> IO ()) -> IO ()
98 doOutput filenm io_action = bracket (openFile filenm WriteMode) hClose io_action
99 \end{code}
100
101
102 %************************************************************************
103 %*                                                                      *
104 \subsection{C}
105 %*                                                                      *
106 %************************************************************************
107
108 \begin{code}
109 outputC :: DynFlags
110         -> FilePath
111         -> [RawCmm]
112         -> [PackageId]
113         -> IO ()
114
115 outputC dflags filenm flat_absC packages
116   = do 
117        -- figure out which header files to #include in the generated .hc file:
118        --
119        --   * extra_includes from packages
120        --   * -#include options from the cmdline and OPTIONS pragmas
121        --   * the _stub.h file, if there is one.
122        --
123        let rts = getPackageDetails (pkgState dflags) rtsPackageId
124                        
125        let cc_injects = unlines (map mk_include (includes rts))
126            mk_include h_file = 
127             case h_file of 
128                '"':_{-"-} -> "#include "++h_file
129                '<':_      -> "#include "++h_file
130                _          -> "#include \""++h_file++"\""
131
132        pkg_configs <- getPreloadPackagesAnd dflags packages
133        let pkg_names = map (display.sourcePackageId) pkg_configs
134
135        doOutput filenm $ \ h -> do
136           hPutStr h ("/* GHC_PACKAGES " ++ unwords pkg_names ++ "\n*/\n")
137           hPutStr h cc_injects
138           writeCs dflags h flat_absC
139 \end{code}
140
141
142 %************************************************************************
143 %*                                                                      *
144 \subsection{Assembler}
145 %*                                                                      *
146 %************************************************************************
147
148 \begin{code}
149 outputAsm :: DynFlags -> FilePath -> [RawCmm] -> IO ()
150 outputAsm dflags filenm flat_absC
151  | cGhcWithNativeCodeGen == "YES"
152   = do ncg_uniqs <- mkSplitUniqSupply 'n'
153
154        {-# SCC "OutputAsm" #-} doOutput filenm $
155            \f -> {-# SCC "NativeCodeGen" #-}
156                  nativeCodeGen dflags f ncg_uniqs flat_absC
157
158  | otherwise
159   = panic "This compiler was built without a native code generator"
160 \end{code}
161
162
163 %************************************************************************
164 %*                                                                      *
165 \subsection{LLVM}
166 %*                                                                      *
167 %************************************************************************
168
169 \begin{code}
170 outputLlvm :: DynFlags -> FilePath -> [RawCmm] -> IO ()
171 outputLlvm dflags filenm flat_absC
172   = do ncg_uniqs <- mkSplitUniqSupply 'n'
173        doOutput filenm $ \f -> llvmCodeGen dflags f ncg_uniqs flat_absC
174 \end{code}
175
176
177 %************************************************************************
178 %*                                                                      *
179 \subsection{Java}
180 %*                                                                      *
181 %************************************************************************
182
183 \begin{code}
184 #ifdef JAVA
185 outputJava dflags filenm mod tycons core_binds
186   = doOutput filenm (\ f -> printForUser f alwaysQualify pp_java)
187         -- User style printing for now to keep indentation
188   where
189     occ_anal_binds = occurAnalyseBinds core_binds
190         -- Make sure we have up to date dead-var information
191     java_code = javaGen mod [{- Should be imports-}] tycons occ_anal_binds
192     pp_java   = PrintJava.compilationUnit java_code
193 #endif
194 \end{code}
195
196
197 %************************************************************************
198 %*                                                                      *
199 \subsection{Foreign import/export}
200 %*                                                                      *
201 %************************************************************************
202
203 \begin{code}
204 outputForeignStubs :: DynFlags -> Module -> ModLocation -> ForeignStubs
205                    -> IO (Bool,         -- Header file created
206                           Maybe FilePath) -- C file created
207 outputForeignStubs dflags mod location stubs
208  = do
209    let stub_h = mkStubPaths dflags (moduleName mod) location
210    stub_c <- newTempName dflags "c"
211
212    case stubs of
213      NoStubs -> do
214         -- When compiling External Core files, may need to use stub
215         -- files from a previous compilation
216         stub_h_exists <- doesFileExist stub_h
217         return (stub_h_exists, Nothing)
218
219      ForeignStubs h_code c_code -> do
220         let
221             stub_c_output_d = pprCode CStyle c_code
222             stub_c_output_w = showSDoc stub_c_output_d
223         
224             -- Header file protos for "foreign export"ed functions.
225             stub_h_output_d = pprCode CStyle h_code
226             stub_h_output_w = showSDoc stub_h_output_d
227         -- in
228
229         createDirectoryHierarchy (takeDirectory stub_h)
230
231         dumpIfSet_dyn dflags Opt_D_dump_foreign
232                       "Foreign export header file" stub_h_output_d
233
234         -- we need the #includes from the rts package for the stub files
235         let rts_includes = 
236                let rts_pkg = getPackageDetails (pkgState dflags) rtsPackageId in
237                concatMap mk_include (includes rts_pkg)
238             mk_include i = "#include \"" ++ i ++ "\"\n"
239
240             -- wrapper code mentions the ffi_arg type, which comes from ffi.h
241             ffi_includes | cLibFFI   = "#include \"ffi.h\"\n"
242                          | otherwise = ""
243
244         stub_h_file_exists
245            <- outputForeignStubs_help stub_h stub_h_output_w
246                 ("#include \"HsFFI.h\"\n" ++ cplusplus_hdr) cplusplus_ftr
247
248         dumpIfSet_dyn dflags Opt_D_dump_foreign
249                       "Foreign export stubs" stub_c_output_d
250
251         stub_c_file_exists
252            <- outputForeignStubs_help stub_c stub_c_output_w
253                 ("#define IN_STG_CODE 0\n" ++ 
254                  "#include \"Rts.h\"\n" ++
255                  rts_includes ++
256                  ffi_includes ++
257                  cplusplus_hdr)
258                  cplusplus_ftr
259            -- We're adding the default hc_header to the stub file, but this
260            -- isn't really HC code, so we need to define IN_STG_CODE==0 to
261            -- avoid the register variables etc. being enabled.
262
263         return (stub_h_file_exists, if stub_c_file_exists
264                                        then Just stub_c
265                                        else Nothing )
266  where
267    cplusplus_hdr = "#ifdef __cplusplus\nextern \"C\" {\n#endif\n"
268    cplusplus_ftr = "#ifdef __cplusplus\n}\n#endif\n"
269
270
271 -- Don't use doOutput for dumping the f. export stubs
272 -- since it is more than likely that the stubs file will
273 -- turn out to be empty, in which case no file should be created.
274 outputForeignStubs_help :: FilePath -> String -> String -> String -> IO Bool
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