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