[project @ 1998-08-14 11:35:33 by sof]
[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 \end{code}
91
92 %************************************************************************
93 %*                                                                      *
94 \subsection[TysPrim-state]{The @State#@ type (and @_RealWorld@ types)}
95 %*                                                                      *
96 %************************************************************************
97
98 State# is the primitive, unboxed type of states.  It has one type parameter,
99 thus
100         State# RealWorld
101 or
102         State# s
103
104 where s is a type variable. The only purpose of the type parameter is to
105 keep different state threads separate.  It is represented by nothing at all.
106
107 \begin{code}
108 mkStatePrimTy ty = mkTyConApp statePrimTyCon [ty]
109 statePrimTyCon   = pcPrimTyCon statePrimTyConKey SLIT("State#") 1 VoidRep
110 \end{code}
111
112 @_RealWorld@ is deeply magical.  It {\em is primitive}, but it
113 {\em is not unboxed}.
114 We never manipulate values of type RealWorld; it's only used in the type
115 system, to parameterise State#.
116
117 \begin{code}
118 realWorldTy          = mkTyConTy realWorldTyCon
119 realWorldTyCon       = mk_no_constr_tycon realWorldTyConKey SLIT("RealWorld") 
120 realWorldStatePrimTy = mkStatePrimTy realWorldTy
121 \end{code}
122
123 Note: the ``state-pairing'' types are not truly primitive, so they are
124 defined in \tr{TysWiredIn.lhs}, not here.
125
126 \begin{code}
127 -- The Void type is represented as a data type with no constructors
128 -- It's a built in type (i.e. there's no way to define it in Haskell;
129 --      the nearest would be
130 --
131 --              data Void =             -- No constructors!
132 --
133 -- ) It's boxed; there is only one value of this
134 -- type, namely "void", whose semantics is just bottom.
135 voidTy    = mkTyConTy voidTyCon
136 voidTyCon = mk_no_constr_tycon voidTyConKey SLIT("Void")
137 \end{code}
138
139 \begin{code}
140 mk_no_constr_tycon key str
141   = the_tycon
142   where
143     name      = mkWiredInTyConName key pREL_GHC str the_tycon
144     the_tycon = mkDataTyCon name mkBoxedTypeKind 
145                         []              -- No tyvars
146                         []              -- No context
147                         []              -- No constructors; we tell you *nothing* about this guy
148                         []              -- No derivings
149                         Nothing         -- Not a dictionary
150                         DataType
151                         NonRecursive
152 \end{code}
153
154 %************************************************************************
155 %*                                                                      *
156 \subsection[TysPrim-arrays]{The primitive array types}
157 %*                                                                      *
158 %************************************************************************
159
160 \begin{code}
161 arrayPrimTyCon  = pcPrimTyCon arrayPrimTyConKey SLIT("Array#") 1 ArrayRep
162
163 byteArrayPrimTyCon = pcPrimTyCon byteArrayPrimTyConKey SLIT("ByteArray#") 0 ByteArrayRep
164
165 mutableArrayPrimTyCon = pcPrimTyCon mutableArrayPrimTyConKey SLIT("MutableArray#") 2 ArrayRep
166
167 mutableByteArrayPrimTyCon = pcPrimTyCon mutableByteArrayPrimTyConKey SLIT("MutableByteArray#") 1 ByteArrayRep
168
169 mkArrayPrimTy elt           = mkTyConApp arrayPrimTyCon [elt]
170 byteArrayPrimTy             = mkTyConTy byteArrayPrimTyCon
171 mkMutableArrayPrimTy s elt  = mkTyConApp mutableArrayPrimTyCon [s, elt]
172 mkMutableByteArrayPrimTy s  = mkTyConApp mutableByteArrayPrimTyCon [s]
173 \end{code}
174
175 %************************************************************************
176 %*                                                                      *
177 \subsection[TysPrim-synch-var]{The synchronizing variable type}
178 %*                                                                      *
179 %************************************************************************
180
181 \begin{code}
182 synchVarPrimTyCon = pcPrimTyCon synchVarPrimTyConKey SLIT("SynchVar#") 2 PtrRep
183
184 mkSynchVarPrimTy s elt      = mkTyConApp synchVarPrimTyCon [s, elt]
185 \end{code}
186
187 %************************************************************************
188 %*                                                                      *
189 \subsection[TysPrim-stable-ptrs]{The stable-pointer type}
190 %*                                                                      *
191 %************************************************************************
192
193 \begin{code}
194 stablePtrPrimTyCon = pcPrimTyCon stablePtrPrimTyConKey SLIT("StablePtr#") 1 StablePtrRep
195
196 mkStablePtrPrimTy ty = mkTyConApp stablePtrPrimTyCon [ty]
197 \end{code}
198
199 %************************************************************************
200 %*                                                                      *
201 \subsection[TysPrim-foreign-objs]{The ``foreign object'' type}
202 %*                                                                      *
203 %************************************************************************
204
205 Foreign objects (formerly ``Malloc'' pointers) provide a mechanism which
206 will let Haskell's garbage collector communicate with a {\em simple\/}
207 garbage collector in the IO world. We want Haskell to be able to hold
208 onto references to objects in the IO world and for Haskell's garbage
209 collector to tell the IO world when these references become garbage.
210 We are not aiming to provide a mechanism that could
211 talk to a sophisticated garbage collector such as that provided by a
212 LISP system (with a correspondingly complex interface); in particular,
213 we shall ignore the danger of circular structures spread across the
214 two systems.
215
216 There are no primitive operations on @ForeignObj#@s (although equality
217 could possibly be added?)
218
219 \begin{code}
220 foreignObjPrimTy    = mkTyConTy foreignObjPrimTyCon
221 foreignObjPrimTyCon = pcPrimTyCon foreignObjPrimTyConKey SLIT("ForeignObj#") 0 ForeignObjRep
222 \end{code}