a58240bdc21440df2b5548d916e5b6a87367f418
[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         PrimRep(..),
13         separateByPtrFollowness,
14         isFollowableRep,
15         isFloatingRep,
16         isNonPtrRep,     
17         is64BitRep,
18         getPrimRepSize,
19         getPrimRepSizeInBytes,
20         retPrimRepSize,
21
22         ArgRep(..), primRepToArgRep,
23  ) where
24
25 #include "HsVersions.h"
26
27 import Constants ( dOUBLE_SIZE, iNT64_SIZE, wORD64_SIZE, wORD_SIZE )
28 import Outputable
29 \end{code}
30
31 %************************************************************************
32 %*                                                                      *
33 \subsection[PrimRep-datatype]{The @PrimRep@ datatype}
34 %*                                                                      *
35 %************************************************************************
36
37 These pretty much correspond to the C types declared in StgTypes.h.
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   | IntRep              --         signed   integers (same size as ptr on this arch)
51   | WordRep             --         unsigned integers (same size as ptr on this arch)
52   | AddrRep             --         addresses (C pointers)
53   | FloatRep            --         floats
54   | DoubleRep           --         doubles
55
56   | Int8Rep             --          8 bit signed   integers
57   | Int16Rep            --         16 bit signed   integers
58   | Int32Rep            --         32 bit signed   integers
59   | Int64Rep            --         64 bit signed   integers
60   | Word8Rep            --          8 bit unsigned integers
61   | Word16Rep           --         16 bit unsigned integers
62   | Word32Rep           --         32 bit unsigned integers
63   | Word64Rep           --         64 bit unsigned integers
64
65   | StablePtrRep        -- guaranteed to be represented by a pointer
66
67   | VoidRep             -- Occupies no space at all!
68                         -- (Primitive states are mapped onto this)
69   deriving (Eq, Ord)
70 \end{code}
71
72
73 %************************************************************************
74 %*                                                                      *
75 \subsection[PrimRep-predicates]{Follow-ness, sizes, and such---on @PrimitiveKinds@}
76 %*                                                                      *
77 %************************************************************************
78
79 Whether or not the thing is a pointer that the garbage-collector
80 should follow. Or, to put it another (less confusing) way, whether
81 the object in question is a heap object. 
82
83 Depending on the outcome, this predicate determines what stack
84 the pointer/object possibly will have to be saved onto, and the
85 computation of GC liveness info.
86
87 \begin{code}
88 isFollowableRep :: PrimRep -> Bool  -- True <=> points to a heap object
89 isFollowableRep PtrRep        = True
90 isFollowableRep other         = False
91
92 separateByPtrFollowness :: (a -> PrimRep) -> [a] -> ([a], [a])
93 separateByPtrFollowness kind_fun things
94   = sep_things kind_fun things [] []
95     -- accumulating params for follow-able and don't-follow things...
96   where
97     sep_things kfun []     bs us = (reverse bs, reverse us)
98     sep_things kfun (t:ts) bs us
99       = if (isFollowableRep . kfun) t then
100             sep_things kfun ts (t:bs) us
101         else
102             sep_things kfun ts bs (t:us)
103 \end{code}
104
105 @isFloatingRep@ is used to distinguish @Double@ and @Float@ which
106 cause inadvertent numeric conversions if you aren't jolly careful.
107 See codeGen/CgCon:cgTopRhsCon.
108
109 \begin{code}
110 isFloatingRep :: PrimRep -> Bool
111 isFloatingRep DoubleRep = True
112 isFloatingRep FloatRep  = True
113 isFloatingRep _         = False
114 \end{code}
115
116 Identify anything which is one word large and not a pointer.
117
118 \begin{code}
119 isNonPtrRep :: PrimRep -> Bool
120 isNonPtrRep PtrRep  = False
121 isNonPtrRep VoidRep = False
122 isNonPtrRep r       = not (isFloatingRep r) && not (is64BitRep r)
123 \end{code}
124
125 \begin{code}
126 is64BitRep :: PrimRep -> Bool
127 is64BitRep Int64Rep  = True
128 is64BitRep Word64Rep = True
129 is64BitRep _         = False
130
131 -- Size in words.
132
133 getPrimRepSize :: PrimRep -> Int
134 getPrimRepSize DoubleRep = dOUBLE_SIZE
135 getPrimRepSize Word64Rep = wORD64_SIZE
136 getPrimRepSize Int64Rep  = iNT64_SIZE
137 getPrimRepSize VoidRep   = 0
138 getPrimRepSize _         = 1
139
140 retPrimRepSize :: Int
141 retPrimRepSize = getPrimRepSize RetRep
142
143 -- Sizes in bytes.  (used in some settings to figure out how many
144 -- bytes we have to push onto the stack when calling external entry
145 -- points (e.g., stdcalling on win32)
146
147 -- Note: the "size in bytes" is also the scaling factor used when we
148 -- have an array of these things.  For example, a ByteArray# of
149 -- Int16Rep will use a scaling factor of 2 when accessing the
150 -- elements.
151
152 getPrimRepSizeInBytes :: PrimRep -> Int
153 getPrimRepSizeInBytes PtrRep        = wORD_SIZE
154 getPrimRepSizeInBytes CodePtrRep    = wORD_SIZE
155 getPrimRepSizeInBytes DataPtrRep    = wORD_SIZE
156 getPrimRepSizeInBytes RetRep        = wORD_SIZE
157 getPrimRepSizeInBytes CostCentreRep = wORD_SIZE
158 getPrimRepSizeInBytes CharRep       = 4
159 getPrimRepSizeInBytes IntRep        = wORD_SIZE
160 getPrimRepSizeInBytes WordRep       = wORD_SIZE
161 getPrimRepSizeInBytes AddrRep       = wORD_SIZE
162 getPrimRepSizeInBytes FloatRep      = wORD_SIZE
163 getPrimRepSizeInBytes DoubleRep     = dOUBLE_SIZE * wORD_SIZE
164 getPrimRepSizeInBytes Int8Rep       = 1
165 getPrimRepSizeInBytes Int16Rep      = 2
166 getPrimRepSizeInBytes Int32Rep      = 4
167 getPrimRepSizeInBytes Int64Rep      = 8
168 getPrimRepSizeInBytes Word8Rep      = 1
169 getPrimRepSizeInBytes Word16Rep     = 2
170 getPrimRepSizeInBytes Word32Rep     = 4
171 getPrimRepSizeInBytes Word64Rep     = 8
172 getPrimRepSizeInBytes StablePtrRep  = wORD_SIZE
173 getPrimRepSizeInBytes other         = pprPanic "getPrimRepSizeInBytes" (ppr other)
174 \end{code}
175
176 %************************************************************************
177 %*                                                                      *
178 \subsection{ArgReps}
179 %*                                                                      *
180 %************************************************************************
181
182 An ArgRep is similar to a PrimRep, except that it is slightly
183 narrower.  It corresponds to the distinctions we make between
184 different type of function arguments for the purposes of a function's
185 calling convention.  These reps are used to decide which of the RTS's
186 generic apply functions to call when applying an unknown function.
187
188 All 64-bit PrimReps map to the same ArgRep, because they're passed in
189 the same register, but a PtrRep is still different from an IntRep
190 (RepP vs. RepN respectively) because the function's entry convention
191 has to take into account the pointer-hood of arguments for the
192 purposes of describing the stack on entry to the garbage collector.
193
194 \begin{code}
195 data ArgRep = RepV | RepP | RepN | RepF | RepD | RepL
196
197 primRepToArgRep VoidRep   = RepV
198 primRepToArgRep FloatRep  = RepF
199 primRepToArgRep DoubleRep = RepD
200 primRepToArgRep r
201    | isFollowableRep r     = RepP
202    | is64BitRep r          = RepL
203    | otherwise             = ASSERT(getPrimRepSize r == 1) RepN
204 \end{code}
205
206 %************************************************************************
207 %*                                                                      *
208 \subsection[PrimRep-instances]{Boring instance decls for @PrimRep@}
209 %*                                                                      *
210 %************************************************************************
211
212 \begin{code}
213 instance Outputable PrimRep where
214     ppr kind = text (showPrimRep kind)
215
216 showPrimRep  :: PrimRep -> String
217 showPrimRep PtrRep         = "P_"       -- short for StgPtr
218 showPrimRep CodePtrRep     = "P_"       -- DEATH to StgFunPtr! (94/02/22 WDP)
219 showPrimRep DataPtrRep     = "D_"
220 showPrimRep RetRep         = "P_"
221 showPrimRep CostCentreRep  = "CostCentre"
222 showPrimRep CharRep        = "C_"
223 showPrimRep Int8Rep        = "StgInt8"
224 showPrimRep Int16Rep       = "StgInt16"
225 showPrimRep Int32Rep       = "StgInt32"
226 showPrimRep Word8Rep       = "StgWord8"
227 showPrimRep Word16Rep      = "StgWord16"
228 showPrimRep Word32Rep      = "StgWord32"
229 showPrimRep IntRep         = "I_"       -- short for StgInt
230 showPrimRep WordRep        = "W_"       -- short for StgWord
231 showPrimRep Int64Rep       = "LI_"       -- short for StgLongInt
232 showPrimRep Word64Rep      = "LW_"       -- short for StgLongWord
233 showPrimRep AddrRep        = "StgAddr"
234 showPrimRep FloatRep       = "StgFloat"
235 showPrimRep DoubleRep      = "StgDouble"
236 showPrimRep StablePtrRep   = "StgStablePtr"
237 showPrimRep VoidRep        = "!!VOID_KIND!!"
238 \end{code}
239
240