[project @ 1997-09-03 23:52:17 by sof]
[ghc-hetmet.git] / ghc / compiler / prelude / PrimRep.lhs
1 %
2 % (c) The GRASP Project, Glasgow University, 1992-1996
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 #include "HsVersions.h"
12
13 module PrimRep (
14         PrimRep(..),
15
16         separateByPtrFollowness, isFollowableRep, isFloatingRep,
17         getPrimRepSize, retPrimRepSize,
18         showPrimRep,  ppPrimRep,
19         guessPrimRep, decodePrimRep
20     ) where
21
22 IMP_Ubiq()
23
24 import Pretty           -- pretty-printing code
25 import Util
26 #if __GLASGOW_HASKELL__ >= 202
27 import Outputable
28 #endif
29
30 -- Oh dear.
31 #include "../../includes/GhcConstants.h"
32 \end{code}
33
34 %************************************************************************
35 %*                                                                      *
36 \subsection[PrimRep-datatype]{The @PrimRep@ datatype}
37 %*                                                                      *
38 %************************************************************************
39
40 \begin{code}
41 data PrimRep
42   = -- These pointer-kinds are all really the same, but we keep
43     -- them separate for documentation purposes.
44     PtrRep              -- Pointer to a closure; a ``word''.
45   | CodePtrRep          -- Pointer to code
46   | DataPtrRep          -- Pointer to data
47   | RetRep              -- Pointer to code or data (return vector or code pointer)
48   | CostCentreRep       -- Pointer to a cost centre
49
50   | CharRep             -- Machine characters
51   | IntRep              --         integers (at least 32 bits)
52   | WordRep             --         ditto (but *unsigned*)
53   | AddrRep             --         addresses ("C pointers")
54   | FloatRep            --         floats
55   | DoubleRep           --         doubles
56
57   | ForeignObjRep       -- This has to be a special kind because ccall
58                         -- generates special code when passing/returning
59                         -- one of these. [ADR]
60
61   | StablePtrRep        -- We could replace this with IntRep but maybe
62                         -- there's some documentation gain from having
63                         -- it special? [ADR]
64
65   | ArrayRep            -- Primitive array of Haskell pointers
66   | ByteArrayRep        -- Primitive array of bytes (no Haskell pointers)
67
68   | VoidRep             -- Occupies no space at all!
69                         -- (Primitive states are mapped onto this)
70   deriving (Eq, Ord)
71         -- Kinds are used in PrimTyCons, which need both Eq and Ord
72 \end{code}
73
74 %************************************************************************
75 %*                                                                      *
76 \subsection[PrimRep-predicates]{Follow-ness, sizes, and such---on @PrimitiveKinds@}
77 %*                                                                      *
78 %************************************************************************
79
80 Whether or not the thing is a pointer that the garbage-collector
81 should follow. Or, to put it another (less confusing) way, whether
82 the object in question is a heap object. 
83
84 Depending on the outcome, this predicate determines what stack
85 the pointer/object possibly will have to be saved onto, and the
86 computation of GC liveness info.
87
88 \begin{code}
89 isFollowableRep :: PrimRep -> Bool
90
91 isFollowableRep PtrRep        = True
92 isFollowableRep ArrayRep      = True
93 isFollowableRep ByteArrayRep  = True
94 -- why is a ForeignObj followable? 4/96 SOF
95 --
96 -- A: they're followable because these objects
97 -- should be lugged around by the storage manager
98 -- (==> registers containing them are live) -- 3/97 SOF
99 isFollowableRep ForeignObjRep  = True
100
101 isFollowableRep StablePtrRep  = False
102 -- StablePtrs aren't followable because they are just indices into a
103 -- table for which explicit allocation/ deallocation is required.
104
105 isFollowableRep other           = False
106
107 separateByPtrFollowness :: (a -> PrimRep) -> [a] -> ([a], [a])
108
109 separateByPtrFollowness kind_fun things
110   = sep_things kind_fun things [] []
111     -- accumulating params for follow-able and don't-follow things...
112   where
113     sep_things kfun []     bs us = (reverse bs, reverse us)
114     sep_things kfun (t:ts) bs us
115       = if (isFollowableRep . kfun) t then
116             sep_things kfun ts (t:bs) us
117         else
118             sep_things kfun ts bs (t:us)
119 \end{code}
120
121 @isFloatingRep@ is used to distinguish @Double@ and @Float@ which
122 cause inadvertent numeric conversions if you aren't jolly careful.
123 See codeGen/CgCon:cgTopRhsCon.
124
125 \begin{code}
126 isFloatingRep :: PrimRep -> Bool
127
128 isFloatingRep DoubleRep = True
129 isFloatingRep FloatRep  = True
130 isFloatingRep other     = False
131 \end{code}
132
133 \begin{code}
134 getPrimRepSize :: PrimRep -> Int
135
136 getPrimRepSize DoubleRep  = DOUBLE_SIZE -- "words", of course
137 --getPrimRepSize FloatRep = 1
138 --getPrimRepSize CharRep  = 1   -- ToDo: count in bytes?
139 --getPrimRepSize ArrayRep = 1   -- Listed specifically for *documentation*
140 --getPrimRepSize ByteArrayRep = 1
141 getPrimRepSize VoidRep    = 0
142 getPrimRepSize other      = 1
143
144 retPrimRepSize = getPrimRepSize RetRep
145 \end{code}
146
147 %************************************************************************
148 %*                                                                      *
149 \subsection[PrimRep-instances]{Boring instance decls for @PrimRep@}
150 %*                                                                      *
151 %************************************************************************
152
153 \begin{code}
154 instance Outputable PrimRep where
155     ppr sty kind = text (showPrimRep kind)
156
157 showPrimRep  :: PrimRep -> String
158 -- dumping PrimRep tag for unfoldings
159 ppPrimRep  :: PrimRep -> Doc
160
161 guessPrimRep :: String -> PrimRep       -- a horrible "inverse" function
162 decodePrimRep :: Char  -> PrimRep       -- of equal nature
163
164 ppPrimRep k =
165  char 
166   (case k of
167      PtrRep        -> 'P'
168      CodePtrRep    -> 'p'
169      DataPtrRep    -> 'd'
170      CostCentreRep -> 'c'       -- Pointer to a cost centre
171      RetRep        -> 'R'
172      CharRep       -> 'C'
173      IntRep        -> 'I'
174      WordRep       -> 'W'
175      AddrRep       -> 'A'
176      FloatRep      -> 'F'
177      DoubleRep     -> 'D'
178      ArrayRep      -> 'a'
179      ByteArrayRep  -> 'b'
180      StablePtrRep  -> 'S'
181      ForeignObjRep -> 'f'
182      VoidRep       -> 'V'
183      _             -> panic "ppPrimRep")
184
185 showPrimRep PtrRep          = "P_"      -- short for StgPtr
186
187 showPrimRep CodePtrRep    = "P_"        -- DEATH to StgFunPtr! (94/02/22 WDP)
188     -- but aren't code pointers and function pointers different sizes
189     -- on some machines (eg 80x86)? ADR
190     -- Are you trying to ruin my life, or what? (WDP)
191
192 showPrimRep DataPtrRep    = "D_"
193 showPrimRep RetRep        = "StgRetAddr"
194 showPrimRep CostCentreRep = "CostCentre"
195 showPrimRep CharRep       = "StgChar"
196 showPrimRep IntRep        = "I_"        -- short for StgInt
197 showPrimRep WordRep       = "W_"        -- short for StgWord
198 showPrimRep AddrRep       = "StgAddr"
199 showPrimRep FloatRep      = "StgFloat"
200 showPrimRep DoubleRep     = "StgDouble"
201 showPrimRep ArrayRep      = "StgArray" -- see comment below
202 showPrimRep ByteArrayRep  = "StgByteArray"
203 showPrimRep StablePtrRep  = "StgStablePtr"
204 showPrimRep ForeignObjRep  = "StgPtr" -- see comment below
205 showPrimRep VoidRep       = "!!VOID_KIND!!"
206
207 decodePrimRep ch =
208  case ch of
209      'P' -> PtrRep        
210      'p' -> CodePtrRep    
211      'd' -> DataPtrRep    
212      'c' -> CostCentreRep 
213      'R' -> RetRep        
214      'C' -> CharRep       
215      'I' -> IntRep        
216      'W' -> WordRep       
217      'A' -> AddrRep       
218      'F' -> FloatRep      
219      'D' -> DoubleRep     
220      'a' -> ArrayRep      
221      'b' -> ByteArrayRep  
222      'S' -> StablePtrRep  
223      'f' -> ForeignObjRep 
224      'V' -> VoidRep
225      _   -> panic "decodePrimRep"
226
227 guessPrimRep "D_"            = DataPtrRep
228 guessPrimRep "StgRetAddr"   = RetRep
229 guessPrimRep "StgChar"       = CharRep
230 guessPrimRep "I_"            = IntRep
231 guessPrimRep "W_"            = WordRep
232 guessPrimRep "StgAddr"       = AddrRep
233 guessPrimRep "StgFloat"     = FloatRep
234 guessPrimRep "StgDouble"    = DoubleRep
235 guessPrimRep "StgArray"     = ArrayRep
236 guessPrimRep "StgByteArray" = ByteArrayRep
237 guessPrimRep "StgStablePtr" = StablePtrRep
238 \end{code}
239
240 All local C variables of @ArrayRep@ are declared in C as type
241 @StgArray@.  The coercion to a more precise C type is done just before
242 indexing (by the relevant C primitive-op macro).
243
244 Nota Bene. There are three types associated with @ForeignObj@ (MallocPtr++): 
245 \begin{itemize}
246 \item
247 @StgForeignObjClosure@ is the type of the thing the prim. op @mkForeignObj@ returns.
248 {- old comment for MallocPtr
249 (This typename is hardwired into @ppr_casm_results@ in
250 @PprAbsC.lhs@.)
251 -}
252
253 \item
254 @StgForeignObj@ is the type of the thing we give the C world.
255
256 \item
257 @StgPtr@ is the type of the (pointer to the) heap object which we
258 pass around inside the STG machine.
259 \end{itemize}
260
261 It is really easy to confuse the two.  (I'm not sure this choice of
262 type names helps.) [ADR]