[project @ 2000-09-06 10:23:52 by simonmar]
[ghc-hetmet.git] / ghc / compiler / prelude / PrimRep.lhs
1 %
2 % (c) The GRASP Project, Glasgow University, 1992-1998
3 %
4 \section[PrimRep]{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 module PrimRep 
12       (
13         PrimRep(..)
14       , separateByPtrFollowness
15       , isFollowableRep
16       , isFloatingRep
17       , is64BitRep
18       , getPrimRepSize
19       , getPrimRepSizeInBytes
20       , retPrimRepSize
21       , showPrimRep
22       , primRepString
23       , showPrimRepToUser
24       ) where
25
26 #include "HsVersions.h"
27
28 import Constants ( dOUBLE_SIZE, iNT64_SIZE, wORD64_SIZE, wORD_SIZE )
29 import Outputable
30 \end{code}
31
32 %************************************************************************
33 %*                                                                      *
34 \subsection[PrimRep-datatype]{The @PrimRep@ datatype}
35 %*                                                                      *
36 %************************************************************************
37
38 \begin{code}
39 data PrimRep
40   = -- These pointer-kinds are all really the same, but we keep
41     -- them separate for documentation purposes.
42     PtrRep              -- Pointer to a closure; a ``word''.
43   | CodePtrRep          -- Pointer to code
44   | DataPtrRep          -- Pointer to data
45   | RetRep              -- Pointer to code or data (return vector or code pointer)
46   | CostCentreRep       -- Pointer to a cost centre
47
48   | CharRep             -- Machine characters
49   | Int8Rep             --         8 bit integers
50   | IntRep              --         integers (same size as ptr on this arch)
51   | WordRep             --         ditto (but *unsigned*)
52   | AddrRep             --         addresses ("C pointers")
53   | FloatRep            --         floats
54   | DoubleRep           --         doubles
55   | Word64Rep           --    guaranteed to be 64 bits (no more, no less.)
56   | Int64Rep            --    guaranteed to be 64 bits (no more, no less.)
57   
58   -- Perhaps all sized integers and words should be primitive types.
59   
60   -- Int8Rep is currently used to simulate some old CharRep usages
61   -- when Char changed size from 8 to 31 bits. It does not correspond
62   -- to a Haskell unboxed type, in particular it's not used by Int8.
63   
64   | WeakPtrRep
65   | ForeignObjRep       
66   | BCORep
67
68   | StablePtrRep        -- guaranteed to be represented by a pointer
69
70   | StableNameRep       -- A stable name is a real heap object, unpointed,
71                         -- with one field containing an index into the
72                         -- stable pointer table.  It has to be a heap
73                         -- object so the garbage collector can track these
74                         -- objects and reclaim stable pointer entries.
75
76   | ThreadIdRep         -- Really a pointer to a TSO
77
78   | ArrayRep            -- Primitive array of Haskell pointers
79   | ByteArrayRep        -- Primitive array of bytes (no Haskell pointers)
80
81   | PrimPtrRep          -- Used for MutVars and MVars; 
82                         -- a pointer to a primitive object
83                         -- ToDo: subsumes WeakPtrRep, ThreadIdRep, 
84                         -- StableNameRep, ForeignObjRep, and BCORep ?
85
86   | VoidRep             -- Occupies no space at all!
87                         -- (Primitive states are mapped onto this)
88   deriving (Eq, Ord)
89         -- Kinds are used in PrimTyCons, which need both Eq and Ord
90 \end{code}
91
92 These pretty much correspond to the C types declared in StgTypes.h,
93 with the following exceptions:
94
95    - when an Array or ByteArray is passed to C, we again pass a pointer
96      to the contents.  The actual type that is passed is StgPtr for
97      ArrayRep, and StgByteArray (probably a char *) for ByteArrayRep.
98
99 These hacks are left until the final printing of the C, in
100 PprAbsC.lhs.
101
102 %************************************************************************
103 %*                                                                      *
104 \subsection[PrimRep-predicates]{Follow-ness, sizes, and such---on @PrimitiveKinds@}
105 %*                                                                      *
106 %************************************************************************
107
108 Whether or not the thing is a pointer that the garbage-collector
109 should follow. Or, to put it another (less confusing) way, whether
110 the object in question is a heap object. 
111
112 Depending on the outcome, this predicate determines what stack
113 the pointer/object possibly will have to be saved onto, and the
114 computation of GC liveness info.
115
116 \begin{code}
117 isFollowableRep :: PrimRep -> Bool
118
119 isFollowableRep PtrRep        = True
120 isFollowableRep ArrayRep      = True    -- all heap objects:
121 isFollowableRep ByteArrayRep  = True    --      ''
122 isFollowableRep WeakPtrRep    = True    --      ''
123 isFollowableRep ForeignObjRep = True    --      ''
124 isFollowableRep StableNameRep = True    --      ''
125 isFollowableRep PrimPtrRep    = True    --      ''
126 isFollowableRep ThreadIdRep   = True    -- pointer to a TSO
127
128 isFollowableRep other         = False
129
130 separateByPtrFollowness :: (a -> PrimRep) -> [a] -> ([a], [a])
131
132 separateByPtrFollowness kind_fun things
133   = sep_things kind_fun things [] []
134     -- accumulating params for follow-able and don't-follow things...
135   where
136     sep_things kfun []     bs us = (reverse bs, reverse us)
137     sep_things kfun (t:ts) bs us
138       = if (isFollowableRep . kfun) t then
139             sep_things kfun ts (t:bs) us
140         else
141             sep_things kfun ts bs (t:us)
142 \end{code}
143
144 @isFloatingRep@ is used to distinguish @Double@ and @Float@ which
145 cause inadvertent numeric conversions if you aren't jolly careful.
146 See codeGen/CgCon:cgTopRhsCon.
147
148 \begin{code}
149 isFloatingRep :: PrimRep -> Bool
150
151 isFloatingRep DoubleRep = True
152 isFloatingRep FloatRep  = True
153 isFloatingRep other     = False
154
155 \end{code}
156
157 \begin{code}
158 is64BitRep :: PrimRep -> Bool
159
160 is64BitRep Int64Rep  = True
161 is64BitRep Word64Rep = True
162 is64BitRep other     = False
163
164 \end{code}
165
166
167
168 \begin{code}
169 getPrimRepSize :: PrimRep -> Int
170
171 getPrimRepSize DoubleRep  = dOUBLE_SIZE -- "words", of course
172 getPrimRepSize Word64Rep  = wORD64_SIZE
173 getPrimRepSize Int64Rep   = iNT64_SIZE
174 --getPrimRepSize FloatRep = 1
175 --getPrimRepSize CharRep  = 1   -- ToDo: count in bytes?
176 --getPrimRepSize ArrayRep = 1   -- Listed specifically for *documentation*
177 --getPrimRepSize ByteArrayRep = 1
178 getPrimRepSize VoidRep    = 0
179 getPrimRepSize other      = 1
180
181 retPrimRepSize = getPrimRepSize RetRep
182
183 -- sizes in bytes.
184 -- (used in some settings to figure out how many bytes
185 -- we have to push onto the stack when calling external
186 -- entry points (e.g., stdcalling on win32)
187 getPrimRepSizeInBytes :: PrimRep -> Int
188 getPrimRepSizeInBytes pr =
189  case pr of
190     CharRep        ->    4
191     Int8Rep        ->    1
192     IntRep         ->    wORD_SIZE
193     AddrRep        ->    wORD_SIZE
194     FloatRep       ->    wORD_SIZE
195     DoubleRep      ->    dOUBLE_SIZE * wORD_SIZE
196     Word64Rep      ->    wORD64_SIZE * wORD_SIZE
197     Int64Rep       ->    iNT64_SIZE * wORD_SIZE
198     WeakPtrRep     ->    wORD_SIZE
199     ForeignObjRep  ->    wORD_SIZE
200     StablePtrRep   ->    wORD_SIZE
201     StableNameRep  ->    wORD_SIZE
202     ArrayRep       ->    wORD_SIZE
203     ByteArrayRep   ->    wORD_SIZE
204     _              ->    panic "getPrimRepSize: ouch - this wasn't supposed to happen!"
205
206 \end{code}
207
208 %************************************************************************
209 %*                                                                      *
210 \subsection[PrimRep-instances]{Boring instance decls for @PrimRep@}
211 %*                                                                      *
212 %************************************************************************
213
214 \begin{code}
215 instance Outputable PrimRep where
216     ppr kind = text (showPrimRep kind)
217
218 showPrimRep  :: PrimRep -> String
219 showPrimRepToUser :: PrimRep -> String
220
221 showPrimRep PtrRep         = "P_"       -- short for StgPtr
222 showPrimRep CodePtrRep     = "P_"       -- DEATH to StgFunPtr! (94/02/22 WDP)
223 showPrimRep DataPtrRep     = "D_"
224 showPrimRep RetRep         = "P_"
225 showPrimRep CostCentreRep  = "CostCentre"
226 showPrimRep CharRep        = "C_"
227 showPrimRep Int8Rep        = "StgInt8"
228 showPrimRep IntRep         = "I_"       -- short for StgInt
229 showPrimRep WordRep        = "W_"       -- short for StgWord
230 showPrimRep Int64Rep       = "LI_"       -- short for StgLongInt
231 showPrimRep Word64Rep      = "LW_"       -- short for StgLongWord
232 showPrimRep AddrRep        = "StgAddr"
233 showPrimRep FloatRep       = "StgFloat"
234 showPrimRep DoubleRep      = "StgDouble"
235 showPrimRep ArrayRep       = "P_" -- see comment below
236 showPrimRep PrimPtrRep     = "P_"
237 showPrimRep ByteArrayRep   = "StgByteArray"
238 showPrimRep StablePtrRep   = "StgStablePtr"
239 showPrimRep StableNameRep  = "P_"
240 showPrimRep ThreadIdRep    = "StgTSO*"
241 showPrimRep WeakPtrRep     = "P_"
242 showPrimRep ForeignObjRep  = "StgAddr"
243 showPrimRep VoidRep        = "!!VOID_KIND!!"
244
245 primRepString CharRep           = "Char"
246 primRepString Int8Rep           = "Char" -- To have names like newCharArray#
247 primRepString IntRep            = "Int"
248 primRepString WordRep           = "Word"
249 primRepString Int64Rep          = "Int64"
250 primRepString Word64Rep         = "Word64"
251 primRepString AddrRep           = "Addr"
252 primRepString FloatRep          = "Float"
253 primRepString DoubleRep         = "Double"
254 primRepString WeakPtrRep        = "Weak"
255 primRepString ForeignObjRep     = "ForeignObj"
256 primRepString StablePtrRep      = "StablePtr"
257 primRepString StableNameRep     = "StableName"
258 primRepString other             = pprPanic "primRepString" (ppr other)
259
260 showPrimRepToUser pr = primRepString pr
261 \end{code}
262
263 Foreign Objects and Arrays are treated specially by the code for
264 _ccall_s: we pass a pointer to the contents of the object, not the
265 object itself.