#6156: Optimiser bug on linux-powerpc
-----------------------------------------+----------------------------------
 Reporter:  erikd                        |          Owner:          
     Type:  bug                          |         Status:  new     
 Priority:  normal                       |      Component:  Compiler
  Version:  7.4.1                        |       Keywords:          
       Os:  Linux                        |   Architecture:  powerpc 
  Failure:  Incorrect result at runtime  |       Testcase:          
Blockedby:                               |       Blocking:          
  Related:                               |  
-----------------------------------------+----------------------------------
 Found a small chunk of code in the cryptocipher package that when compiled
 and run, produces a difference result when optimised compared to compiling
 un-optimised.

 Note this is only a problem with PowerPC. On x86-64 there is no difference
 in the output between the optimised version and the un-optimised version.

 I have two simple files (Camellia.hs):

 {{{
 module Camellia where

 import Data.Bits
 import Data.Word

 import Debug.Trace

 fl :: Word64 -> Word64 -> Word64
 fl fin sk =
         let (x1, x2) = w64tow32 fin in
         let (k1, k2) = w64tow32 sk in
         let y2 = x2 `xor` ((x1 .&. k1) `rotateL` 1) in
         let y1 = x1 `xor` (y2 .|. k2) in
         trace (show fin ++ " " ++ show sk ++ " -> " ++ show (w32tow64 (y1,
 y2))) $ w32tow64 (y1, y2)

 w64tow32 :: Word64 -> (Word32, Word32)
 w64tow32 w = (fromIntegral (w `shiftR` 32), fromIntegral (w .&.
 0xffffffff))

 w32tow64 :: (Word32, Word32) -> Word64
 w32tow64 (x1, x2) = ((fromIntegral x1) `shiftL` 32) .|. (fromIntegral x2)
 }}}

 and a main program (camellia-test.hs):

 {{{

 import Data.Word
 import qualified Camellia as Camellia

 a, b :: Word64
 a = 1238988323332265734
 b = 11185553392205053542

 main :: IO ()
 main =
     putStrLn $ "Camellia.fl " ++ show a ++ " " ++ show b ++ " -> " ++ show
 (Camellia.fl a b)

 }}}

 I'm also using this Makefile:

 {{{
 TARGETS = camilla-test-std camilla-test-opt

 check : $(TARGETS)
         ./camilla-test-std
         ./camilla-test-opt

 clean :
         make clean-temp-files
         rm -f $(TARGETS)

 clean-temp-files :
         rm -f camilla-test.o camilla-test.hi Camellia.o Camellia.hi

 camilla-test-opt : camilla-test.hs Camellia.hs
         ghc -Wall -O2 --make -i:Tests $< -o $@
         make clean-temp-files

 camilla-test-std : camilla-test.hs Camellia.hs
         ghc -Wall --make -i:Tests $< -o $@
         make clean-temp-files
 }}}

 When I run the two programs I get:

 {{{
 ./camilla-test-std
 1238988323332265734 11185553392205053542 -> 18360184157246690566
 Camellia.fl 1238988323332265734 11185553392205053542 ->
 18360184157246690566
 ./camilla-test-opt
 1238988323332265734 11185553392205053542 -> 3698434091925017862
 Camellia.fl 38662 15974 -> 3698434091925017862
 }}}

 So there are two problems here:

 a) Showing Word64 values is not working correctly in the optimised
 version.

 b) The function Camelia.fl produces the wrong result in the optimised
 version.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/6156>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler

_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to