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