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