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