[project @ 1996-04-05 08:26:04 by partain]
[ghc-hetmet.git] / ghc / compiler / nativeGen / AsmCodeGen.lhs
1 %
2 % (c) The AQUA Project, Glasgow University, 1993-1996
3 %
4
5 \begin{code}
6 #include "HsVersions.h"
7
8 module AsmCodeGen ( writeRealAsm, dumpRealAsm ) where
9
10 import Ubiq{-uitous-}
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(..) )
26 import Unpretty         ( uppAppendFile, uppShow, uppAboves, Unpretty(..) )
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 @Unpretty@).
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 :: _FILE -> AbstractC -> UniqSupply -> IO ()
77
78 writeRealAsm file absC us
79   = uppAppendFile file 80 (runNCG absC us)
80
81 dumpRealAsm :: AbstractC -> UniqSupply -> String
82
83 dumpRealAsm absC us = uppShow 80 (runNCG absC us)
84
85 runNCG absC
86   = genCodeAbstractC absC       `thenUs` \ treelists ->
87     let
88         stix = map (map genericOpt) treelists
89     in
90     codeGen stix
91 \end{code}
92
93 @codeGen@ is the top-level code-generation function:
94 \begin{code}
95 codeGen :: [[StixTree]] -> UniqSM Unpretty
96
97 codeGen trees
98   = mapUs genMachCode trees     `thenUs` \ dynamic_codes ->
99     let
100         static_instrs = scheduleMachCode dynamic_codes
101     in
102     returnUs (uppAboves (map pprInstr static_instrs))
103 \end{code}
104
105 Top level code generator for a chunk of stix code:
106 \begin{code}
107 genMachCode :: [StixTree] -> UniqSM InstrList
108
109 genMachCode stmts
110   = mapUs stmt2Instrs stmts             `thenUs` \ blocks ->
111     returnUs (foldr (.) id blocks asmVoid)
112 \end{code}
113
114 The next bit does the code scheduling.  The scheduler must also deal
115 with register allocation of temporaries.  Much parallelism can be
116 exposed via the OrdList, but more might occur, so further analysis
117 might be needed.
118
119 \begin{code}
120 scheduleMachCode :: [InstrList] -> [Instr]
121
122 scheduleMachCode
123   = concat . map (runRegAllocate freeRegsState reservedRegs)
124   where
125     freeRegsState = mkMRegsState (extractMappedRegNos freeRegs)
126 \end{code}
127
128 %************************************************************************
129 %*                                                                      *
130 \subsection[NCOpt]{The Generic Optimiser}
131 %*                                                                      *
132 %************************************************************************
133
134 This is called between translating Abstract C to its Tree and actually
135 using the Native Code Generator to generate the annotations.  It's a
136 chance to do some strength reductions.
137
138 ** Remember these all have to be machine independent ***
139
140 Note that constant-folding should have already happened, but we might
141 have introduced some new opportunities for constant-folding wrt
142 address manipulations.
143
144 \begin{code}
145 genericOpt :: StixTree -> StixTree
146 \end{code}
147
148 For most nodes, just optimize the children.
149
150 \begin{code}
151 genericOpt (StInd pk addr) = StInd pk (genericOpt addr)
152
153 genericOpt (StAssign pk dst src)
154   = StAssign pk (genericOpt dst) (genericOpt src)
155
156 genericOpt (StJump addr) = StJump (genericOpt addr)
157
158 genericOpt (StCondJump addr test)
159   = StCondJump addr (genericOpt test)
160
161 genericOpt (StCall fn pk args)
162   = StCall fn pk (map genericOpt args)
163 \end{code}
164
165 Fold indices together when the types match:
166 \begin{code}
167 genericOpt (StIndex pk (StIndex pk' base off) off')
168   | pk == pk'
169   = StIndex pk (genericOpt base)
170                (genericOpt (StPrim IntAddOp [off, off']))
171
172 genericOpt (StIndex pk base off)
173   = StIndex pk (genericOpt base) (genericOpt off)
174 \end{code}
175
176 For PrimOps, we first optimize the children, and then we try our hand
177 at some constant-folding.
178
179 \begin{code}
180 genericOpt (StPrim op args) = primOpt op (map genericOpt args)
181 \end{code}
182
183 Replace register leaves with appropriate StixTrees for the given
184 target.
185
186 \begin{code}
187 genericOpt leaf@(StReg (StixMagicId id))
188   = case (stgReg id) of
189         Always tree -> genericOpt tree
190         Save _      -> leaf
191
192 genericOpt other = other
193 \end{code}
194
195 Now, try to constant-fold the PrimOps.  The arguments have already
196 been optimized and folded.
197
198 \begin{code}
199 primOpt
200     :: PrimOp           -- The operation from an StPrim
201     -> [StixTree]       -- The optimized arguments
202     -> StixTree
203
204 primOpt op arg@[StInt x]
205   = case op of
206         IntNegOp -> StInt (-x)
207         IntAbsOp -> StInt (abs x)
208         _ -> StPrim op arg
209
210 primOpt op args@[StInt x, StInt y]
211   = case op of
212         CharGtOp -> StInt (if x > y  then 1 else 0)
213         CharGeOp -> StInt (if x >= y then 1 else 0)
214         CharEqOp -> StInt (if x == y then 1 else 0)
215         CharNeOp -> StInt (if x /= y then 1 else 0)
216         CharLtOp -> StInt (if x < y  then 1 else 0)
217         CharLeOp -> StInt (if x <= y then 1 else 0)
218         IntAddOp -> StInt (x + y)
219         IntSubOp -> StInt (x - y)
220         IntMulOp -> StInt (x * y)
221         IntQuotOp -> StInt (x `quot` y)
222         IntRemOp -> StInt (x `rem` y)
223         IntGtOp -> StInt (if x > y  then 1 else 0)
224         IntGeOp -> StInt (if x >= y then 1 else 0)
225         IntEqOp -> StInt (if x == y then 1 else 0)
226         IntNeOp -> StInt (if x /= y then 1 else 0)
227         IntLtOp -> StInt (if x < y  then 1 else 0)
228         IntLeOp -> StInt (if x <= y then 1 else 0)
229         _ -> StPrim op args
230 \end{code}
231
232 When possible, shift the constants to the right-hand side, so that we
233 can match for strength reductions.  Note that the code generator will
234 also assume that constants have been shifted to the right when
235 possible.
236
237 \begin{code}
238 primOpt op [x@(StInt _), y] | commutableOp op = primOpt op [y, x]
239 \end{code}
240
241 We can often do something with constants of 0 and 1 ...
242
243 \begin{code}
244 primOpt op args@[x, y@(StInt 0)]
245   = case op of
246         IntAddOp -> x
247         IntSubOp -> x
248         IntMulOp -> y
249         AndOp    -> y
250         OrOp     -> x
251         SllOp    -> x
252         SraOp    -> x
253         SrlOp    -> x
254         ISllOp   -> x
255         ISraOp   -> x
256         ISrlOp   -> x
257         _        -> StPrim op args
258
259 primOpt op args@[x, y@(StInt 1)]
260   = case op of
261         IntMulOp  -> x
262         IntQuotOp -> x
263         IntRemOp  -> StInt 0
264         _         -> StPrim op args
265 \end{code}
266
267 Now look for multiplication/division by powers of 2 (integers).
268
269 \begin{code}
270 primOpt op args@[x, y@(StInt n)]
271   = case op of
272         IntMulOp -> case exactLog2 n of
273             Nothing -> StPrim op args
274             Just p  -> StPrim SllOp [x, StInt p]
275         IntQuotOp -> case exactLog2 n of
276             Nothing -> StPrim op args
277             Just p  -> StPrim SraOp [x, StInt p]
278         _ -> StPrim op args
279 \end{code}
280
281 Anything else is just too hard.
282
283 \begin{code}
284 primOpt op args = StPrim op args
285 \end{code}