X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2Fprelude%2FTysPrim.lhs;h=9ba28873754da69a84adb1832bfb79c1b5ed0b99;hb=6942766ac64f71b57c85a4069900b383495e2bdb;hp=d70ed565dbaccd85bd62612695dca3846ff2ba2a;hpb=e7d21ee4f8ac907665a7e170c71d59e13a01da09;p=ghc-hetmet.git diff --git a/ghc/compiler/prelude/TysPrim.lhs b/ghc/compiler/prelude/TysPrim.lhs index d70ed56..9ba2887 100644 --- a/ghc/compiler/prelude/TysPrim.lhs +++ b/ghc/compiler/prelude/TysPrim.lhs @@ -1,90 +1,242 @@ % -% (c) The AQUA Project, Glasgow University, 1994-1995 +% (c) The AQUA Project, Glasgow University, 1994-1998 % \section[TysPrim]{Wired-in knowledge about primitive types} -This module tracks the ``state interface'' document, ``GHC prelude: -types and operations.'' - \begin{code} -#include "HsVersions.h" - -module TysPrim where +module TysPrim( + alphaTyVars, betaTyVars, alphaTyVar, betaTyVar, gammaTyVar, deltaTyVar, + alphaTy, betaTy, gammaTy, deltaTy, + openAlphaTy, openAlphaTyVar, openAlphaTyVars, + + primTyCons, + + charPrimTyCon, charPrimTy, + intPrimTyCon, intPrimTy, + wordPrimTyCon, wordPrimTy, + addrPrimTyCon, addrPrimTy, + floatPrimTyCon, floatPrimTy, + doublePrimTyCon, doublePrimTy, + + statePrimTyCon, mkStatePrimTy, + realWorldTyCon, realWorldTy, realWorldStatePrimTy, + + arrayPrimTyCon, mkArrayPrimTy, + byteArrayPrimTyCon, byteArrayPrimTy, + mutableArrayPrimTyCon, mkMutableArrayPrimTy, + mutableByteArrayPrimTyCon, mkMutableByteArrayPrimTy, + mutVarPrimTyCon, mkMutVarPrimTy, + + mVarPrimTyCon, mkMVarPrimTy, + stablePtrPrimTyCon, mkStablePtrPrimTy, + stableNamePrimTyCon, mkStableNamePrimTy, + bcoPrimTyCon, bcoPrimTy, + weakPrimTyCon, mkWeakPrimTy, + foreignObjPrimTyCon, foreignObjPrimTy, + threadIdPrimTyCon, threadIdPrimTy, + + int32PrimTyCon, int32PrimTy, + word32PrimTyCon, word32PrimTy, + + int64PrimTyCon, int64PrimTy, + word64PrimTyCon, word64PrimTy + ) where -import PrelFuns -- help functions, types and things -import PrimKind +#include "HsVersions.h" -import AbsUniType ( applyTyCon ) -import Unique -import Util +import Var ( TyVar, mkTyVar ) +import Name ( Name, mkInternalName ) +import OccName ( mkVarOcc ) +import PrimRep ( PrimRep(..) ) +import TyCon ( TyCon, ArgVrcs, mkPrimTyCon, mkLiftedPrimTyCon ) +import Type ( mkTyConApp, mkTyConTy, mkTyVarTys, mkTyVarTy, + unliftedTypeKind, liftedTypeKind, openTypeKind, + Kind, mkArrowKinds + ) +import SrcLoc ( noSrcLoc ) +import Unique ( mkAlphaTyVarUnique ) +import PrelNames +import FastString ( mkFastString ) +import Outputable + +import Char ( ord, chr ) \end{code} %************************************************************************ %* * -\subsection[TysPrim-basic]{Basic primitive types (@Char#@, @Int#@, etc.)} +\subsection{Primitive type constructors} %* * %************************************************************************ \begin{code} -charPrimTy = applyTyCon charPrimTyCon [] -charPrimTyCon = pcPrimTyCon charPrimTyConKey SLIT("Char#") 0 (\ [] -> CharKind) - -intPrimTy = applyTyCon intPrimTyCon [] -intPrimTyCon = pcPrimTyCon intPrimTyConKey SLIT("Int#") 0 (\ [] -> IntKind) +primTyCons :: [TyCon] +primTyCons + = [ addrPrimTyCon + , arrayPrimTyCon + , byteArrayPrimTyCon + , charPrimTyCon + , doublePrimTyCon + , floatPrimTyCon + , intPrimTyCon + , int32PrimTyCon + , int64PrimTyCon + , foreignObjPrimTyCon + , bcoPrimTyCon + , weakPrimTyCon + , mutableArrayPrimTyCon + , mutableByteArrayPrimTyCon + , mVarPrimTyCon + , mutVarPrimTyCon + , realWorldTyCon + , stablePtrPrimTyCon + , stableNamePrimTyCon + , statePrimTyCon + , threadIdPrimTyCon + , wordPrimTyCon + , word32PrimTyCon + , word64PrimTyCon + ] +\end{code} -wordPrimTy = applyTyCon wordPrimTyCon [] -wordPrimTyCon = pcPrimTyCon wordPrimTyConKey SLIT("Word#") 0 (\ [] -> WordKind) -addrPrimTy = applyTyCon addrPrimTyCon [] -addrPrimTyCon = pcPrimTyCon addrPrimTyConKey SLIT("Addr#") 0 (\ [] -> AddrKind) +%************************************************************************ +%* * +\subsection{Support code} +%* * +%************************************************************************ -floatPrimTy = applyTyCon floatPrimTyCon [] -floatPrimTyCon = pcPrimTyCon floatPrimTyConKey SLIT("Float#") 0 (\ [] -> FloatKind) +alphaTyVars is a list of type variables for use in templates: + ["a", "b", ..., "z", "t1", "t2", ... ] -doublePrimTy = applyTyCon doublePrimTyCon [] -doublePrimTyCon = pcPrimTyCon doublePrimTyConKey SLIT("Double#") 0 (\ [] -> DoubleKind) +\begin{code} +tyVarList :: Kind -> [TyVar] +tyVarList kind = [ mkTyVar (mkInternalName (mkAlphaTyVarUnique u) + (mkVarOcc (mkFastString name)) + noSrcLoc) kind + | u <- [2..], + let name | c <= 'z' = [c] + | otherwise = 't':show u + where c = chr (u-2 + ord 'a') + ] + +alphaTyVars :: [TyVar] +alphaTyVars = tyVarList liftedTypeKind + +betaTyVars = tail alphaTyVars + +alphaTyVar, betaTyVar, gammaTyVar :: TyVar +(alphaTyVar:betaTyVar:gammaTyVar:deltaTyVar:_) = alphaTyVars + +alphaTys = mkTyVarTys alphaTyVars +(alphaTy:betaTy:gammaTy:deltaTy:_) = alphaTys + + -- openAlphaTyVar is prepared to be instantiated + -- to a lifted or unlifted type variable. It's used for the + -- result type for "error", so that we can have (error Int# "Help") +openAlphaTyVars :: [TyVar] +openAlphaTyVars@(openAlphaTyVar:_) = tyVarList openTypeKind + +openAlphaTy = mkTyVarTy openAlphaTyVar + +vrcPos,vrcZero :: (Bool,Bool) +vrcPos = (True,False) +vrcZero = (False,False) + +vrcsP,vrcsZ,vrcsZP :: ArgVrcs +vrcsP = [vrcPos] +vrcsZ = [vrcZero] +vrcsZP = [vrcZero,vrcPos] \end{code} + %************************************************************************ %* * -\subsection[TysPrim-void]{The @Void#@ type} +\subsection[TysPrim-basic]{Basic primitive types (@Char#@, @Int#@, etc.)} %* * %************************************************************************ -Very similar to the @State#@ type. \begin{code} -voidPrimTy = applyTyCon voidPrimTyCon [] +-- only used herein +pcPrimTyCon :: Name -> ArgVrcs -> PrimRep -> TyCon +pcPrimTyCon name arg_vrcs rep + = mkPrimTyCon name kind arity arg_vrcs rep where - voidPrimTyCon = pcPrimTyCon voidPrimTyConKey SLIT("Void#") 0 - (\ [] -> VoidKind) + arity = length arg_vrcs + kind = mkArrowKinds (replicate arity liftedTypeKind) result_kind + result_kind = unliftedTypeKind -- all primitive types are unlifted + +pcPrimTyCon0 :: Name -> PrimRep -> TyCon +pcPrimTyCon0 name rep + = mkPrimTyCon name result_kind 0 [] rep + where + result_kind = unliftedTypeKind -- all primitive types are unlifted + +charPrimTy = mkTyConTy charPrimTyCon +charPrimTyCon = pcPrimTyCon0 charPrimTyConName CharRep + +intPrimTy = mkTyConTy intPrimTyCon +intPrimTyCon = pcPrimTyCon0 intPrimTyConName IntRep + +int32PrimTy = mkTyConTy int32PrimTyCon +int32PrimTyCon = pcPrimTyCon0 int32PrimTyConName Int32Rep + +int64PrimTy = mkTyConTy int64PrimTyCon +int64PrimTyCon = pcPrimTyCon0 int64PrimTyConName Int64Rep + +wordPrimTy = mkTyConTy wordPrimTyCon +wordPrimTyCon = pcPrimTyCon0 wordPrimTyConName WordRep + +word32PrimTy = mkTyConTy word32PrimTyCon +word32PrimTyCon = pcPrimTyCon0 word32PrimTyConName Word32Rep + +word64PrimTy = mkTyConTy word64PrimTyCon +word64PrimTyCon = pcPrimTyCon0 word64PrimTyConName Word64Rep + +addrPrimTy = mkTyConTy addrPrimTyCon +addrPrimTyCon = pcPrimTyCon0 addrPrimTyConName AddrRep + +floatPrimTy = mkTyConTy floatPrimTyCon +floatPrimTyCon = pcPrimTyCon0 floatPrimTyConName FloatRep + +doublePrimTy = mkTyConTy doublePrimTyCon +doublePrimTyCon = pcPrimTyCon0 doublePrimTyConName DoubleRep \end{code} + %************************************************************************ %* * \subsection[TysPrim-state]{The @State#@ type (and @_RealWorld@ types)} %* * %************************************************************************ +State# is the primitive, unlifted type of states. It has one type parameter, +thus + State# RealWorld +or + State# s + +where s is a type variable. The only purpose of the type parameter is to +keep different state threads separate. It is represented by nothing at all. + \begin{code} -mkStatePrimTy ty = applyTyCon statePrimTyCon [ty] -statePrimTyCon = pcPrimTyCon statePrimTyConKey SLIT("State#") 1 - (\ [s_kind] -> VoidKind) +mkStatePrimTy ty = mkTyConApp statePrimTyCon [ty] +statePrimTyCon = pcPrimTyCon statePrimTyConName vrcsZ VoidRep \end{code} -@_RealWorld@ is deeply magical. It {\em is primitive}, but it -{\em is not unboxed}. -\begin{code} -realWorldTy = applyTyCon realWorldTyCon [] -realWorldTyCon - = pcDataTyCon realWorldTyConKey pRELUDE_BUILTIN SLIT("_RealWorld") [] - [{-no data cons!-}] -- we tell you *nothing* about this guy +RealWorld is deeply magical. It is *primitive*, but it is not +*unlifted* (hence PtrRep). We never manipulate values of type +RealWorld; it's only used in the type system, to parameterise State#. -realWorldStatePrimTy = mkStatePrimTy realWorldTy +\begin{code} +realWorldTyCon = mkLiftedPrimTyCon realWorldTyConName liftedTypeKind 0 [] PtrRep +realWorldTy = mkTyConTy realWorldTyCon +realWorldStatePrimTy = mkStatePrimTy realWorldTy -- State# RealWorld \end{code} Note: the ``state-pairing'' types are not truly primitive, so they are defined in \tr{TysWiredIn.lhs}, not here. + %************************************************************************ %* * \subsection[TysPrim-arrays]{The primitive array types} @@ -92,22 +244,27 @@ defined in \tr{TysWiredIn.lhs}, not here. %************************************************************************ \begin{code} -arrayPrimTyCon = pcPrimTyCon arrayPrimTyConKey SLIT("Array#") 1 - (\ [elt_kind] -> ArrayKind) - -byteArrayPrimTyCon = pcPrimTyCon byteArrayPrimTyConKey SLIT("ByteArray#") 0 - (\ [] -> ByteArrayKind) +arrayPrimTyCon = pcPrimTyCon arrayPrimTyConName vrcsP PtrRep +mutableArrayPrimTyCon = pcPrimTyCon mutableArrayPrimTyConName vrcsZP PtrRep +mutableByteArrayPrimTyCon = pcPrimTyCon mutableByteArrayPrimTyConName vrcsZ PtrRep +byteArrayPrimTyCon = pcPrimTyCon0 byteArrayPrimTyConName PtrRep + +mkArrayPrimTy elt = mkTyConApp arrayPrimTyCon [elt] +byteArrayPrimTy = mkTyConTy byteArrayPrimTyCon +mkMutableArrayPrimTy s elt = mkTyConApp mutableArrayPrimTyCon [s, elt] +mkMutableByteArrayPrimTy s = mkTyConApp mutableByteArrayPrimTyCon [s] +\end{code} -mutableArrayPrimTyCon = pcPrimTyCon mutableArrayPrimTyConKey SLIT("MutableArray#") 2 - (\ [s_kind, elt_kind] -> ArrayKind) +%************************************************************************ +%* * +\subsection[TysPrim-mut-var]{The mutable variable type} +%* * +%************************************************************************ -mutableByteArrayPrimTyCon = pcPrimTyCon mutableByteArrayPrimTyConKey SLIT("MutableByteArray#") 1 - (\ [s_kind] -> ByteArrayKind) +\begin{code} +mutVarPrimTyCon = pcPrimTyCon mutVarPrimTyConName vrcsZP PtrRep -mkArrayPrimTy elt = applyTyCon arrayPrimTyCon [elt] -byteArrayPrimTy = applyTyCon byteArrayPrimTyCon [] -mkMutableArrayPrimTy s elt = applyTyCon mutableArrayPrimTyCon [s, elt] -mkMutableByteArrayPrimTy s = applyTyCon mutableByteArrayPrimTyCon [s] +mkMutVarPrimTy s elt = mkTyConApp mutVarPrimTyCon [s, elt] \end{code} %************************************************************************ @@ -117,10 +274,9 @@ mkMutableByteArrayPrimTy s = applyTyCon mutableByteArrayPrimTyCon [s] %************************************************************************ \begin{code} -synchVarPrimTyCon = pcPrimTyCon synchVarPrimTyConKey SLIT("SynchVar#") 2 - (\ [s_kind, elt_kind] -> PtrKind) +mVarPrimTyCon = pcPrimTyCon mVarPrimTyConName vrcsZP PtrRep -mkSynchVarPrimTy s elt = applyTyCon synchVarPrimTyCon [s, elt] +mkMVarPrimTy s elt = mkTyConApp mVarPrimTyCon [s, elt] \end{code} %************************************************************************ @@ -130,33 +286,83 @@ mkSynchVarPrimTy s elt = applyTyCon synchVarPrimTyCon [s, elt] %************************************************************************ \begin{code} -stablePtrPrimTyCon = pcPrimTyCon stablePtrPrimTyConKey SLIT("StablePtr#") 1 - (\ [elt_kind] -> StablePtrKind) +stablePtrPrimTyCon = pcPrimTyCon stablePtrPrimTyConName vrcsP StablePtrRep + +mkStablePtrPrimTy ty = mkTyConApp stablePtrPrimTyCon [ty] +\end{code} + +%************************************************************************ +%* * +\subsection[TysPrim-stable-names]{The stable-name type} +%* * +%************************************************************************ + +\begin{code} +stableNamePrimTyCon = pcPrimTyCon stableNamePrimTyConName vrcsP PtrRep + +mkStableNamePrimTy ty = mkTyConApp stableNamePrimTyCon [ty] +\end{code} + +%************************************************************************ +%* * +\subsection[TysPrim-foreign-objs]{The ``foreign object'' type} +%* * +%************************************************************************ + +A Foreign Object is just a boxed, unlifted, Addr#. They're needed +because finalisers (weak pointers) can't watch Addr#s, they can only +watch heap-resident objects. + +We can't use a lifted Addr# (such as Addr) because race conditions +could bite us. For example, if the program deconstructed the Addr +before passing its contents to a ccall, and a weak pointer was +watching the Addr, the weak pointer might deduce that the Addr was +dead before it really was. + +\begin{code} +foreignObjPrimTy = mkTyConTy foreignObjPrimTyCon +foreignObjPrimTyCon = pcPrimTyCon0 foreignObjPrimTyConName PtrRep +\end{code} + +%************************************************************************ +%* * +\subsection[TysPrim-BCOs]{The ``bytecode object'' type} +%* * +%************************************************************************ + +\begin{code} +bcoPrimTy = mkTyConTy bcoPrimTyCon +bcoPrimTyCon = pcPrimTyCon0 bcoPrimTyConName PtrRep +\end{code} + +%************************************************************************ +%* * +\subsection[TysPrim-Weak]{The ``weak pointer'' type} +%* * +%************************************************************************ + +\begin{code} +weakPrimTyCon = pcPrimTyCon weakPrimTyConName vrcsP PtrRep -mkStablePtrPrimTy ty = applyTyCon stablePtrPrimTyCon [ty] +mkWeakPrimTy v = mkTyConApp weakPrimTyCon [v] \end{code} %************************************************************************ %* * -\subsection[TysPrim-malloc-ptrs]{The ``malloc''-pointer type} +\subsection[TysPrim-thread-ids]{The ``thread id'' type} %* * %************************************************************************ -``Malloc'' pointers provide a mechanism which will let Haskell's -garbage collector communicate with a {\em simple\/} garbage collector -in the IO world (probably \tr{malloc}, hence the name).We want Haskell -to be able to hold onto references to objects in the IO world and for -Haskell's garbage collector to tell the IO world when these references -become garbage. We are not aiming to provide a mechanism that could -talk to a sophisticated garbage collector such as that provided by a -LISP system (with a correspondingly complex interface); in particular, -we shall ignore the danger of circular structures spread across the -two systems. +A thread id is represented by a pointer to the TSO itself, to ensure +that they are always unique and we can always find the TSO for a given +thread id. However, this has the unfortunate consequence that a +ThreadId# for a given thread is treated as a root by the garbage +collector and can keep TSOs around for too long. -There are no primitive operations on @CHeapPtr#@s (although equality -could possibly be added?) +Hence the programmer API for thread manipulation uses a weak pointer +to the thread id internally. \begin{code} -mallocPtrPrimTyCon = pcPrimTyCon mallocPtrPrimTyConKey SLIT("MallocPtr#") 0 - (\ [] -> MallocPtrKind) +threadIdPrimTy = mkTyConTy threadIdPrimTyCon +threadIdPrimTyCon = pcPrimTyCon0 threadIdPrimTyConName PtrRep \end{code}