summaryrefslogtreecommitdiff
path: root/ghc/utils
diff options
context:
space:
mode:
authorrrt <unknown>2001-02-13 16:11:27 +0000
committerrrt <unknown>2001-02-13 16:11:27 +0000
commit389d6b3e346d65db94ec3eda10bd0deab614143c (patch)
treef8a799e28630bf1ac1ac785f2076059755e4c39b /ghc/utils
parent443ecdbee2a43b79812fb22ce93337e1991f7200 (diff)
downloadhaskell-389d6b3e346d65db94ec3eda10bd0deab614143c.tar.gz
[project @ 2001-02-13 16:11:27 by rrt]
Make work again on Windows. Main.hs has to be passed through CPP now.
Diffstat (limited to 'ghc/utils')
-rw-r--r--ghc/utils/hsc2hs/Main.hs48
1 files changed, 26 insertions, 22 deletions
diff --git a/ghc/utils/hsc2hs/Main.hs b/ghc/utils/hsc2hs/Main.hs
index 84ed204d92..8b24b53202 100644
--- a/ghc/utils/hsc2hs/Main.hs
+++ b/ghc/utils/hsc2hs/Main.hs
@@ -1,5 +1,7 @@
+{-# OPTIONS -cpp #-}
+
-----------------------------------------------------------------------------
--- $Id: Main.hs,v 1.19 2001/02/13 15:53:10 qrczak Exp $
+-- $Id: Main.hs,v 1.20 2001/02/13 16:11:27 rrt Exp $
--
-- (originally "GlueHsc.hs" by Marcin 'Qrczak' Kowalczyk)
--
@@ -11,6 +13,8 @@
--
-- See the documentation in the Users' Guide for more details.
+#include "../../includes/config.h"
+
import GetOpt
import System (getProgName, getArgs, ExitCode(..), exitWith, exitFailure)
import KludgedSystem (system, defaultCompiler)
@@ -252,15 +256,15 @@ output flags name toks = let
removeFile progName
when needsH $ writeFile outHName $
- "#ifndef "++includeGuard++"\n\
- \#define "++includeGuard++"\n\
- \#if __GLASGOW_HASKELL__ && __GLASGOW_HASKELL__ < 409\n\
- \#include <Rts.h>\n\
- \#endif\n\
- \#include <HsFFI.h>\n\
- \#if __NHC__\n\
- \#undef HsChar\n\
- \#define HsChar int\n\
+ "#ifndef "++includeGuard++"\n\
+ \#define "++includeGuard++"\n\
+ \#if __GLASGOW_HASKELL__ && __GLASGOW_HASKELL__ < 409\n\
+ \#include <Rts.h>\n\
+ \#endif\n\
+ \#include <HsFFI.h>\n\
+ \#if __NHC__\n\
+ \#undef HsChar\n\
+ \#define HsChar int\n\
\#endif\n"++
concat ["#include "++n++"\n" | Include n <- flags]++
concatMap outTokenH specials++
@@ -291,7 +295,7 @@ outHeaderCProg =
(header, _:body) -> case break isSpace header of
(name, args) ->
outCLine pos++
- "#define hsc_"++name++"("++dropWhile isSpace args++") \
+ "#define hsc_"++name++"("++dropWhile isSpace args++") \
\printf ("++joinLines body++");\n"
_ -> ""
where
@@ -299,9 +303,9 @@ outHeaderCProg =
outHeaderHs :: [Flag] -> Maybe String -> [(SourcePos, String, String)] -> String
outHeaderHs flags inH toks =
- "#if __GLASGOW_HASKELL__ && __GLASGOW_HASKELL__ < 409\n\
- \ printf (\"{-# OPTIONS -optc-D__GLASGOW_HASKELL__=%d #-}\\n\", \
- \__GLASGOW_HASKELL__);\n\
+ "#if __GLASGOW_HASKELL__ && __GLASGOW_HASKELL__ < 409\n\
+ \ printf (\"{-# OPTIONS -optc-D__GLASGOW_HASKELL__=%d #-}\\n\", \
+ \__GLASGOW_HASKELL__);\n\
\#endif\n"++
includeH++
concatMap outSpecial toks
@@ -363,11 +367,11 @@ outEnum arg =
(enum, rest) -> let
this = case break (== '=') $ dropWhile isSpace enum of
(name, []) ->
- " hsc_enum ("++t++", "++f++", \
+ " hsc_enum ("++t++", "++f++", \
\hsc_haskellize (\""++name++"\"), "++
name++");\n"
(hsName, _:cName) ->
- " hsc_enum ("++t++", "++f++", \
+ " hsc_enum ("++t++", "++f++", \
\printf (\"%s\", \""++hsName++"\"), "++
cName++");\n"
in this++enums rest
@@ -383,8 +387,8 @@ outTokenH (pos, key, arg) =
's':'t':'r':'u':'c':'t':' ':_ -> arg++"\n"
't':'y':'p':'e':'d':'e':'f':' ':_ -> arg++"\n"
'i':'n':'l':'i':'n':'e':' ':_ ->
- "#ifdef __GNUC__\n\
- \extern\n\
+ "#ifdef __GNUC__\n\
+ \extern\n\
\#endif\n"++
arg++"\n"
_ -> "extern "++header++";\n"
@@ -400,12 +404,12 @@ outTokenC (pos, key, arg) =
't':'y':'p':'e':'d':'e':'f':' ':_ -> ""
'i':'n':'l':'i':'n':'e':' ':_ ->
outCLine pos++
- "#ifndef __GNUC__\n\
- \extern\n\
+ "#ifndef __GNUC__\n\
+ \extern\n\
\#endif\n"++
header++
- "\n#ifndef __GNUC__\n\
- \;\n\
+ "\n#ifndef __GNUC__\n\
+ \;\n\
\#else\n"++
body++
"\n#endif\n"