[project @ 2003-08-19 21:59:40 by krc]
[ghc-hetmet.git] / ghc / compiler / coreSyn / MkExternalCore.lhs
index a5d1751..86c77da 100644 (file)
@@ -18,13 +18,14 @@ import TyCon
 import Class
 import TypeRep
 import Type
-import DataCon
+import DataCon ( DataCon, dataConExistentialTyVars, dataConRepArgTys, 
+                 dataConName, dataConWrapId_maybe )
 import CoreSyn
 import Var
 import IdInfo
-import Id( idUnfolding )
-import CoreTidy( tidyExpr )
-import VarEnv( emptyTidyEnv )
+import Id      ( idUnfolding )
+import CoreTidy        ( tidyExpr )
+import VarEnv  ( emptyTidyEnv )
 import Literal
 import Name
 import CostCentre
@@ -32,7 +33,7 @@ import Outputable
 import ForeignCall
 import PprExternalCore 
 import CmdLineOpts
-import Maybes( orElse )
+import Maybes  ( orElse, catMaybes )
 import IO
 import FastString
 
@@ -72,8 +73,8 @@ mkExternalCore (ModGuts {mg_module=this_mod, mg_types = type_env, mg_binds = bin
     other_implicit_binds  = map get_defn (concatMap other_implicit_ids (typeEnvElts type_env))
 
 implicit_con_ids :: TyThing -> [Id]
-implicit_con_ids (ATyCon tc) = map dataConWrapId (tyConDataCons_maybe tc `orElse` [])
-implicit_con_ids other       = []
+implicit_con_ids (ATyCon tc) | isAlgTyCon tc = catMaybes (map dataConWrapId_maybe (tyConDataCons tc))
+implicit_con_ids other                      = []
 
 other_implicit_ids :: TyThing -> [Id]
 other_implicit_ids (ATyCon tc) = tyConSelIds tc ++ tyConGenIds tc
@@ -95,6 +96,7 @@ collect_tdefs tcon tdefs
   where
     tdef | isNewTyCon tcon = 
                 C.Newtype (make_con_qid (tyConName tcon)) (map make_tbind tyvars) repclause 
+         | null (tyConDataCons tcon) = error "MkExternalCore died: can't handle datatype declarations with no data constructors"
          | otherwise = 
                 C.Data (make_con_qid (tyConName tcon)) (map make_tbind tyvars) (map make_cdef (tyConDataCons tcon)) 
          where repclause | isRecursiveTyCon tcon = Nothing
@@ -134,7 +136,7 @@ make_exp (Var v) =
     FCallId (CCall (CCallSpec (StaticTarget nm) _ _)) -> C.External (unpackFS nm) (make_ty (varType v))
     FCallId _ -> error "MkExternalCore died: can't handle non-static-C foreign call"
     _ -> C.Var (make_var_qid (Var.varName v))
-make_exp (Lit (l@(MachLabel s))) = C.External (unpackFS s) (make_ty (literalType l))
+make_exp (Lit (l@(MachLabel s _))) = error "MkExternalCore died: can't handle \"foreign label\" declarations"
 make_exp (Lit l) = C.Lit (make_lit l)
 make_exp (App e (Type t)) = C.Appt (make_exp e) (make_ty t)
 make_exp (App e1 e2) = C.App (make_exp e1) (make_exp e2)
@@ -145,6 +147,7 @@ make_exp (Case e v alts) = C.Case (make_exp e) (make_vbind v) (map make_alt alts
 make_exp (Note (SCC cc) e) = C.Note "SCC"  (make_exp e) -- temporary
 make_exp (Note (Coerce t_to t_from) e) = C.Coerce (make_ty t_to) (make_exp e)
 make_exp (Note InlineCall e) = C.Note "InlineCall" (make_exp e)
+make_exp (Note (CoreNote s) e) = C.Note s (make_exp e)  -- hdaume: core annotations
 make_exp (Note InlineMe e) = C.Note "InlineMe" (make_exp e)
 make_exp _ = error "MkExternalCore died: make_exp"
 
@@ -163,8 +166,9 @@ make_lit l =
   case l of
     MachChar i | i <= 0xff -> C.Lchar (chr i) t
     MachChar i | otherwise -> C.Lint (toEnum i) t
+       -- For big characters, use an integer literal with a character type sig
     MachStr s -> C.Lstring (unpackFS s) t
-    MachAddr i -> C.Lint i t  
+    MachNullAddr -> C.Lint 0 t
     MachInt i -> C.Lint i t
     MachInt64 i -> C.Lint i t
     MachWord i -> C.Lint i t