diff options
Diffstat (limited to 'compiler/nativeGen/SPARC')
-rw-r--r-- | compiler/nativeGen/SPARC/AddrMode.hs | 2 | ||||
-rw-r--r-- | compiler/nativeGen/SPARC/Base.hs | 2 | ||||
-rw-r--r-- | compiler/nativeGen/SPARC/CodeGen.hs | 31 | ||||
-rw-r--r-- | compiler/nativeGen/SPARC/CodeGen/Amode.hs | 2 | ||||
-rw-r--r-- | compiler/nativeGen/SPARC/CodeGen/Base.hs | 2 | ||||
-rw-r--r-- | compiler/nativeGen/SPARC/CodeGen/CondCode.hs | 2 | ||||
-rw-r--r-- | compiler/nativeGen/SPARC/CodeGen/Expand.hs | 4 | ||||
-rw-r--r-- | compiler/nativeGen/SPARC/CodeGen/Gen32.hs | 2 | ||||
-rw-r--r-- | compiler/nativeGen/SPARC/CodeGen/Gen64.hs | 20 | ||||
-rw-r--r-- | compiler/nativeGen/SPARC/CodeGen/Sanity.hs | 2 | ||||
-rw-r--r-- | compiler/nativeGen/SPARC/Cond.hs | 2 | ||||
-rw-r--r-- | compiler/nativeGen/SPARC/Imm.hs | 4 | ||||
-rw-r--r-- | compiler/nativeGen/SPARC/Instr.hs | 2 | ||||
-rw-r--r-- | compiler/nativeGen/SPARC/Ppr.hs | 13 | ||||
-rw-r--r-- | compiler/nativeGen/SPARC/Regs.hs | 6 | ||||
-rw-r--r-- | compiler/nativeGen/SPARC/ShortcutJump.hs | 14 | ||||
-rw-r--r-- | compiler/nativeGen/SPARC/Stack.hs | 2 |
17 files changed, 90 insertions, 22 deletions
diff --git a/compiler/nativeGen/SPARC/AddrMode.hs b/compiler/nativeGen/SPARC/AddrMode.hs index bf4d480005..ee40843351 100644 --- a/compiler/nativeGen/SPARC/AddrMode.hs +++ b/compiler/nativeGen/SPARC/AddrMode.hs @@ -6,6 +6,8 @@ module SPARC.AddrMode ( where +import GhcPrelude + import SPARC.Imm import SPARC.Base import Reg diff --git a/compiler/nativeGen/SPARC/Base.hs b/compiler/nativeGen/SPARC/Base.hs index a57d5e1c9a..04e8fed2b3 100644 --- a/compiler/nativeGen/SPARC/Base.hs +++ b/compiler/nativeGen/SPARC/Base.hs @@ -18,6 +18,8 @@ module SPARC.Base ( where +import GhcPrelude + import DynFlags import Panic diff --git a/compiler/nativeGen/SPARC/CodeGen.hs b/compiler/nativeGen/SPARC/CodeGen.hs index 71d320fa63..a95a22274b 100644 --- a/compiler/nativeGen/SPARC/CodeGen.hs +++ b/compiler/nativeGen/SPARC/CodeGen.hs @@ -22,6 +22,8 @@ where #include "../includes/MachDeps.h" -- NCG stuff: +import GhcPrelude + import SPARC.Base import SPARC.CodeGen.Sanity import SPARC.CodeGen.Amode @@ -58,7 +60,6 @@ import FastString import OrdList import Outputable import Platform -import Unique import Control.Monad ( mapAndUnzipM ) @@ -162,7 +163,7 @@ stmtToInstrs stmt = do {- -Now, given a tree (the argument to an CmmLoad) that references memory, +Now, given a tree (the argument to a CmmLoad) that references memory, produce a suitable addressing mode. A Rule of the Game (tm) for Amodes: use of the addr bit must @@ -185,7 +186,7 @@ temporary, then do the other computation, and then use the temporary: jumpTableEntry :: DynFlags -> Maybe BlockId -> CmmStatic jumpTableEntry dflags Nothing = CmmStaticLit (CmmInt 0 (wordWidth dflags)) jumpTableEntry _ (Just blockid) = CmmStaticLit (CmmLabel blockLabel) - where blockLabel = mkAsmTempLabel (getUnique blockid) + where blockLabel = blockLbl blockid @@ -313,7 +314,7 @@ genCondJump bid bool = do genSwitch :: DynFlags -> CmmExpr -> SwitchTargets -> NatM InstrBlock genSwitch dflags expr targets - | gopt Opt_PIC dflags + | positionIndependent dflags = error "MachCodeGen: sparc genSwitch PIC not finished\n" | otherwise @@ -422,7 +423,10 @@ genCCall target dest_regs args return (unitOL (CALL (Left (litToImm (CmmLabel lbl))) n_argRegs_used False)) ForeignTarget expr _ - -> do (dyn_c, [dyn_r]) <- arg_to_int_vregs expr + -> do (dyn_c, dyn_rs) <- arg_to_int_vregs expr + let dyn_r = case dyn_rs of + [dyn_r'] -> dyn_r' + _ -> panic "SPARC.CodeGen.genCCall: arg_to_int" return (dyn_c `snocOL` CALL (Right dyn_r) n_argRegs_used False) PrimTarget mop @@ -432,7 +436,10 @@ genCCall target dest_regs args return (unitOL (CALL (Left (litToImm (CmmLabel lbl))) n_argRegs_used False)) Right mopExpr -> do - (dyn_c, [dyn_r]) <- arg_to_int_vregs mopExpr + (dyn_c, dyn_rs) <- arg_to_int_vregs mopExpr + let dyn_r = case dyn_rs of + [dyn_r'] -> dyn_r' + _ -> panic "SPARC.CodeGen.genCCall: arg_to_int" return (dyn_c `snocOL` CALL (Right dyn_r) n_argRegs_used False) return lblOrMopExpr @@ -626,6 +633,10 @@ outOfLineMachOp_table mop MO_F32_Cosh -> fsLit "coshf" MO_F32_Tanh -> fsLit "tanhf" + MO_F32_Asinh -> fsLit "asinhf" + MO_F32_Acosh -> fsLit "acoshf" + MO_F32_Atanh -> fsLit "atanhf" + MO_F64_Exp -> fsLit "exp" MO_F64_Log -> fsLit "log" MO_F64_Sqrt -> fsLit "sqrt" @@ -644,14 +655,21 @@ outOfLineMachOp_table mop MO_F64_Cosh -> fsLit "cosh" MO_F64_Tanh -> fsLit "tanh" + MO_F64_Asinh -> fsLit "asinh" + MO_F64_Acosh -> fsLit "acosh" + MO_F64_Atanh -> fsLit "atanh" + MO_UF_Conv w -> fsLit $ word2FloatLabel w MO_Memcpy _ -> fsLit "memcpy" MO_Memset _ -> fsLit "memset" MO_Memmove _ -> fsLit "memmove" + MO_Memcmp _ -> fsLit "memcmp" MO_BSwap w -> fsLit $ bSwapLabel w MO_PopCnt w -> fsLit $ popCntLabel w + MO_Pdep w -> fsLit $ pdepLabel w + MO_Pext w -> fsLit $ pextLabel w MO_Clz w -> fsLit $ clzLabel w MO_Ctz w -> fsLit $ ctzLabel w MO_AtomicRMW w amop -> fsLit $ atomicRMWLabel w amop @@ -663,6 +681,7 @@ outOfLineMachOp_table mop MO_U_QuotRem {} -> unsupported MO_U_QuotRem2 {} -> unsupported MO_Add2 {} -> unsupported + MO_AddWordC {} -> unsupported MO_SubWordC {} -> unsupported MO_AddIntC {} -> unsupported MO_SubIntC {} -> unsupported diff --git a/compiler/nativeGen/SPARC/CodeGen/Amode.hs b/compiler/nativeGen/SPARC/CodeGen/Amode.hs index a59287f171..33e3f535da 100644 --- a/compiler/nativeGen/SPARC/CodeGen/Amode.hs +++ b/compiler/nativeGen/SPARC/CodeGen/Amode.hs @@ -4,6 +4,8 @@ module SPARC.CodeGen.Amode ( where +import GhcPrelude + import {-# SOURCE #-} SPARC.CodeGen.Gen32 import SPARC.CodeGen.Base import SPARC.AddrMode diff --git a/compiler/nativeGen/SPARC/CodeGen/Base.hs b/compiler/nativeGen/SPARC/CodeGen/Base.hs index 27b533f46b..039bb6496c 100644 --- a/compiler/nativeGen/SPARC/CodeGen/Base.hs +++ b/compiler/nativeGen/SPARC/CodeGen/Base.hs @@ -13,6 +13,8 @@ module SPARC.CodeGen.Base ( where +import GhcPrelude + import SPARC.Instr import SPARC.Cond import SPARC.AddrMode diff --git a/compiler/nativeGen/SPARC/CodeGen/CondCode.hs b/compiler/nativeGen/SPARC/CodeGen/CondCode.hs index e5fb82df4d..e6b2e174b6 100644 --- a/compiler/nativeGen/SPARC/CodeGen/CondCode.hs +++ b/compiler/nativeGen/SPARC/CodeGen/CondCode.hs @@ -6,6 +6,8 @@ module SPARC.CodeGen.CondCode ( where +import GhcPrelude + import {-# SOURCE #-} SPARC.CodeGen.Gen32 import SPARC.CodeGen.Base import SPARC.Instr diff --git a/compiler/nativeGen/SPARC/CodeGen/Expand.hs b/compiler/nativeGen/SPARC/CodeGen/Expand.hs index 70cb0111c0..0b318740db 100644 --- a/compiler/nativeGen/SPARC/CodeGen/Expand.hs +++ b/compiler/nativeGen/SPARC/CodeGen/Expand.hs @@ -5,6 +5,8 @@ module SPARC.CodeGen.Expand ( where +import GhcPrelude + import SPARC.Instr import SPARC.Imm import SPARC.AddrMode @@ -140,7 +142,7 @@ expandMisalignedDoubles instr --- | The the high partner for this float reg. +-- | The high partner for this float reg. fRegHi :: Reg -> Reg fRegHi (RegReal (RealRegSingle r1)) | r1 >= 32 diff --git a/compiler/nativeGen/SPARC/CodeGen/Gen32.hs b/compiler/nativeGen/SPARC/CodeGen/Gen32.hs index a0e86f14c4..a7a1f60416 100644 --- a/compiler/nativeGen/SPARC/CodeGen/Gen32.hs +++ b/compiler/nativeGen/SPARC/CodeGen/Gen32.hs @@ -6,6 +6,8 @@ module SPARC.CodeGen.Gen32 ( where +import GhcPrelude + import SPARC.CodeGen.CondCode import SPARC.CodeGen.Amode import SPARC.CodeGen.Gen64 diff --git a/compiler/nativeGen/SPARC/CodeGen/Gen64.hs b/compiler/nativeGen/SPARC/CodeGen/Gen64.hs index f186d437d0..6fa7482f9b 100644 --- a/compiler/nativeGen/SPARC/CodeGen/Gen64.hs +++ b/compiler/nativeGen/SPARC/CodeGen/Gen64.hs @@ -7,6 +7,8 @@ module SPARC.CodeGen.Gen64 ( where +import GhcPrelude + import {-# SOURCE #-} SPARC.CodeGen.Gen32 import SPARC.CodeGen.Base import SPARC.CodeGen.Amode @@ -191,6 +193,24 @@ iselExpr64 (CmmMachOp (MO_UU_Conv _ W64) [expr]) return $ ChildCode64 code r_dst_lo +-- only W32 supported for now +iselExpr64 (CmmMachOp (MO_SS_Conv W32 W64) [expr]) + = do + r_dst_lo <- getNewRegNat II32 + let r_dst_hi = getHiVRegFromLo r_dst_lo + + -- compute expr and load it into r_dst_lo + (a_reg, a_code) <- getSomeReg expr + + dflags <- getDynFlags + let platform = targetPlatform dflags + code = a_code + `appOL` toOL + [ SRA a_reg (RIImm (ImmInt 31)) r_dst_hi + , mkRegRegMoveInstr platform a_reg r_dst_lo ] + + return $ ChildCode64 code r_dst_lo + iselExpr64 expr = pprPanic "iselExpr64(sparc)" (ppr expr) diff --git a/compiler/nativeGen/SPARC/CodeGen/Sanity.hs b/compiler/nativeGen/SPARC/CodeGen/Sanity.hs index 81641326f2..fcf5b65bde 100644 --- a/compiler/nativeGen/SPARC/CodeGen/Sanity.hs +++ b/compiler/nativeGen/SPARC/CodeGen/Sanity.hs @@ -6,6 +6,8 @@ module SPARC.CodeGen.Sanity ( where +import GhcPrelude + import SPARC.Instr import SPARC.Ppr () import Instruction diff --git a/compiler/nativeGen/SPARC/Cond.hs b/compiler/nativeGen/SPARC/Cond.hs index da41457950..3fbfb8603f 100644 --- a/compiler/nativeGen/SPARC/Cond.hs +++ b/compiler/nativeGen/SPARC/Cond.hs @@ -7,6 +7,8 @@ module SPARC.Cond ( where +import GhcPrelude + -- | Branch condition codes. data Cond = ALWAYS diff --git a/compiler/nativeGen/SPARC/Imm.hs b/compiler/nativeGen/SPARC/Imm.hs index cb53ba411c..bd2d4ab131 100644 --- a/compiler/nativeGen/SPARC/Imm.hs +++ b/compiler/nativeGen/SPARC/Imm.hs @@ -7,6 +7,8 @@ module SPARC.Imm ( where +import GhcPrelude + import Cmm import CLabel @@ -57,7 +59,7 @@ litToImm lit CmmLabel l -> ImmCLbl l CmmLabelOff l off -> ImmIndex l off - CmmLabelDiffOff l1 l2 off + CmmLabelDiffOff l1 l2 off _ -> ImmConstantSum (ImmConstantDiff (ImmCLbl l1) (ImmCLbl l2)) (ImmInt off) diff --git a/compiler/nativeGen/SPARC/Instr.hs b/compiler/nativeGen/SPARC/Instr.hs index 4c19ac69a7..54fb513478 100644 --- a/compiler/nativeGen/SPARC/Instr.hs +++ b/compiler/nativeGen/SPARC/Instr.hs @@ -25,6 +25,8 @@ module SPARC.Instr ( where +import GhcPrelude + import SPARC.Stack import SPARC.Imm import SPARC.AddrMode diff --git a/compiler/nativeGen/SPARC/Ppr.hs b/compiler/nativeGen/SPARC/Ppr.hs index 88b04b952a..eb401fff06 100644 --- a/compiler/nativeGen/SPARC/Ppr.hs +++ b/compiler/nativeGen/SPARC/Ppr.hs @@ -25,6 +25,8 @@ where #include "HsVersions.h" #include "nativeGen/NCG.h" +import GhcPrelude + import SPARC.Regs import SPARC.Instr import SPARC.Cond @@ -38,11 +40,12 @@ import PprBase import Cmm hiding (topInfoTable) import PprCmm() +import BlockId import CLabel import Hoopl.Label import Hoopl.Collections -import Unique ( Uniquable(..), pprUniqueAlways ) +import Unique ( pprUniqueAlways ) import Outputable import Platform import FastString @@ -91,7 +94,7 @@ dspSection = Section Text $ pprBasicBlock :: LabelMap CmmStatics -> NatBasicBlock Instr -> SDoc pprBasicBlock info_env (BasicBlock blockid instrs) = maybe_infotable $$ - pprLabel (mkAsmTempLabel (getUnique blockid)) $$ + pprLabel (blockLbl blockid) $$ vcat (map pprInstr instrs) where maybe_infotable = case mapLookup blockid info_env of @@ -402,7 +405,7 @@ pprInstr (LD format addr reg) pprReg reg ] --- 64 bit FP storees are expanded into individual instructions in CodeGen.Expand +-- 64 bit FP stores are expanded into individual instructions in CodeGen.Expand pprInstr (ST FF64 reg _) | RegReal (RealRegSingle{}) <- reg = panic "SPARC.Ppr: not emitting potentially misaligned ST FF64 instr" @@ -541,7 +544,7 @@ pprInstr (BI cond b blockid) text "\tb", pprCond cond, if b then pp_comma_a else empty, char '\t', - ppr (mkAsmTempLabel (getUnique blockid)) + ppr (blockLbl blockid) ] pprInstr (BF cond b blockid) @@ -549,7 +552,7 @@ pprInstr (BF cond b blockid) text "\tfb", pprCond cond, if b then pp_comma_a else empty, char '\t', - ppr (mkAsmTempLabel (getUnique blockid)) + ppr (blockLbl blockid) ] pprInstr (JMP addr) = text "\tjmp\t" <> pprAddr addr diff --git a/compiler/nativeGen/SPARC/Regs.hs b/compiler/nativeGen/SPARC/Regs.hs index 14a5192c2d..d6aadbae94 100644 --- a/compiler/nativeGen/SPARC/Regs.hs +++ b/compiler/nativeGen/SPARC/Regs.hs @@ -32,6 +32,8 @@ module SPARC.Regs ( where +import GhcPrelude + import CodeGen.Platform.SPARC import Reg import RegClass @@ -75,7 +77,7 @@ classOfRealReg reg -- | regSqueeze_class reg --- Calculuate the maximum number of register colors that could be +-- Calculate the maximum number of register colors that could be -- denied to a node of this class due to having this reg -- as a neighbour. -- @@ -191,7 +193,7 @@ fPair reg -- | All the regs that the register allocator can allocate to, --- with the the fixed use regs removed. +-- with the fixed use regs removed. -- allocatableRegs :: [RealReg] allocatableRegs diff --git a/compiler/nativeGen/SPARC/ShortcutJump.hs b/compiler/nativeGen/SPARC/ShortcutJump.hs index 123a345130..83e366cb04 100644 --- a/compiler/nativeGen/SPARC/ShortcutJump.hs +++ b/compiler/nativeGen/SPARC/ShortcutJump.hs @@ -8,6 +8,8 @@ module SPARC.ShortcutJump ( where +import GhcPrelude + import SPARC.Instr import SPARC.Imm @@ -16,8 +18,6 @@ import BlockId import Cmm import Panic -import Unique - data JumpDest @@ -46,14 +46,14 @@ shortcutStatics fn (Statics lbl statics) shortcutLabel :: (BlockId -> Maybe JumpDest) -> CLabel -> CLabel shortcutLabel fn lab - | Just uq <- maybeAsmTemp lab = shortBlockId fn (mkBlockId uq) - | otherwise = lab + | Just blkId <- maybeLocalBlockLabel lab = shortBlockId fn blkId + | otherwise = lab shortcutStatic :: (BlockId -> Maybe JumpDest) -> CmmStatic -> CmmStatic shortcutStatic fn (CmmStaticLit (CmmLabel lab)) = CmmStaticLit (CmmLabel (shortcutLabel fn lab)) -shortcutStatic fn (CmmStaticLit (CmmLabelDiffOff lbl1 lbl2 off)) - = CmmStaticLit (CmmLabelDiffOff (shortcutLabel fn lbl1) lbl2 off) +shortcutStatic fn (CmmStaticLit (CmmLabelDiffOff lbl1 lbl2 off w)) + = CmmStaticLit (CmmLabelDiffOff (shortcutLabel fn lbl1) lbl2 off w) -- slightly dodgy, we're ignoring the second label, but this -- works with the way we use CmmLabelDiffOff for jump tables now. shortcutStatic _ other_static @@ -63,7 +63,7 @@ shortcutStatic _ other_static shortBlockId :: (BlockId -> Maybe JumpDest) -> BlockId -> CLabel shortBlockId fn blockid = case fn blockid of - Nothing -> mkAsmTempLabel (getUnique blockid) + Nothing -> blockLbl blockid Just (DestBlockId blockid') -> shortBlockId fn blockid' Just (DestImm (ImmCLbl lbl)) -> lbl _other -> panic "shortBlockId" diff --git a/compiler/nativeGen/SPARC/Stack.hs b/compiler/nativeGen/SPARC/Stack.hs index 629b18789f..3f5b2a7289 100644 --- a/compiler/nativeGen/SPARC/Stack.hs +++ b/compiler/nativeGen/SPARC/Stack.hs @@ -7,6 +7,8 @@ module SPARC.Stack ( where +import GhcPrelude + import SPARC.AddrMode import SPARC.Regs import SPARC.Base |