[project @ 2000-09-06 10:23:52 by simonmar]
[ghc-hetmet.git] / ghc / compiler / prelude / PrimRep.lhs
index 94ab0c5..ab6fdc4 100644 (file)
@@ -1,5 +1,5 @@
 %
-% (c) The GRASP Project, Glasgow University, 1992-1996
+% (c) The GRASP Project, Glasgow University, 1992-1998
 %
 \section[PrimRep]{Primitive machine-level kinds of things.}
 
@@ -8,23 +8,25 @@ At various places in the back end, we want to be to tag things with a
 types.
 
 \begin{code}
-#include "HsVersions.h"
-
-module PrimRep (
-       PrimRep(..),
-
-       separateByPtrFollowness, isFollowableRep, isFloatingRep,
-       getPrimRepSize, retPrimRepSize,
-       showPrimRep,
-       guessPrimRep
-    ) where
+module PrimRep 
+      (
+       PrimRep(..)
+      , separateByPtrFollowness
+      , isFollowableRep
+      , isFloatingRep
+      , is64BitRep
+      , getPrimRepSize
+      , getPrimRepSizeInBytes
+      , retPrimRepSize
+      , showPrimRep
+      , primRepString
+      , showPrimRepToUser
+      ) where
 
-IMP_Ubiq()
-
-import Pretty          -- pretty-printing code
-import Util
+#include "HsVersions.h"
 
-#include "../../includes/GhcConstants.h"
+import Constants ( dOUBLE_SIZE, iNT64_SIZE, wORD64_SIZE, wORD_SIZE )
+import Outputable
 \end{code}
 
 %************************************************************************
@@ -44,29 +46,59 @@ data PrimRep
   | CostCentreRep      -- Pointer to a cost centre
 
   | CharRep            -- Machine characters
-  | IntRep             --         integers (at least 32 bits)
+  | Int8Rep             --         8 bit integers
+  | IntRep             --         integers (same size as ptr on this arch)
   | WordRep            --         ditto (but *unsigned*)
   | AddrRep            --         addresses ("C pointers")
   | FloatRep           --         floats
   | DoubleRep          --         doubles
-
-  | ForeignObjRep      -- This has to be a special kind because ccall
-                       -- generates special code when passing/returning
-                       -- one of these. [ADR]
-
-  | StablePtrRep       -- We could replace this with IntRep but maybe
-                       -- there's some documentation gain from having
-                       -- it special? [ADR]
+  | Word64Rep          --    guaranteed to be 64 bits (no more, no less.)
+  | Int64Rep           --    guaranteed to be 64 bits (no more, no less.)
+  
+  -- Perhaps all sized integers and words should be primitive types.
+  
+  -- Int8Rep is currently used to simulate some old CharRep usages
+  -- when Char changed size from 8 to 31 bits. It does not correspond
+  -- to a Haskell unboxed type, in particular it's not used by Int8.
+  
+  | WeakPtrRep
+  | ForeignObjRep      
+  | BCORep
+
+  | StablePtrRep       -- guaranteed to be represented by a pointer
+
+  | StableNameRep      -- A stable name is a real heap object, unpointed,
+                       -- with one field containing an index into the
+                       -- stable pointer table.  It has to be a heap
+                       -- object so the garbage collector can track these
+                       -- objects and reclaim stable pointer entries.
+
+  | ThreadIdRep                -- Really a pointer to a TSO
 
   | ArrayRep           -- Primitive array of Haskell pointers
   | ByteArrayRep       -- Primitive array of bytes (no Haskell pointers)
 
+  | PrimPtrRep         -- Used for MutVars and MVars; 
+                       -- a pointer to a primitive object
+                       -- ToDo: subsumes WeakPtrRep, ThreadIdRep, 
+                       -- StableNameRep, ForeignObjRep, and BCORep ?
+
   | VoidRep            -- Occupies no space at all!
                        -- (Primitive states are mapped onto this)
   deriving (Eq, Ord)
        -- Kinds are used in PrimTyCons, which need both Eq and Ord
 \end{code}
 
+These pretty much correspond to the C types declared in StgTypes.h,
+with the following exceptions:
+
+   - when an Array or ByteArray is passed to C, we again pass a pointer
+     to the contents.  The actual type that is passed is StgPtr for
+     ArrayRep, and StgByteArray (probably a char *) for ByteArrayRep.
+
+These hacks are left until the final printing of the C, in
+PprAbsC.lhs.
+
 %************************************************************************
 %*                                                                     *
 \subsection[PrimRep-predicates]{Follow-ness, sizes, and such---on @PrimitiveKinds@}
@@ -74,25 +106,26 @@ data PrimRep
 %************************************************************************
 
 Whether or not the thing is a pointer that the garbage-collector
