[project @ 2000-02-02 11:40:33 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          (debug_stix, insns)
93 \end{code}
94
95 @codeGen@ is the top-level code-generation function:
96 \begin{code}
97 codeGen :: [[StixTree]] -> UniqSM SDoc
98
99 codeGen stixFinal
100   = mapUs genMachCode stixFinal `thenUs` \ dynamic_codes ->
101     let
102         fp_kludge :: [Instr] -> [Instr]
103         fp_kludge = IF_ARCH_i386(i386_insert_ffrees,id)
104
105         static_instrss :: [[Instr]]
106         static_instrss = map fp_kludge (scheduleMachCode dynamic_codes)
107         docs           = map (vcat . map pprInstr) static_instrss
108
109         -- for debugging only
110         docs_prealloc  = map (vcat . map pprInstr . flattenOrdList) 
111                              dynamic_codes
112         text_prealloc  = vcat (intersperse (char ' ' $$ char ' ') docs_prealloc)
113     in
114     -- trace (showSDoc text_prealloc) (
115     returnUs (vcat (intersperse (char ' ' 
116                                  $$ text "# ___stg_split_marker" 
117                                  $$ char ' ') 
118                     docs))
119     -- )
120 \end{code}
121
122 Top level code generator for a chunk of stix code:
123 \begin{code}
124 genMachCode :: [StixTree] -> UniqSM InstrList
125
126 genMachCode stmts
127   = mapUs stmt2Instrs stmts             `thenUs` \ blocks ->
128     returnUs (foldr (.) id blocks asmVoid)
129 \end{code}
130
131 The next bit does the code scheduling.  The scheduler must also deal
132 with register allocation of temporaries.  Much parallelism can be
133 exposed via the OrdList, but more might occur, so further analysis
134 might be needed.
135
136 \begin{code}
137 scheduleMachCode :: [InstrList] -> [[Instr]]
138
139 scheduleMachCode
140   = map (runRegAllocate freeRegsState findReservedRegs)
141   where
142     freeRegsState = mkMRegsState (extractMappedRegNos freeRegs)
143 \end{code}
144
145 %************************************************************************
146 %*                                                                      *
147 \subsection[NCOpt]{The Generic Optimiser}
148 %*                                                                      *
149 %************************************************************************
150
151 This is called between translating Abstract C to its Tree and actually
152 using the Native Code Generator to generate the annotations.  It's a
153 chance to do some strength reductions.
154
155 ** Remember these all have to be machine independent ***
156
157 Note that constant-folding should have already happened, but we might
158 have introduced some new opportunities for constant-folding wrt
159 address manipulations.
160
161 \begin{code}
162 genericOpt :: StixTree -> StixTree
163 \end{code}
164
165 For most nodes, just optimize the children.
166
167 \begin{code}
168 genericOpt (StInd pk addr) = StInd pk (genericOpt addr)
169
170 genericOpt (StAssign pk dst src)
171   = StAssign pk (genericOpt dst) (genericOpt src)
172
173 genericOpt (StJump addr) = StJump (genericOpt addr)
174
175 genericOpt (StCondJump addr test)
176   = StCondJump addr (genericOpt test)
177
178 genericOpt (StCall fn cconv pk args)
179   = StCall fn cconv pk (map genericOpt args)
180 \end{code}
181
182 Fold indices together when the types match:
183 \begin{code}
184 genericOpt (StIndex pk (StIndex pk' base off) off')
185   | pk == pk'
186   = StIndex pk (genericOpt base)
187                (genericOpt (StPrim IntAddOp [off, off']))
188
189 genericOpt (StIndex pk base off)
190   = StIndex pk (genericOpt base) (genericOpt off)
191 \end{code}
192
193 For PrimOps, we first optimize the children, and then we try our hand
194 at some constant-folding.
195
196 \begin{code}
197 genericOpt (StPrim op args) = primOpt op (map genericOpt args)
198 \end{code}
199
200 Replace register leaves with appropriate StixTrees for the given
201 target.
202
203 \begin{code}
204 genericOpt leaf@(StReg (StixMagicId id))
205   = case (stgReg id) of
206         Always tree -> genericOpt tree
207         Save _      -> leaf
208
209 genericOpt other = other
210 \end{code}
211
212 Now, try to constant-fold the PrimOps.  The arguments have already
213 been optimized and folded.
214
215 \begin{code}
216 primOpt
217     :: PrimOp           -- The operation from an StPrim
218     -> [StixTree]       -- The optimized arguments
219     -> StixTree
220
221 primOpt op arg@[StInt x]
222   = case op of
223         IntNegOp -> StInt (-x)
224         _ -> StPrim op arg
225
226 primOpt op args@[StInt x, StInt y]
227   = case op of
228         CharGtOp -> StInt (if x > y  then 1 else 0)
229         CharGeOp -> StInt (if x >= y then 1 else 0)
230         CharEqOp -> StInt (if x == y then 1 else 0)
231         CharNeOp -> StInt (if x /= y then 1 else 0)
232         CharLtOp -> StInt (if x < y  then 1 else 0)
233         CharLeOp -> StInt (if x <= y then 1 else 0)
234         IntAddOp -> StInt (x + y)
235         IntSubOp -> StInt (x - y)
236         IntMulOp -> StInt (x * y)
237         IntQuotOp -> StInt (x `quot` y)
238         IntRemOp -> StInt (x `rem` y)
239         IntGtOp -> StInt (if x > y  then 1 else 0)
240         IntGeOp -> StInt (if x >= y then 1 else 0)
241         IntEqOp -> StInt (if x == y then 1 else 0)
242         IntNeOp -> StInt (if x /= y then 1 else 0)
243         IntLtOp -> StInt (if x < y  then 1 else 0)
244         IntLeOp -> StInt (if x <= y then 1 else 0)
245         -- ToDo: WordQuotOp, WordRemOp.
246         _ -> StPrim op args
247 \end{code}
248
249 When possible, shift the constants to the right-hand side, so that we
250 can match for strength reductions.  Note that the code generator will
251 also assume that constants have been shifted to the right when
252 possible.
253
254 \begin{code}
255 primOpt op [x@(StInt _), y] | commutableOp op = primOpt op [y, x]
256 \end{code}
257
258 We can often do something with constants of 0 and 1 ...
259
260 \begin{code}
261 primOpt op args@[x, y@(StInt 0)]
262   = case op of
263         IntAddOp -> x
264         IntSubOp -> x
265         IntMulOp -> y
266         AndOp    -> y
267         OrOp     -> x
268         XorOp    -> x
269         SllOp    -> x
270         SrlOp    -> x
271         ISllOp   -> x
272         ISraOp   -> x
273         ISrlOp   -> x
274         _        -> StPrim op args
275
276 primOpt op args@[x, y@(StInt 1)]
277   = case op of
278         IntMulOp  -> x
279         IntQuotOp -> x
280         IntRemOp  -> StInt 0
281         _         -> StPrim op args
282 \end{code}
283
284 Now look for multiplication/division by powers of 2 (integers).
285
286 \begin{code}
287 primOpt op args@[x, y@(StInt n)]
288   = case op of
289         IntMulOp -> case exactLog2 n of
290             Nothing -> StPrim op args
291             Just p  -> StPrim ISllOp [x, StInt p]
292         IntQuotOp -> case exactLog2 n of
293             Nothing -> StPrim op args
294             Just p  -> StPrim ISrlOp [x, StInt p]
295         _ -> StPrim op args
296 \end{code}
297
298 Anything else is just too hard.
299
300 \begin{code}
301 primOpt op args = StPrim op args
302 \end{code}