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