-should follow.
+should follow. Or, to put it another (less confusing) way, whether
+the object in question is a heap object. 
 
-Or, to put it another (less confusing) way, whether the object in
-question is a heap object.
+Depending on the outcome, this predicate determines what stack
+the pointer/object possibly will have to be saved onto, and the
+computation of GC liveness info.
 
 \begin{code}
 isFollowableRep :: PrimRep -> Bool
 
 isFollowableRep PtrRep        = True
-isFollowableRep ArrayRep      = True
-isFollowableRep ByteArrayRep  = True
--- why is a MallocPtr followable? 4/96 SOF
--- isFollowableRep ForeignObjRep  = True
+isFollowableRep ArrayRep      = True   -- all heap objects:
+isFollowableRep ByteArrayRep  = True   --      ''
+isFollowableRep WeakPtrRep    = True   --      ''
+isFollowableRep ForeignObjRep = True   --      ''
+isFollowableRep StableNameRep = True    --      ''
+isFollowableRep PrimPtrRep    = True    --      ''
+isFollowableRep ThreadIdRep   = True   -- pointer to a TSO
 
-isFollowableRep StablePtrRep  = False
--- StablePtrs aren't followable because they are just indices into a
--- table for which explicit allocation/ deallocation is required.
-
-isFollowableRep other          = False
+isFollowableRep other        = False
 
 separateByPtrFollowness :: (a -> PrimRep) -> [a] -> ([a], [a])
 
@@ -118,12 +151,26 @@ isFloatingRep :: PrimRep -> Bool
 isFloatingRep DoubleRep = True
 isFloatingRep FloatRep  = True
 isFloatingRep other     = False
+
 \end{code}
 
 \begin{code}
+is64BitRep :: PrimRep -> Bool
+
+is64BitRep Int64Rep  = True
+is64BitRep Word64Rep = True
+is64BitRep other     = False
+
+\end{code}
+
+
+
+\begin{code}
 getPrimRepSize :: PrimRep -> Int
 
-getPrimRepSize DoubleRep  = DOUBLE_SIZE        -- "words", of course
+getPrimRepSize DoubleRep  = dOUBLE_SIZE        -- "words", of course
+getPrimRepSize Word64Rep  = wORD64_SIZE
+getPrimRepSize Int64Rep   = iNT64_SIZE
 --getPrimRepSize FloatRep = 1
 --getPrimRepSize CharRep  = 1  -- ToDo: count in bytes?
 --getPrimRepSize ArrayRep = 1  -- Listed specifically for *documentation*
@@ -132,6 +179,30 @@ getPrimRepSize VoidRep       = 0
 getPrimRepSize other     = 1
 
 retPrimRepSize = getPrimRepSize RetRep
