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