[project @ 2002-08-02 13:08:33 by simonmar]
[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       , is64BitRep
17       , getPrimRepSize
18       , getPrimRepSizeInBytes
19       , retPrimRepSize
20       ) where
21
22 #include "HsVersions.h"
23
24 import Constants ( dOUBLE_SIZE, iNT64_SIZE, wORD64_SIZE, wORD_SIZE )
25 import Outputable
26 \end{code}
27
28 %************************************************************************
29 %*                                                                      *
30 \subsection[PrimRep-datatype]{The @PrimRep@ datatype}
31 %*                                                                      *
32 %************************************************************************
33
34 These pretty much correspond to the C types declared in StgTypes.h.
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              --         signed   integers (same size as ptr on this arch)
48   | WordRep             --         unsigned integers (same size as ptr on this arch)
49   | AddrRep             --         addresses (C pointers)
50   | FloatRep            --         floats
51   | DoubleRep           --         doubles
52
53   | Int8Rep             --          8 bit signed   integers
54   | Int16Rep            --         16 bit signed   integers
55   | Int32Rep            --         32 bit signed   integers
56   | Int64Rep            --         64 bit signed   integers
57   | Word8Rep            --          8 bit unsigned integers
58   | Word16Rep           --         16 bit unsigned integers
59   | Word32Rep           --         32 bit unsigned integers
60   | Word64Rep           --         64 bit unsigned integers
61
62   | StablePtrRep        -- guaranteed to be represented by a pointer
63
64   | VoidRep             -- Occupies no space at all!
65                         -- (Primitive states are mapped onto this)
66   deriving (Eq, Ord)
67 \end{code}
68
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. Or, to put it another (less confusing) way, whether
78 the object in question is a heap object. 
79
80 Depending on the outcome, this predicate determines what stack
81 the pointer/object possibly will have to be saved onto, and the
82 computation of GC liveness info.
83
84 \begin{code}
85 isFollowableRep :: PrimRep -> Bool  -- True <=> points to a heap object
86 isFollowableRep PtrRep        = True
87 isFollowableRep other         = False
88
89 separateByPtrFollowness :: (a -> PrimRep) -> [a] -> ([a], [a])
90 separateByPtrFollowness kind_fun things
91   = sep_things kind_fun things [] []
92     -- accumulating params for follow-able and don't-follow things...
93   where
94     sep_things kfun []     bs us = (reverse bs, reverse us)
95     sep_things kfun (t:ts) bs us
96       = if (isFollowableRep . kfun) t then
97             sep_things kfun ts (t:bs) us
98         else
99             sep_things kfun ts bs (t:us)
100 \end{code}
101
102 @isFloatingRep@ is used to distinguish @Double@ and @Float@ which
103 cause inadvertent numeric conversions if you aren't jolly careful.
104 See codeGen/CgCon:cgTopRhsCon.
105
106 \begin{code}
107 isFloatingRep :: PrimRep -> Bool
108 isFloatingRep DoubleRep = True
109 isFloatingRep FloatRep  = True
110 isFloatingRep _         = False
111 \end{code}
112
113 \begin{code}
114 is64BitRep :: PrimRep -> Bool
115 is64BitRep Int64Rep  = True
116 is64BitRep Word64Rep = True
117 is64BitRep _         = False
118
119 -- Size in words.
120
121 getPrimRepSize :: PrimRep -> Int
122 getPrimRepSize DoubleRep = dOUBLE_SIZE
123 getPrimRepSize Word64Rep = wORD64_SIZE
124 getPrimRepSize Int64Rep  = iNT64_SIZE
125 getPrimRepSize VoidRep   = 0
126 getPrimRepSize _         = 1
127
128 retPrimRepSize :: Int
129 retPrimRepSize = getPrimRepSize RetRep
130
131 -- Sizes in bytes.  (used in some settings to figure out how many
132 -- bytes we have to push onto the stack when calling external entry
133 -- points (e.g., stdcalling on win32)
134
135 -- Note: the "size in bytes" is also the scaling factor used when we
136 -- have an array of these things.  For example, a ByteArray# of
137 -- Int16Rep will use a scaling factor of 2 when accessing the
138 -- elements.
139
140 getPrimRepSizeInBytes :: PrimRep -> Int
141 getPrimRepSizeInBytes PtrRep        = wORD_SIZE
142 getPrimRepSizeInBytes CodePtrRep    = wORD_SIZE
143 getPrimRepSizeInBytes DataPtrRep    = wORD_SIZE
144 getPrimRepSizeInBytes RetRep        = wORD_SIZE
145 getPrimRepSizeInBytes CostCentreRep = wORD_SIZE
146 getPrimRepSizeInBytes CharRep       = 4
147 getPrimRepSizeInBytes IntRep        = wORD_SIZE
148 getPrimRepSizeInBytes WordRep       = wORD_SIZE
149 getPrimRepSizeInBytes AddrRep       = wORD_SIZE
150 getPrimRepSizeInBytes FloatRep      = wORD_SIZE
151 getPrimRepSizeInBytes DoubleRep     = dOUBLE_SIZE * wORD_SIZE
152 getPrimRepSizeInBytes Int8Rep       = 1
153 getPrimRepSizeInBytes Int16Rep      = 2
154 getPrimRepSizeInBytes Int32Rep      = 4
155 getPrimRepSizeInBytes Int64Rep      = 8
156 getPrimRepSizeInBytes Word8Rep      = 1
157 getPrimRepSizeInBytes Word16Rep     = 2
158 getPrimRepSizeInBytes Word32Rep     = 4
159 getPrimRepSizeInBytes Word64Rep     = 8
160 getPrimRepSizeInBytes StablePtrRep  = wORD_SIZE
161 getPrimRepSizeInBytes other         = pprPanic "getPrimRepSizeInBytes" (ppr other)
162 \end{code}
163
164 %************************************************************************
165 %*                                                                      *
166 \subsection[PrimRep-instances]{Boring instance decls for @PrimRep@}
167 %*                                                                      *
168 %************************************************************************
169
170 \begin{code}
171 instance Outputable PrimRep where
172     ppr kind = text (showPrimRep kind)
173
174 showPrimRep  :: PrimRep -> String
175 showPrimRep PtrRep         = "P_"       -- short for StgPtr
176 showPrimRep CodePtrRep     = "P_"       -- DEATH to StgFunPtr! (94/02/22 WDP)
177 showPrimRep DataPtrRep     = "D_"
178 showPrimRep RetRep         = "P_"
179 showPrimRep CostCentreRep  = "CostCentre"
180 showPrimRep CharRep        = "C_"
181 showPrimRep Int8Rep        = "StgInt8"
182 showPrimRep Int16Rep       = "StgInt16"
183 showPrimRep Int32Rep       = "StgInt32"
184 showPrimRep Word8Rep       = "StgWord8"
185 showPrimRep Word16Rep      = "StgWord16"
186 showPrimRep Word32Rep      = "StgWord32"
187 showPrimRep IntRep         = "I_"       -- short for StgInt
188 showPrimRep WordRep        = "W_"       -- short for StgWord
189 showPrimRep Int64Rep       = "LI_"       -- short for StgLongInt
190 showPrimRep Word64Rep      = "LW_"       -- short for StgLongWord
191 showPrimRep AddrRep        = "StgAddr"
192 showPrimRep FloatRep       = "StgFloat"
193 showPrimRep DoubleRep      = "StgDouble"
194 showPrimRep StablePtrRep   = "StgStablePtr"
195 showPrimRep VoidRep        = "!!VOID_KIND!!"
196 \end{code}