Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC

Commits:

1 changed file:

Changes:

  • compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
    ... ... @@ -317,15 +317,9 @@ stmtToInstrs stmt = do
    317 317
           CmmComment s   -> return (unitOL (COMMENT (ftext s)))
    
    318 318
           CmmTick {}     -> return nilOL
    
    319 319
     
    
    320
    -      CmmAssign reg src
    
    321
    -        | isFloatType ty         -> assignReg_FltCode format reg src
    
    322
    -        | otherwise              -> assignReg_IntCode format reg src
    
    323
    -          where ty = cmmRegType reg
    
    324
    -                format = cmmTypeFormat ty
    
    320
    +      CmmAssign reg src -> assignReg reg src
    
    325 321
     
    
    326
    -      CmmStore addr src _alignment
    
    327
    -        | isFloatType ty         -> assignMem_FltCode format addr src
    
    328
    -        | otherwise              -> assignMem_IntCode format addr src
    
    322
    +      CmmStore addr src _alignment -> assignMem format addr src
    
    329 323
               where ty = cmmExprType platform src
    
    330 324
                     format = cmmTypeFormat ty
    
    331 325
     
    
    ... ... @@ -1480,13 +1474,8 @@ getAmode _platform _ expr
    1480 1474
     -- fails when the right hand side is forced into a fixed register
    
    1481 1475
     -- (e.g. the result of a call).
    
    1482 1476
     
    
    1483
    -assignMem_IntCode :: Format -> CmmExpr -> CmmExpr -> NatM InstrBlock
    
    1484
    -assignReg_IntCode :: Format -> CmmReg  -> CmmExpr -> NatM InstrBlock
    
    1485
    -
    
    1486
    -assignMem_FltCode :: Format -> CmmExpr -> CmmExpr -> NatM InstrBlock
    
    1487
    -assignReg_FltCode :: Format -> CmmReg  -> CmmExpr -> NatM InstrBlock
    
    1488
    -
    
    1489
    -assignMem_IntCode rep addrE srcE
    
    1477
    +assignMem :: Format -> CmmExpr -> CmmExpr -> NatM InstrBlock
    
    1478
    +assignMem rep addrE srcE
    
    1490 1479
       = do
    
    1491 1480
         (src_reg, _format, code) <- getSomeReg srcE
    
    1492 1481
         platform <- getPlatform
    
    ... ... @@ -1497,19 +1486,17 @@ assignMem_IntCode rep addrE srcE
    1497 1486
                 `appOL` addr_code
    
    1498 1487
                 `snocOL` STR rep (OpReg w src_reg) (OpAddr addr))
    
    1499 1488
     
    
    1500
    -assignReg_IntCode _ reg src
    
    1489
    +assignReg :: CmmReg  -> CmmExpr -> NatM InstrBlock
    
    1490
    +assignReg reg src
    
    1501 1491
       = do
    
    1502 1492
         platform <- getPlatform
    
    1503 1493
         let dst = getRegisterReg platform reg
    
    1504 1494
         r <- getRegister src
    
    1505 1495
         return $ case r of
    
    1506
    -      Any _ code              -> COMMENT (text "CmmAssign" <+> parens (text (show reg)) <+> parens (text (show src))) `consOL` code dst
    
    1507
    -      Fixed format freg fcode -> COMMENT (text "CmmAssign" <+> parens (text (show reg)) <+> parens (text (show src))) `consOL` (fcode `snocOL` MOV (OpReg (formatToWidth format) dst) (OpReg (formatToWidth format) freg))
    
    1508
    -
    
    1509
    --- Let's treat Floating point stuff
    
    1510
    --- as integer code for now. Opaque.
    
    1511
    -assignMem_FltCode = assignMem_IntCode
    
    1512
    -assignReg_FltCode = assignReg_IntCode
    
    1496
    +      Any _ code              -> COMMENT (text "CmmAssign" <+> parens (text (show reg)) <+> parens (text (show src)))
    
    1497
    +                                `consOL` code dst
    
    1498
    +      Fixed format freg fcode -> COMMENT (text "CmmAssign" <+> parens (text (show reg)) <+> parens (text (show src)))
    
    1499
    +                                `consOL` (fcode `snocOL` MOV (OpReg (formatToWidth format) dst) (OpReg (formatToWidth format) freg))
    
    1513 1500
     
    
    1514 1501
     -- -----------------------------------------------------------------------------
    
    1515 1502
     -- Jumps