[project @ 1996-06-26 10:26:00 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             ( mkPrimitiveName )
18 import PrelMods         ( gHC_BUILTINS )
19 import PrimRep          ( PrimRep(..) ) -- getPrimRepInfo uses PrimRep repn
20 import TyCon            ( mkPrimTyCon, mkDataTyCon, NewOrData(..) )
21 import Type             ( applyTyCon, mkTyVarTys, mkTyConTy )
22 import TyVar            ( GenTyVar(..), alphaTyVars )
23 import Usage            ( usageOmega )
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   = mkPrimTyCon name (mk_kind arity) primrep
44   where
45     name = mkPrimitiveName key (OrigName gHC_BUILTINS str)
46
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
116   = mkDataTyCon name mkBoxedTypeKind 
117         [{-no tyvars-}]
118         [{-no context-}]
119         [{-no data cons!-}] -- we tell you *nothing* about this guy
120         [{-no derivings-}]
121         DataType
122   where
123     name = mkPrimitiveName realWorldTyConKey (OrigName gHC_BUILTINS SLIT("RealWorld"))
124
125 realWorldStatePrimTy = mkStatePrimTy realWorldTy
126 \end{code}
127
128 Note: the ``state-pairing'' types are not truly primitive, so they are
129 defined in \tr{TysWiredIn.lhs}, not here.
130
131 \begin{code}
132 -- The Void type is represented as a data type with no constructors
133 -- It's a built in type (i.e. there's no way to define it in Haskell;
134 --      the nearest would be
135 --
136 --              data Void =             -- No constructors!
137 --
138 -- ) It's boxed; there is only one value of this
139 -- type, namely "void", whose semantics is just bottom.
140 voidTy = mkTyConTy voidTyCon
141
142 voidTyCon
143   = mkDataTyCon name mkBoxedTypeKind 
144         [{-no tyvars-}]
145         [{-no context-}]
146         [{-no data cons!-}]
147         [{-no derivings-}]
148         DataType
149   where
150     name = mkPrimitiveName voidTyConKey (OrigName gHC_BUILTINS SLIT("Void"))
151 \end{code}
152
153 %************************************************************************
154 %*                                                                      *
155 \subsection[TysPrim-arrays]{The primitive array types}
156 %*                                                                      *
157 %************************************************************************
158
159 \begin{code}
160 arrayPrimTyCon  = pcPrimTyCon arrayPrimTyConKey SLIT("Array#") 1 ArrayRep
161
162 byteArrayPrimTyCon = pcPrimTyCon byteArrayPrimTyConKey SLIT("ByteArray#") 0 ByteArrayRep
163
164 mutableArrayPrimTyCon = pcPrimTyCon mutableArrayPrimTyConKey SLIT("MutableArray#") 2 ArrayRep
165
166 mutableByteArrayPrimTyCon = pcPrimTyCon mutableByteArrayPrimTyConKey SLIT("MutableByteArray#") 1 ByteArrayRep
167
168 mkArrayPrimTy elt           = applyTyCon arrayPrimTyCon [elt]
169 byteArrayPrimTy             = applyTyCon byteArrayPrimTyCon []
170 mkMutableArrayPrimTy s elt  = applyTyCon mutableArrayPrimTyCon [s, elt]
171 mkMutableByteArrayPrimTy s  = applyTyCon mutableByteArrayPrimTyCon [s]
172 \end{code}
173
174 %************************************************************************
175 %*                                                                      *
176 \subsection[TysPrim-synch-var]{The synchronizing variable type}
177 %*                                                                      *
178 %************************************************************************
179
180 \begin{code}
181 synchVarPrimTyCon = pcPrimTyCon synchVarPrimTyConKey SLIT("SynchVar#") 2 PtrRep
182
183 mkSynchVarPrimTy s elt      = applyTyCon synchVarPrimTyCon [s, elt]
184 \end{code}
185
186 %************************************************************************
187 %*                                                                      *
188 \subsection[TysPrim-stable-ptrs]{The stable-pointer type}
189 %*                                                                      *
190 %************************************************************************
191
192 \begin{code}
193 stablePtrPrimTyCon = pcPrimTyCon stablePtrPrimTyConKey SLIT("StablePtr#") 1 StablePtrRep
194
195 mkStablePtrPrimTy ty = applyTyCon stablePtrPrimTyCon [ty]
196 \end{code}
197
198 %************************************************************************
199 %*                                                                      *
200 \subsection[TysPrim-foreign-objs]{The ``foreign object'' type}
201 %*                                                                      *
202 %************************************************************************
203
204 Foreign objects (formerly ``Malloc'' pointers) provide a mechanism which
205 will let Haskell's garbage collector communicate with a {\em simple\/}
206 garbage collector in the IO world. We want Haskell to be able to hold
207 onto references to objects in the IO world and for Haskell's garbage
208 collector to tell the IO world when these references become garbage.
209 We are not aiming to provide a mechanism that could
210 talk to a sophisticated garbage collector such as that provided by a
211 LISP system (with a correspondingly complex interface); in particular,
212 we shall ignore the danger of circular structures spread across the
213 two systems.
214
215 There are no primitive operations on @ForeignObj#@s (although equality
216 could possibly be added?)
217
218 \begin{code}
219 foreignObjPrimTy    = applyTyCon foreignObjPrimTyCon []
220 foreignObjPrimTyCon = pcPrimTyCon foreignObjPrimTyConKey SLIT("ForeignObj#") 0 ForeignObjRep
221 \end{code}