fe9828c6d425672b0a3405f0682fdc961fdb72d0
[ghc-hetmet.git] / ghc / compiler / nativeGen / AsmCodeGen.lhs
1 %
2 % (c) The AQUA Project, Glasgow University, 1993-1996
3 %
4
5 \begin{code}
6 module AsmCodeGen ( writeRealAsm, dumpRealAsm ) where
7
8 #include "HsVersions.h"
9
10 import IO               ( Handle )
11
12 import MachMisc
13 import MachRegs
14 import MachCode
15 import PprMach
16
17 import AbsCStixGen      ( genCodeAbstractC )
18 import AbsCSyn          ( AbstractC, MagicId )
19 import AsmRegAlloc      ( runRegAllocate )
20 import OrdList          ( OrdList )
21 import PrimOp           ( commutableOp, PrimOp(..) )
22 import PrimRep          ( PrimRep{-instance Eq-} )
23 import RegAllocInfo     ( mkMRegsState, MRegsState )
24 import Stix             ( StixTree(..), StixReg(..), CodeSegment )
25 import UniqSupply       ( returnUs, thenUs, mapUs, UniqSM, UniqSupply )
26 import Outputable       
27 \end{code}
28
29 The 96/03 native-code generator has machine-independent and
30 machine-dependent modules (those \tr{#include}'ing \tr{NCG.h}).
31
32 This module (@AsmCodeGen@) is the top-level machine-independent
33 module.  It uses @AbsCStixGen.genCodeAbstractC@ to produce @StixTree@s
34 (defined in module @Stix@), using support code from @StixInfo@ (info
35 tables), @StixPrim@ (primitive operations), @StixMacro@ (Abstract C
36 macros), and @StixInteger@ (GMP arbitrary-precision operations).
37
38 Before entering machine-dependent land, we do some machine-independent
39 @genericOpt@imisations (defined below) on the @StixTree@s.
40
41 We convert to the machine-specific @Instr@ datatype with
42 @stmt2Instrs@, assuming an ``infinite'' supply of registers.  We then
43 use a machine-independent register allocator (@runRegAllocate@) to
44 rejoin reality.  Obviously, @runRegAllocate@ has machine-specific
45 helper functions (see about @RegAllocInfo@ below).
46
47 The machine-dependent bits break down as follows:
48 \begin{description}
49 \item[@MachRegs@:]  Everything about the target platform's machine
50     registers (and immediate operands, and addresses, which tend to
51     intermingle/interact with registers).
52
53 \item[@MachMisc@:]  Includes the @Instr@ datatype (possibly should
54     have a module of its own), plus a miscellany of other things
55     (e.g., @targetDoubleSize@, @smStablePtrTable@, ...)
56
57 \item[@MachCode@:]  @stmt2Instrs@ is where @Stix@ stuff turns into
58     machine instructions.
59
60 \item[@PprMach@:] @pprInstr@ turns an @Instr@ into text (well, really
61     an @Doc@).
62
63 \item[@RegAllocInfo@:] In the register allocator, we manipulate
64     @MRegsState@s, which are @BitSet@s, one bit per machine register.
65     When we want to say something about a specific machine register
66     (e.g., ``it gets clobbered by this instruction''), we set/unset
67     its bit.  Obviously, we do this @BitSet@ thing for efficiency
68     reasons.
69
70     The @RegAllocInfo@ module collects together the machine-specific
71     info needed to do register allocation.
72 \end{description}
73
74 So, here we go:
75 \begin{code}
76 writeRealAsm :: Handle -> AbstractC -> UniqSupply -> IO ()
77 writeRealAsm handle absC us
78   = _scc_ "writeRealAsm" (printForAsm handle (runNCG absC us))
79
80 dumpRealAsm :: AbstractC -> UniqSupply -> SDoc
81 dumpRealAsm = runNCG
82
83 runNCG absC
84   = genCodeAbstractC absC       `thenUs` \ treelists ->
85     let
86         stix = map (map genericOpt) treelists
87     in
88     codeGen stix
89 \end{code}
90
91 @codeGen@ is the top-level code-generation function:
92 \begin{code}
93 codeGen :: [[StixTree]] -> UniqSM SDoc
94
95 codeGen trees
96   = mapUs genMachCode trees     `thenUs` \ dynamic_codes ->
97     let
98         static_instrs = scheduleMachCode dynamic_codes
99     in
100     returnUs (vcat (map pprInstr static_instrs))
101 \end{code}
102
103 Top level code generator for a chunk of stix code:
104 \begin{code}
105 genMachCode :: [StixTree] -> UniqSM InstrList
106
107 genMachCode stmts
108   = mapUs stmt2Instrs stmts             `thenUs` \ blocks ->
109     returnUs (foldr (.) id blocks asmVoid)
110 \end{code}
111
112 The next bit does the code scheduling.  The scheduler must also deal
113 with register allocation of temporaries.  Much parallelism can be
114 exposed via the OrdList, but more might occur, so further analysis
115 might be needed.
116
117 \begin{code}
118 scheduleMachCode :: [InstrList] -> [Instr]
119
120 scheduleMachCode
121   = concat . map (runRegAllocate freeRegsState reservedRegs)
122   where
123     freeRegsState = mkMRegsState (extractMappedRegNos freeRegs)
124 \end{code}
125
126 %************************************************************************
127 %*                                                                      *
128 \subsection[NCOpt]{The Generic Optimiser}
129 %*                                                                      *
130 %************************************************************************
131
132 This is called between translating Abstract C to its Tree and actually
133 using the Native Code Generator to generate the annotations.  It's a
134 chance to do some strength reductions.
135
136 ** Remember these all have to be machine independent ***
137
138 Note that constant-folding should have already happened, but we might
139 have introduced some new opportunities for constant-folding wrt
140 address manipulations.
141
142 \begin{code}
143 genericOpt :: StixTree -> StixTree
144 \end{code}
145
146 For most nodes, just optimize the children.
147
148 \begin{code}
149 genericOpt (StInd pk addr) = StInd pk (genericOpt addr)
150
151 genericOpt (StAssign pk dst src)
152   = StAssign pk (genericOpt dst) (genericOpt src)
153
154 genericOpt (StJump addr) = StJump (genericOpt addr)
155
156 genericOpt (StCondJump addr test)
157   = StCondJump addr (genericOpt test)
158
159 genericOpt (StCall fn cconv pk args)
160   = StCall fn cconv pk (map genericOpt args)
161 \end{code}
162
163 Fold indices together when the types match:
164 \begin{code}
165 genericOpt (StIndex pk (StIndex pk' base off) off')
166   | pk == pk'
167   = StIndex pk (genericOpt base)
168                (genericOpt (StPrim IntAddOp [off, off']))
169
170 genericOpt (StIndex pk base off)
171   = StIndex pk (genericOpt base) (genericOpt off)
172 \end{code}
173
174 For PrimOps, we first optimize the children, and then we try our hand
175 at some constant-folding.
176
177 \begin{code}
178 genericOpt (StPrim op args) = primOpt op (map genericOpt args)
179 \end{code}
180
181 Replace register leaves with appropriate StixTrees for the given
182 target.
183
184 \begin{code}
185 genericOpt leaf@(StReg (StixMagicId id))
186   = case (stgReg id) of
187         Always tree -> genericOpt tree
188         Save _      -> leaf
189
190 genericOpt other = other
191 \end{code}
192
193 Now, try to constant-fold the PrimOps.  The arguments have already
194 been optimized and folded.
195
196 \begin{code}
197 primOpt
198     :: PrimOp           -- The operation from an StPrim
199     -> [StixTree]       -- The optimized arguments
200     -> StixTree
201
202 primOpt op arg@[StInt x]
203   = case op of
204         IntNegOp -> StInt (-x)
205         IntAbsOp -> StInt (abs x)
206         _ -> StPrim op arg
207
208 primOpt op args@[StInt x, StInt y]
209   = case op of
210         CharGtOp -> StInt (if x > y  then 1 else 0)
211         CharGeOp -> StInt (if x >= y then 1 else 0)
212         CharEqOp -> StInt (if x == y then 1 else 0)
213         CharNeOp -> StInt (if x /= y then 1 else 0)
214         CharLtOp -> StInt (if x < y  then 1 else 0)
215         CharLeOp -> StInt (if x <= y then 1 else 0)
216         IntAddOp -> StInt (x + y)
217         IntSubOp -> StInt (x - y)
218         IntMulOp -> StInt (x * y)
219         IntQuotOp -> StInt (x `quot` y)
220         IntRemOp -> StInt (x `rem` y)
221         IntGtOp -> StInt (if x > y  then 1 else 0)
222         IntGeOp -> StInt (if x >= y then 1 else 0)
223         IntEqOp -> StInt (if x == y then 1 else 0)
224         IntNeOp -> StInt (if x /= y then 1 else 0)
225         IntLtOp -> StInt (if x < y  then 1 else 0)
226         IntLeOp -> StInt (if x <= y then 1 else 0)
227         -- ToDo: WordQuotOp, WordRemOp.
228         _ -> StPrim op args
229 \end{code}
230
231 When possible, shift the constants to the right-hand side, so that we
232 can match for strength reductions.  Note that the code generator will
233 also assume that constants have been shifted to the right when
234 possible.
235
236 \begin{code}
237 primOpt op [x@(StInt _), y] | commutableOp op = primOpt op [y, x]
238 \end{code}
239
240 We can often do something with constants of 0 and 1 ...
241
242 \begin{code}
243 primOpt op args@[x, y@(StInt 0)]
244   = case op of
245         IntAddOp -> x
246         IntSubOp -> x
247         IntMulOp -> y
248         AndOp    -> y
249         OrOp     -> x
250         XorOp    -> x
251         SllOp    -> x
252         SrlOp    -> x
253         ISllOp   -> x
254         ISraOp   -> x
255         ISrlOp   -> x
256         _        -> StPrim op args
257
258 primOpt op args@[x, y@(StInt 1)]
259   = case op of
260         IntMulOp  -> x
261         IntQuotOp -> x
262         IntRemOp  -> StInt 0
263         _         -> StPrim op args
264 \end{code}
265
266 Now look for multiplication/division by powers of 2 (integers).
267
268 \begin{code}
269 primOpt op args@[x, y@(StInt n)]
270   = case op of
271         IntMulOp -> case exactLog2 n of
272             Nothing -> StPrim op args
273             Just p  -> StPrim ISllOp [x, StInt p]
274         IntQuotOp -> case exactLog2 n of
275             Nothing -> StPrim op args
276             Just p  -> StPrim ISrlOp [x, StInt p]
277         _ -> StPrim op args
278 \end{code}
279
280 Anything else is just too hard.
281
282 \begin{code}
283 primOpt op args = StPrim op args
284 \end{code}