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