Hi Austin,

thanks for your suggestion. Unfortunately this completely go over my head now. :-) I'm not able to write single line of C-- test yet. Anyway, I've tackled this from different side: added debugging message to the function and then see where it's emitted while building GHC, it looks like GHC.Word.hs from base library is my friend here. I've also have a look into generated asm and it looks reasonable so I think my implementation of iselExpr64 is correct.

Thanks!
Karel

On 03/ 1/14 09:26 PM, Austin Seipp wrote:
Hi Karel,

Although I haven't looked extremely closely, may I suggest perhaps
writing your test case in C-- instead of Haskell? It looks like you
can trigger this simply with a CmmAssign or CmmStore node with a 64bit
type, which will call assign(Reg|Mem)_I64Code, in turn calling
iselExpr64 - see nativeGen/SPARC/CodeGen.hs:stmtToInstrs (line 121).
If you trace through from CmmParse.y to find emitAssign in
StgCmmMonad, it'll create an assignment node for you.

Do that with -S and check out the assembly files (-ddump-asm should
also do the trick).

This should make it easy to trigger and examine. Then you can link it
into a Haskell program as a foreign primop and test it extensively
with a working executable.



On Sat, Mar 1, 2014 at 12:12 PM, Karel Gardas<karel.gar...@centrum.cz>  wrote:

Hello,

I'm trying to resurrect SPARC NCG. I've switched it on and basically
provided functions on which NCG has panic during the build, basically just 2
were missing so far (cut from git diff):

+genCCall (PrimTarget MO_Touch) _ _
+ = return $ nilOL
+


+iselExpr64 (CmmLit (CmmInt i _)) = do
+  (rlo, rhi)<- getNewRegPairNat II32
+  let
+      half0 = fromIntegral (fromIntegral i :: Word32)
+      half1 = fromIntegral (fromIntegral (i `shiftR` 32) :: Word32)
+      code = toOL [
+              SETHI (HI $ ImmInt half0) rlo,
+              OR False rlo (RIImm (LO $ ImmInt half0)) rlo,
+              SETHI (HI $ ImmInt half1) rhi,
+              OR False rhi (RIImm (LO $ ImmInt half1)) rhi
+             ]
+  return (ChildCode64 code rlo)


Now, my ghc-stage2 badly fails and testsuite run with stage=1 reveals 1390
unexpected failures. Perhaps this is unrelated, but still I'd like to test
that my iselExpr64 implementation above is correct. Is there any simple
haskell code which makes this function in NCG run? I'm trying this:

import GHC.Prim
import GHC.Exts

main = do
         let x = 18446744073709551615#
         --- 2^64-1 = 18446744073709551615
         putStrLn (show $ I# x)
         return()


I've had a hope that unboxed long int constant is what causes iselExpr64
being called, but generated assembly looks suspicious -- like it's not
called so my idea was wrong here probably. Do you have any idea how to test
this function and see its generated assembly?

BTW: I hope I got the function semantics correct as a loading of 64bit
constant/integer into a pair of 32bits registers...

Thanks a lot!
Karel

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





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

Reply via email to