Implement dead basic block elimination.
[ghc-hetmet.git] / compiler / nativeGen / AsmCodeGen.lhs
1 -- -----------------------------------------------------------------------------
2 --
3 -- (c) The University of Glasgow 1993-2004
4 -- 
5 -- This is the top-level module in the native code generator.
6 --
7 -- -----------------------------------------------------------------------------
8
9 \begin{code}
10 module AsmCodeGen ( nativeCodeGen ) where
11
12 #include "HsVersions.h"
13 #include "nativeGen/NCG.h"
14
15
16 #if i386_TARGET_ARCH || x86_64_TARGET_ARCH
17 import X86.CodeGen
18 import X86.Regs
19 import X86.Instr
20 import X86.Ppr
21
22 #elif sparc_TARGET_ARCH
23 import SPARC.CodeGen
24 import SPARC.CodeGen.Expand
25 import SPARC.Regs
26 import SPARC.Instr
27 import SPARC.Ppr
28 import SPARC.ShortcutJump
29
30 #elif powerpc_TARGET_ARCH
31 import PPC.CodeGen
32 import PPC.Cond
33 import PPC.Regs
34 import PPC.RegInfo
35 import PPC.Instr
36 import PPC.Ppr
37
38 #else
39 #error "AsmCodeGen: unknown architecture"
40
41 #endif
42
43 import RegAlloc.Liveness
44 import qualified RegAlloc.Linear.Main           as Linear
45
46 import qualified GraphColor                     as Color
47 import qualified RegAlloc.Graph.Main            as Color
48 import qualified RegAlloc.Graph.Stats           as Color
49 import qualified RegAlloc.Graph.TrivColorable   as Color
50
51 import TargetReg
52 import Platform
53 import Instruction
54 import PIC
55 import Reg
56 import NCGMonad
57
58 import BlockId
59 import CgUtils          ( fixStgRegisters )
60 import OldCmm
61 import CmmOpt           ( cmmEliminateDeadBlocks, cmmMiniInline, cmmMachOpFold )
62 import OldPprCmm
63 import CLabel
64
65 import UniqFM
66 import Unique           ( Unique, getUnique )
67 import UniqSupply
68 import DynFlags
69 import StaticFlags
70 import Util
71 import Config
72
73 import Digraph
74 import qualified Pretty
75 import BufWrite
76 import Outputable
77 import FastString
78 import UniqSet
79 import ErrUtils
80 import Module
81
82 -- DEBUGGING ONLY
83 --import OrdList
84
85 import Data.List
86 import Data.Maybe
87 import Control.Monad
88 import System.IO
89 import Distribution.System
90
91 {-
92 The native-code generator has machine-independent and
93 machine-dependent modules.
94
95 This module ("AsmCodeGen") is the top-level machine-independent
96 module.  Before entering machine-dependent land, we do some
97 machine-independent optimisations (defined below) on the
98 'CmmStmts's.
99
100 We convert to the machine-specific 'Instr' datatype with
101 'cmmCodeGen', assuming an infinite supply of registers.  We then use
102 a machine-independent register allocator ('regAlloc') to rejoin
103 reality.  Obviously, 'regAlloc' has machine-specific helper
104 functions (see about "RegAllocInfo" below).
105
106 Finally, we order the basic blocks of the function so as to minimise
107 the number of jumps between blocks, by utilising fallthrough wherever
108 possible.
109
110 The machine-dependent bits break down as follows:
111
112   * ["MachRegs"]  Everything about the target platform's machine
113     registers (and immediate operands, and addresses, which tend to
114     intermingle/interact with registers).
115
116   * ["MachInstrs"]  Includes the 'Instr' datatype (possibly should
117     have a module of its own), plus a miscellany of other things
118     (e.g., 'targetDoubleSize', 'smStablePtrTable', ...)
119
120   * ["MachCodeGen"]  is where 'Cmm' stuff turns into
121     machine instructions.
122
123   * ["PprMach"] 'pprInstr' turns an 'Instr' into text (well, really
124     a 'Doc').
125
126   * ["RegAllocInfo"] In the register allocator, we manipulate
127     'MRegsState's, which are 'BitSet's, one bit per machine register.
128     When we want to say something about a specific machine register
129     (e.g., ``it gets clobbered by this instruction''), we set/unset
130     its bit.  Obviously, we do this 'BitSet' thing for efficiency
131     reasons.
132
133     The 'RegAllocInfo' module collects together the machine-specific
134     info needed to do register allocation.
135
136    * ["RegisterAlloc"] The (machine-independent) register allocator.
137 -}
138
139 -- -----------------------------------------------------------------------------
140 -- Top-level of the native codegen
141
142 --------------------
143 nativeCodeGen :: DynFlags -> Handle -> UniqSupply -> [RawCmm] -> IO ()
144 nativeCodeGen dflags h us cmms
145  = do
146         let split_cmms  = concat $ map add_split cmms
147
148         -- BufHandle is a performance hack.  We could hide it inside
149         -- Pretty if it weren't for the fact that we do lots of little
150         -- printDocs here (in order to do codegen in constant space).
151         bufh <- newBufHandle h
152         (imports, prof) <- cmmNativeGens dflags bufh us split_cmms [] [] 0
153         bFlush bufh
154
155         let (native, colorStats, linearStats)
156                 = unzip3 prof
157
158         -- dump native code
159         dumpIfSet_dyn dflags
160                 Opt_D_dump_asm "Asm code"
161                 (vcat $ map (docToSDoc . pprNatCmmTop) $ concat native)
162
163         -- dump global NCG stats for graph coloring allocator
164         (case concat $ catMaybes colorStats of
165           []    -> return ()
166           stats -> do   
167                 -- build the global register conflict graph
168                 let graphGlobal 
169                         = foldl Color.union Color.initGraph
170                         $ [ Color.raGraph stat
171                                 | stat@Color.RegAllocStatsStart{} <- stats]
172            
173                 dumpSDoc dflags Opt_D_dump_asm_stats "NCG stats"
174                         $ Color.pprStats stats graphGlobal
175
176                 dumpIfSet_dyn dflags
177                         Opt_D_dump_asm_conflicts "Register conflict graph"
178                         $ Color.dotGraph 
179                                 targetRegDotColor 
180                                 (Color.trivColorable 
181                                         targetVirtualRegSqueeze 
182                                         targetRealRegSqueeze)
183                         $ graphGlobal)
184
185
186         -- dump global NCG stats for linear allocator
187         (case concat $ catMaybes linearStats of
188                 []      -> return ()
189                 stats   -> dumpSDoc dflags Opt_D_dump_asm_stats "NCG stats"
190                                 $ Linear.pprStats (concat native) stats)
191
192         -- write out the imports
193         Pretty.printDoc Pretty.LeftMode h
194                 $ makeImportsDoc dflags (concat imports)
195
196         return  ()
197
198  where  add_split (Cmm tops)
199                 | dopt Opt_SplitObjs dflags = split_marker : tops
200                 | otherwise                 = tops
201
202         split_marker = CmmProc [] mkSplitMarkerLabel (ListGraph [])
203
204
205 -- | Do native code generation on all these cmms.
206 --
207 cmmNativeGens :: DynFlags
208               -> BufHandle
209               -> UniqSupply
210               -> [RawCmmTop]
211               -> [[CLabel]]
212               -> [ ([NatCmmTop Instr],
213                    Maybe [Color.RegAllocStats Instr],
214                    Maybe [Linear.RegAllocStats]) ]
215               -> Int
216               -> IO ( [[CLabel]],
217                       [([NatCmmTop Instr],
218                       Maybe [Color.RegAllocStats Instr],
219                       Maybe [Linear.RegAllocStats])] )
220
221 cmmNativeGens _ _ _ [] impAcc profAcc _
222         = return (reverse impAcc, reverse profAcc)
223
224 cmmNativeGens dflags h us (cmm : cmms) impAcc profAcc count
225  = do
226         (us', native, imports, colorStats, linearStats)
227                 <- cmmNativeGen dflags us cmm count
228
229         Pretty.bufLeftRender h
230                 $ {-# SCC "pprNativeCode" #-} Pretty.vcat $ map pprNatCmmTop native
231
232            -- carefully evaluate this strictly.  Binding it with 'let'
233            -- and then using 'seq' doesn't work, because the let
234            -- apparently gets inlined first.
235         lsPprNative <- return $!
236                 if  dopt Opt_D_dump_asm       dflags
237                  || dopt Opt_D_dump_asm_stats dflags
238                         then native
239                         else []
240
241         count' <- return $! count + 1;
242
243         -- force evaulation all this stuff to avoid space leaks
244         seqString (showSDoc $ vcat $ map ppr imports) `seq` return ()
245
246         cmmNativeGens dflags h us' cmms
247                         (imports : impAcc)
248                         ((lsPprNative, colorStats, linearStats) : profAcc)
249                         count'
250
251  where  seqString []            = ()
252         seqString (x:xs)        = x `seq` seqString xs `seq` ()
253
254
255 -- | Complete native code generation phase for a single top-level chunk of Cmm.
256 --      Dumping the output of each stage along the way.
257 --      Global conflict graph and NGC stats
258 cmmNativeGen 
259         :: DynFlags
260         -> UniqSupply
261         -> RawCmmTop                                    -- ^ the cmm to generate code for
262         -> Int                                          -- ^ sequence number of this top thing
263         -> IO   ( UniqSupply
264                 , [NatCmmTop Instr]                     -- native code
265                 , [CLabel]                              -- things imported by this cmm
266                 , Maybe [Color.RegAllocStats Instr]     -- stats for the coloring register allocator
267                 , Maybe [Linear.RegAllocStats])         -- stats for the linear register allocators
268
269 cmmNativeGen dflags us cmm count
270  = do
271
272         -- rewrite assignments to global regs
273         let fixed_cmm =
274                 {-# SCC "fixStgRegisters" #-}
275                 fixStgRegisters cmm
276
277         -- cmm to cmm optimisations
278         let (opt_cmm, imports) =
279                 {-# SCC "cmmToCmm" #-}
280                 cmmToCmm dflags fixed_cmm
281
282         dumpIfSet_dyn dflags
283                 Opt_D_dump_opt_cmm "Optimised Cmm"
284                 (pprCmm $ Cmm [opt_cmm])
285
286         -- generate native code from cmm
287         let ((native, lastMinuteImports), usGen) =
288                 {-# SCC "genMachCode" #-}
289                 initUs us $ genMachCode dflags opt_cmm
290
291         dumpIfSet_dyn dflags
292                 Opt_D_dump_asm_native "Native code"
293                 (vcat $ map (docToSDoc . pprNatCmmTop) native)
294
295         -- tag instructions with register liveness information
296         let (withLiveness, usLive) =
297                 {-# SCC "regLiveness" #-}
298                 initUs usGen 
299                         $ mapUs regLiveness 
300                         $ map natCmmTopToLive native
301
302         dumpIfSet_dyn dflags
303                 Opt_D_dump_asm_liveness "Liveness annotations added"
304                 (vcat $ map ppr withLiveness)
305                 
306         -- allocate registers
307         (alloced, usAlloc, ppr_raStatsColor, ppr_raStatsLinear) <-
308          if ( dopt Opt_RegsGraph dflags
309            || dopt Opt_RegsIterative dflags)
310           then do
311                 -- the regs usable for allocation
312                 let (alloc_regs :: UniqFM (UniqSet RealReg))
313                         = foldr (\r -> plusUFM_C unionUniqSets
314                                         $ unitUFM (targetClassOfRealReg r) (unitUniqSet r))
315                                 emptyUFM
316                         $ allocatableRegs
317
318                 -- do the graph coloring register allocation
319                 let ((alloced, regAllocStats), usAlloc)
320                         = {-# SCC "RegAlloc" #-}
321                           initUs usLive
322                           $ Color.regAlloc
323                                 dflags
324                                 alloc_regs
325                                 (mkUniqSet [0..maxSpillSlots])
326                                 withLiveness
327
328                 -- dump out what happened during register allocation
329                 dumpIfSet_dyn dflags
330                         Opt_D_dump_asm_regalloc "Registers allocated"
331                         (vcat $ map (docToSDoc . pprNatCmmTop) alloced)
332
333                 dumpIfSet_dyn dflags
334                         Opt_D_dump_asm_regalloc_stages "Build/spill stages"
335                         (vcat   $ map (\(stage, stats)
336                                         -> text "# --------------------------"
337                                         $$ text "#  cmm " <> int count <> text " Stage " <> int stage
338                                         $$ ppr stats)
339                                 $ zip [0..] regAllocStats)
340
341                 let mPprStats =
342                         if dopt Opt_D_dump_asm_stats dflags
343                          then Just regAllocStats else Nothing
344
345                 -- force evaluation of the Maybe to avoid space leak
346                 mPprStats `seq` return ()
347
348                 return  ( alloced, usAlloc
349                         , mPprStats
350                         , Nothing)
351
352           else do
353                 -- do linear register allocation
354                 let ((alloced, regAllocStats), usAlloc) 
355                         = {-# SCC "RegAlloc" #-}
356                           initUs usLive
357                           $ liftM unzip
358                           $ mapUs Linear.regAlloc withLiveness
359
360                 dumpIfSet_dyn dflags
361                         Opt_D_dump_asm_regalloc "Registers allocated"
362                         (vcat $ map (docToSDoc . pprNatCmmTop) alloced)
363
364                 let mPprStats =
365                         if dopt Opt_D_dump_asm_stats dflags
366                          then Just (catMaybes regAllocStats) else Nothing
367
368                 -- force evaluation of the Maybe to avoid space leak
369                 mPprStats `seq` return ()
370
371                 return  ( alloced, usAlloc
372                         , Nothing
373                         , mPprStats)
374
375         ---- generate jump tables
376         let tabled      =
377                 {-# SCC "generateJumpTables" #-}
378                 alloced ++ generateJumpTables alloced
379
380         ---- shortcut branches
381         let shorted     =
382                 {-# SCC "shortcutBranches" #-}
383                 shortcutBranches dflags tabled
384
385         ---- sequence blocks
386         let sequenced   =
387                 {-# SCC "sequenceBlocks" #-}
388                 map sequenceTop shorted
389
390         ---- x86fp_kludge
391         let kludged =
392 #if i386_TARGET_ARCH
393                 {-# SCC "x86fp_kludge" #-}
394                 map x86fp_kludge sequenced
395 #else
396                 sequenced
397 #endif
398
399         ---- expansion of SPARC synthetic instrs
400 #if sparc_TARGET_ARCH
401         let expanded = 
402                 {-# SCC "sparc_expand" #-}
403                 map expandTop kludged
404
405         dumpIfSet_dyn dflags
406                 Opt_D_dump_asm_expanded "Synthetic instructions expanded"
407                 (vcat $ map (docToSDoc . pprNatCmmTop) expanded)
408 #else
409         let expanded = 
410                 kludged
411 #endif
412
413         return  ( usAlloc
414                 , expanded
415                 , lastMinuteImports ++ imports
416                 , ppr_raStatsColor
417                 , ppr_raStatsLinear)
418
419
420 #if i386_TARGET_ARCH
421 x86fp_kludge :: NatCmmTop Instr -> NatCmmTop Instr
422 x86fp_kludge top@(CmmData _ _) = top
423 x86fp_kludge (CmmProc info lbl (ListGraph code)) = 
424         CmmProc info lbl (ListGraph $ i386_insert_ffrees code)
425 #endif
426
427
428 -- | Build a doc for all the imports.
429 --
430 makeImportsDoc :: DynFlags -> [CLabel] -> Pretty.Doc
431 makeImportsDoc dflags imports
432  = dyld_stubs imports
433
434 #if HAVE_SUBSECTIONS_VIA_SYMBOLS
435                 -- On recent versions of Darwin, the linker supports
436                 -- dead-stripping of code and data on a per-symbol basis.
437                 -- There's a hack to make this work in PprMach.pprNatCmmTop.
438             Pretty.$$ Pretty.text ".subsections_via_symbols"
439 #endif
440 #if HAVE_GNU_NONEXEC_STACK
441                 -- On recent GNU ELF systems one can mark an object file
442                 -- as not requiring an executable stack. If all objects
443                 -- linked into a program have this note then the program
444                 -- will not use an executable stack, which is good for
445                 -- security. GHC generated code does not need an executable
446                 -- stack so add the note in:
447             Pretty.$$ Pretty.text ".section .note.GNU-stack,\"\",@progbits"
448 #endif
449 #if !defined(darwin_TARGET_OS)
450                 -- And just because every other compiler does, lets stick in
451                 -- an identifier directive: .ident "GHC x.y.z"
452             Pretty.$$ let compilerIdent = Pretty.text "GHC" Pretty.<+>
453                                           Pretty.text cProjectVersion
454                        in Pretty.text ".ident" Pretty.<+>
455                           Pretty.doubleQuotes compilerIdent
456 #endif
457
458  where
459         -- Generate "symbol stubs" for all external symbols that might
460         -- come from a dynamic library.
461         dyld_stubs :: [CLabel] -> Pretty.Doc
462 {-      dyld_stubs imps = Pretty.vcat $ map pprDyldSymbolStub $
463                                     map head $ group $ sort imps-}
464
465         arch    = platformArch  $ targetPlatform dflags
466         os      = platformOS    $ targetPlatform dflags
467         
468         -- (Hack) sometimes two Labels pretty-print the same, but have
469         -- different uniques; so we compare their text versions...
470         dyld_stubs imps
471                 | needImportedSymbols arch os
472                 = Pretty.vcat $
473                         (pprGotDeclaration arch os :) $
474                         map ( pprImportedSymbol arch os . fst . head) $
475                         groupBy (\(_,a) (_,b) -> a == b) $
476                         sortBy (\(_,a) (_,b) -> compare a b) $
477                         map doPpr $
478                         imps
479                 | otherwise
480                 = Pretty.empty
481
482         doPpr lbl = (lbl, Pretty.render $ pprCLabel lbl astyle)
483         astyle = mkCodeStyle AsmStyle
484
485
486 -- -----------------------------------------------------------------------------
487 -- Sequencing the basic blocks
488
489 -- Cmm BasicBlocks are self-contained entities: they always end in a
490 -- jump, either non-local or to another basic block in the same proc.
491 -- In this phase, we attempt to place the basic blocks in a sequence
492 -- such that as many of the local jumps as possible turn into
493 -- fallthroughs.
494
495 sequenceTop 
496         :: NatCmmTop Instr
497         -> NatCmmTop Instr
498
499 sequenceTop top@(CmmData _ _) = top
500 sequenceTop (CmmProc info lbl (ListGraph blocks)) = 
501   CmmProc info lbl (ListGraph $ makeFarBranches $ sequenceBlocks blocks)
502
503 -- The algorithm is very simple (and stupid): we make a graph out of
504 -- the blocks where there is an edge from one block to another iff the
505 -- first block ends by jumping to the second.  Then we topologically
506 -- sort this graph.  Then traverse the list: for each block, we first
507 -- output the block, then if it has an out edge, we move the
508 -- destination of the out edge to the front of the list, and continue.
509
510 -- FYI, the classic layout for basic blocks uses postorder DFS; this
511 -- algorithm is implemented in Hoopl.
512
513 sequenceBlocks 
514         :: Instruction instr
515         => [NatBasicBlock instr] 
516         -> [NatBasicBlock instr]
517
518 sequenceBlocks [] = []
519 sequenceBlocks (entry:blocks) = 
520   seqBlocks (mkNode entry : reverse (flattenSCCs (sccBlocks blocks)))
521   -- the first block is the entry point ==> it must remain at the start.
522
523
524 sccBlocks 
525         :: Instruction instr
526         => [NatBasicBlock instr] 
527         -> [SCC ( NatBasicBlock instr
528                 , Unique
529                 , [Unique])]
530
531 sccBlocks blocks = stronglyConnCompFromEdgedVerticesR (map mkNode blocks)
532
533 -- we're only interested in the last instruction of
534 -- the block, and only if it has a single destination.
535 getOutEdges 
536         :: Instruction instr
537         => [instr] -> [Unique]
538
539 getOutEdges instrs 
540         = case jumpDestsOfInstr (last instrs) of
541                 [one] -> [getUnique one]
542                 _many -> []
543
544 mkNode :: (Instruction t)
545        => GenBasicBlock t
546        -> (GenBasicBlock t, Unique, [Unique])
547 mkNode block@(BasicBlock id instrs) = (block, getUnique id, getOutEdges instrs)
548
549 seqBlocks :: (Eq t) => [(GenBasicBlock t1, t, [t])] -> [GenBasicBlock t1]
550 seqBlocks [] = []
551 seqBlocks ((block,_,[]) : rest)
552   = block : seqBlocks rest
553 seqBlocks ((block@(BasicBlock id instrs),_,[next]) : rest)
554   | can_fallthrough = BasicBlock id (init instrs) : seqBlocks rest'
555   | otherwise       = block : seqBlocks rest'
556   where
557         (can_fallthrough, rest') = reorder next [] rest
558           -- TODO: we should do a better job for cycles; try to maximise the
559           -- fallthroughs within a loop.
560 seqBlocks _ = panic "AsmCodegen:seqBlocks"
561
562 reorder :: (Eq a) => a -> [(t, a, t1)] -> [(t, a, t1)] -> (Bool, [(t, a, t1)])
563 reorder  _ accum [] = (False, reverse accum)
564 reorder id accum (b@(block,id',out) : rest)
565   | id == id'  = (True, (block,id,out) : reverse accum ++ rest)
566   | otherwise  = reorder id (b:accum) rest
567
568
569 -- -----------------------------------------------------------------------------
570 -- Making far branches
571
572 -- Conditional branches on PowerPC are limited to +-32KB; if our Procs get too
573 -- big, we have to work around this limitation.
574
575 makeFarBranches 
576         :: [NatBasicBlock Instr] 
577         -> [NatBasicBlock Instr]
578
579 #if powerpc_TARGET_ARCH
580 makeFarBranches blocks
581     | last blockAddresses < nearLimit = blocks
582     | otherwise = zipWith handleBlock blockAddresses blocks
583     where
584         blockAddresses = scanl (+) 0 $ map blockLen blocks
585         blockLen (BasicBlock _ instrs) = length instrs
586         
587         handleBlock addr (BasicBlock id instrs)
588                 = BasicBlock id (zipWith makeFar [addr..] instrs)
589         
590         makeFar _ (BCC ALWAYS tgt) = BCC ALWAYS tgt
591         makeFar addr (BCC cond tgt)
592             | abs (addr - targetAddr) >= nearLimit
593             = BCCFAR cond tgt
594             | otherwise
595             = BCC cond tgt
596             where Just targetAddr = lookupUFM blockAddressMap tgt
597         makeFar _ other            = other
598         
599         nearLimit = 7000 -- 8192 instructions are allowed; let's keep some
600                          -- distance, as we have a few pseudo-insns that are
601                          -- pretty-printed as multiple instructions,
602                          -- and it's just not worth the effort to calculate
603                          -- things exactly
604         
605         blockAddressMap = listToUFM $ zip (map blockId blocks) blockAddresses
606 #else
607 makeFarBranches = id
608 #endif
609
610 -- -----------------------------------------------------------------------------
611 -- Generate jump tables
612
613 -- Analyzes all native code and generates data sections for all jump
614 -- table instructions.
615 generateJumpTables
616         :: [NatCmmTop Instr] -> [NatCmmTop Instr]
617 generateJumpTables xs = concatMap f xs
618     where f (CmmProc _ _ (ListGraph xs)) = concatMap g xs
619           f _ = []
620           g (BasicBlock _ xs) = catMaybes (map generateJumpTableForInstr xs)
621
622 -- -----------------------------------------------------------------------------
623 -- Shortcut branches
624
625 shortcutBranches 
626         :: DynFlags 
627         -> [NatCmmTop Instr] 
628         -> [NatCmmTop Instr]
629
630 shortcutBranches dflags tops
631   | optLevel dflags < 1 = tops    -- only with -O or higher
632   | otherwise           = map (apply_mapping mapping) tops'
633   where
634     (tops', mappings) = mapAndUnzip build_mapping tops
635     mapping = foldr plusUFM emptyUFM mappings
636
637 build_mapping :: GenCmmTop d t (ListGraph Instr)
638               -> (GenCmmTop d t (ListGraph Instr), UniqFM JumpDest)
639 build_mapping top@(CmmData _ _) = (top, emptyUFM)
640 build_mapping (CmmProc info lbl (ListGraph []))
641   = (CmmProc info lbl (ListGraph []), emptyUFM)
642 build_mapping (CmmProc info lbl (ListGraph (head:blocks)))
643   = (CmmProc info lbl (ListGraph (head:others)), mapping)
644         -- drop the shorted blocks, but don't ever drop the first one,
645         -- because it is pointed to by a global label.
646   where
647     -- find all the blocks that just consist of a jump that can be
648     -- shorted.
649     -- Don't completely eliminate loops here -- that can leave a dangling jump!
650     (_, shortcut_blocks, others) = foldl split (emptyBlockSet, [], []) blocks
651     split (s, shortcut_blocks, others) b@(BasicBlock id [insn])
652         | Just (DestBlockId dest) <- canShortcut insn,
653           (setMember dest s) || dest == id -- loop checks
654         = (s, shortcut_blocks, b : others)
655     split (s, shortcut_blocks, others) (BasicBlock id [insn])
656         | Just dest <- canShortcut insn
657         = (setInsert id s, (id,dest) : shortcut_blocks, others)
658     split (s, shortcut_blocks, others) other = (s, shortcut_blocks, other : others)
659
660
661     -- build a mapping from BlockId to JumpDest for shorting branches
662     mapping = foldl add emptyUFM shortcut_blocks
663     add ufm (id,dest) = addToUFM ufm id dest
664     
665 apply_mapping :: UniqFM JumpDest
666               -> GenCmmTop CmmStatic h (ListGraph Instr)
667               -> GenCmmTop CmmStatic h (ListGraph Instr)
668 apply_mapping ufm (CmmData sec statics) 
669   = CmmData sec (map (shortcutStatic (lookupUFM ufm)) statics)
670   -- we need to get the jump tables, so apply the mapping to the entries
671   -- of a CmmData too.
672 apply_mapping ufm (CmmProc info lbl (ListGraph blocks))
673   = CmmProc info lbl (ListGraph $ map short_bb blocks)
674   where
675     short_bb (BasicBlock id insns) = BasicBlock id $! map short_insn insns
676     short_insn i = shortcutJump (lookupUFM ufm) i
677                  -- shortcutJump should apply the mapping repeatedly,
678                  -- just in case we can short multiple branches.
679
680 -- -----------------------------------------------------------------------------
681 -- Instruction selection
682
683 -- Native code instruction selection for a chunk of stix code.  For
684 -- this part of the computation, we switch from the UniqSM monad to
685 -- the NatM monad.  The latter carries not only a Unique, but also an
686 -- Int denoting the current C stack pointer offset in the generated
687 -- code; this is needed for creating correct spill offsets on
688 -- architectures which don't offer, or for which it would be
689 -- prohibitively expensive to employ, a frame pointer register.  Viz,
690 -- x86.
691
692 -- The offset is measured in bytes, and indicates the difference
693 -- between the current (simulated) C stack-ptr and the value it was at
694 -- the beginning of the block.  For stacks which grow down, this value
695 -- should be either zero or negative.
696
697 -- Switching between the two monads whilst carrying along the same
698 -- Unique supply breaks abstraction.  Is that bad?
699
700 genMachCode 
701         :: DynFlags 
702         -> RawCmmTop 
703         -> UniqSM 
704                 ( [NatCmmTop Instr]
705                 , [CLabel])
706
707 genMachCode dflags cmm_top
708   = do  { initial_us <- getUs
709         ; let initial_st           = mkNatM_State initial_us 0 dflags
710               (new_tops, final_st) = initNat initial_st (cmmTopCodeGen dflags cmm_top)
711               final_delta          = natm_delta final_st
712               final_imports        = natm_imports final_st
713         ; if   final_delta == 0
714           then return (new_tops, final_imports)
715           else pprPanic "genMachCode: nonzero final delta" (int final_delta)
716     }
717
718 -- -----------------------------------------------------------------------------
719 -- Generic Cmm optimiser
720
721 {-
722 Here we do:
723
724   (a) Constant folding
725   (b) Simple inlining: a temporary which is assigned to and then
726       used, once, can be shorted.
727   (c) Position independent code and dynamic linking
728         (i)  introduce the appropriate indirections
729              and position independent refs
730         (ii) compile a list of imported symbols
731
732 Ideas for other things we could do:
733
734   - shortcut jumps-to-jumps
735   - simple CSE: if an expr is assigned to a temp, then replace later occs of
736     that expr with the temp, until the expr is no longer valid (can push through
737     temp assignments, and certain assigns to mem...)
738 -}
739
740 cmmToCmm :: DynFlags -> RawCmmTop -> (RawCmmTop, [CLabel])
741 cmmToCmm _ top@(CmmData _ _) = (top, [])
742 cmmToCmm dflags (CmmProc info lbl (ListGraph blocks)) = runCmmOpt dflags $ do
743   blocks' <- mapM cmmBlockConFold (cmmMiniInline (cmmEliminateDeadBlocks blocks))
744   return $ CmmProc info lbl (ListGraph blocks')
745
746 newtype CmmOptM a = CmmOptM (([CLabel], DynFlags) -> (# a, [CLabel] #))
747
748 instance Monad CmmOptM where
749   return x = CmmOptM $ \(imports, _) -> (# x,imports #)
750   (CmmOptM f) >>= g =
751     CmmOptM $ \(imports, dflags) ->
752                 case f (imports, dflags) of
753                   (# x, imports' #) ->
754                     case g x of
755                       CmmOptM g' -> g' (imports', dflags)
756
757 addImportCmmOpt :: CLabel -> CmmOptM ()
758 addImportCmmOpt lbl = CmmOptM $ \(imports, _dflags) -> (# (), lbl:imports #)
759
760 getDynFlagsCmmOpt :: CmmOptM DynFlags
761 getDynFlagsCmmOpt = CmmOptM $ \(imports, dflags) -> (# dflags, imports #)
762
763 runCmmOpt :: DynFlags -> CmmOptM a -> (a, [CLabel])
764 runCmmOpt dflags (CmmOptM f) = case f ([], dflags) of
765                         (# result, imports #) -> (result, imports)
766
767 cmmBlockConFold :: CmmBasicBlock -> CmmOptM CmmBasicBlock
768 cmmBlockConFold (BasicBlock id stmts) = do
769   stmts' <- mapM cmmStmtConFold stmts
770   return $ BasicBlock id stmts'
771
772 cmmStmtConFold :: CmmStmt -> CmmOptM CmmStmt
773 cmmStmtConFold stmt
774    = case stmt of
775         CmmAssign reg src
776            -> do src' <- cmmExprConFold DataReference src
777                  return $ case src' of
778                    CmmReg reg' | reg == reg' -> CmmNop
779                    new_src -> CmmAssign reg new_src
780
781         CmmStore addr src
782            -> do addr' <- cmmExprConFold DataReference addr
783                  src'  <- cmmExprConFold DataReference src
784                  return $ CmmStore addr' src'
785
786         CmmJump addr regs
787            -> do addr' <- cmmExprConFold JumpReference addr
788                  return $ CmmJump addr' regs
789
790         CmmCall target regs args srt returns
791            -> do target' <- case target of
792                               CmmCallee e conv -> do
793                                 e' <- cmmExprConFold CallReference e
794                                 return $ CmmCallee e' conv
795                               other -> return other
796                  args' <- mapM (\(CmmHinted arg hint) -> do
797                                   arg' <- cmmExprConFold DataReference arg
798                                   return (CmmHinted arg' hint)) args
799                  return $ CmmCall target' regs args' srt returns
800
801         CmmCondBranch test dest
802            -> do test' <- cmmExprConFold DataReference test
803                  return $ case test' of
804                    CmmLit (CmmInt 0 _) -> 
805                      CmmComment (mkFastString ("deleted: " ++ 
806                                         showSDoc (pprStmt stmt)))
807
808                    CmmLit (CmmInt _ _) -> CmmBranch dest
809                    _other -> CmmCondBranch test' dest
810
811         CmmSwitch expr ids
812            -> do expr' <- cmmExprConFold DataReference expr
813                  return $ CmmSwitch expr' ids
814
815         other
816            -> return other
817
818
819 cmmExprConFold :: ReferenceKind -> CmmExpr -> CmmOptM CmmExpr
820 cmmExprConFold referenceKind expr
821    = case expr of
822         CmmLoad addr rep
823            -> do addr' <- cmmExprConFold DataReference addr
824                  return $ CmmLoad addr' rep
825
826         CmmMachOp mop args
827            -- For MachOps, we first optimize the children, and then we try 
828            -- our hand at some constant-folding.
829            -> do args' <- mapM (cmmExprConFold DataReference) args
830                  return $ cmmMachOpFold mop args'
831
832         CmmLit (CmmLabel lbl)
833            -> do
834                 dflags <- getDynFlagsCmmOpt
835                 cmmMakeDynamicReference dflags addImportCmmOpt referenceKind lbl
836         CmmLit (CmmLabelOff lbl off)
837            -> do
838                  dflags <- getDynFlagsCmmOpt
839                  dynRef <- cmmMakeDynamicReference dflags addImportCmmOpt referenceKind lbl
840                  return $ cmmMachOpFold (MO_Add wordWidth) [
841                      dynRef,
842                      (CmmLit $ CmmInt (fromIntegral off) wordWidth)
843                    ]
844
845         -- On powerpc (non-PIC), it's easier to jump directly to a label than
846         -- to use the register table, so we replace these registers
847         -- with the corresponding labels:
848         CmmReg (CmmGlobal EagerBlackholeInfo)
849           | cTargetArch == PPC && not opt_PIC
850           -> cmmExprConFold referenceKind $
851              CmmLit (CmmLabel (mkCmmCodeLabel rtsPackageId (fsLit "__stg_EAGER_BLACKHOLE_info")))
852         CmmReg (CmmGlobal GCEnter1)
853           | cTargetArch == PPC && not opt_PIC
854           -> cmmExprConFold referenceKind $
855              CmmLit (CmmLabel (mkCmmCodeLabel rtsPackageId (fsLit "__stg_gc_enter_1"))) 
856         CmmReg (CmmGlobal GCFun)
857           | cTargetArch == PPC && not opt_PIC
858           -> cmmExprConFold referenceKind $
859              CmmLit (CmmLabel (mkCmmCodeLabel rtsPackageId (fsLit "__stg_gc_fun")))
860
861         other
862            -> return other
863
864 \end{code}
865