+
+-- sizes in bytes.
+-- (used in some settings to figure out how many bytes
+-- we have to push onto the stack when calling external
+-- entry points (e.g., stdcalling on win32)
+getPrimRepSizeInBytes :: PrimRep -> Int
+getPrimRepSizeInBytes pr =
+ case pr of
+    CharRep        ->    4
+    Int8Rep        ->    1
+    IntRep         ->    wORD_SIZE
+    AddrRep        ->    wORD_SIZE
+    FloatRep       ->    wORD_SIZE
+    DoubleRep      ->    dOUBLE_SIZE * wORD_SIZE
+    Word64Rep      ->    wORD64_SIZE * wORD_SIZE
+    Int64Rep       ->    iNT64_SIZE * wORD_SIZE
+    WeakPtrRep     ->    wORD_SIZE
+    ForeignObjRep  ->    wORD_SIZE
+    StablePtrRep   ->    wORD_SIZE
+    StableNameRep  ->    wORD_SIZE
+    ArrayRep       ->    wORD_SIZE
+    ByteArrayRep   ->    wORD_SIZE
+    _             ->    panic "getPrimRepSize: ouch - this wasn't supposed to happen!"
+
 \end{code}
 
 %************************************************************************
@@ -142,66 +213,53 @@ retPrimRepSize = getPrimRepSize RetRep
 
 \begin{code}
 instance Outputable PrimRep where
-    ppr sty kind = ppStr (showPrimRep kind)
+    ppr kind = text (showPrimRep kind)
 
 showPrimRep  :: PrimRep -> String
-guessPrimRep :: String -> PrimRep      -- a horrible "inverse" function
-
-showPrimRep PtrRep         = "P_"      -- short for StgPtr
-
-showPrimRep CodePtrRep    = "P_"       -- DEATH to StgFunPtr! (94/02/22 WDP)
-    -- but aren't code pointers and function pointers different sizes
-    -- on some machines (eg 80x86)? ADR
-    -- Are you trying to ruin my life, or what? (WDP)
-
-showPrimRep DataPtrRep    = "D_"
-showPrimRep RetRep        = "StgRetAddr"
-showPrimRep CostCentreRep = "CostCentre"
-showPrimRep CharRep      = "StgChar"
-showPrimRep IntRep       = "I_"        -- short for StgInt
-showPrimRep WordRep      = "W_"        -- short for StgWord
-showPrimRep AddrRep      = "StgAddr"
-showPrimRep FloatRep     = "StgFloat"
-showPrimRep DoubleRep    = "StgDouble"
-showPrimRep ArrayRep     = "StgArray" -- see comment below
-showPrimRep ByteArrayRep  = "StgByteArray"
-showPrimRep StablePtrRep  = "StgStablePtr"
-showPrimRep ForeignObjRep  = "StgPtr" -- see comment below
-showPrimRep VoidRep      = "!!VOID_KIND!!"
-
-guessPrimRep "D_"           = DataPtrRep
-guessPrimRep "StgRetAddr"   = RetRep
-guessPrimRep "StgChar"      = CharRep
-guessPrimRep "I_"           = IntRep
-guessPrimRep "W_"           = WordRep
-guessPrimRep "StgAddr"      = AddrRep
-guessPrimRep "StgFloat"     = FloatRep
-guessPrimRep "StgDouble"    = DoubleRep
-guessPrimRep "StgArray"     = ArrayRep
-guessPrimRep "StgByteArray" = ByteArrayRep
-guessPrimRep "StgStablePtr" = StablePtrRep
+showPrimRepToUser :: PrimRep -> String
+
+showPrimRep PtrRep        = "P_"       -- short for StgPtr
+showPrimRep CodePtrRep     = "P_"      -- DEATH to StgFunPtr! (94/02/22 WDP)
+showPrimRep DataPtrRep     = "D_"
+showPrimRep RetRep         = "P_"
+showPrimRep CostCentreRep  = "CostCentre"
+showPrimRep CharRep       = "C_"
+showPrimRep Int8Rep       = "StgInt8"
+showPrimRep IntRep        = "I_"       -- short for StgInt
+showPrimRep WordRep       = "W_"       -- short for StgWord
+showPrimRep Int64Rep       = "LI_"       -- short for StgLongInt
+showPrimRep Word64Rep      = "LW_"       -- short for StgLongWord
+showPrimRep AddrRep       = "StgAddr"
+showPrimRep FloatRep      = "StgFloat"
+showPrimRep DoubleRep     = "StgDouble"
+showPrimRep ArrayRep      = "P_" -- see comment below
+showPrimRep PrimPtrRep    = "P_"
+showPrimRep ByteArrayRep   = "StgByteArray"
+showPrimRep StablePtrRep   = "StgStablePtr"
+showPrimRep StableNameRep  = "P_"
+showPrimRep ThreadIdRep           = "StgTSO*"
+showPrimRep WeakPtrRep     = "P_"
+showPrimRep ForeignObjRep  = "StgAddr"
+showPrimRep VoidRep       = "!!VOID_KIND!!"
+
+primRepString CharRep          = "Char"
+primRepString Int8Rep          = "Char" -- To have names like newCharArray#
+primRepString IntRep           = "Int"
+primRepString WordRep          = "Word"
+primRepString Int64Rep         = "Int64"
+primRepString Word64Rep        = "Word64"
+primRepString AddrRep          = "Addr"
+primRepString FloatRep         = "Float"
+primRepString DoubleRep        = "Double"
+primRepString WeakPtrRep       = "Weak"
+primRepString ForeignObjRep    = "ForeignObj"
+primRepString StablePtrRep     = "StablePtr"
+primRepString StableNameRep    = "StableName"
+primRepString other            = pprPanic "primRepString" (ppr other)
+
+showPrimRepToUser pr = primRepString pr
 \end{code}
 
-All local C variables of @ArrayRep@ are declared in C as type
-@StgArray@.  The coercion to a more precise C type is done just before
-indexing (by the relevant C primitive-op macro).
-
-Nota Bene. There are three types associated with @ForeignObj@ (MallocPtr++): 
-\begin{itemize}
-\item
-@StgForeignObjClosure@ is the type of the thing the prim. op @mkForeignObj@ returns.
-{- old comment for MallocPtr
-(This typename is hardwired into @ppr_casm_results@ in
-@PprAbsC.lhs@.)
--}
-
-\item
-@StgForeignObj@ is the type of the thing we give the C world.
-
-\item
-@StgPtr@ is the type of the (pointer to the) heap object which we
-pass around inside the STG machine.
-\end{itemize}
-
-It is really easy to confuse the two.  (I'm not sure this choice of
-type names helps.) [ADR]
+Foreign Objects and Arrays are treated specially by the code for
+_ccall_s: we pass a pointer to the contents of the object, not the
+object itself.