[project @ 1996-03-19 08:58:34 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 import Ubiq
15
16 import Kind             ( mkUnboxedTypeKind, mkBoxedTypeKind )
17 import NameTypes        ( mkPreludeCoreName, FullName )
18 import PrelMods         ( pRELUDE_BUILTIN )
19 import PrimRep          ( PrimRep(..) ) -- getPrimRepInfo uses PrimRep repn
20 import TyCon            ( mkPrimTyCon, mkDataTyCon,
21                           ConsVisible(..), NewOrData(..) )
22 import TyVar            ( GenTyVar(..), alphaTyVars )
23 import Type             ( applyTyCon, mkTyVarTy )
24 import Usage            ( usageOmega )
25 import Unique
26
27 \end{code}
28
29 \begin{code}
30 alphaTys = map mkTyVarTy 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] -> PrimRep) -> TyCon
43 pcPrimTyCon key name arity{-UNUSED-} kind_fn{-UNUSED-}
44   = mkPrimTyCon key full_name mkUnboxedTypeKind
45   where
46     full_name = mkPreludeCoreName pRELUDE_BUILTIN name
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 realWorldTyConKey mkBoxedTypeKind full_name
118         [{-no tyvars-}]
119         [{-no context-}]
120         [{-no data cons!-}] -- we tell you *nothing* about this guy
121         [{-no derivings-}]
122         ConsInvisible
123         DataType
124   where
125     full_name = mkPreludeCoreName pRELUDE_BUILTIN 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 %************************************************************************
134 %*                                                                      *
135 \subsection[TysPrim-arrays]{The primitive array types}
136 %*                                                                      *
137 %************************************************************************
138
139 \begin{code}
140 arrayPrimTyCon  = pcPrimTyCon arrayPrimTyConKey SLIT("Array#") 1
141                         (\ [elt_kind] -> ArrayRep)
142
143 byteArrayPrimTyCon = pcPrimTyCon byteArrayPrimTyConKey SLIT("ByteArray#") 0
144                         (\ [] -> ByteArrayRep)
145
146 mutableArrayPrimTyCon = pcPrimTyCon mutableArrayPrimTyConKey SLIT("MutableArray#") 2
147                         (\ [s_kind, elt_kind] -> ArrayRep)
148
149 mutableByteArrayPrimTyCon = pcPrimTyCon mutableByteArrayPrimTyConKey SLIT("MutableByteArray#") 1
150                         (\ [s_kind] -> ByteArrayRep)
151
152 mkArrayPrimTy elt           = applyTyCon arrayPrimTyCon [elt]
153 byteArrayPrimTy             = applyTyCon byteArrayPrimTyCon []
154 mkMutableArrayPrimTy s elt  = applyTyCon mutableArrayPrimTyCon [s, elt]
155 mkMutableByteArrayPrimTy s  = applyTyCon mutableByteArrayPrimTyCon [s]
156 \end{code}
157
158 %************************************************************************
159 %*                                                                      *
160 \subsection[TysPrim-synch-var]{The synchronizing variable type}
161 %*                                                                      *
162 %************************************************************************
163
164 \begin{code}
165 synchVarPrimTyCon = pcPrimTyCon synchVarPrimTyConKey SLIT("SynchVar#") 2
166                         (\ [s_kind, elt_kind] -> PtrRep)
167
168 mkSynchVarPrimTy s elt      = applyTyCon synchVarPrimTyCon [s, elt]
169 \end{code}
170
171 %************************************************************************
172 %*                                                                      *
173 \subsection[TysPrim-stable-ptrs]{The stable-pointer type}
174 %*                                                                      *
175 %************************************************************************
176
177 \begin{code}
178 stablePtrPrimTyCon = pcPrimTyCon stablePtrPrimTyConKey SLIT("StablePtr#") 1
179                         (\ [elt_kind] -> StablePtrRep)
180
181 mkStablePtrPrimTy ty = applyTyCon stablePtrPrimTyCon [ty]
182 \end{code}
183
184 %************************************************************************
185 %*                                                                      *
186 \subsection[TysPrim-malloc-ptrs]{The ``malloc''-pointer type}
187 %*                                                                      *
188 %************************************************************************
189
190 ``Malloc'' pointers provide a mechanism which will let Haskell's
191 garbage collector communicate with a {\em simple\/} garbage collector
192 in the IO world (probably \tr{malloc}, hence the name).We want Haskell
193 to be able to hold onto references to objects in the IO world and for
194 Haskell's garbage collector to tell the IO world when these references
195 become garbage.  We are not aiming to provide a mechanism that could
196 talk to a sophisticated garbage collector such as that provided by a
197 LISP system (with a correspondingly complex interface); in particular,
198 we shall ignore the danger of circular structures spread across the
199 two systems.
200
201 There are no primitive operations on @CHeapPtr#@s (although equality
202 could possibly be added?)
203
204 \begin{code}
205 mallocPtrPrimTyCon = pcPrimTyCon mallocPtrPrimTyConKey SLIT("MallocPtr#") 0
206                         (\ [] -> MallocPtrRep)
207 \end{code}