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