X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2Fprelude%2FTysPrim.lhs;h=7a8796a216c464213f2e90e1b98b26dda6fbde44;hb=be33dbc967b4915cfdb0307ae1b7ae3cee651b8c;hp=afc81b93b3fd113f8aff084e979359249ed16c7e;hpb=6c381e873e222417d9a67aeec77b9555eca7b7a8;p=ghc-hetmet.git diff --git a/ghc/compiler/prelude/TysPrim.lhs b/ghc/compiler/prelude/TysPrim.lhs index afc81b9..7a8796a 100644 --- a/ghc/compiler/prelude/TysPrim.lhs +++ b/ghc/compiler/prelude/TysPrim.lhs @@ -7,27 +7,23 @@ This module tracks the ``state interface'' document, ``GHC prelude: types and operations.'' \begin{code} -#include "HsVersions.h" - module TysPrim where -import Ubiq +#include "HsVersions.h" -import Kind ( mkUnboxedTypeKind, mkBoxedTypeKind ) -import NameTypes ( mkPreludeCoreName, FullName ) -import PrelMods ( pRELUDE_BUILTIN ) +import Kind ( mkBoxedTypeKind ) +import Name ( mkWiredInTyConName ) import PrimRep ( PrimRep(..) ) -- getPrimRepInfo uses PrimRep repn -import TyCon ( mkPrimTyCon, mkDataTyCon, - ConsVisible(..), NewOrData(..) ) +import TyCon ( mkPrimTyCon, mkDataTyCon, TyCon ) +import BasicTypes ( NewOrData(..), RecFlag(..) ) +import Type ( mkTyConApp, mkTyConTy, mkTyVarTys, Type ) import TyVar ( GenTyVar(..), alphaTyVars ) -import Type ( applyTyCon, mkTyVarTy ) -import Usage ( usageOmega ) +import PrelMods ( pREL_GHC ) import Unique - \end{code} \begin{code} -alphaTys = map mkTyVarTy alphaTyVars +alphaTys = mkTyVarTys alphaTyVars (alphaTy:betaTy:gammaTy:deltaTy:_) = alphaTys \end{code} @@ -39,30 +35,32 @@ alphaTys = map mkTyVarTy alphaTyVars \begin{code} -- only used herein -pcPrimTyCon :: Unique{-TyConKey-} -> FAST_STRING -> Int -> ([PrimRep] -> PrimRep) -> TyCon -pcPrimTyCon key name arity{-UNUSED-} kind_fn{-UNUSED-} - = mkPrimTyCon key full_name mkUnboxedTypeKind +pcPrimTyCon :: Unique{-TyConKey-} -> FAST_STRING -> Int -> PrimRep -> TyCon + +pcPrimTyCon key str arity primrep + = the_tycon where - full_name = mkPreludeCoreName pRELUDE_BUILTIN name + name = mkWiredInTyConName key pREL_GHC str the_tycon + the_tycon = mkPrimTyCon name arity primrep -charPrimTy = applyTyCon charPrimTyCon [] -charPrimTyCon = pcPrimTyCon charPrimTyConKey SLIT("Char#") 0 (\ [] -> CharRep) +charPrimTy = mkTyConTy charPrimTyCon +charPrimTyCon = pcPrimTyCon charPrimTyConKey SLIT("Char#") 0 CharRep -intPrimTy = applyTyCon intPrimTyCon [] -intPrimTyCon = pcPrimTyCon intPrimTyConKey SLIT("Int#") 0 (\ [] -> IntRep) +intPrimTy = mkTyConTy intPrimTyCon +intPrimTyCon = pcPrimTyCon intPrimTyConKey SLIT("Int#") 0 IntRep -wordPrimTy = applyTyCon wordPrimTyCon [] -wordPrimTyCon = pcPrimTyCon wordPrimTyConKey SLIT("Word#") 0 (\ [] -> WordRep) +wordPrimTy = mkTyConTy wordPrimTyCon +wordPrimTyCon = pcPrimTyCon wordPrimTyConKey SLIT("Word#") 0 WordRep -addrPrimTy = applyTyCon addrPrimTyCon [] -addrPrimTyCon = pcPrimTyCon addrPrimTyConKey SLIT("Addr#") 0 (\ [] -> AddrRep) +addrPrimTy = mkTyConTy addrPrimTyCon +addrPrimTyCon = pcPrimTyCon addrPrimTyConKey SLIT("Addr#") 0 AddrRep -floatPrimTy = applyTyCon floatPrimTyCon [] -floatPrimTyCon = pcPrimTyCon floatPrimTyConKey SLIT("Float#") 0 (\ [] -> FloatRep) +floatPrimTy = mkTyConTy floatPrimTyCon +floatPrimTyCon = pcPrimTyCon floatPrimTyConKey SLIT("Float#") 0 FloatRep -doublePrimTy = applyTyCon doublePrimTyCon [] -doublePrimTyCon = pcPrimTyCon doublePrimTyConKey SLIT("Double#") 0 (\ [] -> DoubleRep) +doublePrimTy = mkTyConTy doublePrimTyCon +doublePrimTyCon = pcPrimTyCon doublePrimTyConKey SLIT("Double#") 0 DoubleRep \end{code} @PrimitiveKinds@ are used in @PrimitiveOps@, for which we often need @@ -85,51 +83,66 @@ getPrimRepInfo DoubleRep = ("Double", doublePrimTy, doublePrimTyCon) %************************************************************************ %* * -\subsection[TysPrim-void]{The @Void#@ type} +\subsection[TysPrim-state]{The @State#@ type (and @_RealWorld@ types)} %* * %************************************************************************ -Very similar to the @State#@ type. -\begin{code} -voidPrimTy = applyTyCon voidPrimTyCon [] - where - voidPrimTyCon = pcPrimTyCon voidPrimTyConKey SLIT("Void#") 0 - (\ [] -> VoidRep) -\end{code} +State# is the primitive, unboxed type of states. It has one type parameter, +thus + State# RealWorld +or + State# s -%************************************************************************ -%* * -\subsection[TysPrim-state]{The @State#@ type (and @_RealWorld@ types)} -%* * -%************************************************************************ +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] -> VoidRep) +mkStatePrimTy ty = mkTyConApp statePrimTyCon [ty] +statePrimTyCon = pcPrimTyCon statePrimTyConKey SLIT("State#") 1 VoidRep \end{code} @_RealWorld@ is deeply magical. It {\em is primitive}, but it {\em is not unboxed}. -\begin{code} -realWorldTy = applyTyCon realWorldTyCon [] -realWorldTyCon - = mkDataTyCon realWorldTyConKey mkBoxedTypeKind full_name - [{-no tyvars-}] - [{-no context-}] - [{-no data cons!-}] -- we tell you *nothing* about this guy - [{-no derivings-}] - ConsInvisible - DataType - where - full_name = mkPreludeCoreName pRELUDE_BUILTIN SLIT("_RealWorld") +We never manipulate values of type RealWorld; it's only used in the type +system, to parameterise State#. +\begin{code} +realWorldTy = mkTyConTy realWorldTyCon +realWorldTyCon = mk_no_constr_tycon realWorldTyConKey SLIT("RealWorld") realWorldStatePrimTy = mkStatePrimTy realWorldTy \end{code} Note: the ``state-pairing'' types are not truly primitive, so they are defined in \tr{TysWiredIn.lhs}, not here. +\begin{code} +-- The Void type is represented as a data type with no constructors +-- It's a built in type (i.e. there's no way to define it in Haskell; +-- the nearest would be +-- +-- data Void = -- No constructors! +-- +-- ) It's boxed; there is only one value of this +-- type, namely "void", whose semantics is just bottom. +voidTy = mkTyConTy voidTyCon +voidTyCon = mk_no_constr_tycon voidTyConKey SLIT("Void") +\end{code} + +\begin{code} +mk_no_constr_tycon key str + = the_tycon + where + name = mkWiredInTyConName key pREL_GHC str the_tycon + the_tycon = mkDataTyCon name mkBoxedTypeKind + [] -- No tyvars + [] -- No context + [] -- No constructors; we tell you *nothing* about this guy + [] -- No derivings + Nothing -- Not a dictionary + DataType + NonRecursive +\end{code} + %************************************************************************ %* * \subsection[TysPrim-arrays]{The primitive array types} @@ -137,22 +150,18 @@ defined in \tr{TysWiredIn.lhs}, not here. %************************************************************************ \begin{code} -arrayPrimTyCon = pcPrimTyCon arrayPrimTyConKey SLIT("Array#") 1 - (\ [elt_kind] -> ArrayRep) +arrayPrimTyCon = pcPrimTyCon arrayPrimTyConKey SLIT("Array#") 1 ArrayRep -byteArrayPrimTyCon = pcPrimTyCon byteArrayPrimTyConKey SLIT("ByteArray#") 0 - (\ [] -> ByteArrayRep) +byteArrayPrimTyCon = pcPrimTyCon byteArrayPrimTyConKey SLIT("ByteArray#") 0 ByteArrayRep -mutableArrayPrimTyCon = pcPrimTyCon mutableArrayPrimTyConKey SLIT("MutableArray#") 2 - (\ [s_kind, elt_kind] -> ArrayRep) +mutableArrayPrimTyCon = pcPrimTyCon mutableArrayPrimTyConKey SLIT("MutableArray#") 2 ArrayRep -mutableByteArrayPrimTyCon = pcPrimTyCon mutableByteArrayPrimTyConKey SLIT("MutableByteArray#") 1 - (\ [s_kind] -> ByteArrayRep) +mutableByteArrayPrimTyCon = pcPrimTyCon mutableByteArrayPrimTyConKey SLIT("MutableByteArray#") 1 ByteArrayRep -mkArrayPrimTy elt = applyTyCon arrayPrimTyCon [elt] -byteArrayPrimTy = applyTyCon byteArrayPrimTyCon [] -mkMutableArrayPrimTy s elt = applyTyCon mutableArrayPrimTyCon [s, elt] -mkMutableByteArrayPrimTy s = applyTyCon mutableByteArrayPrimTyCon [s] +mkArrayPrimTy elt = mkTyConApp arrayPrimTyCon [elt] +byteArrayPrimTy = mkTyConTy byteArrayPrimTyCon +mkMutableArrayPrimTy s elt = mkTyConApp mutableArrayPrimTyCon [s, elt] +mkMutableByteArrayPrimTy s = mkTyConApp mutableByteArrayPrimTyCon [s] \end{code} %************************************************************************ @@ -162,10 +171,9 @@ mkMutableByteArrayPrimTy s = applyTyCon mutableByteArrayPrimTyCon [s] %************************************************************************ \begin{code} -synchVarPrimTyCon = pcPrimTyCon synchVarPrimTyConKey SLIT("SynchVar#") 2 - (\ [s_kind, elt_kind] -> PtrRep) +synchVarPrimTyCon = pcPrimTyCon synchVarPrimTyConKey SLIT("SynchVar#") 2 PtrRep -mkSynchVarPrimTy s elt = applyTyCon synchVarPrimTyCon [s, elt] +mkSynchVarPrimTy s elt = mkTyConApp synchVarPrimTyCon [s, elt] \end{code} %************************************************************************ @@ -175,33 +183,32 @@ mkSynchVarPrimTy s elt = applyTyCon synchVarPrimTyCon [s, elt] %************************************************************************ \begin{code} -stablePtrPrimTyCon = pcPrimTyCon stablePtrPrimTyConKey SLIT("StablePtr#") 1 - (\ [elt_kind] -> StablePtrRep) +stablePtrPrimTyCon = pcPrimTyCon stablePtrPrimTyConKey SLIT("StablePtr#") 1 StablePtrRep -mkStablePtrPrimTy ty = applyTyCon stablePtrPrimTyCon [ty] +mkStablePtrPrimTy ty = mkTyConApp stablePtrPrimTyCon [ty] \end{code} %************************************************************************ %* * -\subsection[TysPrim-malloc-ptrs]{The ``malloc''-pointer type} +\subsection[TysPrim-foreign-objs]{The ``foreign object'' 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 +Foreign objects (formerly ``Malloc'' pointers) provide a mechanism which +will let Haskell's garbage collector communicate with a {\em simple\/} +garbage collector in the IO world. 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. -There are no primitive operations on @CHeapPtr#@s (although equality +There are no primitive operations on @ForeignObj#@s (although equality could possibly be added?) \begin{code} -mallocPtrPrimTyCon = pcPrimTyCon mallocPtrPrimTyConKey SLIT("MallocPtr#") 0 - (\ [] -> MallocPtrRep) +foreignObjPrimTy = mkTyConTy foreignObjPrimTyCon +foreignObjPrimTyCon = pcPrimTyCon foreignObjPrimTyConKey SLIT("ForeignObj#") 0 ForeignObjRep \end{code}