Folks,

from time to time I'm attempting to resurrect SPARC NCG. It looks like it's off by default since 7.4? release and I feel it's kind of pity. I've been able to hack it on 7.6.x and make it functional. I failed on 7.8 and later. Double float load was broken there.

Now, I'm attempting on fairly recent GHC HEAD as of Jan 17 and I do have problem with illegal isn generated into the binary. This is caused by LD II64 ... Instr to be translated to SPARC ldd <addr>,g1 where g1 reg is not even, but odd and this fails as spec. says:

"
The load doubleword integer instructions (LDD, LDDA) move a doubleword
from memory into an r register pair. The more significant word at the
effective memory address is moved into the even r register. The less
significant word (at the effective memory address + 4) is moved into the following
odd r register. (Note that a load doubleword with rd = 0 modifies
only r[1].) The least significant bit of the rd field is unused and should be set
to zero by software. An attempt to execute a load doubleword instruction
that refers to a mis-aligned (odd) destination register number may cause an
illegal_instruction trap.
"

I've found out that the problematic source code is HeapStackCheck.cmm and the problematic piece is:

            if (Capability_context_switch(MyCapability()) != 0 :: CInt ||
                Capability_interrupt(MyCapability())      != 0 :: CInt ||
                (StgTSO_alloc_limit(CurrentTSO) `lt` (0::I64) &&
(TO_W_(StgTSO_flags(CurrentTSO)) & TSO_ALLOC_LIMIT) != 0)) {
                ret = ThreadYielding;
                goto sched;


This "(0::I64)" causes it. So that's the problem description. Now I'm attempting to debug it a little bit to find out where the LD II64 Instr is generated and I'm not able to find single place which would looks familiar with asm I get here:

.Lcq:
        ld      [%i1+812],%g1
        ldd     [%g1+64],%g1
        cmp     %g1,0
        bge     .Lcs
        nop
        b       .Lcr
        nop



more importantly when I look into sparc's version on mkLoadInstr, I don't see any way how it may generate LD II64:

sparc_mkLoadInstr dflags reg _ slot
  = let platform = targetPlatform dflags
        off      = spillSlotToOffset dflags slot
        off_w   = 1 + (off `div` 4)
        sz      = case targetClassOfReg platform reg of
                        RcInteger -> II32
                        RcFloat   -> FF32
                        RcDouble  -> FF64
                        _         -> panic "sparc_mkLoadInstr"

        in LD sz (fpRel (- off_w)) reg


In whole SPARC NCG I've found the only place which clearly uses LD II64 and this is in Gen32.hs for loading literal float into reg:

getRegister (CmmLit (CmmFloat d W64)) = do
    lbl <- getNewLabelNat
    tmp <- getNewRegNat II32
    let code dst = toOL [
            LDATA ReadOnlyData $ Statics lbl
                         [CmmStaticLit (CmmFloat d W64)],
            SETHI (HI (ImmCLbl lbl)) tmp,
            LD II64 (AddrRegImm tmp (LO (ImmCLbl lbl))) dst]
    return (Any FF64 code)


It's interesting but also iselExpr64 which should be probably here for manipulating 64bit data on 32bit platform, so even this is using pairs of LD II32 Instrs instead of single LD II64....

So I'm kind of out of idea where the LD II64 gets in the flow and is later translated into ldd with problematic reg.

Do you have any idea how to debug this issue? Or do you have any idea where to read more about general structure of NCG, I've already seen https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/Backends/NCG -- but this is kind of dated...

Thanks for any idea how to proceed!
Karel

_______________________________________________
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs

Reply via email to