[project @ 1996-01-08 20:28:12 by partain]
[ghc-hetmet.git] / ghc / compiler / prelude / PrimKind.lhs
1 %
2 % (c) The GRASP Project, Glasgow University, 1992-1995
3 %
4 \section[PrimKind]{Primitive machine-level kinds of things.}
5
6 At various places in the back end, we want to be to tag things with a
7 ``primitive kind''---i.e., the machine-manipulable implementation
8 types.
9
10 \begin{code}
11 #include "HsVersions.h"
12
13 module PrimKind (
14         PrimKind(..),
15         separateByPtrFollowness, isFollowableKind, isFloatingKind,
16         getKindSize, retKindSize,
17         getKindInfo, -- ToDo: DIE DIE DIE DIE DIE
18         showPrimKind,
19         guessPrimKind,
20
21         -- and to make the interface self-sufficient...
22         Id, DataCon(..), TyCon, UniType
23     ) where
24
25 IMPORT_Trace
26
27 #ifdef DPH
28 import TyPod
29 #endif {- Data Parallel Haskell -}
30
31 import AbsUniType       -- we use more than I want to type in...
32 import Id               ( Id, DataCon(..) )
33 import Outputable       -- class for printing, forcing
34 import TysPrim
35 import Pretty           -- pretty-printing code
36 import Util
37
38 #ifndef DPH
39 #include "../../includes/GhcConstants.h"
40 #else
41 #include "../dphsystem/imports/DphConstants.h"
42 #endif {- Data Parallel Haskell -}
43 \end{code}
44
45 %************************************************************************
46 %*                                                                      *
47 \subsection[PrimKind-datatype]{The @PrimKind@ datatype}
48 %*                                                                      *
49 %************************************************************************
50
51 \begin{code}
52 data PrimKind
53   = -- These pointer-kinds are all really the same, but we keep
54     -- them separate for documentation purposes.
55     PtrKind             -- Pointer to a closure; a ``word''.
56   | CodePtrKind         -- Pointer to code
57   | DataPtrKind         -- Pointer to data
58   | RetKind             -- Pointer to code or data (return vector or code pointer)
59   | InfoPtrKind         -- Pointer to info table (DPH only?)
60   | CostCentreKind      -- Pointer to a cost centre
61
62   | CharKind            -- Machine characters
63   | IntKind             --         integers (at least 32 bits)
64   | WordKind            --         ditto (but *unsigned*)
65   | AddrKind            --         addresses ("C pointers")
66   | FloatKind           --         floats
67   | DoubleKind          --         doubles
68
69   | MallocPtrKind       -- This has to be a special kind because ccall
70                         -- generates special code when passing/returning
71                         -- one of these. [ADR]
72
73   | StablePtrKind       -- We could replace this with IntKind but maybe
74                         -- there's some documentation gain from having
75                         -- it special? [ADR]
76
77   | ArrayKind           -- Primitive array of Haskell pointers
78   | ByteArrayKind       -- Primitive array of bytes (no Haskell pointers)
79
80   | VoidKind            -- Occupies no space at all!
81                         -- (Primitive states are mapped onto this)
82 #ifdef DPH
83   | PodNKind Int PrimKind
84 #endif {- Data Parallel Haskell -}
85   deriving (Eq, Ord)
86         -- Kinds are used in PrimTyCons, which need both Eq and Ord
87         -- Text is needed for derived-Text on PrimitiveOps
88 \end{code}
89
90 %************************************************************************
91 %*                                                                      *
92 \subsection[PrimKind-predicates]{Follow-ness, sizes, and such---on @PrimitiveKinds@}
93 %*                                                                      *
94 %************************************************************************
95
96 Whether or not the thing is a pointer that the garbage-collector
97 should follow.
98
99 Or, to put it another (less confusing) way, whether the object in
100 question is a heap object.
101
102 \begin{code}
103 isFollowableKind :: PrimKind -> Bool
104 isFollowableKind PtrKind        = True
105 isFollowableKind ArrayKind      = True
106 isFollowableKind ByteArrayKind  = True
107 isFollowableKind MallocPtrKind  = True
108
109 isFollowableKind StablePtrKind  = False
110 -- StablePtrs aren't followable because they are just indices into a
111 -- table for which explicit allocation/ deallocation is required.
112
113 isFollowableKind other          = False
114
115 separateByPtrFollowness :: (a -> PrimKind) -> [a] -> ([a], [a])
116 separateByPtrFollowness kind_fun things
117   = sep_things kind_fun things [] []
118     -- accumulating params for follow-able and don't-follow things...
119   where
120     sep_things kfun []     bs us = (reverse bs, reverse us)
121     sep_things kfun (t:ts) bs us
122       = if (isFollowableKind . kfun) t then
123             sep_things kfun ts (t:bs) us
124         else
125             sep_things kfun ts bs (t:us)
126 \end{code}
127
128 @isFloatingKind@ is used to distinguish @Double@ and @Float@ which
129 cause inadvertent numeric conversions if you aren't jolly careful.
130 See codeGen/CgCon:cgTopRhsCon.
131
132 \begin{code}
133 isFloatingKind :: PrimKind -> Bool
134 isFloatingKind DoubleKind = True
135 isFloatingKind FloatKind  = True
136 isFloatingKind other      = False
137 \end{code}
138
139 \begin{code}
140 getKindSize :: PrimKind -> Int
141 getKindSize DoubleKind    = DOUBLE_SIZE -- "words", of course
142 --getKindSize FloatKind   = 1
143 --getKindSize CharKind    = 1   -- ToDo: count in bytes?
144 --getKindSize ArrayKind   = 1   -- Listed specifically for *documentation*
145 --getKindSize ByteArrayKind = 1
146
147 #ifdef DPH
148 getKindSize (PodNKind _ _) = panic "getKindSize: PodNKind"
149 #endif {- Data Parallel Haskell -}
150
151 getKindSize VoidKind      = 0
152 getKindSize other         = 1
153
154
155 retKindSize :: Int
156 retKindSize = getKindSize RetKind
157 \end{code}
158
159 %************************************************************************
160 %*                                                                      *
161 \subsection[PrimKind-type-fns]{@PrimitiveKinds@ and @UniTypes@}
162 %*                                                                      *
163 %************************************************************************
164
165 @PrimitiveKinds@ are used in @PrimitiveOps@, for which we often need
166 to reconstruct various type information.  (It's slightly more
167 convenient/efficient to make type info from kinds, than kinds [etc.]
168 from type info.)
169
170 \begin{code}
171 getKindInfo ::
172     PrimKind -> (String,                        -- tag string
173                       UniType, TyCon)           -- prim type and tycon
174
175 getKindInfo CharKind   = ("Char",   charPrimTy,   charPrimTyCon)
176 getKindInfo IntKind    = ("Int",    intPrimTy,    intPrimTyCon)
177 getKindInfo WordKind   = ("Word",   wordPrimTy,   wordPrimTyCon)
178 getKindInfo AddrKind   = ("Addr",   addrPrimTy,   addrPrimTyCon)
179 getKindInfo FloatKind  = ("Float",  floatPrimTy,  floatPrimTyCon)
180 getKindInfo DoubleKind = ("Double", doublePrimTy, doublePrimTyCon)
181 #ifdef DPH
182 getKindInfo k@(PodNKind d kind)
183   = case kind of
184       PtrKind   ->(no_no, no_no, no_no, no_no, no_no, no_no)
185       CharKind  ->("Char.Pod"++show d, mkPodizedPodNTy d charPrimTy,
186                     no_no, mkPodizedPodNTy d charTy, no_no, no_no)
187
188       IntKind   ->("Int.Pod"++show d, mkPodizedPodNTy d intPrimTy,
189                     no_no, mkPodizedPodNTy d intTy, no_no , no_no)
190
191       FloatKind ->("Float.Pod"++show d, mkPodizedPodNTy d floatPrimTy,
192                     no_no ,mkPodizedPodNTy d floatTy, no_no, no_no)
193
194       DoubleKind->("Double.Pod"++show d, mkPodizedPodNTy d doublePrimTy,
195                     no_no, mkPodizedPodNTy d doubleTy, no_no, no_no)
196       AddrKind  ->("Addr.Pod"++show d, mkPodizedPodNTy d addrPrimTy,
197                       no_no, no_no, no_no, no_no)
198       _         -> pprPanic "Found PodNKind" (ppr PprDebug k)
199    where
200      no_no = panic "getKindInfo: PodNKind"
201
202 getKindInfo other = pprPanic "getKindInfo" (ppr PprDebug other)
203 #endif {- Data Parallel Haskell -}
204 \end{code}
205
206 %************************************************************************
207 %*                                                                      *
208 \subsection[PrimKind-instances]{Boring instance decls for @PrimKind@}
209 %*                                                                      *
210 %************************************************************************
211
212 \begin{code}
213 instance Outputable PrimKind where
214 #ifdef DPH
215     ppr sty (PodNKind d k)  = ppBesides [ppr sty k , ppStr ".POD" , ppr sty d]
216 #endif {- Data Parallel Haskell -}
217     ppr sty kind = ppStr (showPrimKind kind)
218
219 showPrimKind  :: PrimKind -> String
220 guessPrimKind :: String -> PrimKind     -- a horrible "inverse" function
221
222 showPrimKind PtrKind        = "P_"      -- short for StgPtr
223
224 showPrimKind CodePtrKind    = "P_"      -- DEATH to StgFunPtr! (94/02/22 WDP)
225     -- but aren't code pointers and function pointers different sizes
226     -- on some machines (eg 80x86)? ADR
227     -- Are you trying to ruin my life, or what? (WDP)
228
229 showPrimKind DataPtrKind    = "D_"
230 showPrimKind RetKind        = "StgRetAddr"
231 showPrimKind InfoPtrKind    = "StgInfoPtr"
232 showPrimKind CostCentreKind = "CostCentre"
233 showPrimKind CharKind       = "StgChar"
234 showPrimKind IntKind        = "I_"      -- short for StgInt
235 showPrimKind WordKind       = "W_"      -- short for StgWord
236 showPrimKind AddrKind       = "StgAddr"
237 showPrimKind FloatKind      = "StgFloat"
238 showPrimKind DoubleKind     = "StgDouble"
239 showPrimKind ArrayKind      = "StgArray" -- see comment below
240 showPrimKind ByteArrayKind  = "StgByteArray"
241 showPrimKind StablePtrKind  = "StgStablePtr"
242 showPrimKind MallocPtrKind  = "StgPtr" -- see comment below
243 showPrimKind VoidKind       = "!!VOID_KIND!!"
244
245 guessPrimKind "D_"           = DataPtrKind
246 guessPrimKind "StgRetAddr"   = RetKind
247 guessPrimKind "StgInfoPtr"   = InfoPtrKind
248 guessPrimKind "StgChar"      = CharKind
249 guessPrimKind "I_"           = IntKind
250 guessPrimKind "W_"           = WordKind
251 guessPrimKind "StgAddr"      = AddrKind
252 guessPrimKind "StgFloat"     = FloatKind
253 guessPrimKind "StgDouble"    = DoubleKind
254 guessPrimKind "StgArray"     = ArrayKind
255 guessPrimKind "StgByteArray" = ByteArrayKind
256 guessPrimKind "StgStablePtr" = StablePtrKind
257 \end{code}
258
259 All local C variables of @ArrayKind@ are declared in C as type
260 @StgArray@.  The coercion to a more precise C type is done just before
261 indexing (by the relevant C primitive-op macro).
262
263 Nota Bene. There are three types associated with Malloc Pointers: 
264 \begin{itemize}
265 \item
266 @StgMallocClosure@ is the type of the thing the C world gives us.
267 (This typename is hardwired into @ppr_casm_results@ in
268 @PprAbsC.lhs@.)
269
270 \item
271 @StgMallocPtr@ is the type of the thing we give the C world.
272
273 \item
274 @StgPtr@ is the type of the (pointer to the) heap object which we
275 pass around inside the STG machine.
276 \end{itemize}
277
278 It is really easy to confuse the two.  (I'm not sure this choice of
279 type names helps.) [ADR]