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