[project @ 2002-11-06 12:49:47 by simonpj]
[ghc-hetmet.git] / ghc / compiler / main / CodeOutput.lhs
index c320964..2b0d745 100644 (file)
@@ -4,7 +4,7 @@
 \section{Code output phase}
 
 \begin{code}
-module CodeOutput( codeOutput ) where
+module CodeOutput( codeOutput, outputForeignStubs ) where
 
 #include "HsVersions.h"
 
@@ -17,25 +17,28 @@ import AsmCodeGen   ( nativeCodeGen )
 import IlxGen          ( ilxGen )
 #endif
 
+#ifdef JAVA
 import JavaGen         ( javaGen )
+import OccurAnal       ( occurAnalyseBinds )
 import qualified PrintJava
+import OccurAnal       ( occurAnalyseBinds )
+#endif
 
-import TyCon           ( TyCon )
+import FastString      ( unpackFS )
+import DriverState     ( v_HCHeader )
 import Id              ( Id )
-import CoreSyn         ( CoreBind )
-import OccurAnal       ( occurAnalyseBinds )
 import StgSyn          ( StgBinding )
 import AbsCSyn         ( AbstractC )
 import PprAbsC         ( dumpRealC, writeRealC )
-import Module          ( Module )
+import HscTypes                ( ModGuts(..), ModGuts, ForeignStubs(..), typeEnvTyCons )
 import CmdLineOpts
 import ErrUtils                ( dumpIfSet_dyn, showPass )
 import Outputable
+import Pretty          ( Mode(..), printDoc )
 import CmdLineOpts     ( DynFlags, HscLang(..), dopt_OutName )
-import TmpFiles                ( newTempName )
-
-import IO              ( IOMode(..), hClose, openFile, Handle )
-import IO              ( hPutStr, stderr)      -- Debugging
+import DATA_IOREF      ( readIORef, writeIORef )
+import Monad           ( when )
+import IO
 \end{code}
 
 
@@ -47,17 +50,20 @@ import IO           ( hPutStr, stderr)      -- Debugging
 
 \begin{code}
 codeOutput :: DynFlags
-          -> Module
-          -> [TyCon]                   -- Local tycons
-          -> [CoreBind]                -- Core bindings
+          -> ModGuts
           -> [(StgBinding,[Id])]       -- The STG program with SRTs
-          -> SDoc              -- C stubs for foreign exported functions
-          -> SDoc              -- Header file prototype for foreign exported functions
-          -> AbstractC         -- Compiled abstract C
-          -> IO (Maybe FilePath, Maybe FilePath)
-codeOutput dflags mod_name tycons core_binds stg_binds 
-          c_code h_code flat_abstractC
-  = -- You can have C (c_output) or assembly-language (ncg_output),
+          -> AbstractC                 -- Compiled abstract C
+          -> IO (Bool{-stub_h_exists-}, Bool{-stub_c_exists-})
+codeOutput dflags 
+          (ModGuts {mg_module = mod_name,
+                    mg_types  = type_env,
+                    mg_foreign = foreign_stubs,
+                    mg_binds   = core_binds})
+          stg_binds flat_abstractC
+  = let
+       tycons = typeEnvTyCons type_env
+    in
+    -- You can have C (c_output) or assembly-language (ncg_output),
     -- but not both.  [Allowing for both gives a space leak on
     -- flat_abstractC.  WDP 94/10]
 
@@ -65,28 +71,31 @@ codeOutput dflags mod_name tycons core_binds stg_binds
 
     do { showPass dflags "CodeOutput"
        ; let filenm = dopt_OutName dflags 
-       ; stub_names <- outputForeignStubs dflags c_code h_code
+       ; stub_names <- outputForeignStubs dflags foreign_stubs
        ; case dopt_HscLang dflags of
              HscInterpreted -> return stub_names
              HscAsm         -> outputAsm dflags filenm flat_abstractC
                               >> return stub_names
-             HscC           -> outputC dflags filenm flat_abstractC    
+             HscC           -> outputC dflags filenm flat_abstractC stub_names
                               >> return stub_names
-             HscJava        -> outputJava dflags filenm mod_name tycons core_binds
+             HscJava        -> 
+#ifdef JAVA
+                              outputJava dflags filenm mod_name tycons core_binds
                               >> return stub_names
+#else
+                               panic "Java support not compiled into this ghc"
+#endif
+            HscILX         -> 
 #ifdef ILX
-            HscILX         -> outputIlx dflags filenm mod_name tycons stg_binds
+                              outputIlx dflags filenm mod_name tycons stg_binds
                               >> return stub_names
+#else
+                               panic "ILX support not compiled into this ghc"
 #endif
        }
 
 doOutput :: String -> (Handle -> IO ()) -> IO ()
-doOutput filenm io_action
-  = (do        handle <- openFile filenm WriteMode
-       io_action handle
-       hClose handle)
-    `catch` (\err -> pprPanic "Failed to open or write code output file" 
-                             (text filenm))
+doOutput filenm io_action = bracket (openFile filenm WriteMode) hClose io_action
 \end{code}
 
 
@@ -97,9 +106,14 @@ doOutput filenm io_action
 %************************************************************************
 
 \begin{code}
-outputC dflags filenm flat_absC
+outputC dflags filenm flat_absC (stub_h_exists, _)
   = do dumpIfSet_dyn dflags Opt_D_dump_realC "Real C" (dumpRealC flat_absC)
