[project @ 2004-08-13 13:04:50 by simonmar]
[ghc-hetmet.git] / ghc / compiler / ghci / ByteCodeItbls.lhs
index 605ddae..c44e562 100644 (file)
@@ -12,22 +12,20 @@ module ByteCodeItbls ( ItblEnv, ItblPtr, mkITbls ) where
 #include "HsVersions.h"
 
 import Name            ( Name, getName )
-import FiniteMap       ( FiniteMap, listToFM, emptyFM, plusFM )
-import Type            ( typePrimRep )
+import NameEnv
+import SMRep           ( typeCgRep )
 import DataCon         ( DataCon, dataConRepArgTys )
 import TyCon           ( TyCon, tyConFamilySize, isDataTyCon, tyConDataCons )
 import Constants       ( mIN_SIZE_NonUpdHeapObject )
-import ClosureInfo     ( mkVirtHeapOffsets )
+import CgHeapery       ( mkVirtHeapOffsets )
 import FastString      ( FastString(..) )
 import Util             ( lengthIs, listLengthCmp )
 
 import Foreign         ( Storable(..), Word8, Word16, Word32, Word64,
                          malloc, castPtr, plusPtr )
-import Bits            ( Bits(..), shiftR )
+import DATA_BITS       ( Bits(..), shiftR )
 
-import Monad           ( liftM )
-
-import GlaExts         ( Int(I#), addr2Int# )
+import GHC.Exts                ( Int(I#), addr2Int# )
 #if __GLASGOW_HASKELL__ < 503
 import Ptr             ( Ptr(..) )
 #else
@@ -42,40 +40,45 @@ import GHC.Ptr              ( Ptr(..) )
 %************************************************************************
 
 \begin{code}
-
 type ItblPtr = Ptr StgInfoTable
-type ItblEnv = FiniteMap Name ItblPtr
+type ItblEnv = NameEnv (Name, ItblPtr)
+       -- We need the Name in the range so we know which
+       -- elements to filter out when unloading a module
+
+mkItblEnv :: [(Name,ItblPtr)] -> ItblEnv
+mkItblEnv pairs = mkNameEnv [(n, (n,p)) | (n,p) <- pairs]
 
 
 -- Make info tables for the data decls in this module
 mkITbls :: [TyCon] -> IO ItblEnv
-mkITbls [] = return emptyFM
+mkITbls [] = return emptyNameEnv
 mkITbls (tc:tcs) = do itbls  <- mkITbl tc
                       itbls2 <- mkITbls tcs
-                      return (itbls `plusFM` itbls2)
+                      return (itbls `plusNameEnv` itbls2)
 
 mkITbl :: TyCon -> IO ItblEnv
 mkITbl tc
    | not (isDataTyCon tc) 
-   = return emptyFM
+   = return emptyNameEnv
    | dcs `lengthIs` n -- paranoia; this is an assertion.
    = make_constr_itbls dcs
      where
         dcs = tyConDataCons tc
         n   = tyConFamilySize tc
 
-cONSTR :: Int
-cONSTR = 1  -- as defined in ghc/includes/ClosureTypes.h
+#include "../includes/ClosureTypes.h"
+cONSTR :: Int  -- Defined in ClosureTypes.h
+cONSTR = CONSTR 
 
 -- Assumes constructors are numbered from zero, not one
 make_constr_itbls :: [DataCon] -> IO ItblEnv
 make_constr_itbls cons
    | listLengthCmp cons 8 /= GT -- <= 8 elements in the list
    = do is <- mapM mk_vecret_itbl (zip cons [0..])
-       return (listToFM is)
+       return (mkItblEnv is)
    | otherwise
    = do is <- mapM mk_dirret_itbl (zip cons [0..])
-       return (listToFM is)
+       return (mkItblEnv is)
      where
         mk_vecret_itbl (dcon, conNo)
            = mk_itbl dcon conNo (vecret_entry conNo)
@@ -84,8 +87,10 @@ make_constr_itbls cons
 
         mk_itbl :: DataCon -> Int -> Ptr () -> IO (Name,ItblPtr)
         mk_itbl dcon conNo entry_addr
-           = let (tot_wds, ptr_wds, _) 
-                    = mkVirtHeapOffsets typePrimRep (dataConRepArgTys dcon)
+           = let rep_args = [ (typeCgRep arg,arg) 
+                           | arg <- dataConRepArgTys dcon ]
+                (tot_wds, ptr_wds, _) = mkVirtHeapOffsets rep_args
+
                  ptrs  = ptr_wds
                  nptrs = tot_wds - ptr_wds
                  nptrs_really
@@ -148,6 +153,25 @@ mkJumpToAddr a
            0x81C0C000,
            0x01000000 ]
 
+#elif powerpc_TARGET_ARCH
+-- We'll use r12, for no particular reason.
+-- 0xDEADBEEF stands for the adress:
+-- 3D80DEAD lis r12,0xDEAD
+-- 618CBEEF ori r12,r12,0xBEEF
+-- 7D8903A6 mtctr r12
+-- 4E800420 bctr
+
+type ItblCode = Word32
+mkJumpToAddr a =
+    let w32 = fromIntegral (ptrToInt a)
+       hi16 x = (x `shiftR` 16) .&. 0xFFFF
+       lo16 x = x .&. 0xFFFF
+    in [
+       0x3D800000 .|. hi16 w32,
+       0x618C0000 .|. lo16 w32,
+       0x7D8903A6, 0x4E800420
+       ]
+
 #elif i386_TARGET_ARCH
 -- Let the address to jump to be 0xWWXXYYZZ.
 -- Generate   movl $0xWWXXYYZZ,%eax  ;  jmp *%eax