[project @ 1996-06-05 06:44:31 by partain]
[ghc-hetmet.git] / ghc / compiler / prelude / TysPrim.lhs
1 %
2 % (c) The AQUA Project, Glasgow University, 1994-1996
3 %
4 \section[TysPrim]{Wired-in knowledge about primitive types}
5
6 This module tracks the ``state interface'' document, ``GHC prelude:
7 types and operations.''
8
9 \begin{code}
10 #include "HsVersions.h"
11
12 module TysPrim where
13
14 IMP_Ubiq(){-uitous-}
15
16 import Kind             ( mkUnboxedTypeKind, mkBoxedTypeKind, mkTypeKind, mkArrowKind )
17 import Name             ( mkBuiltinName )
18 import PrelMods         ( pRELUDE_BUILTIN )
19 import PrimRep          ( PrimRep(..) ) -- getPrimRepInfo uses PrimRep repn
20 import TyCon            ( mkPrimTyCon, mkDataTyCon, NewOrData(..) )
21 import TyVar            ( GenTyVar(..), alphaTyVars )
22 import Type             ( applyTyCon, mkTyVarTys )
23 import Usage            ( usageOmega )
24 import Unique
25
26 \end{code}
27
28 \begin{code}
29 alphaTys = mkTyVarTys alphaTyVars
30 (alphaTy:betaTy:gammaTy:deltaTy:_) = alphaTys
31 \end{code}
32
33 %************************************************************************
34 %*                                                                      *
35 \subsection[TysPrim-basic]{Basic primitive types (@Char#@, @Int#@, etc.)}
36 %*                                                                      *
37 %************************************************************************
38
39 \begin{code}
40 -- only used herein
41 pcPrimTyCon :: Unique{-TyConKey-} -> FAST_STRING -> Int -> PrimRep -> TyCon
42
43 pcPrimTyCon key str arity primrep
44   = mkPrimTyCon name (mk_kind arity) primrep
45   where
46     name = mkBuiltinName key pRELUDE_BUILTIN str
47
48     mk_kind 0 = mkUnboxedTypeKind
49     mk_kind n = mkTypeKind `mkArrowKind` mk_kind (n-1)
50
51
52 charPrimTy      = applyTyCon charPrimTyCon []
53 charPrimTyCon   = pcPrimTyCon charPrimTyConKey SLIT("Char#") 0 CharRep
54
55 intPrimTy       = applyTyCon intPrimTyCon []
56 intPrimTyCon    = pcPrimTyCon intPrimTyConKey SLIT("Int#") 0 IntRep
57
58 wordPrimTy      = applyTyCon wordPrimTyCon []
59 wordPrimTyCon   = pcPrimTyCon wordPrimTyConKey SLIT("Word#") 0 WordRep
60
61 addrPrimTy      = applyTyCon addrPrimTyCon []
62 addrPrimTyCon   = pcPrimTyCon addrPrimTyConKey SLIT("Addr#") 0 AddrRep
63
64 floatPrimTy     = applyTyCon floatPrimTyCon []
65 floatPrimTyCon  = pcPrimTyCon floatPrimTyConKey SLIT("Float#") 0 FloatRep
66
67 doublePrimTy    = applyTyCon doublePrimTyCon []
68 doublePrimTyCon = pcPrimTyCon doublePrimTyConKey SLIT("Double#") 0 DoubleRep
69 \end{code}
70
71 @PrimitiveKinds@ are used in @PrimitiveOps@, for which we often need
72 to reconstruct various type information.  (It's slightly more
73 convenient/efficient to make type info from kinds, than kinds [etc.]
74 from type info.)
75
76 \begin{code}
77 getPrimRepInfo ::
78     PrimRep -> (String,         -- tag string
79                 Type, TyCon)    -- prim type and tycon
80
81 getPrimRepInfo CharRep   = ("Char",   charPrimTy,   charPrimTyCon)
82 getPrimRepInfo IntRep    = ("Int",    intPrimTy,    intPrimTyCon)
83 getPrimRepInfo WordRep   = ("Word",   wordPrimTy,   wordPrimTyCon)
84 getPrimRepInfo AddrRep   = ("Addr",   addrPrimTy,   addrPrimTyCon)
85 getPrimRepInfo FloatRep  = ("Float",  floatPrimTy,  floatPrimTyCon)
86 getPrimRepInfo DoubleRep = ("Double", doublePrimTy, doublePrimTyCon)
87 \end{code}
88
89 %************************************************************************
90 %*                                                                      *
91 \subsection[TysPrim-state]{The @State#@ type (and @_RealWorld@ types)}
92 %*                                                                      *
93 %************************************************************************
94
95 State# is the primitive, unboxed type of states.  It has one type parameter,
96 thus
97         State# RealWorld
98 or
99         State# s
100
101 where s is a type variable. The only purpose of the type parameter is to
102 keep different state threads separate.  It is represented by nothing at all.
103
104 \begin{code}
105 mkStatePrimTy ty = applyTyCon statePrimTyCon [ty]
106 statePrimTyCon   = pcPrimTyCon statePrimTyConKey SLIT("State#") 1 VoidRep
107 \end{code}
108
109 @_RealWorld@ is deeply magical.  It {\em is primitive}, but it
110 {\em is not unboxed}.
111 We never manipulate values of type RealWorld; it's only used in the type
112 system, to parameterise State#.
113
114 \begin{code}
115 realWorldTy = applyTyCon realWorldTyCon []
116 realWorldTyCon
117   = mkDataTyCon name mkBoxedTypeKind 
118         [{-no tyvars-}]
119         [{-no context-}]
120         [{-no data cons!-}] -- we tell you *nothing* about this guy
121         [{-no derivings-}]
122         DataType
123   where
124     name = mkBuiltinName realWorldTyConKey pRELUDE_BUILTIN SLIT("_RealWorld")
125
126 realWorldStatePrimTy = mkStatePrimTy realWorldTy
127 \end{code}
128
129 Note: the ``state-pairing'' types are not truly primitive, so they are
130 defined in \tr{TysWiredIn.lhs}, not here.
131
132 %************************************************************************
133 %*                                                                      *
134 \subsection[TysPrim-arrays]{The primitive array types}
135 %*                                                                      *
136 %************************************************************************
137
138 \begin{code}
139 arrayPrimTyCon  = pcPrimTyCon arrayPrimTyConKey SLIT("Array#") 1 ArrayRep
140
141 byteArrayPrimTyCon = pcPrimTyCon byteArrayPrimTyConKey SLIT("ByteArray#") 0 ByteArrayRep
142
143 mutableArrayPrimTyCon = pcPrimTyCon mutableArrayPrimTyConKey SLIT("MutableArray#") 2 ArrayRep
144
145 mutableByteArrayPrimTyCon = pcPrimTyCon mutableByteArrayPrimTyConKey SLIT("MutableByteArray#") 1 ByteArrayRep
146
147 mkArrayPrimTy elt           = applyTyCon arrayPrimTyCon [elt]
148 byteArrayPrimTy             = applyTyCon byteArrayPrimTyCon []
149 mkMutableArrayPrimTy s elt  = applyTyCon mutableArrayPrimTyCon [s, elt]
150 mkMutableByteArrayPrimTy s  = applyTyCon mutableByteArrayPrimTyCon [s]
151 \end{code}
152
153 %************************************************************************
154 %*                                                                      *
155 \subsection[TysPrim-synch-var]{The synchronizing variable type}
156 %*                                                                      *
157 %************************************************************************
158
159 \begin{code}
160 synchVarPrimTyCon = pcPrimTyCon synchVarPrimTyConKey SLIT("SynchVar#") 2 PtrRep
161
162 mkSynchVarPrimTy s elt      = applyTyCon synchVarPrimTyCon [s, elt]
163 \end{code}
164
165 %************************************************************************
166 %*                                                                      *
167 \subsection[TysPrim-stable-ptrs]{The stable-pointer type}
168 %*                                                                      *
169 %************************************************************************
170
171 \begin{code}
172 stablePtrPrimTyCon = pcPrimTyCon stablePtrPrimTyConKey SLIT("StablePtr#") 1 StablePtrRep
173
174 mkStablePtrPrimTy ty = applyTyCon stablePtrPrimTyCon [ty]
175 \end{code}
176
177 %************************************************************************
178 %*                                                                      *
179 \subsection[TysPrim-foreign-objs]{The ``foreign object'' type}
180 %*                                                                      *
181 %************************************************************************
182
183 Foreign objects (formerly ``Malloc'' pointers) provide a mechanism which
184 will let Haskell's garbage collector communicate with a {\em simple\/}
185 garbage collector in the IO world. We want Haskell to be able to hold
186 onto references to objects in the IO world and for Haskell's garbage
187 collector to tell the IO world when these references become garbage.
188 We are not aiming to provide a mechanism that could
189 talk to a sophisticated garbage collector such as that provided by a
190 LISP system (with a correspondingly complex interface); in particular,
191 we shall ignore the danger of circular structures spread across the
192 two systems.
193
194 There are no primitive operations on @ForeignObj#@s (although equality
195 could possibly be added?)
196
197 \begin{code}
198 foreignObjPrimTy    = applyTyCon foreignObjPrimTyCon []
199 foreignObjPrimTyCon = pcPrimTyCon foreignObjPrimTyConKey SLIT("ForeignObj#") 0 ForeignObjRep
200 \end{code}