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