X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2FcoreSyn%2FMkExternalCore.lhs;h=eae4b932657cf8c6ee906dd5bfd5c1ba08ad7916;hp=861f501cc43a731873433b00a910abdc48853790;hb=6e9c0431a7cf2bf1a48f01db48c6a1d41fe15a09;hpb=391a3e9c08c470bd1444cba2e5111e253c19ea84 diff --git a/compiler/coreSyn/MkExternalCore.lhs b/compiler/coreSyn/MkExternalCore.lhs index 861f501..eae4b93 100644 --- a/compiler/coreSyn/MkExternalCore.lhs +++ b/compiler/coreSyn/MkExternalCore.lhs @@ -26,15 +26,14 @@ import Outputable import Encoding import ForeignCall import DynFlags -import StaticFlags import FastString -import IO import Data.Char +import System.IO emitExternalCore :: DynFlags -> CgGuts -> IO () emitExternalCore dflags cg_guts - | opt_EmitExternalCore + | dopt Opt_EmitExternalCore dflags = (do handle <- openFile corename WriteMode hPutStrLn handle (show (mkExternalCore cg_guts)) hClose handle) @@ -65,16 +64,9 @@ mkExternalCore :: CgGuts -> C.Module -- implicit in the data type declaration itself mkExternalCore (CgGuts {cg_module=this_mod, cg_tycons = tycons, cg_binds = binds}) - -- Note that we flatten binds at the top level: - -- every module is just a single recursive bag of declarations. - -- Rationale: since modules can be mutually recursive, - -- there's not much reason to preserve dependency info within a module. - = C.Module mname tdefs (case flattenBinds binds of - -- check for empty list so we don't create an - -- empty Rec group - [] -> [] - bs -> [(runCoreM (make_vdef True - (Rec bs)) this_mod)]) +{- Note that modules can be mutually recursive, but even so, we + print out dependency information within each module. -} + = C.Module mname tdefs (runCoreM (mapM (make_vdef True) binds) this_mod) where mname = make_mid this_mod tdefs = foldr collect_tdefs [] tycons @@ -90,12 +82,10 @@ collect_tdefs tcon tdefs Nothing -> pprPanic ("MkExternalCore: newtype tcon\ should have a coercion: ") (ppr tcon)) (map make_tbind tyvars) - repclause + (make_ty (snd (newTyConRhs tcon))) | otherwise = C.Data (qtc tcon) (map make_tbind tyvars) (map make_cdef (tyConDataCons tcon)) - where repclause | isRecursiveTyCon tcon || isOpenTyCon tcon= Nothing - | otherwise = Just (make_ty (snd (newTyConRhs tcon))) tyvars = tyConTyVars tcon collect_tdefs _ tdefs = tdefs @@ -116,7 +106,7 @@ make_tbind :: TyVar -> C.Tbind make_tbind tv = (make_var_id (tyVarName tv), make_kind (tyVarKind tv)) make_vbind :: Var -> C.Vbind -make_vbind v = (make_var_id (Var.varName v), make_ty (idType v)) +make_vbind v = (make_var_id (Var.varName v), make_ty (varType v)) make_vdef :: Bool -> CoreBind -> CoreM C.Vdefg make_vdef topLevel b = @@ -130,7 +120,7 @@ make_vdef topLevel b = let local = not topLevel || localN rhs <- make_exp e -- use local flag to determine where to add the module name - return (local, make_qid local True vName, make_ty (idType v),rhs) + return (local, make_qid local True vName, make_ty (varType v),rhs) where vName = Var.varName v make_exp :: CoreExpr -> CoreM C.Exp @@ -138,20 +128,17 @@ make_exp (Var v) = do let vName = Var.varName v isLocal <- isALocal vName return $ - case globalIdDetails v of - FCallId (CCall (CCallSpec (StaticTarget nm) callconv _)) - -> C.External (unpackFS nm) (showSDoc (ppr callconv)) (make_ty (idType v)) + case idDetails v of + FCallId (CCall (CCallSpec (StaticTarget nm _) callconv _)) + -> C.External (unpackFS nm) (showSDoc (ppr callconv)) (make_ty (varType v)) FCallId (CCall (CCallSpec DynamicTarget callconv _)) - -> C.DynExternal (showSDoc (ppr callconv)) (make_ty (idType v)) - FCallId _ - -> pprPanic "MkExternalCore died: can't handle non-{static,dynamic}-C foreign call" - (ppr v) + -> C.DynExternal (showSDoc (ppr callconv)) (make_ty (varType v)) -- Constructors are always exported, so make sure to declare them -- with qualified names DataConWorkId _ -> C.Var (make_var_qid False vName) DataConWrapId _ -> C.Var (make_var_qid False vName) _ -> C.Var (make_var_qid isLocal vName) -make_exp (Lit (MachLabel s _)) = return $ C.Label (unpackFS s) +make_exp (Lit (MachLabel s _ _)) = return $ C.Label (unpackFS s) make_exp (Lit l) = return $ C.Lit (make_lit l) make_exp (App e (Type t)) = make_exp e >>= (\ b -> return $ C.Appt b (make_ty t)) make_exp (App e1 e2) = do @@ -173,7 +160,6 @@ make_exp (Case e v ty alts) = do return $ C.Case scrut (make_vbind v) (make_ty ty) newAlts make_exp (Note (SCC _) e) = make_exp e >>= (return . C.Note "SCC") -- temporary make_exp (Note (CoreNote s) e) = make_exp e >>= (return . C.Note s) -- hdaume: core annotations -make_exp (Note InlineMe e) = make_exp e >>= (return . C.Note "InlineMe") make_exp _ = error "MkExternalCore died: make_exp" make_alt :: CoreAlt -> CoreM C.Alt