
#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: Compile-time crash | Blockedby: Blocking: | Related: #7571, #7574 -------------------------------+-------------------------------------------- Comment(by thoughtpolice): Correction: this test correctly triggers the bug: {{{ {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE MagicHash, UnliftedFFITypes #-} module T7575 where import GHC.Prim import GHC.Word import GHC.Types foreign import ccall unsafe "hs_eqWord64" dummy_eqWord64# :: Word64# -> Word64# -> Bool check :: Word64 -> Word64 -> Bool check (W64# x#) (W64# y#) = dummy_eqWord64# x# y# check2 :: Word64 -> Bool check2 x = check x 0 }}} Testing vs 7.4.1: {{{ $ ghc --version The Glorious Glasgow Haskell Compilation System, version 7.4.1 $ ghc -c -O2 -fforce-recomp T7575.hs $ ~/code/ghc/inplace/bin/ghc-stage1 --version The Glorious Glasgow Haskell Compilation System, version 7.7.20130113 $ ~/code/ghc/inplace/bin/ghc-stage1 -c -O2 -fforce-recomp T7575.hs You are using a new version of LLVM that hasn't been tested yet! We will try though... /home/linaro/bin/opt: /tmp/ghc26188_0/ghc26188_0.ll:594:60: error: argument is not of expected type 'i64' %lnxh = call ccc i32 (i64,i64)* @hs_eqWord64( i64 %lnxg, i32 0 ) nounwind ^ $ ~/code/ghc/inplace/bin/ghc-stage1 -c -O2 -fforce-recomp T7575.hs -pgmlo opt-3.0 -pgmlc llc-3.0 opt-3.0: /tmp/ghc26199_0/ghc26199_0.ll:594:60: error: argument is not of expected type 'i64' %lnxh = call ccc i32 (i64,i64)* @hs_eqWord64( i64 %lnxg, i32 0 ) nounwind ^ $ }}} So this is definitely a compiler regression in the backend somewhere. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7575#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler