68958d22a96d9766eb1ffc525429f317ce241d62
[ghc-hetmet.git] / ghc / compiler / codeGen / CgUtils.hs
1 -----------------------------------------------------------------------------
2 --
3 -- Code generator utilities; mostly monadic
4 --
5 -- (c) The University of Glasgow 2004
6 --
7 -----------------------------------------------------------------------------
8
9 module CgUtils (
10         addIdReps,
11         cgLit,
12         emitDataLits, emitRODataLits, emitIf, emitIfThenElse,
13         emitRtsCall, emitRtsCallWithVols, emitRtsCallWithResult,
14         assignTemp, newTemp,
15         emitSimultaneously,
16         emitSwitch, emitLitSwitch,
17         tagToClosure,
18
19         cmmAndWord, cmmOrWord, cmmNegate, cmmEqWord, cmmNeWord,
20         cmmOffsetExprW, cmmOffsetExprB,
21         cmmRegOffW, cmmRegOffB,
22         cmmLabelOffW, cmmLabelOffB,
23         cmmOffsetW, cmmOffsetB,
24         cmmOffsetLitW, cmmOffsetLitB,
25         cmmLoadIndexW,
26
27         addToMem, addToMemE,
28         mkWordCLit,
29         mkStringCLit,
30         packHalfWordsCLit,
31         blankWord
32   ) where
33
34 #include "HsVersions.h"
35
36 import CgMonad
37 import TyCon            ( TyCon, tyConName )
38 import Id               ( Id )
39 import Constants        ( wORD_SIZE )
40 import SMRep            ( CgRep, StgWord, hALF_WORD_SIZE_IN_BITS, ByteOff,
41                           WordOff, idCgRep )
42 import PprCmm           ( {- instances -} )
43 import Cmm
44 import CLabel
45 import CmmUtils
46 import MachOp           ( MachRep(..), wordRep, MachOp(..),  MachHint(..),
47                           mo_wordOr, mo_wordAnd, mo_wordNe, mo_wordEq,
48                           mo_wordULt, mo_wordUGt, mo_wordUGe, machRepByteWidth )
49 import ForeignCall      ( CCallConv(..) )
50 import Literal          ( Literal(..) )
51 import CLabel           ( CLabel, mkStringLitLabel )
52 import Digraph          ( SCC(..), stronglyConnComp )
53 import ListSetOps       ( assocDefault )
54 import Util             ( filterOut, sortLe )
55 import DynFlags         ( DynFlags(..), HscTarget(..) )
56 import Packages         ( HomeModules )
57 import FastString       ( LitString, FastString, unpackFS )
58 import Outputable
59
60 import Char             ( ord )
61 import DATA_BITS
62 import Maybe            ( isNothing )
63
64 -------------------------------------------------------------------------
65 --
66 --      Random small functions
67 --
68 -------------------------------------------------------------------------
69
70 addIdReps :: [Id] -> [(CgRep, Id)]
71 addIdReps ids = [(idCgRep id, id) | id <- ids]
72
73 -------------------------------------------------------------------------
74 --
75 --      Literals
76 --
77 -------------------------------------------------------------------------
78
79 cgLit :: Literal -> FCode CmmLit
80 cgLit (MachStr s) = mkStringCLit (unpackFS s)
81 cgLit other_lit   = return (mkSimpleLit other_lit)
82
83 mkSimpleLit :: Literal -> CmmLit
84 mkSimpleLit (MachChar   c)    = CmmInt (fromIntegral (ord c)) wordRep
85 mkSimpleLit MachNullAddr      = zeroCLit
86 mkSimpleLit (MachInt i)       = CmmInt i wordRep
87 mkSimpleLit (MachInt64 i)     = CmmInt i I64
88 mkSimpleLit (MachWord i)      = CmmInt i wordRep
89 mkSimpleLit (MachWord64 i)    = CmmInt i I64
90 mkSimpleLit (MachFloat r)     = CmmFloat r F32
91 mkSimpleLit (MachDouble r)    = CmmFloat r F64
92 mkSimpleLit (MachLabel fs ms) = CmmLabel (mkForeignLabel fs ms is_dyn)
93                               where
94                                 is_dyn = False  -- ToDo: fix me
95         
96 mkLtOp :: Literal -> MachOp
97 -- On signed literals we must do a signed comparison
98 mkLtOp (MachInt _)    = MO_S_Lt wordRep
99 mkLtOp (MachFloat _)  = MO_S_Lt F32
100 mkLtOp (MachDouble _) = MO_S_Lt F64
101 mkLtOp lit            = MO_U_Lt (cmmLitRep (mkSimpleLit lit))
102
103
104 ---------------------------------------------------
105 --
106 --      Cmm data type functions
107 --
108 ---------------------------------------------------
109
110 -----------------------
111 -- The "B" variants take byte offsets
112 cmmRegOffB :: CmmReg -> ByteOff -> CmmExpr
113 cmmRegOffB = cmmRegOff
114
115 cmmOffsetB :: CmmExpr -> ByteOff -> CmmExpr
116 cmmOffsetB = cmmOffset
117
118 cmmOffsetExprB :: CmmExpr -> CmmExpr -> CmmExpr
119 cmmOffsetExprB = cmmOffsetExpr
120
121 cmmLabelOffB :: CLabel -> ByteOff -> CmmLit
122 cmmLabelOffB = cmmLabelOff
123
124 cmmOffsetLitB :: CmmLit -> ByteOff -> CmmLit
125 cmmOffsetLitB = cmmOffsetLit
126
127 -----------------------
128 -- The "W" variants take word offsets
129 cmmOffsetExprW :: CmmExpr -> CmmExpr -> CmmExpr
130 -- The second arg is a *word* offset; need to change it to bytes
131 cmmOffsetExprW e (CmmLit (CmmInt n _)) = cmmOffsetW e (fromInteger n)
132 cmmOffsetExprW e wd_off = cmmIndexExpr wordRep e wd_off
133
134 cmmOffsetW :: CmmExpr -> WordOff -> CmmExpr
135 cmmOffsetW e n = cmmOffsetB e (wORD_SIZE * n)
136
137 cmmRegOffW :: CmmReg -> WordOff -> CmmExpr
138 cmmRegOffW reg wd_off = cmmRegOffB reg (wd_off * wORD_SIZE)
139
140 cmmOffsetLitW :: CmmLit -> WordOff -> CmmLit
141 cmmOffsetLitW lit wd_off = cmmOffsetLitB lit (wORD_SIZE * wd_off)
142
143 cmmLabelOffW :: CLabel -> WordOff -> CmmLit
144 cmmLabelOffW lbl wd_off = cmmLabelOffB lbl (wORD_SIZE * wd_off)
145
146 cmmLoadIndexW :: CmmExpr -> Int -> CmmExpr
147 cmmLoadIndexW base off
148   = CmmLoad (cmmOffsetW base off) wordRep
149
150 -----------------------
151 cmmNeWord, cmmEqWord, cmmOrWord, cmmAndWord :: CmmExpr -> CmmExpr -> CmmExpr
152 cmmOrWord  e1 e2 = CmmMachOp mo_wordOr  [e1, e2]
153 cmmAndWord e1 e2 = CmmMachOp mo_wordAnd [e1, e2]
154 cmmNeWord  e1 e2 = CmmMachOp mo_wordNe  [e1, e2]
155 cmmEqWord  e1 e2 = CmmMachOp mo_wordEq  [e1, e2]
156 cmmULtWord e1 e2 = CmmMachOp mo_wordULt [e1, e2]
157 cmmUGeWord e1 e2 = CmmMachOp mo_wordUGe [e1, e2]
158 cmmUGtWord e1 e2 = CmmMachOp mo_wordUGt [e1, e2]
159
160 cmmNegate :: CmmExpr -> CmmExpr
161 cmmNegate (CmmLit (CmmInt n rep)) = CmmLit (CmmInt (-n) rep)
162 cmmNegate e                       = CmmMachOp (MO_S_Neg (cmmExprRep e)) [e]
163
164 blankWord :: CmmStatic
165 blankWord = CmmUninitialised wORD_SIZE
166
167 -----------------------
168 --      Making literals
169
170 mkWordCLit :: StgWord -> CmmLit
171 mkWordCLit wd = CmmInt (fromIntegral wd) wordRep
172
173 packHalfWordsCLit :: (Integral a, Integral b) => a -> b -> CmmLit
174 -- Make a single word literal in which the lower_half_word is
175 -- at the lower address, and the upper_half_word is at the 
176 -- higher address
177 -- ToDo: consider using half-word lits instead
178 --       but be careful: that's vulnerable when reversed
179 packHalfWordsCLit lower_half_word upper_half_word
180 #ifdef WORDS_BIGENDIAN
181    = mkWordCLit ((fromIntegral lower_half_word `shiftL` hALF_WORD_SIZE_IN_BITS)
182                  .|. fromIntegral upper_half_word)
183 #else 
184    = mkWordCLit ((fromIntegral lower_half_word) 
185                  .|. (fromIntegral upper_half_word `shiftL` hALF_WORD_SIZE_IN_BITS))
186 #endif
187
188 --------------------------------------------------------------------------
189 --
190 -- Incrementing a memory location
191 --
192 --------------------------------------------------------------------------
193
194 addToMem :: MachRep     -- rep of the counter
195          -> CmmExpr     -- Address
196          -> Int         -- What to add (a word)
197          -> CmmStmt
198 addToMem rep ptr n = addToMemE rep ptr (CmmLit (CmmInt (toInteger n) rep))
199
200 addToMemE :: MachRep    -- rep of the counter
201           -> CmmExpr    -- Address
202           -> CmmExpr    -- What to add (a word-typed expression)
203           -> CmmStmt
204 addToMemE rep ptr n
205   = CmmStore ptr (CmmMachOp (MO_Add rep) [CmmLoad ptr rep, n])
206
207 -------------------------------------------------------------------------
208 --
209 --      Converting a closure tag to a closure for enumeration types
210 --      (this is the implementation of tagToEnum#).
211 --
212 -------------------------------------------------------------------------
213
214 tagToClosure :: HomeModules -> TyCon -> CmmExpr -> CmmExpr
215 tagToClosure hmods tycon tag
216   = CmmLoad (cmmOffsetExprW closure_tbl tag) wordRep
217   where closure_tbl = CmmLit (CmmLabel lbl)
218         lbl = mkClosureTableLabel hmods (tyConName tycon)
219
220 -------------------------------------------------------------------------
221 --
222 --      Conditionals and rts calls
223 --
224 -------------------------------------------------------------------------
225
226 emitIf :: CmmExpr       -- Boolean
227        -> Code          -- Then part
228        -> Code          
229 -- Emit (if e then x)
230 -- ToDo: reverse the condition to avoid the extra branch instruction if possible
231 -- (some conditionals aren't reversible. eg. floating point comparisons cannot
232 -- be inverted because there exist some values for which both comparisons
233 -- return False, such as NaN.)
234 emitIf cond then_part
235   = do { then_id <- newLabelC
236        ; join_id <- newLabelC
237        ; stmtC (CmmCondBranch cond then_id)
238        ; stmtC (CmmBranch join_id)
239        ; labelC then_id
240        ; then_part
241        ; labelC join_id
242        }
243
244 emitIfThenElse :: CmmExpr       -- Boolean
245                 -> Code         -- Then part
246                 -> Code         -- Else part
247                 -> Code         
248 -- Emit (if e then x else y)
249 emitIfThenElse cond then_part else_part
250   = do { then_id <- newLabelC
251        ; else_id <- newLabelC
252        ; join_id <- newLabelC
253        ; stmtC (CmmCondBranch cond then_id)
254        ; else_part
255        ; stmtC (CmmBranch join_id)
256        ; labelC then_id
257        ; then_part
258        ; labelC join_id
259        }
260
261 emitRtsCall :: LitString -> [(CmmExpr,MachHint)] -> Code
262 emitRtsCall fun args = emitRtsCall' [] fun args Nothing
263    -- The 'Nothing' says "save all global registers"
264
265 emitRtsCallWithVols :: LitString -> [(CmmExpr,MachHint)] -> [GlobalReg] -> Code
266 emitRtsCallWithVols fun args vols
267    = emitRtsCall' [] fun args (Just vols)
268
269 emitRtsCallWithResult :: CmmReg -> MachHint -> LitString
270         -> [(CmmExpr,MachHint)] -> Code
271 emitRtsCallWithResult res hint fun args
272    = emitRtsCall' [(res,hint)] fun args Nothing
273
274 -- Make a call to an RTS C procedure
275 emitRtsCall'
276    :: [(CmmReg,MachHint)]
277    -> LitString
278    -> [(CmmExpr,MachHint)]
279    -> Maybe [GlobalReg]
280    -> Code
281 emitRtsCall' res fun args vols = stmtC (CmmCall target res args vols)
282   where
283     target   = CmmForeignCall fun_expr CCallConv
284     fun_expr = mkLblExpr (mkRtsCodeLabel fun)
285
286
287 -------------------------------------------------------------------------
288 --
289 --      Strings gnerate a top-level data block
290 --
291 -------------------------------------------------------------------------
292
293 emitDataLits :: CLabel -> [CmmLit] -> Code
294 -- Emit a data-segment data block
295 emitDataLits lbl lits
296   = emitData Data (CmmDataLabel lbl : map CmmStaticLit lits)
297
298 emitRODataLits :: CLabel -> [CmmLit] -> Code
299 -- Emit a read-only data block
300 emitRODataLits lbl lits
301   = emitData section (CmmDataLabel lbl : map CmmStaticLit lits)
302   where section | any needsRelocation lits = RelocatableReadOnlyData
303                 | otherwise                = ReadOnlyData
304         needsRelocation (CmmLabel _)      = True
305         needsRelocation (CmmLabelOff _ _) = True
306         needsRelocation _                 = False
307
308 mkStringCLit :: String -> FCode CmmLit
309 -- Make a global definition for the string,
310 -- and return its label
311 mkStringCLit str 
312   = do  { uniq <- newUnique
313         ; let lbl = mkStringLitLabel uniq
314         ; emitData ReadOnlyData [CmmDataLabel lbl, CmmString str]
315         ; return (CmmLabel lbl) }
316
317 -------------------------------------------------------------------------
318 --
319 --      Assigning expressions to temporaries
320 --
321 -------------------------------------------------------------------------
322
323 assignTemp :: CmmExpr -> FCode CmmExpr
324 -- For a non-trivial expression, e, create a local
325 -- variable and assign the expression to it
326 assignTemp e 
327   | isTrivialCmmExpr e = return e
328   | otherwise          = do { reg <- newTemp (cmmExprRep e)
329                             ; stmtC (CmmAssign reg e)
330                             ; return (CmmReg reg) }
331
332
333 newTemp :: MachRep -> FCode CmmReg
334 newTemp rep = do { uniq <- newUnique; return (CmmLocal (LocalReg uniq rep)) }
335
336
337 -------------------------------------------------------------------------
338 --
339 --      Building case analysis
340 --
341 -------------------------------------------------------------------------
342
343 emitSwitch
344         :: CmmExpr                -- Tag to switch on
345         -> [(ConTagZ, CgStmts)]   -- Tagged branches
346         -> Maybe CgStmts          -- Default branch (if any)
347         -> ConTagZ -> ConTagZ     -- Min and Max possible values; behaviour
348                                   --    outside this range is undefined
349         -> Code
350
351 -- ONLY A DEFAULT BRANCH: no case analysis to do
352 emitSwitch tag_expr [] (Just stmts) _ _
353   = emitCgStmts stmts
354
355 -- Right, off we go
356 emitSwitch tag_expr branches mb_deflt lo_tag hi_tag
357   =     -- Just sort the branches before calling mk_sritch
358     do  { mb_deflt_id <-
359                 case mb_deflt of
360                   Nothing    -> return Nothing
361                   Just stmts -> do id <- forkCgStmts stmts; return (Just id)
362
363         ; dflags <- getDynFlags
364         ; let via_C | HscC <- hscTarget dflags = True
365                     | otherwise                = False
366
367         ; stmts <- mk_switch tag_expr (sortLe le branches) 
368                         mb_deflt_id lo_tag hi_tag via_C
369         ; emitCgStmts stmts
370         }
371   where
372     (t1,_) `le` (t2,_) = t1 <= t2
373
374
375 mk_switch :: CmmExpr -> [(ConTagZ, CgStmts)]
376           -> Maybe BlockId -> ConTagZ -> ConTagZ -> Bool
377           -> FCode CgStmts
378
379 -- SINGLETON TAG RANGE: no case analysis to do
380 mk_switch tag_expr [(tag,stmts)] _ lo_tag hi_tag via_C
381   | lo_tag == hi_tag
382   = ASSERT( tag == lo_tag )
383     return stmts
384
385 -- SINGLETON BRANCH, NO DEFUALT: no case analysis to do
386 mk_switch tag_expr [(tag,stmts)] Nothing lo_tag hi_tag via_C
387   = return stmts
388         -- The simplifier might have eliminated a case
389         --       so we may have e.g. case xs of 
390         --                               [] -> e
391         -- In that situation we can be sure the (:) case 
392         -- can't happen, so no need to test
393
394 -- SINGLETON BRANCH: one equality check to do
395 mk_switch tag_expr [(tag,stmts)] (Just deflt) lo_tag hi_tag via_C
396   = return (CmmCondBranch cond deflt `consCgStmt` stmts)
397   where
398     cond  =  cmmNeWord tag_expr (CmmLit (mkIntCLit tag))
399         -- We have lo_tag < hi_tag, but there's only one branch, 
400         -- so there must be a default
401
402 -- ToDo: we might want to check for the two branch case, where one of
403 -- the branches is the tag 0, because comparing '== 0' is likely to be
404 -- more efficient than other kinds of comparison.
405
406 -- DENSE TAG RANGE: use a switch statment.
407 --
408 -- We also use a switch uncoditionally when compiling via C, because
409 -- this will get emitted as a C switch statement and the C compiler
410 -- should do a good job of optimising it.  Also, older GCC versions
411 -- (2.95 in particular) have problems compiling the complicated
412 -- if-trees generated by this code, so compiling to a switch every
413 -- time works around that problem.
414 --
415 mk_switch tag_expr branches mb_deflt lo_tag hi_tag via_C
416   | use_switch  -- Use a switch
417   = do  { branch_ids <- mapM forkCgStmts (map snd branches)
418         ; let 
419                 tagged_blk_ids = zip (map fst branches) (map Just branch_ids)
420
421                 find_branch :: ConTagZ -> Maybe BlockId
422                 find_branch i = assocDefault mb_deflt tagged_blk_ids i
423
424                 -- NB. we have eliminated impossible branches at
425                 -- either end of the range (see below), so the first
426                 -- tag of a real branch is real_lo_tag (not lo_tag).
427                 arms = [ find_branch i | i <- [real_lo_tag..real_hi_tag]]
428
429                 switch_stmt = CmmSwitch (cmmOffset tag_expr (- real_lo_tag)) arms
430
431         ; ASSERT(not (all isNothing arms)) 
432           return (oneCgStmt switch_stmt)
433         }
434
435   -- if we can knock off a bunch of default cases with one if, then do so
436   | Just deflt <- mb_deflt, (lowest_branch - lo_tag) >= n_branches
437   = do { (assign_tag, tag_expr') <- assignTemp' tag_expr
438        ; let cond = cmmULtWord tag_expr' (CmmLit (mkIntCLit lowest_branch))
439              branch = CmmCondBranch cond deflt
440        ; stmts <- mk_switch tag_expr' branches mb_deflt 
441                         lowest_branch hi_tag via_C
442        ; return (assign_tag `consCgStmt` (branch `consCgStmt` stmts))
443        }
444
445   | Just deflt <- mb_deflt, (hi_tag - highest_branch) >= n_branches
446   = do { (assign_tag, tag_expr') <- assignTemp' tag_expr
447        ; let cond = cmmUGtWord tag_expr' (CmmLit (mkIntCLit highest_branch))
448              branch = CmmCondBranch cond deflt
449        ; stmts <- mk_switch tag_expr' branches mb_deflt 
450                         lo_tag highest_branch via_C
451        ; return (assign_tag `consCgStmt` (branch `consCgStmt` stmts))
452        }
453
454   | otherwise   -- Use an if-tree
455   = do  { (assign_tag, tag_expr') <- assignTemp' tag_expr
456                 -- To avoid duplication
457         ; lo_stmts <- mk_switch tag_expr' lo_branches mb_deflt 
458                                 lo_tag (mid_tag-1) via_C
459         ; hi_stmts <- mk_switch tag_expr' hi_branches mb_deflt 
460                                 mid_tag hi_tag via_C
461         ; hi_id <- forkCgStmts hi_stmts
462         ; let cond = cmmUGeWord tag_expr' (CmmLit (mkIntCLit mid_tag))
463               branch_stmt = CmmCondBranch cond hi_id
464         ; return (assign_tag `consCgStmt` (branch_stmt `consCgStmt` lo_stmts)) 
465         }
466         -- we test (e >= mid_tag) rather than (e < mid_tag), because
467         -- the former works better when e is a comparison, and there
468         -- are two tags 0 & 1 (mid_tag == 1).  In this case, the code
469         -- generator can reduce the condition to e itself without
470         -- having to reverse the sense of the comparison: comparisons
471         -- can't always be easily reversed (eg. floating
472         -- pt. comparisons).
473   where
474     use_switch   = {- pprTrace "mk_switch" (
475                         ppr tag_expr <+> text "n_tags:" <+> int n_tags <+>
476                         text "n_branches:" <+> int n_branches <+>
477                         text "lo_tag: " <+> int lo_tag <+>
478                         text "hi_tag: " <+> int hi_tag <+>
479                         text "real_lo_tag: " <+> int real_lo_tag <+>
480                         text "real_hi_tag: " <+> int real_hi_tag) $ -}
481                    ASSERT( n_branches > 1 && n_tags > 1 ) 
482                    n_tags > 2 && (small || dense || via_C)
483                  -- a 2-branch switch always turns into an if.
484     small        = n_tags <= 4
485     dense        = n_branches > (n_tags `div` 2)
486     exhaustive   = n_tags == n_branches
487     n_branches   = length branches
488     
489     -- ignore default slots at each end of the range if there's 
490     -- no default branch defined.
491     lowest_branch  = fst (head branches)
492     highest_branch = fst (last branches)
493
494     real_lo_tag
495         | isNothing mb_deflt = lowest_branch
496         | otherwise          = lo_tag
497
498     real_hi_tag
499         | isNothing mb_deflt = highest_branch
500         | otherwise          = hi_tag
501
502     n_tags = real_hi_tag - real_lo_tag + 1
503
504         -- INVARIANT: Provided hi_tag > lo_tag (which is true)
505         --      lo_tag <= mid_tag < hi_tag
506         --      lo_branches have tags <  mid_tag
507         --      hi_branches have tags >= mid_tag
508
509     (mid_tag,_) = branches !! (n_branches `div` 2)
510         -- 2 branches => n_branches `div` 2 = 1
511         --            => branches !! 1 give the *second* tag
512         -- There are always at least 2 branches here
513
514     (lo_branches, hi_branches) = span is_lo branches
515     is_lo (t,_) = t < mid_tag
516
517
518 assignTemp' e
519   | isTrivialCmmExpr e = return (CmmNop, e)
520   | otherwise          = do { reg <- newTemp (cmmExprRep e)
521                             ; return (CmmAssign reg e, CmmReg reg) }
522
523
524 emitLitSwitch :: CmmExpr                        -- Tag to switch on
525               -> [(Literal, CgStmts)]           -- Tagged branches
526               -> CgStmts                        -- Default branch (always)
527               -> Code                           -- Emit the code
528 -- Used for general literals, whose size might not be a word, 
529 -- where there is always a default case, and where we don't know
530 -- the range of values for certain.  For simplicity we always generate a tree.
531 --
532 -- ToDo: for integers we could do better here, perhaps by generalising
533 -- mk_switch and using that.  --SDM 15/09/2004
534 emitLitSwitch scrut [] deflt 
535   = emitCgStmts deflt
536 emitLitSwitch scrut branches deflt_blk
537   = do  { scrut' <- assignTemp scrut
538         ; deflt_blk_id <- forkCgStmts deflt_blk
539         ; blk <- mk_lit_switch scrut' deflt_blk_id (sortLe le branches)
540         ; emitCgStmts blk }
541   where
542     le (t1,_) (t2,_) = t1 <= t2
543
544 mk_lit_switch :: CmmExpr -> BlockId 
545               -> [(Literal,CgStmts)]
546               -> FCode CgStmts
547 mk_lit_switch scrut deflt_blk_id [(lit,blk)] 
548   = return (consCgStmt if_stmt blk)
549   where
550     cmm_lit = mkSimpleLit lit
551     rep     = cmmLitRep cmm_lit
552     cond    = CmmMachOp (MO_Ne rep) [scrut, CmmLit cmm_lit]
553     if_stmt = CmmCondBranch cond deflt_blk_id
554
555 mk_lit_switch scrut deflt_blk_id branches
556   = do  { hi_blk <- mk_lit_switch scrut deflt_blk_id hi_branches
557         ; lo_blk <- mk_lit_switch scrut deflt_blk_id lo_branches
558         ; lo_blk_id <- forkCgStmts lo_blk
559         ; let if_stmt = CmmCondBranch cond lo_blk_id
560         ; return (if_stmt `consCgStmt` hi_blk) }
561   where
562     n_branches = length branches
563     (mid_lit,_) = branches !! (n_branches `div` 2)
564         -- See notes above re mid_tag
565
566     (lo_branches, hi_branches) = span is_lo branches
567     is_lo (t,_) = t < mid_lit
568
569     cond    = CmmMachOp (mkLtOp mid_lit) 
570                         [scrut, CmmLit (mkSimpleLit mid_lit)]
571
572 -------------------------------------------------------------------------
573 --
574 --      Simultaneous assignment
575 --
576 -------------------------------------------------------------------------
577
578
579 emitSimultaneously :: CmmStmts -> Code
580 -- Emit code to perform the assignments in the
581 -- input simultaneously, using temporary variables when necessary.
582 --
583 -- The Stmts must be:
584 --      CmmNop, CmmComment, CmmAssign, CmmStore
585 -- and nothing else
586
587
588 -- We use the strongly-connected component algorithm, in which
589 --      * the vertices are the statements
590 --      * an edge goes from s1 to s2 iff
591 --              s1 assigns to something s2 uses
592 --        that is, if s1 should *follow* s2 in the final order
593
594 type CVertex = (Int, CmmStmt)   -- Give each vertex a unique number,
595                                 -- for fast comparison
596
597 emitSimultaneously stmts
598   = codeOnly $
599     case filterOut isNopStmt (stmtList stmts) of 
600         -- Remove no-ops
601       []        -> nopC
602       [stmt]    -> stmtC stmt   -- It's often just one stmt
603       stmt_list -> doSimultaneously1 (zip [(1::Int)..] stmt_list)
604
605 doSimultaneously1 :: [CVertex] -> Code
606 doSimultaneously1 vertices
607   = let
608         edges = [ (vertex, key1, edges_from stmt1)
609                 | vertex@(key1, stmt1) <- vertices
610                 ]
611         edges_from stmt1 = [ key2 | (key2, stmt2) <- vertices, 
612                                     stmt1 `mustFollow` stmt2
613                            ]
614         components = stronglyConnComp edges
615
616         -- do_components deal with one strongly-connected component
617         -- Not cyclic, or singleton?  Just do it
618         do_component (AcyclicSCC (n,stmt))  = stmtC stmt
619         do_component (CyclicSCC [(n,stmt)]) = stmtC stmt
620
621                 -- Cyclic?  Then go via temporaries.  Pick one to
622                 -- break the loop and try again with the rest.
623         do_component (CyclicSCC ((n,first_stmt) : rest))
624           = do  { from_temp <- go_via_temp first_stmt
625                 ; doSimultaneously1 rest
626                 ; stmtC from_temp }
627
628         go_via_temp (CmmAssign dest src)
629           = do  { tmp <- newTemp (cmmRegRep dest)
630                 ; stmtC (CmmAssign tmp src)
631                 ; return (CmmAssign dest (CmmReg tmp)) }
632         go_via_temp (CmmStore dest src)
633           = do  { tmp <- newTemp (cmmExprRep src)
634                 ; stmtC (CmmAssign tmp src)
635                 ; return (CmmStore dest (CmmReg tmp)) }
636     in
637     mapCs do_component components
638
639 mustFollow :: CmmStmt -> CmmStmt -> Bool
640 CmmAssign reg _  `mustFollow` stmt = anySrc (reg `regUsedIn`) stmt
641 CmmStore loc e   `mustFollow` stmt = anySrc (locUsedIn loc (cmmExprRep e)) stmt
642 CmmNop           `mustFollow` stmt = False
643 CmmComment _     `mustFollow` stmt = False
644
645
646 anySrc :: (CmmExpr -> Bool) -> CmmStmt -> Bool
647 -- True if the fn is true of any input of the stmt
648 anySrc p (CmmAssign _ e)    = p e
649 anySrc p (CmmStore e1 e2)   = p e1 || p e2      -- Might be used in either side
650 anySrc p (CmmComment _)     = False
651 anySrc p CmmNop             = False
652 anySrc p other              = True              -- Conservative
653
654 regUsedIn :: CmmReg -> CmmExpr -> Bool
655 reg `regUsedIn` CmmLit _         = False
656 reg `regUsedIn` CmmLoad e  _     = reg `regUsedIn` e
657 reg `regUsedIn` CmmReg reg'      = reg == reg'
658 reg `regUsedIn` CmmRegOff reg' _ = reg == reg'
659 reg `regUsedIn` CmmMachOp _ es   = any (reg `regUsedIn`) es
660
661 locUsedIn :: CmmExpr -> MachRep -> CmmExpr -> Bool
662 -- (locUsedIn a r e) checks whether writing to r[a] could affect the value of
663 -- 'e'.  Returns True if it's not sure.
664 locUsedIn loc rep (CmmLit _)         = False
665 locUsedIn loc rep (CmmLoad e ld_rep) = possiblySameLoc loc rep e ld_rep
666 locUsedIn loc rep (CmmReg reg')      = False
667 locUsedIn loc rep (CmmRegOff reg' _) = False
668 locUsedIn loc rep (CmmMachOp _ es)   = any (locUsedIn loc rep) es
669
670 possiblySameLoc :: CmmExpr -> MachRep -> CmmExpr -> MachRep -> Bool
671 -- Assumes that distinct registers (eg Hp, Sp) do not 
672 -- point to the same location, nor any offset thereof.
673 possiblySameLoc (CmmReg r1)       rep1 (CmmReg r2)      rep2  = r1==r2
674 possiblySameLoc (CmmReg r1)       rep1 (CmmRegOff r2 0) rep2  = r1==r2
675 possiblySameLoc (CmmRegOff r1 0)  rep1 (CmmReg r2)      rep2  = r1==r2
676 possiblySameLoc (CmmRegOff r1 start1) rep1 (CmmRegOff r2 start2) rep2 
677   = r1==r2 && end1 > start2 && end2 > start1
678   where
679     end1 = start1 + machRepByteWidth rep1
680     end2 = start2 + machRepByteWidth rep2
681
682 possiblySameLoc l1 rep1 (CmmLit _) rep2 = False
683 possiblySameLoc l1 rep1 l2         rep2 = True  -- Conservative