[project @ 2003-02-04 12:40:00 by simonpj]
[ghc-hetmet.git] / ghc / utils / genprimopcode / Main.hs
index 5be75a6..d92d3a9 100644 (file)
@@ -1,11 +1,16 @@
-
+{-# OPTIONS -cpp #-}
 ------------------------------------------------------------------
 -- A primop-table mangling program                              --
 ------------------------------------------------------------------
 
 module Main where
 
+#if __GLASGOW_HASKELL__ >= 504
+import Text.ParserCombinators.Parsec
+#else
 import Parsec
+#endif
+
 import Monad
 import Char
 import List
@@ -249,7 +254,10 @@ gen_latex_doc (Info defaults entries)
           latex_encode (c:cs) = c:(latex_encode cs)
 
 gen_wrappers (Info defaults entries)
-   = "module GHC.PrimopWrappers where\n" 
+   = "{-# OPTIONS -fno-implicit-prelude #-}\n" 
+       -- Dependencies on Prelude must be explicit in libraries/base, but we
+       -- don't need the Prelude here so we add -fno-implicit-prelude.
+     ++ "module GHC.PrimopWrappers where\n" 
      ++ "import qualified GHC.Prim\n" 
      ++ unlines (map f (filter (not.dodgy) (filter is_primop entries)))
      where
@@ -349,7 +357,7 @@ mkPOI_RHS_text i
                       ++ listify (map ppType argTys) ++ " "
                       ++ "(" ++ ppType resTy ++ ")"
             
-sl_name i = "SLIT(\"" ++ name i ++ "\") "
+sl_name i = "FSLIT(\"" ++ name i ++ "\") "
 
 ppTyVar "a" = "alphaTyVar"
 ppTyVar "b" = "betaTyVar"
@@ -375,7 +383,7 @@ ppType (TyApp "RealWorld"   []) = "realWorldTy"
 ppType (TyApp "ThreadId#"   []) = "threadIdPrimTy"
 ppType (TyApp "ForeignObj#" []) = "foreignObjPrimTy"
 ppType (TyApp "BCO#"        []) = "bcoPrimTy"
-ppType (TyApp "Unit"        []) = "unitTy"   -- dodgy
+ppType (TyApp "()"          []) = "unitTy"     -- unitTy is TysWiredIn's name for ()
 
 
 ppType (TyVar "a")               = "alphaTy"
@@ -639,7 +647,7 @@ ppT = alts [apply TyVar pTyvar,
            ]
 
 pTyvar       = sat (`notElem` ["section","primop","with"]) pName
-pTycon       = pConstructor
+pTycon       = alts [pConstructor, lexeme (string "()")]
 pName        = lexeme (then2 (:) lower (many isIdChar))
 pConstructor = lexeme (then2 (:) upper (many isIdChar))