
#14251: LLVM Code Gen messes up registers -------------------------------------+------------------------------------- Reporter: angerman | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.3 (LLVM) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Incorrect result Unknown/Multiple | at runtime Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Due to the way the LLVM Code Gen generates Function Singnatures, it is possible to end up mixed up registers. A slightly adapted T8064 {{{#!hs {-# LANGUAGE MagicHash, BangPatterns #-} module Main where import GHC.Exts {-# NOINLINE f #-} f :: (Int# -> Float# -> Double# -> Float# -> Double# -> String) -> String f g = g 3# 4.0# 5.0## 6.0# 6.9## ++ " World!" {-# NOINLINE p #-} p :: Int# -> Float# -> Double# -> Float# -> Double# -> String p i j k l m = "Hello" {-# NOINLINE q #-} q :: Int# -> Int# -> Float# -> Double# -> Float# -> Double# -> String q _ i j k l m = "Hello " ++ show (F# l) ++ " " ++ show (D# m) {-# NOINLINE r #-} r :: Int# -> Float# -> Double# -> Float# -> Double# -> String r i = let !(I# z) = length [I# 1# .. I# i] in \j k l m -> p z j k l m -- ghc won't eta-expand around the length, because it has unknown cost main = do putStrLn (f p) -- fast call putStrLn (f r) -- slow call: function but wrong arity let g = last [q 1#] putStrLn (f g) -- slow call: thunk }}} will produce the following results: {{{ ../inplace/bin/ghc-stage1 -fllvm -fforce-recomp T6084.hs -O2 -o T6084-llvm && ./T6084-llvm [1 of 1] Compiling Main ( T6084.hs, T6084.o ) Linking T6084-llvm ... Hello World! Hello World! Hello 4.0 5.0 World! ../inplace/bin/ghc-stage1 -fasm -fforce-recomp T6084.hs -O2 -o T6084-asm && ./T6084-asm [1 of 1] Compiling Main ( T6084.hs, T6084.o ) Linking T6084-asm ... Hello World! Hello World! Hello 6.0 6.9 World! }}} The underlying reason is that (at least for X86_64) the Float and Double registers alternate. The llvm code gen creates function signatures based on the live registers (instead of all). For `q` only the last Float and Double register are `live`. However when calling `q` we pass `f1: Float -> d1: Double -> f2: Float -> d2: Double`. `f2` and `d2` are silently ignored, and in the function body, we now have `f2 <- f1` and `d2 <- d1`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14251 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler