[GHC] #7575: LLVM backend does not properly widen certain literal types in call expressions

GHC cvs-ghc at haskell.org
Sun Jan 13 21:09:05 CET 2013


#7575: LLVM backend does not properly widen certain literal types in call
expressions
--------------------------------+-------------------------------------------
Reporter:  thoughtpolice        |          Owner:                  
    Type:  bug                  |         Status:  new             
Priority:  normal               |      Component:  Compiler (LLVM) 
 Version:  7.7                  |       Keywords:  llvm, codegen   
      Os:  Unknown/Multiple     |   Architecture:  Unknown/Multiple
 Failure:  Building GHC failed  |      Blockedby:                  
Blocking:                       |        Related:  #7571, #7574    
--------------------------------+-------------------------------------------
Changes (by thoughtpolice):

 * cc: mad.one@… (added)
  * failure:  None/Unknown => Building GHC failed
  * version:  7.6.1 => 7.7
  * component:  Compiler => Compiler (LLVM)
  * keywords:  => llvm, codegen


Comment:

 Word of note. I think I have a test for this:

 {{{
 {-# LANGUAGE MagicHash, UnliftedFFITypes #-}
 module Main where
 import GHC.Prim
 import GHC.Word
 import System.Environment (getArgs)

 foreign import ccall unsafe "hs_eqWord64" dummy_eqWord64# :: Word64# ->
 Word64# -> Bool

 check :: Word64 -> Word64 -> Bool
 check (W64# x#) (W64# y#) = dummy_eqWord64# x# y#

 main :: IO ()
 main = do
   a <- (read . head) `fmap` getArgs
   print $ check a 0
 }}}

 At ```-O2```, '''with GHC 7.4.1 on ARM''', this dumps code like:

 {{{
 ...
 %ln2EJ = call ccc i32 (i64,i64)* @hs_eqWord64( i64 %ln2EI, i64 0 )
 nounwind
 ...
 }}}

 So it seems like a regression. I'm rebuilding on my ODROID at the moment
 and will run this test with the stage1 compiler and see what happens.
 Intuition tells me this should trigger it based on the code I saw under
 ```base```.

 Also note that this will only affect 32 bit builds obviously. On 64bit
 machines, Word64 is native and does not shell out to ```long long``` and
 ```ghc-prim``` for Word64.

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



More information about the ghc-tickets mailing list