-       doOutput filenm (\ h -> writeRealC h flat_absC)
+       header <- readIORef v_HCHeader
+       doOutput filenm $ \ h -> do
+         hPutStr h header
+         when stub_h_exists $ 
+            hPutStrLn h ("#include \"" ++ (hscStubHOutName dflags) ++ "\"")
+         writeRealC h flat_absC
 \end{code}
 
 
@@ -118,8 +132,9 @@ outputAsm dflags filenm flat_absC
        let (stix_final, ncg_output_d) = _scc_ "NativeCodeGen" 
                                        nativeCodeGen flat_absC ncg_uniqs
        dumpIfSet_dyn dflags Opt_D_dump_stix "Final stix code" stix_final
-       dumpIfSet_dyn dflags Opt_D_dump_asm "Asm code" ncg_output_d
-       _scc_ "OutputAsm" doOutput filenm ( \f -> printForAsm f ncg_output_d)
+       dumpIfSet_dyn dflags Opt_D_dump_asm "Asm code" (docToSDoc ncg_output_d)
+       _scc_ "OutputAsm" doOutput filenm $
+          \f -> printDoc LeftMode f ncg_output_d
   where
 
 #else /* OMIT_NATIVE_CODEGEN */
@@ -138,6 +153,7 @@ outputAsm dflags filenm flat_absC
 %************************************************************************
 
 \begin{code}
+#ifdef JAVA
 outputJava dflags filenm mod tycons core_binds
   = doOutput filenm (\ f -> printForUser f alwaysQualify pp_java)
        -- User style printing for now to keep indentation
@@ -146,6 +162,7 @@ outputJava dflags filenm mod tycons core_binds
        -- Make sure we have up to date dead-var information
     java_code = javaGen mod [{- Should be imports-}] tycons occ_anal_binds
     pp_java   = PrintJava.compilationUnit java_code
+#endif
 \end{code}
 
 
@@ -172,21 +189,48 @@ outputIlx dflags filename mod tycons stg_binds
 %************************************************************************
 
 \begin{code}
-outputForeignStubs dflags c_code h_code
+    -- Turn the list of headers requested in foreign import
+    -- declarations into a string suitable for emission into generated
+    -- C code...
+mkForeignHeaders headers
+  = unlines 
+  . map (\fname -> "#include \"" ++ unpackFS fname ++ "\"")
+  . reverse 
+  $ headers
+
+outputForeignStubs :: DynFlags -> ForeignStubs
+                  -> IO (Bool,         -- Header file created
+                         Bool)         -- C file created
+outputForeignStubs dflags NoStubs = return (False, False)
+outputForeignStubs dflags (ForeignStubs h_code c_code hdrs _)
   = do
        dumpIfSet_dyn dflags Opt_D_dump_foreign
                       "Foreign export header file" stub_h_output_d
 
-       maybe_stub_h_file
-           <- outputForeignStubs_help True{-.h output-} stub_h_output_w
+       stub_h_file_exists
+           <- outputForeignStubs_help (hscStubHOutName dflags) stub_h_output_w
+               ("#include \"HsFFI.h\"\n" ++ cplusplus_hdr) cplusplus_ftr
 
        dumpIfSet_dyn dflags Opt_D_dump_foreign
                       "Foreign export stubs" stub_c_output_d
 
-        maybe_stub_c_file
-           <- outputForeignStubs_help False{-not .h-} stub_c_output_w
-
-        return (maybe_stub_h_file, maybe_stub_c_file)
+         -- Extend the list of foreign headers (used in outputC)
+        fhdrs <- readIORef v_HCHeader
+       let new_fhdrs = fhdrs ++ mkForeignHeaders hdrs
+        writeIORef v_HCHeader new_fhdrs
+
+       stub_c_file_exists
+           <- outputForeignStubs_help (hscStubCOutName dflags) stub_c_output_w
+               ("#define IN_STG_CODE 0\n" ++ 
+                new_fhdrs ++
+                "#include \"RtsAPI.h\"\n" ++
+                cplusplus_hdr)
+                cplusplus_ftr
+          -- We're adding the default hc_header to the stub file, but this
+          -- isn't really HC code, so we need to define IN_STG_CODE==0 to
+          -- avoid the register variables etc. being enabled.
+
+        return (stub_h_file_exists, stub_c_file_exists)
   where
     -- C stubs for "foreign export"ed functions.
     stub_c_output_d = pprCode CStyle c_code
@@ -196,21 +240,15 @@ outputForeignStubs dflags c_code h_code
     stub_h_output_d = pprCode CStyle h_code
     stub_h_output_w = showSDoc stub_h_output_d
 
+cplusplus_hdr = "#ifdef __cplusplus\nextern \"C\" {\n#endif\n"
+cplusplus_ftr = "#ifdef __cplusplus\n}\n#endif\n"
 
 -- Don't use doOutput for dumping the f. export stubs
 -- since it is more than likely that the stubs file will
 -- turn out to be empty, in which case no file should be created.
-outputForeignStubs_help is_header ""      = return Nothing
-outputForeignStubs_help is_header doc_str 
-   = do fname <- newTempName suffix
-        writeFile fname (include_prefix ++ doc_str)
-        return (Just fname)
-  where
-    suffix
-       | is_header   = "h_stub"
-       | otherwise   = "c_stub"
-    include_prefix
-       | is_header   = "#include \"HsFFI.h\"\n"
-       | otherwise   = "#include \"RtsAPI.h\"\n"
+outputForeignStubs_help fname ""      header footer = return False
+outputForeignStubs_help fname doc_str header footer
+   = do writeFile fname (header ++ doc_str ++ '\n':footer ++ "\n")
+        return True
 \end{code}