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