The fix for #4914 was wrong and broke other things (see #5149). We
[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         ---- x86fp_kludge.  This pass inserts ffree instructions to clear
376         ---- the FPU stack on x86.  The x86 ABI requires that the FPU stack
377         ---- is clear, and library functions can return odd results if it
378         ---- isn't.
379         ----
380         ---- NB. must happen before shortcutBranches, because that
381         ---- generates JXX_GBLs which we can't fix up in x86fp_kludge.
382         let kludged =
383 #if i386_TARGET_ARCH
384                 {-# SCC "x86fp_kludge" #-}
385                 map x86fp_kludge alloced
386 #else
387                 alloced
388 #endif
389
390         ---- generate jump tables
391         let tabled      =
392                 {-# SCC "generateJumpTables" #-}
393                 generateJumpTables kludged
394
395         ---- shortcut branches
396         let shorted     =
397                 {-# SCC "shortcutBranches" #-}
398                 shortcutBranches dflags tabled
399
400         ---- sequence blocks
401         let sequenced   =
402                 {-# SCC "sequenceBlocks" #-}
403                 map sequenceTop shorted
404
405         ---- expansion of SPARC synthetic instrs
406 #if sparc_TARGET_ARCH
407         let expanded = 
408                 {-# SCC "sparc_expand" #-}
409                 map expandTop sequenced
410
411         dumpIfSet_dyn dflags
412                 Opt_D_dump_asm_expanded "Synthetic instructions expanded"
413                 (vcat $ map (docToSDoc . pprNatCmmTop) expanded)
414 #else
415         let expanded = 
416                 sequenced
417 #endif
418
419         return  ( usAlloc
420                 , expanded
421                 , lastMinuteImports ++ imports
422                 , ppr_raStatsColor
423                 , ppr_raStatsLinear)
424
425
426 #if i386_TARGET_ARCH
427 x86fp_kludge :: NatCmmTop Instr -> NatCmmTop Instr
428 x86fp_kludge top@(CmmData _ _) = top
429 x86fp_kludge (CmmProc info lbl (ListGraph code)) = 
430         CmmProc info lbl (ListGraph $ i386_insert_ffrees code)
431 #endif
432
433
434 -- | Build a doc for all the imports.
435 --
436 makeImportsDoc :: DynFlags -> [CLabel] -> Pretty.Doc
437 makeImportsDoc dflags imports
438  = dyld_stubs imports
439
440 #if HAVE_SUBSECTIONS_VIA_SYMBOLS
441                 -- On recent versions of Darwin, the linker supports
442                 -- dead-stripping of code and data on a per-symbol basis.
443                 -- There's a hack to make this work in PprMach.pprNatCmmTop.
444             Pretty.$$ Pretty.text ".subsections_via_symbols"
445 #endif
446 #if HAVE_GNU_NONEXEC_STACK
447                 -- On recent GNU ELF systems one can mark an object file
448                 -- as not requiring an executable stack. If all objects
449                 -- linked into a program have this note then the program
450                 -- will not use an executable stack, which is good for
451                 -- security. GHC generated code does not need an executable
452                 -- stack so add the note in:
453             Pretty.$$ Pretty.text ".section .note.GNU-stack,\"\",@progbits"
454 #endif
455 #if !defined(darwin_TARGET_OS)
456                 -- And just because every other compiler does, lets stick in
457                 -- an identifier directive: .ident "GHC x.y.z"
458             Pretty.$$ let compilerIdent = Pretty.text "GHC" Pretty.<+>
459                                           Pretty.text cProjectVersion
460                        in Pretty.text ".ident" Pretty.<+>
461                           Pretty.doubleQuotes compilerIdent
462 #endif
463
464  where
465         -- Generate "symbol stubs" for all external symbols that might
466         -- come from a dynamic library.
467         dyld_stubs :: [CLabel] -> Pretty.Doc
468 {-      dyld_stubs imps = Pretty.vcat $ map pprDyldSymbolStub $
469                                     map head $ group $ sort imps-}
470
471         arch    = platformArch  $ targetPlatform dflags
472         os      = platformOS    $ targetPlatform dflags
473         
474         -- (Hack) sometimes two Labels pretty-print the same, but have
475         -- different uniques; so we compare their text versions...
476         dyld_stubs imps
477                 | needImportedSymbols arch os
478                 = Pretty.vcat $
479                         (pprGotDeclaration arch os :) $
480                         map ( pprImportedSymbol arch os . fst . head) $
481                         groupBy (\(_,a) (_,b) -> a == b) $
482                         sortBy (\(_,a) (_,b) -> compare a b) $
483                         map doPpr $
484                         imps
485                 | otherwise
486                 = Pretty.empty
487
488         doPpr lbl = (lbl, Pretty.render $ pprCLabel lbl astyle)
489         astyle = mkCodeStyle AsmStyle
490
491
492 -- -----------------------------------------------------------------------------
493 -- Sequencing the basic blocks
494
495 -- Cmm BasicBlocks are self-contained entities: they always end in a
496 -- jump, either non-local or to another basic block in the same proc.
497 -- In this phase, we attempt to place the basic blocks in a sequence
498 -- such that as many of the local jumps as possible turn into
499 -- fallthroughs.
500
501 sequenceTop 
502         :: NatCmmTop Instr
503         -> NatCmmTop Instr
504
505 sequenceTop top@(CmmData _ _) = top
506 sequenceTop (CmmProc info lbl (ListGraph blocks)) = 
507   CmmProc info lbl (ListGraph $ makeFarBranches $ sequenceBlocks blocks)
508
509 -- The algorithm is very simple (and stupid): we make a graph out of
510 -- the blocks where there is an edge from one block to another iff the
511 -- first block ends by jumping to the second.  Then we topologically
512 -- sort this graph.  Then traverse the list: for each block, we first
513 -- output the block, then if it has an out edge, we move the
514 -- destination of the out edge to the front of the list, and continue.
515
516 -- FYI, the classic layout for basic blocks uses postorder DFS; this
517 -- algorithm is implemented in Hoopl.
518
519 sequenceBlocks 
520         :: Instruction instr
521         => [NatBasicBlock instr] 
522         -> [NatBasicBlock instr]
523
524 sequenceBlocks [] = []
525 sequenceBlocks (entry:blocks) = 
526   seqBlocks (mkNode entry : reverse (flattenSCCs (sccBlocks blocks)))
527   -- the first block is the entry point ==> it must remain at the start.
528
529
530 sccBlocks 
531         :: Instruction instr
532         => [NatBasicBlock instr] 
533         -> [SCC ( NatBasicBlock instr
534                 , Unique
535                 , [Unique])]
536
537 sccBlocks blocks = stronglyConnCompFromEdgedVerticesR (map mkNode blocks)
538
539 -- we're only interested in the last instruction of
540 -- the block, and only if it has a single destination.
541 getOutEdges 
542         :: Instruction instr
543         => [instr] -> [Unique]
544
545 getOutEdges instrs 
546         = case jumpDestsOfInstr (last instrs) of
547                 [one] -> [getUnique one]
548                 _many -> []
549
550 mkNode :: (Instruction t)
551        => GenBasicBlock t
552        -> (GenBasicBlock t, Unique, [Unique])
553 mkNode block@(BasicBlock id instrs) = (block, getUnique id, getOutEdges instrs)
554
555 seqBlocks :: (Eq t) => [(GenBasicBlock t1, t, [t])] -> [GenBasicBlock t1]
556 seqBlocks [] = []
557 seqBlocks ((block,_,[]) : rest)
558   = block : seqBlocks rest
559 seqBlocks ((block@(BasicBlock id instrs),_,[next]) : rest)
560   | can_fallthrough = BasicBlock id (init instrs) : seqBlocks rest'
561   | otherwise       = block : seqBlocks rest'
562   where
563         (can_fallthrough, rest') = reorder next [] rest
564           -- TODO: we should do a better job for cycles; try to maximise the
565           -- fallthroughs within a loop.
566 seqBlocks _ = panic "AsmCodegen:seqBlocks"
567
568 reorder :: (Eq a) => a -> [(t, a, t1)] -> [(t, a, t1)] -> (Bool, [(t, a, t1)])
569 reorder  _ accum [] = (False, reverse accum)
570 reorder id accum (b@(block,id',out) : rest)
571   | id == id'  = (True, (block,id,out) : reverse accum ++ rest)
572   | otherwise  = reorder id (b:accum) rest
573
574
575 -- -----------------------------------------------------------------------------
576 -- Making far branches
577
578 -- Conditional branches on PowerPC are limited to +-32KB; if our Procs get too
579 -- big, we have to work around this limitation.
580
581 makeFarBranches 
582         :: [NatBasicBlock Instr] 
583         -> [NatBasicBlock Instr]
584
585 #if powerpc_TARGET_ARCH
586 makeFarBranches blocks
587     | last blockAddresses < nearLimit = blocks
588     | otherwise = zipWith handleBlock blockAddresses blocks
589     where
590         blockAddresses = scanl (+) 0 $ map blockLen blocks
591         blockLen (BasicBlock _ instrs) = length instrs
592         
593         handleBlock addr (BasicBlock id instrs)
594                 = BasicBlock id (zipWith makeFar [addr..] instrs)
595         
596         makeFar _ (BCC ALWAYS tgt) = BCC ALWAYS tgt
597         makeFar addr (BCC cond tgt)
598             | abs (addr - targetAddr) >= nearLimit
599             = BCCFAR cond tgt
600             | otherwise
601             = BCC cond tgt
602             where Just targetAddr = lookupUFM blockAddressMap tgt
603         makeFar _ other            = other
604         
605         nearLimit = 7000 -- 8192 instructions are allowed; let's keep some
606                          -- distance, as we have a few pseudo-insns that are
607                          -- pretty-printed as multiple instructions,
608                          -- and it's just not worth the effort to calculate
609                          -- things exactly
610         
611         blockAddressMap = listToUFM $ zip (map blockId blocks) blockAddresses
612 #else
613 makeFarBranches = id
614 #endif
615
616 -- -----------------------------------------------------------------------------
617 -- Generate jump tables
618
619 -- Analyzes all native code and generates data sections for all jump
620 -- table instructions.
621 generateJumpTables
622         :: [NatCmmTop Instr] -> [NatCmmTop Instr]
623 generateJumpTables xs = concatMap f xs
624     where f p@(CmmProc _ _ (ListGraph xs)) = p : concatMap g xs
625           f p = [p]
626           g (BasicBlock _ xs) = catMaybes (map generateJumpTableForInstr xs)
627
628 -- -----------------------------------------------------------------------------
629 -- Shortcut branches
630
631 shortcutBranches 
632         :: DynFlags 
633         -> [NatCmmTop Instr] 
634         -> [NatCmmTop Instr]
635
636 shortcutBranches dflags tops
637   | optLevel dflags < 1 = tops    -- only with -O or higher
638   | otherwise           = map (apply_mapping mapping) tops'
639   where
640     (tops', mappings) = mapAndUnzip build_mapping tops
641     mapping = foldr plusUFM emptyUFM mappings
642
643 build_mapping :: GenCmmTop d t (ListGraph Instr)
644               -> (GenCmmTop d t (ListGraph Instr), UniqFM JumpDest)
645 build_mapping top@(CmmData _ _) = (top, emptyUFM)
646 build_mapping (CmmProc info lbl (ListGraph []))
647   = (CmmProc info lbl (ListGraph []), emptyUFM)
648 build_mapping (CmmProc info lbl (ListGraph (head:blocks)))
649   = (CmmProc info lbl (ListGraph (head:others)), mapping)
650         -- drop the shorted blocks, but don't ever drop the first one,
651         -- because it is pointed to by a global label.
652   where
653     -- find all the blocks that just consist of a jump that can be
654     -- shorted.
655     -- Don't completely eliminate loops here -- that can leave a dangling jump!
656     (_, shortcut_blocks, others) = foldl split (emptyBlockSet, [], []) blocks
657     split (s, shortcut_blocks, others) b@(BasicBlock id [insn])
658         | Just (DestBlockId dest) <- canShortcut insn,
659           (setMember dest s) || dest == id -- loop checks
660         = (s, shortcut_blocks, b : others)
661     split (s, shortcut_blocks, others) (BasicBlock id [insn])
662         | Just dest <- canShortcut insn
663         = (setInsert id s, (id,dest) : shortcut_blocks, others)
664     split (s, shortcut_blocks, others) other = (s, shortcut_blocks, other : others)
665
666
667     -- build a mapping from BlockId to JumpDest for shorting branches
668     mapping = foldl add emptyUFM shortcut_blocks
669     add ufm (id,dest) = addToUFM ufm id dest
670     
671 apply_mapping :: UniqFM JumpDest
672               -> GenCmmTop CmmStatic h (ListGraph Instr)
673               -> GenCmmTop CmmStatic h (ListGraph Instr)
674 apply_mapping ufm (CmmData sec statics) 
675   = CmmData sec (map (shortcutStatic (lookupUFM ufm)) statics)
676   -- we need to get the jump tables, so apply the mapping to the entries
677   -- of a CmmData too.
678 apply_mapping ufm (CmmProc info lbl (ListGraph blocks))
679   = CmmProc info lbl (ListGraph $ map short_bb blocks)
680   where
681     short_bb (BasicBlock id insns) = BasicBlock id $! map short_insn insns
682     short_insn i = shortcutJump (lookupUFM ufm) i
683                  -- shortcutJump should apply the mapping repeatedly,
684                  -- just in case we can short multiple branches.
685
686 -- -----------------------------------------------------------------------------
687 -- Instruction selection
688
689 -- Native code instruction selection for a chunk of stix code.  For
690 -- this part of the computation, we switch from the UniqSM monad to
691 -- the NatM monad.  The latter carries not only a Unique, but also an
692 -- Int denoting the current C stack pointer offset in the generated
693 -- code; this is needed for creating correct spill offsets on
694 -- architectures which don't offer, or for which it would be
695 -- prohibitively expensive to employ, a frame pointer register.  Viz,
696 -- x86.
697
698 -- The offset is measured in bytes, and indicates the difference
699 -- between the current (simulated) C stack-ptr and the value it was at
700 -- the beginning of the block.  For stacks which grow down, this value
701 -- should be either zero or negative.
702
703 -- Switching between the two monads whilst carrying along the same
704 -- Unique supply breaks abstraction.  Is that bad?
705
706 genMachCode 
707         :: DynFlags 
708         -> RawCmmTop 
709         -> UniqSM 
710                 ( [NatCmmTop Instr]
711                 , [CLabel])
712
713 genMachCode dflags cmm_top
714   = do  { initial_us <- getUs
715         ; let initial_st           = mkNatM_State initial_us 0 dflags
716               (new_tops, final_st) = initNat initial_st (cmmTopCodeGen dflags cmm_top)
717               final_delta          = natm_delta final_st
718               final_imports        = natm_imports final_st
719         ; if   final_delta == 0
720           then return (new_tops, final_imports)
721           else pprPanic "genMachCode: nonzero final delta" (int final_delta)
722     }
723
724 -- -----------------------------------------------------------------------------
725 -- Generic Cmm optimiser
726
727 {-
728 Here we do:
729
730   (a) Constant folding
731   (b) Simple inlining: a temporary which is assigned to and then
732       used, once, can be shorted.
733   (c) Position independent code and dynamic linking
734         (i)  introduce the appropriate indirections
735              and position independent refs
736         (ii) compile a list of imported symbols
737
738 Ideas for other things we could do:
739
740   - shortcut jumps-to-jumps
741   - simple CSE: if an expr is assigned to a temp, then replace later occs of
742     that expr with the temp, until the expr is no longer valid (can push through
743     temp assignments, and certain assigns to mem...)
744 -}
745
746 cmmToCmm :: DynFlags -> RawCmmTop -> (RawCmmTop, [CLabel])
747 cmmToCmm _ top@(CmmData _ _) = (top, [])
748 cmmToCmm dflags (CmmProc info lbl (ListGraph blocks)) = runCmmOpt dflags $ do
749   blocks' <- mapM cmmBlockConFold (cmmMiniInline (cmmEliminateDeadBlocks blocks))
750   return $ CmmProc info lbl (ListGraph blocks')
751
752 newtype CmmOptM a = CmmOptM (([CLabel], DynFlags) -> (# a, [CLabel] #))
753
754 instance Monad CmmOptM where
755   return x = CmmOptM $ \(imports, _) -> (# x,imports #)
756   (CmmOptM f) >>= g =
757     CmmOptM $ \(imports, dflags) ->
758                 case f (imports, dflags) of
759                   (# x, imports' #) ->
760                     case g x of
761                       CmmOptM g' -> g' (imports', dflags)
762
763 addImportCmmOpt :: CLabel -> CmmOptM ()
764 addImportCmmOpt lbl = CmmOptM $ \(imports, _dflags) -> (# (), lbl:imports #)
765
766 getDynFlagsCmmOpt :: CmmOptM DynFlags
767 getDynFlagsCmmOpt = CmmOptM $ \(imports, dflags) -> (# dflags, imports #)
768
769 runCmmOpt :: DynFlags -> CmmOptM a -> (a, [CLabel])
770 runCmmOpt dflags (CmmOptM f) = case f ([], dflags) of
771                         (# result, imports #) -> (result, imports)
772
773 cmmBlockConFold :: CmmBasicBlock -> CmmOptM CmmBasicBlock
774 cmmBlockConFold (BasicBlock id stmts) = do
775   stmts' <- mapM cmmStmtConFold stmts
776   return $ BasicBlock id stmts'
777
778 cmmStmtConFold :: CmmStmt -> CmmOptM CmmStmt
779 cmmStmtConFold stmt
780    = case stmt of
781         CmmAssign reg src
782            -> do src' <- cmmExprConFold DataReference src
783                  return $ case src' of
784                    CmmReg reg' | reg == reg' -> CmmNop
785                    new_src -> CmmAssign reg new_src
786
787         CmmStore addr src
788            -> do addr' <- cmmExprConFold DataReference addr
789                  src'  <- cmmExprConFold DataReference src
790                  return $ CmmStore addr' src'
791
792         CmmJump addr regs
793            -> do addr' <- cmmExprConFold JumpReference addr
794                  return $ CmmJump addr' regs
795
796         CmmCall target regs args srt returns
797            -> do target' <- case target of
798                               CmmCallee e conv -> do
799                                 e' <- cmmExprConFold CallReference e
800                                 return $ CmmCallee e' conv
801                               other -> return other
802                  args' <- mapM (\(CmmHinted arg hint) -> do
803                                   arg' <- cmmExprConFold DataReference arg
804                                   return (CmmHinted arg' hint)) args
805                  return $ CmmCall target' regs args' srt returns
806
807         CmmCondBranch test dest
808            -> do test' <- cmmExprConFold DataReference test
809                  return $ case test' of
810                    CmmLit (CmmInt 0 _) -> 
811                      CmmComment (mkFastString ("deleted: " ++ 
812                                         showSDoc (pprStmt stmt)))
813
814                    CmmLit (CmmInt _ _) -> CmmBranch dest
815                    _other -> CmmCondBranch test' dest
816
817         CmmSwitch expr ids
818            -> do expr' <- cmmExprConFold DataReference expr
819                  return $ CmmSwitch expr' ids
820
821         other
822            -> return other
823
824
825 cmmExprConFold :: ReferenceKind -> CmmExpr -> CmmOptM CmmExpr
826 cmmExprConFold referenceKind expr
827    = case expr of
828         CmmLoad addr rep
829            -> do addr' <- cmmExprConFold DataReference addr
830                  return $ CmmLoad addr' rep
831
832         CmmMachOp mop args
833            -- For MachOps, we first optimize the children, and then we try 
834            -- our hand at some constant-folding.
835            -> do args' <- mapM (cmmExprConFold DataReference) args
836                  return $ cmmMachOpFold mop args'
837
838         CmmLit (CmmLabel lbl)
839            -> do
840                 dflags <- getDynFlagsCmmOpt
841                 cmmMakeDynamicReference dflags addImportCmmOpt referenceKind lbl
842         CmmLit (CmmLabelOff lbl off)
843            -> do
844                  dflags <- getDynFlagsCmmOpt
845                  dynRef <- cmmMakeDynamicReference dflags addImportCmmOpt referenceKind lbl
846                  return $ cmmMachOpFold (MO_Add wordWidth) [
847                      dynRef,
848                      (CmmLit $ CmmInt (fromIntegral off) wordWidth)
849                    ]
850
851         -- On powerpc (non-PIC), it's easier to jump directly to a label than
852         -- to use the register table, so we replace these registers
853         -- with the corresponding labels:
854         CmmReg (CmmGlobal EagerBlackholeInfo)
855           | cTargetArch == PPC && not opt_PIC
856           -> cmmExprConFold referenceKind $
857              CmmLit (CmmLabel (mkCmmCodeLabel rtsPackageId (fsLit "__stg_EAGER_BLACKHOLE_info")))
858         CmmReg (CmmGlobal GCEnter1)
859           | cTargetArch == PPC && not opt_PIC
860           -> cmmExprConFold referenceKind $
861              CmmLit (CmmLabel (mkCmmCodeLabel rtsPackageId (fsLit "__stg_gc_enter_1"))) 
862         CmmReg (CmmGlobal GCFun)
863           | cTargetArch == PPC && not opt_PIC
864           -> cmmExprConFold referenceKind $
865              CmmLit (CmmLabel (mkCmmCodeLabel rtsPackageId (fsLit "__stg_gc_fun")))
866
867         other
868            -> return other
869
870 \end{code}
871