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