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