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