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