Use System.FilePath
[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 FastString       ( unpackFS )
28 import Cmm              ( RawCmm )
29 import HscTypes
30 import DynFlags
31
32 import ErrUtils         ( dumpIfSet_dyn, showPass, ghcExit )
33 import Outputable
34 import Module
35 import List             ( nub )
36 import Maybes           ( firstJust )
37
38 import Distribution.Package     ( showPackageId )
39 import Directory        ( doesFileExist )
40 import Monad            ( when )
41 import IO
42 import System.FilePath
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-}, Bool{-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 firstJust 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 this_mod location 
85                                  flat_abstractC stubs_exist pkg_deps
86                                  foreign_stubs;
87              HscJava        -> 
88 #ifdef JAVA
89                                outputJava dflags filenm mod_name tycons core_binds;
90 #else
91                                panic "Java support not compiled into this ghc";
92 #endif
93              HscNothing     -> panic "codeOutput: HscNothing"
94           }
95         ; return stubs_exist
96         }
97
98 doOutput :: String -> (Handle -> IO ()) -> IO ()
99 doOutput filenm io_action = bracket (openFile filenm WriteMode) hClose io_action
100 \end{code}
101
102
103 %************************************************************************
104 %*                                                                      *
105 \subsection{C}
106 %*                                                                      *
107 %************************************************************************
108
109 \begin{code}
110 outputC :: DynFlags
111         -> FilePath -> Module -> ModLocation
112         -> [RawCmm]
113         -> (Bool, Bool)
114         -> [PackageId]
115         -> ForeignStubs
116         -> IO ()
117
118 outputC dflags filenm mod location flat_absC 
119         (stub_h_exists, _) packages foreign_stubs
120   = do 
121        -- figure out which header files to #include in the generated .hc file:
122        --
123        --   * extra_includes from packages
124        --   * -#include options from the cmdline and OPTIONS pragmas
125        --   * the _stub.h file, if there is one.
126        --
127        pkg_configs <- getPreloadPackagesAnd dflags packages
128        let pkg_names = map (showPackageId.package) pkg_configs
129
130        c_includes <- getPackageCIncludes pkg_configs
131        let cmdline_includes = cmdlineHcIncludes dflags -- -#include options
132        
133            ffi_decl_headers 
134               = case foreign_stubs of
135                   NoStubs               -> []
136                   ForeignStubs _ _ fdhs -> map unpackFS (nub fdhs)
137                         -- Remove duplicates, because distinct foreign import decls
138                         -- may cite the same #include.  Order doesn't matter.
139
140            all_headers =  c_includes
141                        ++ reverse cmdline_includes
142                        ++ ffi_decl_headers
143                        
144        let cc_injects = unlines (map mk_include all_headers)
145            mk_include h_file = 
146             case h_file of 
147                '"':_{-"-} -> "#include "++h_file
148                '<':_      -> "#include "++h_file
149                _          -> "#include \""++h_file++"\""
150
151        doOutput filenm $ \ h -> do
152           hPutStr h ("/* GHC_PACKAGES " ++ unwords pkg_names ++ "\n*/\n")
153           hPutStr h cc_injects
154           when stub_h_exists $ 
155              hPutStrLn h ("#include \"" ++ inc_stub_h ++ "\"")
156           writeCs dflags h flat_absC
157   where
158     (_, _, inc_stub_h) = mkStubPaths dflags (moduleName mod) location
159 \end{code}
160
161
162 %************************************************************************
163 %*                                                                      *
164 \subsection{Assembler}
165 %*                                                                      *
166 %************************************************************************
167
168 \begin{code}
169 outputAsm :: DynFlags -> FilePath -> [RawCmm] -> IO ()
170 outputAsm dflags filenm flat_absC
171
172 #ifndef OMIT_NATIVE_CODEGEN
173
174   = do ncg_uniqs <- mkSplitUniqSupply 'n'
175
176        {-# SCC "OutputAsm" #-} doOutput filenm $
177            \f -> {-# SCC "NativeCodeGen" #-}
178                  nativeCodeGen dflags f ncg_uniqs flat_absC
179   where
180
181 #else /* OMIT_NATIVE_CODEGEN */
182
183   = pprPanic "This compiler was built without a native code generator"
184              (text "Use -fvia-C instead")
185
186 #endif
187 \end{code}
188
189
190 %************************************************************************
191 %*                                                                      *
192 \subsection{Java}
193 %*                                                                      *
194 %************************************************************************
195
196 \begin{code}
197 #ifdef JAVA
198 outputJava dflags filenm mod tycons core_binds
199   = doOutput filenm (\ f -> printForUser f alwaysQualify pp_java)
200         -- User style printing for now to keep indentation
201   where
202     occ_anal_binds = occurAnalyseBinds core_binds
203         -- Make sure we have up to date dead-var information
204     java_code = javaGen mod [{- Should be imports-}] tycons occ_anal_binds
205     pp_java   = PrintJava.compilationUnit java_code
206 #endif
207 \end{code}
208
209
210 %************************************************************************
211 %*                                                                      *
212 \subsection{Foreign import/export}
213 %*                                                                      *
214 %************************************************************************
215
216 \begin{code}
217 outputForeignStubs :: DynFlags -> Module -> ModLocation -> ForeignStubs
218                    -> IO (Bool,         -- Header file created
219                           Bool)         -- C file created
220 outputForeignStubs dflags mod location stubs
221  = case stubs of
222    NoStubs -> do
223         -- When compiling External Core files, may need to use stub
224         -- files from a previous compilation
225         stub_c_exists <- doesFileExist stub_c
226         stub_h_exists <- doesFileExist stub_h
227         return (stub_h_exists, stub_c_exists)
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_c)
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         stub_h_file_exists
251            <- outputForeignStubs_help stub_h stub_h_output_w
252                 ("#include \"HsFFI.h\"\n" ++ cplusplus_hdr) cplusplus_ftr
253
254         dumpIfSet_dyn dflags Opt_D_dump_foreign
255                       "Foreign export stubs" stub_c_output_d
256
257         stub_c_file_exists
258            <- outputForeignStubs_help stub_c stub_c_output_w
259                 ("#define IN_STG_CODE 0\n" ++ 
260                  "#include \"Rts.h\"\n" ++
261                  rts_includes ++
262                  cplusplus_hdr)
263                  cplusplus_ftr
264            -- We're adding the default hc_header to the stub file, but this
265            -- isn't really HC code, so we need to define IN_STG_CODE==0 to
266            -- avoid the register variables etc. being enabled.
267
268         return (stub_h_file_exists, stub_c_file_exists)
269   where
270    (stub_c, stub_h, _) = mkStubPaths dflags (moduleName mod) location
271
272    cplusplus_hdr = "#ifdef __cplusplus\nextern \"C\" {\n#endif\n"
273    cplusplus_ftr = "#ifdef __cplusplus\n}\n#endif\n"
274
275
276 -- Don't use doOutput for dumping the f. export stubs
277 -- since it is more than likely that the stubs file will
278 -- turn out to be empty, in which case no file should be created.
279 outputForeignStubs_help :: FilePath -> String -> String -> String -> IO Bool
280 outputForeignStubs_help _fname ""      _header _footer = return False
281 outputForeignStubs_help fname doc_str header footer
282    = do writeFile fname (header ++ doc_str ++ '\n':footer ++ "\n")
283         return True
284 \end{code}
285