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