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