diff options
author | sewardj <unknown> | 2001-01-15 17:05:47 +0000 |
---|---|---|
committer | sewardj <unknown> | 2001-01-15 17:05:47 +0000 |
commit | 6c9a37e31afc41d57417a3828877577d8d270266 (patch) | |
tree | 05d49fcf612c03c4a8afd68f0a91caae9211f1d4 /ghc/utils | |
parent | 7385dd9fa7f062997a2860ea13e2c268e0783c40 (diff) | |
download | haskell-6c9a37e31afc41d57417a3828877577d8d270266.tar.gz |
[project @ 2001-01-15 17:05:46 by sewardj]
More stuff to do with primop support in the interpreter. Also, track
some changes to the libraries.
Diffstat (limited to 'ghc/utils')
-rw-r--r-- | ghc/utils/genprimopcode/Main.hs | 38 |
1 files changed, 29 insertions, 9 deletions
diff --git a/ghc/utils/genprimopcode/Main.hs b/ghc/utils/genprimopcode/Main.hs index aaff9c142e..18f5ffecdb 100644 --- a/ghc/utils/genprimopcode/Main.hs +++ b/ghc/utils/genprimopcode/Main.hs @@ -75,8 +75,8 @@ main = getArgs >>= \args -> "--primop-list" -> putStr (gen_primop_list p_o_specs) - "--c-bytecode-enum" - -> putStr (gen_enum_decl p_o_specs) + "--make-haskell-wrappers" + -> putStr (gen_wrappers p_o_specs) ) @@ -93,14 +93,37 @@ known_args "--primop-primop-info", "--primop-tag", "--primop-list", - - "--c-bytecode-enum" + "--make-haskell-wrappers" ] ------------------------------------------------------------------ -- Code generators ----------------------------------------------- ------------------------------------------------------------------ +gen_wrappers (Info defaults pos) + = "module PrelPrimopWrappers where\n" + ++ "import qualified PrelGHC\n" + ++ unlines (map f (filter (not.dodgy) pos)) + where + f spec = let args = map (\n -> "a" ++ show n) [1 .. arity (ty spec)] + src_name = wrap (name spec) + in "{-# NOINLINE " ++ src_name ++ " #-}\n" ++ + src_name ++ " " ++ unwords args + ++ " = (PrelGHC." ++ name spec ++ ") " ++ unwords args + wrap nm | isLower (head nm) = nm + | otherwise = "(" ++ nm ++ ")" + + dodgy spec + = name spec `elem` + [-- C code generator can't handle these + "seq#", + "tagToEnum#", + -- not interested in parallel support + "par#", "parGlobal#", "parLocal#", "parAt#", + "parAtAbs#", "parAtRel#", "parAtForNow#" + ] + + gen_primop_list (Info defaults pos) = unlines ( [ " [" ++ cons (head pos) ] @@ -116,11 +139,6 @@ gen_primop_tag (Info defaults pos) f i n = "tagOf_PrimOp " ++ cons i ++ " = _ILIT(" ++ show n ++ ") :: FastInt" -gen_enum_decl (Info defaults pos) - = let conss = map cons pos - in "enum PrimOp {\n " ++ head conss ++ "\n" - ++ unlines (map (" , "++) (tail conss)) ++ "};\n" - gen_data_decl (Info defaults pos) = let conss = map cons pos in "data PrimOp\n = " ++ head conss ++ "\n" @@ -256,6 +274,8 @@ tvsIn (TyApp tc tys) = concatMap tvsIn tys tvsIn (TyVar tv) = [tv] tvsIn (TyUTup tys) = concatMap tvsIn tys +arity = length . fst . flatTys + ------------------------------------------------------------------ -- Abstract syntax ----------------------------------------------- |