Remove warning flags from individual compiler modules
[ghc-hetmet.git] / compiler / cmm / CmmExpr.hs
1
2 module CmmExpr
3     ( CmmExpr(..), cmmExprRep, maybeInvertCmmExpr
4     , CmmReg(..), cmmRegRep
5     , CmmLit(..), cmmLitRep
6     , LocalReg(..), localRegRep, localRegGCFollow, GCKind(..)
7     , GlobalReg(..), globalRegRep, spReg, hpReg, spLimReg, nodeReg, node
8     , UserOfLocalRegs, foldRegsUsed
9     , RegSet, emptyRegSet, elemRegSet, extendRegSet, deleteFromRegSet, mkRegSet
10             , plusRegSet, minusRegSet, timesRegSet
11     )
12 where
13
14 import CLabel
15 import MachOp
16 import Unique
17 import UniqSet
18
19 -----------------------------------------------------------------------------
20 --              CmmExpr
21 -- An expression.  Expressions have no side effects.
22 -----------------------------------------------------------------------------
23
24 data CmmExpr
25   = CmmLit CmmLit               -- Literal
26   | CmmLoad CmmExpr MachRep     -- Read memory location
27   | CmmReg CmmReg               -- Contents of register
28   | CmmMachOp MachOp [CmmExpr]  -- Machine operation (+, -, *, etc.)
29   | CmmRegOff CmmReg Int        
30         -- CmmRegOff reg i
31         --        ** is shorthand only, meaning **
32         -- CmmMachOp (MO_S_Add rep (CmmReg reg) (CmmLit (CmmInt i rep)))
33         --      where rep = cmmRegRep reg
34   deriving Eq
35
36 data CmmReg 
37   = CmmLocal  LocalReg
38   | CmmGlobal GlobalReg
39   deriving( Eq )
40
41 data CmmLit
42   = CmmInt Integer  MachRep
43         -- Interpretation: the 2's complement representation of the value
44         -- is truncated to the specified size.  This is easier than trying
45         -- to keep the value within range, because we don't know whether
46         -- it will be used as a signed or unsigned value (the MachRep doesn't
47         -- distinguish between signed & unsigned).
48   | CmmFloat  Rational MachRep
49   | CmmLabel    CLabel                  -- Address of label
50   | CmmLabelOff CLabel Int              -- Address of label + byte offset
51   
52         -- Due to limitations in the C backend, the following
53         -- MUST ONLY be used inside the info table indicated by label2
54         -- (label2 must be the info label), and label1 must be an
55         -- SRT, a slow entrypoint or a large bitmap (see the Mangler)
56         -- Don't use it at all unless tablesNextToCode.
57         -- It is also used inside the NCG during when generating
58         -- position-independent code. 
59   | CmmLabelDiffOff CLabel CLabel Int   -- label1 - label2 + offset
60   deriving Eq
61
62 instance Eq LocalReg where
63   (LocalReg u1 _ _) == (LocalReg u2 _ _) = u1 == u2
64
65 instance Uniquable LocalReg where
66   getUnique (LocalReg uniq _ _) = uniq
67
68 --------
69 --- Negation for conditional branches
70
71 maybeInvertCmmExpr :: CmmExpr -> Maybe CmmExpr
72 maybeInvertCmmExpr (CmmMachOp op args) = do op' <- maybeInvertComparison op
73                                             return (CmmMachOp op' args)
74 maybeInvertCmmExpr _ = Nothing
75
76 -----------------------------------------------------------------------------
77 --              Local registers
78 -----------------------------------------------------------------------------
79
80 -- | Whether a 'LocalReg' is a GC followable pointer
81 data GCKind = GCKindPtr | GCKindNonPtr deriving (Eq)
82
83 data LocalReg
84   = LocalReg
85       !Unique   -- ^ Identifier
86       MachRep   -- ^ Type
87       GCKind      -- ^ Should the GC follow as a pointer
88
89 -- | Sets of local registers
90
91 type RegSet              =  UniqSet LocalReg
92 emptyRegSet             :: RegSet
93 elemRegSet              :: LocalReg -> RegSet -> Bool
94 extendRegSet            :: RegSet -> LocalReg -> RegSet
95 deleteFromRegSet        :: RegSet -> LocalReg -> RegSet
96 mkRegSet                :: [LocalReg] -> RegSet
97 minusRegSet, plusRegSet, timesRegSet :: RegSet -> RegSet -> RegSet
98
99 emptyRegSet      = emptyUniqSet
100 elemRegSet       = elementOfUniqSet
101 extendRegSet     = addOneToUniqSet
102 deleteFromRegSet = delOneFromUniqSet
103 mkRegSet         = mkUniqSet
104 minusRegSet      = minusUniqSet
105 plusRegSet       = unionUniqSets
106 timesRegSet      = intersectUniqSets
107
108 -----------------------------------------------------------------------------
109 --    Register-use information for expressions and other types 
110 -----------------------------------------------------------------------------
111
112 class UserOfLocalRegs a where
113   foldRegsUsed :: (b -> LocalReg -> b) -> b -> a -> b
114
115 instance UserOfLocalRegs CmmReg where
116     foldRegsUsed f z (CmmLocal reg) = f z reg
117     foldRegsUsed _ z (CmmGlobal _)  = z
118
119 instance UserOfLocalRegs LocalReg where
120     foldRegsUsed f z r = f z r
121
122 instance UserOfLocalRegs RegSet where
123     foldRegsUsed f = foldUniqSet (flip f)
124
125 instance UserOfLocalRegs CmmExpr where
126   foldRegsUsed f z e = expr z e
127     where expr z (CmmLit _)          = z
128           expr z (CmmLoad addr _)    = foldRegsUsed f z addr
129           expr z (CmmReg r)          = foldRegsUsed f z r
130           expr z (CmmMachOp _ exprs) = foldRegsUsed f z exprs
131           expr z (CmmRegOff r _)     = foldRegsUsed f z r
132
133 instance UserOfLocalRegs a => UserOfLocalRegs [a] where
134   foldRegsUsed _ set [] = set
135   foldRegsUsed f set (x:xs) = foldRegsUsed f (foldRegsUsed f set x) xs
136
137 -----------------------------------------------------------------------------
138 --              MachRep
139 -----------------------------------------------------------------------------
140
141
142
143 cmmExprRep :: CmmExpr -> MachRep
144 cmmExprRep (CmmLit lit)      = cmmLitRep lit
145 cmmExprRep (CmmLoad _ rep)   = rep
146 cmmExprRep (CmmReg reg)      = cmmRegRep reg
147 cmmExprRep (CmmMachOp op _)  = resultRepOfMachOp op
148 cmmExprRep (CmmRegOff reg _) = cmmRegRep reg
149
150 cmmRegRep :: CmmReg -> MachRep
151 cmmRegRep (CmmLocal  reg)       = localRegRep reg
152 cmmRegRep (CmmGlobal reg)       = globalRegRep reg
153
154 localRegRep :: LocalReg -> MachRep
155 localRegRep (LocalReg _ rep _) = rep
156
157
158 localRegGCFollow :: LocalReg -> GCKind
159 localRegGCFollow (LocalReg _ _ p) = p
160
161 cmmLitRep :: CmmLit -> MachRep
162 cmmLitRep (CmmInt _ rep)    = rep
163 cmmLitRep (CmmFloat _ rep)  = rep
164 cmmLitRep (CmmLabel _)      = wordRep
165 cmmLitRep (CmmLabelOff _ _) = wordRep
166 cmmLitRep (CmmLabelDiffOff _ _ _) = wordRep
167
168 -----------------------------------------------------------------------------
169 --              Global STG registers
170 -----------------------------------------------------------------------------
171
172 data GlobalReg
173   -- Argument and return registers
174   = VanillaReg                  -- pointers, unboxed ints and chars
175         {-# UNPACK #-} !Int     -- its number
176
177   | FloatReg            -- single-precision floating-point registers
178         {-# UNPACK #-} !Int     -- its number
179
180   | DoubleReg           -- double-precision floating-point registers
181         {-# UNPACK #-} !Int     -- its number
182
183   | LongReg             -- long int registers (64-bit, really)
184         {-# UNPACK #-} !Int     -- its number
185
186   -- STG registers
187   | Sp                  -- Stack ptr; points to last occupied stack location.
188   | SpLim               -- Stack limit
189   | Hp                  -- Heap ptr; points to last occupied heap location.
190   | HpLim               -- Heap limit register
191   | CurrentTSO          -- pointer to current thread's TSO
192   | CurrentNursery      -- pointer to allocation area
193   | HpAlloc             -- allocation count for heap check failure
194
195                 -- We keep the address of some commonly-called 
196                 -- functions in the register table, to keep code
197                 -- size down:
198   | GCEnter1            -- stg_gc_enter_1
199   | GCFun               -- stg_gc_fun
200
201   -- Base offset for the register table, used for accessing registers
202   -- which do not have real registers assigned to them.  This register
203   -- will only appear after we have expanded GlobalReg into memory accesses
204   -- (where necessary) in the native code generator.
205   | BaseReg
206
207   -- Base Register for PIC (position-independent code) calculations
208   -- Only used inside the native code generator. It's exact meaning differs
209   -- from platform to platform (see module PositionIndependentCode).
210   | PicBaseReg
211
212   deriving( Eq , Show )
213
214 -- convenient aliases
215 spReg, hpReg, spLimReg, nodeReg :: CmmReg
216 spReg = CmmGlobal Sp
217 hpReg = CmmGlobal Hp
218 spLimReg = CmmGlobal SpLim
219 nodeReg = CmmGlobal node
220
221 node :: GlobalReg
222 node = VanillaReg 1
223
224 globalRegRep :: GlobalReg -> MachRep
225 globalRegRep (VanillaReg _)     = wordRep
226 globalRegRep (FloatReg _)       = F32
227 globalRegRep (DoubleReg _)      = F64
228 globalRegRep (LongReg _)        = I64
229 globalRegRep _                  = wordRep