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