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