d70ed565dbaccd85bd62612695dca3846ff2ba2a
[ghc-hetmet.git] / ghc / compiler / prelude / TysPrim.lhs
1 %
2 % (c) The AQUA Project, Glasgow University, 1994-1995
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 PrelFuns         -- help functions, types and things
15 import PrimKind
16
17 import AbsUniType       ( applyTyCon )
18 import Unique
19 import Util
20 \end{code}
21
22 %************************************************************************
23 %*                                                                      *
24 \subsection[TysPrim-basic]{Basic primitive types (@Char#@, @Int#@, etc.)}
25 %*                                                                      *
26 %************************************************************************
27
28 \begin{code}
29 charPrimTy      = applyTyCon charPrimTyCon []
30 charPrimTyCon   = pcPrimTyCon charPrimTyConKey SLIT("Char#") 0 (\ [] -> CharKind)
31
32 intPrimTy       = applyTyCon intPrimTyCon []
33 intPrimTyCon    = pcPrimTyCon intPrimTyConKey SLIT("Int#") 0 (\ [] -> IntKind)
34
35 wordPrimTy      = applyTyCon wordPrimTyCon []
36 wordPrimTyCon   = pcPrimTyCon wordPrimTyConKey SLIT("Word#") 0 (\ [] -> WordKind)
37
38 addrPrimTy      = applyTyCon addrPrimTyCon []
39 addrPrimTyCon   = pcPrimTyCon addrPrimTyConKey SLIT("Addr#") 0 (\ [] -> AddrKind)
40
41 floatPrimTy     = applyTyCon floatPrimTyCon []
42 floatPrimTyCon  = pcPrimTyCon floatPrimTyConKey SLIT("Float#") 0 (\ [] -> FloatKind)
43
44 doublePrimTy    = applyTyCon doublePrimTyCon []
45 doublePrimTyCon = pcPrimTyCon doublePrimTyConKey SLIT("Double#") 0 (\ [] -> DoubleKind)
46 \end{code}
47
48 %************************************************************************
49 %*                                                                      *
50 \subsection[TysPrim-void]{The @Void#@ type}
51 %*                                                                      *
52 %************************************************************************
53
54 Very similar to the @State#@ type.
55 \begin{code}
56 voidPrimTy = applyTyCon voidPrimTyCon []
57   where
58    voidPrimTyCon = pcPrimTyCon voidPrimTyConKey SLIT("Void#") 0
59                         (\ [] -> VoidKind)
60 \end{code}
61
62 %************************************************************************
63 %*                                                                      *
64 \subsection[TysPrim-state]{The @State#@ type (and @_RealWorld@ types)}
65 %*                                                                      *
66 %************************************************************************
67
68 \begin{code}
69 mkStatePrimTy ty = applyTyCon statePrimTyCon [ty]
70 statePrimTyCon   = pcPrimTyCon statePrimTyConKey SLIT("State#") 1
71                         (\ [s_kind] -> VoidKind)
72 \end{code}
73
74 @_RealWorld@ is deeply magical.  It {\em is primitive}, but it
75 {\em is not unboxed}.
76 \begin{code}
77 realWorldTy       = applyTyCon realWorldTyCon []
78 realWorldTyCon
79   = pcDataTyCon realWorldTyConKey pRELUDE_BUILTIN SLIT("_RealWorld") []
80         [{-no data cons!-}] -- we tell you *nothing* about this guy
81
82 realWorldStatePrimTy = mkStatePrimTy realWorldTy
83 \end{code}
84
85 Note: the ``state-pairing'' types are not truly primitive, so they are
86 defined in \tr{TysWiredIn.lhs}, not here.
87
88 %************************************************************************
89 %*                                                                      *
90 \subsection[TysPrim-arrays]{The primitive array types}
91 %*                                                                      *
92 %************************************************************************
93
94 \begin{code}
95 arrayPrimTyCon  = pcPrimTyCon arrayPrimTyConKey SLIT("Array#") 1
96                         (\ [elt_kind] -> ArrayKind)
97
98 byteArrayPrimTyCon = pcPrimTyCon byteArrayPrimTyConKey SLIT("ByteArray#") 0
99                         (\ [] -> ByteArrayKind)
100
101 mutableArrayPrimTyCon = pcPrimTyCon mutableArrayPrimTyConKey SLIT("MutableArray#") 2
102                         (\ [s_kind, elt_kind] -> ArrayKind)
103
104 mutableByteArrayPrimTyCon = pcPrimTyCon mutableByteArrayPrimTyConKey SLIT("MutableByteArray#") 1
105                         (\ [s_kind] -> ByteArrayKind)
106
107 mkArrayPrimTy elt           = applyTyCon arrayPrimTyCon [elt]
108 byteArrayPrimTy             = applyTyCon byteArrayPrimTyCon []
109 mkMutableArrayPrimTy s elt  = applyTyCon mutableArrayPrimTyCon [s, elt]
110 mkMutableByteArrayPrimTy s  = applyTyCon mutableByteArrayPrimTyCon [s]
111 \end{code}
112
113 %************************************************************************
114 %*                                                                      *
115 \subsection[TysPrim-synch-var]{The synchronizing variable type}
116 %*                                                                      *
117 %************************************************************************
118
119 \begin{code}
120 synchVarPrimTyCon = pcPrimTyCon synchVarPrimTyConKey SLIT("SynchVar#") 2
121                         (\ [s_kind, elt_kind] -> PtrKind)
122
123 mkSynchVarPrimTy s elt      = applyTyCon synchVarPrimTyCon [s, elt]
124 \end{code}
125
126 %************************************************************************
127 %*                                                                      *
128 \subsection[TysPrim-stable-ptrs]{The stable-pointer type}
129 %*                                                                      *
130 %************************************************************************
131
132 \begin{code}
133 stablePtrPrimTyCon = pcPrimTyCon stablePtrPrimTyConKey SLIT("StablePtr#") 1
134                         (\ [elt_kind] -> StablePtrKind)
135
136 mkStablePtrPrimTy ty = applyTyCon stablePtrPrimTyCon [ty]
137 \end{code}
138
139 %************************************************************************
140 %*                                                                      *
141 \subsection[TysPrim-malloc-ptrs]{The ``malloc''-pointer type}
142 %*                                                                      *
143 %************************************************************************
144
145 ``Malloc'' pointers provide a mechanism which will let Haskell's
146 garbage collector communicate with a {\em simple\/} garbage collector
147 in the IO world (probably \tr{malloc}, hence the name).We want Haskell
148 to be able to hold onto references to objects in the IO world and for
149 Haskell's garbage collector to tell the IO world when these references
150 become garbage.  We are not aiming to provide a mechanism that could
151 talk to a sophisticated garbage collector such as that provided by a
152 LISP system (with a correspondingly complex interface); in particular,
153 we shall ignore the danger of circular structures spread across the
154 two systems.
155
156 There are no primitive operations on @CHeapPtr#@s (although equality
157 could possibly be added?)
158
159 \begin{code}
160 mallocPtrPrimTyCon = pcPrimTyCon mallocPtrPrimTyConKey SLIT("MallocPtr#") 0
161                         (\ [] -> MallocPtrKind)
162 \end{code}