[project @ 2002-09-13 15:02:25 by simonpj]
[ghc-hetmet.git] / ghc / 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 ILX
17 import IlxGen           ( ilxGen )
18 #endif
19
20 #ifdef JAVA
21 import JavaGen          ( javaGen )
22 import OccurAnal        ( occurAnalyseBinds )
23 import qualified PrintJava
24 import OccurAnal        ( occurAnalyseBinds )
25 #endif
26
27 import FastString       ( unpackFS )
28 import DriverState      ( v_HCHeader )
29 import Id               ( Id )
30 import StgSyn           ( StgBinding )
31 import AbsCSyn          ( AbstractC )
32 import PprAbsC          ( dumpRealC, writeRealC )
33 import HscTypes         ( ModGuts(..), ModGuts, ForeignStubs(..), typeEnvTyCons )
34 import CmdLineOpts
35 import ErrUtils         ( dumpIfSet_dyn, showPass )
36 import Outputable
37 import Pretty           ( Mode(..), printDoc )
38 import CmdLineOpts      ( DynFlags, HscLang(..), dopt_OutName )
39 import DATA_IOREF       ( readIORef, writeIORef )
40 import Monad            ( when )
41 import IO
42 \end{code}
43
44
45 %************************************************************************
46 %*                                                                      *
47 \subsection{Steering}
48 %*                                                                      *
49 %************************************************************************
50
51 \begin{code}
52 codeOutput :: DynFlags
53            -> ModGuts
54            -> [(StgBinding,[Id])]       -- The STG program with SRTs
55            -> AbstractC                 -- Compiled abstract C
56            -> IO (Bool{-stub_h_exists-}, Bool{-stub_c_exists-})
57 codeOutput dflags 
58            (ModGuts {mg_module = mod_name,
59                      mg_types  = type_env,
60                      mg_foreign = foreign_stubs,
61                      mg_binds   = core_binds})
62            stg_binds flat_abstractC
63   = let
64         tycons = typeEnvTyCons type_env
65     in
66     -- You can have C (c_output) or assembly-language (ncg_output),
67     -- but not both.  [Allowing for both gives a space leak on
68     -- flat_abstractC.  WDP 94/10]
69
70     -- Dunno if the above comment is still meaningful now.  JRS 001024.
71
72     do  { showPass dflags "CodeOutput"
73         ; let filenm = dopt_OutName dflags 
74         ; stub_names <- outputForeignStubs dflags foreign_stubs
75         ; case dopt_HscLang dflags of
76              HscInterpreted -> return stub_names
77              HscAsm         -> outputAsm dflags filenm flat_abstractC
78                                >> return stub_names
79              HscC           -> outputC dflags filenm flat_abstractC stub_names
80                                >> return stub_names
81              HscJava        -> 
82 #ifdef JAVA
83                                outputJava dflags filenm mod_name tycons core_binds
84                                >> return stub_names
85 #else
86                                panic "Java support not compiled into this ghc"
87 #endif
88              HscILX         -> 
89 #ifdef ILX
90                                outputIlx dflags filenm mod_name tycons stg_binds
91                                >> return stub_names
92 #else
93                                panic "ILX support not compiled into this ghc"
94 #endif
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 dflags filenm flat_absC (stub_h_exists, _)
110   = do dumpIfSet_dyn dflags Opt_D_dump_realC "Real C" (dumpRealC flat_absC)
111        header <- readIORef v_HCHeader
112        doOutput filenm $ \ h -> do
113           hPutStr h header
114           when stub_h_exists $ 
115              hPutStrLn h ("#include \"" ++ (hscStubHOutName dflags) ++ "\"")
116           writeRealC h flat_absC
117 \end{code}
118
119
120 %************************************************************************
121 %*                                                                      *
122 \subsection{Assembler}
123 %*                                                                      *
124 %************************************************************************
125
126 \begin{code}
127 outputAsm dflags filenm flat_absC
128
129 #ifndef OMIT_NATIVE_CODEGEN
130
131   = do ncg_uniqs <- mkSplitUniqSupply 'n'
132        let (stix_final, ncg_output_d) = _scc_ "NativeCodeGen" 
133                                         nativeCodeGen flat_absC ncg_uniqs
134        dumpIfSet_dyn dflags Opt_D_dump_stix "Final stix code" stix_final
135        dumpIfSet_dyn dflags Opt_D_dump_asm "Asm code" (docToSDoc ncg_output_d)
136        _scc_ "OutputAsm" doOutput filenm $
137            \f -> printDoc LeftMode f ncg_output_d
138   where
139
140 #else /* OMIT_NATIVE_CODEGEN */
141
142   = pprPanic "This compiler was built without a native code generator"
143              (text "Use -fvia-C instead")
144
145 #endif
146 \end{code}
147
148
149 %************************************************************************
150 %*                                                                      *
151 \subsection{Java}
152 %*                                                                      *
153 %************************************************************************
154
155 \begin{code}
156 #ifdef JAVA
157 outputJava dflags filenm mod tycons core_binds
158   = doOutput filenm (\ f -> printForUser f alwaysQualify pp_java)
159         -- User style printing for now to keep indentation
160   where
161     occ_anal_binds = occurAnalyseBinds core_binds
162         -- Make sure we have up to date dead-var information
163     java_code = javaGen mod [{- Should be imports-}] tycons occ_anal_binds
164     pp_java   = PrintJava.compilationUnit java_code
165 #endif
166 \end{code}
167
168
169 %************************************************************************
170 %*                                                                      *
171 \subsection{Ilx}
172 %*                                                                      *
173 %************************************************************************
174
175 \begin{code}
176 #ifdef ILX
177 outputIlx dflags filename mod tycons stg_binds
178   =  doOutput filename (\ f -> printForC f pp_ilx)
179   where
180     pp_ilx = ilxGen mod tycons stg_binds
181 #endif
182 \end{code}
183
184
185 %************************************************************************
186 %*                                                                      *
187 \subsection{Foreign import/export}
188 %*                                                                      *
189 %************************************************************************
190
191 \begin{code}
192     -- Turn the list of headers requested in foreign import
193     -- declarations into a string suitable for emission into generated
194     -- C code...
195 mkForeignHeaders headers
196   = unlines 
197   . map (\fname -> "#include \"" ++ unpackFS fname ++ "\"")
198   . reverse 
199   $ headers
200
201 outputForeignStubs :: DynFlags -> ForeignStubs
202                    -> IO (Bool,         -- Header file created
203                           Bool)         -- C file created
204 outputForeignStubs dflags NoStubs = return (False, False)
205 outputForeignStubs dflags (ForeignStubs h_code c_code hdrs _)
206   = do
207         dumpIfSet_dyn dflags Opt_D_dump_foreign
208                       "Foreign export header file" stub_h_output_d
209
210         stub_h_file_exists
211            <- outputForeignStubs_help (hscStubHOutName dflags) stub_h_output_w
212                 ("#include \"HsFFI.h\"\n" ++ cplusplus_hdr) cplusplus_ftr
213
214         dumpIfSet_dyn dflags Opt_D_dump_foreign
215                       "Foreign export stubs" stub_c_output_d
216
217           -- Extend the list of foreign headers (used in outputC)
218         fhdrs <- readIORef v_HCHeader
219         let new_fhdrs = fhdrs ++ mkForeignHeaders hdrs
220         writeIORef v_HCHeader new_fhdrs
221
222         stub_c_file_exists
223            <- outputForeignStubs_help (hscStubCOutName dflags) stub_c_output_w
224                 ("#define IN_STG_CODE 0\n" ++ 
225                  new_fhdrs ++
226                  "#include \"RtsAPI.h\"\n" ++
227                  cplusplus_hdr)
228                  cplusplus_ftr
229            -- We're adding the default hc_header to the stub file, but this
230            -- isn't really HC code, so we need to define IN_STG_CODE==0 to
231            -- avoid the register variables etc. being enabled.
232
233         return (stub_h_file_exists, stub_c_file_exists)
234   where
235     -- C stubs for "foreign export"ed functions.
236     stub_c_output_d = pprCode CStyle c_code
237     stub_c_output_w = showSDoc stub_c_output_d
238
239     -- Header file protos for "foreign export"ed functions.
240     stub_h_output_d = pprCode CStyle h_code
241     stub_h_output_w = showSDoc stub_h_output_d
242
243 cplusplus_hdr = "#ifdef __cplusplus\nextern \"C\" {\n#endif\n"
244 cplusplus_ftr = "#ifdef __cplusplus\n}\n#endif\n"
245
246 -- Don't use doOutput for dumping the f. export stubs
247 -- since it is more than likely that the stubs file will
248 -- turn out to be empty, in which case no file should be created.
249 outputForeignStubs_help fname ""      header footer = return False
250 outputForeignStubs_help fname doc_str header footer
251    = do writeFile fname (header ++ doc_str ++ '\n':footer ++ "\n")
252         return True
253 \end{code}
254