[GHC] #14251: LLVM Code Gen messes up registers

#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

#14251: LLVM Code Gen messes up registers -------------------------------------+------------------------------------- Reporter: angerman | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Compiler (LLVM) | Version: 8.3 Resolution: | 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: | -------------------------------------+------------------------------------- Comment (by angerman): Reasoing for `putStrLn (f g)` {{{ putStrLn (f g) = putStrLn (f (last [q 1#])) = putStrLn (f (q 1#)) = putStrLn ((q 1#) 3# 4.0# 5.0## 6.0# 6.9## ++ " World!") = putStrLn (q 1# 3# 4.0# 5.0## 6.0# 6.9## ++ " World!") = putStrLn ("Hello " ++ show (F# 6.0#) ++ " " ++ show (D# 6.9##) ++ " World!") = putStrLn ("Hello 6.0 6.9 World!") }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14251#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14251: LLVM Code Gen messes up registers -------------------------------------+------------------------------------- Reporter: angerman | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Compiler (LLVM) | Version: 8.3 Resolution: | 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: | -------------------------------------+------------------------------------- Comment (by kavon): I'll take a look at this later today. I fixed a bug almost exactly the same as this problem in my LLVM backend. This fix should not require a lot of changes. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14251#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14251: LLVM Code Gen messes up registers -------------------------------------+------------------------------------- Reporter: angerman | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Compiler (LLVM) | Version: 8.3 Resolution: | 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: | -------------------------------------+------------------------------------- Comment (by bgamari): What happened to this? It sounds like this bug is still at large. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14251#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14251: LLVM Code Gen messes up registers -------------------------------------+------------------------------------- Reporter: angerman | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Compiler (LLVM) | Version: 8.3 Resolution: | 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: | -------------------------------------+------------------------------------- Comment (by mbw): Does this imply that using the llvm backend is currently a no-no? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14251#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14251: LLVM Code Gen messes up registers -------------------------------------+------------------------------------- Reporter: angerman | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Compiler (LLVM) | Version: 8.3 Resolution: | 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: | -------------------------------------+------------------------------------- Comment (by bgamari): It sounds like using it would be a bit risky. Kavon, did anything ever happen on this front? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14251#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14251: LLVM Code Gen messes up registers -------------------------------------+------------------------------------- Reporter: angerman | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Compiler (LLVM) | Version: 8.3 Resolution: | 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: | -------------------------------------+------------------------------------- Comment (by carter): so anyone using unboxed floats/doubles targetting llvm best be careful of argument order for unlifted double# and float# till this gets fixed? this is eerily similar to some of the previous float/double register bugs we've seen in ghc, like the 7.8-7.10 series bug and the more recent windows64 abi one -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14251#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14251: LLVM Code Gen messes up registers -------------------------------------+------------------------------------- Reporter: angerman | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler (LLVM) | Version: 8.3 Resolution: | 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: | -------------------------------------+------------------------------------- Changes (by monoidal): * milestone: => 8.6.1 Comment: Setting a milestone to increase visibility. If we won't fix it in 8.6 I think this at least deserves a warning in release notes. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14251#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14251: LLVM Code Gen messes up registers -------------------------------------+------------------------------------- Reporter: angerman | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler (LLVM) | Version: 8.3 Resolution: | 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: | -------------------------------------+------------------------------------- Comment (by George): Is this a regression? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14251#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14251: LLVM Code Gen messes up registers -------------------------------------+------------------------------------- Reporter: angerman | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler (LLVM) | Version: 8.3 Resolution: | 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: | -------------------------------------+------------------------------------- Comment (by monoidal): It's present at least in 8.2, 8.4 and HEAD. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14251#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14251: LLVM Code Gen messes up registers -------------------------------------+------------------------------------- Reporter: angerman | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler (LLVM) | Version: 8.3 Resolution: | 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: | -------------------------------------+------------------------------------- Comment (by George): fwiw, imho, documenting this in the release notes makes sense, holding up the release for what may have been a latent bug for a long time does not. Adding a test would be good. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14251#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14251: LLVM Code Gen messes up registers -------------------------------------+------------------------------------- Reporter: angerman | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler (LLVM) | Version: 8.3 Resolution: | 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: | -------------------------------------+------------------------------------- Comment (by awson): AFAIUI, the most recent takes on this problem are: 1. https://phabricator.haskell.org/D4003 by @angerman 2. https://gist.github.com/kavon/566fc6c21ff51803538884b79dc1d841 by @kavon (referred from the former) My understanding is that "1" doesn't quite work (generates wrong code for handwritten `cmm`). Also my understanding is that "2" should work (haven't tested it), but isn't so much aesthetically pleasant, since all padding arguments are of `FloatReg` type regardless of which type they are at the call-site. A year has passed since. Neither these two approaches, no other suggested in the email thread started from https://mail.haskell.org/pipermail/ghc- devs/2017-September/014700.html, were elaborated further. I wonder then what are chances of e.g. "2" to be upstreamed if properly polished? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14251#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14251: LLVM Code Gen messes up registers
-------------------------------------+-------------------------------------
Reporter: angerman | Owner: (none)
Type: bug | Status: new
Priority: highest | Milestone: 8.6.1
Component: Compiler (LLVM) | Version: 8.3
Resolution: | 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: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#14251: LLVM Code Gen messes up registers -------------------------------------+------------------------------------- Reporter: angerman | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler (LLVM) | Version: 8.3 Resolution: | 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: | -------------------------------------+------------------------------------- Comment (by bgamari): In my opinion just about anything is better than the status quo. It would be great if someone could look into finishing up (2). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14251#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14251: LLVM Code Gen messes up registers -------------------------------------+------------------------------------- Reporter: angerman | Owner: kavon Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler (LLVM) | Version: 8.3 Resolution: | 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: | -------------------------------------+------------------------------------- Changes (by kavon): * owner: (none) => kavon Comment: I'll polish up solution (2) ASAP. Sorry I missed this! While it seems ugly to add `FloatReg` as padding, it we need ''something'' to "eat up" a floating point register, since they're assigned left-to- right. We know Float and Double are passed in the same register on x86-64 so it should be fine. I need to look into ARM and other calling conventions to make this correct on other systems. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14251#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14251: LLVM Code Gen messes up registers -------------------------------------+------------------------------------- Reporter: angerman | Owner: kavon Type: bug | Status: patch Priority: highest | Milestone: 8.6.1 Component: Compiler (LLVM) | Version: 8.3 Resolution: | 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): D5190 Wiki Page: | -------------------------------------+------------------------------------- Changes (by kavon): * status: new => patch * differential: => D5190 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14251#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14251: LLVM Code Gen messes up registers -------------------------------------+------------------------------------- Reporter: angerman | Owner: kavon Type: bug | Status: patch Priority: highest | Milestone: 8.6.1 Component: Compiler (LLVM) | Version: 8.3 Resolution: | 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): Phab:D5190 Wiki Page: | -------------------------------------+------------------------------------- Changes (by kavon): * differential: D5190 => Phab:D5190 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14251#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14251: LLVM Code Gen messes up registers -------------------------------------+------------------------------------- Reporter: angerman | Owner: kavon Type: bug | Status: patch Priority: highest | Milestone: 8.6.2 Component: Compiler (LLVM) | Version: 8.3 Resolution: | 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): Phab:D5190 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.6.1 => 8.6.2 Comment: Thanks kavon! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14251#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14251: LLVM Code Gen messes up registers
-------------------------------------+-------------------------------------
Reporter: angerman | Owner: kavon
Type: bug | Status: patch
Priority: highest | Milestone: 8.6.2
Component: Compiler (LLVM) | Version: 8.3
Resolution: | 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): Phab:D5190
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#14251: LLVM Code Gen messes up registers -------------------------------------+------------------------------------- Reporter: angerman | Owner: kavon Type: bug | Status: merge Priority: highest | Milestone: 8.6.2 Component: Compiler (LLVM) | Version: 8.3 Resolution: | 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): Phab:D5190 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => merge -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14251#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14251: LLVM Code Gen messes up registers -------------------------------------+------------------------------------- Reporter: angerman | Owner: kavon Type: bug | Status: closed Priority: highest | Milestone: 8.6.2 Component: Compiler (LLVM) | Version: 8.3 Resolution: fixed | 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): Phab:D5190 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-8.6` with 73273be476a8cc6c13368660b042b3b0614fd928. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14251#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14251: LLVM Code Gen messes up registers -------------------------------------+------------------------------------- Reporter: angerman | Owner: kavon Type: bug | Status: closed Priority: highest | Milestone: 8.6.2 Component: Compiler (LLVM) | Version: 8.3 Resolution: fixed | 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): Phab:D5190 Wiki Page: | -------------------------------------+------------------------------------- Changes (by juhpetersen): * cc: juhpetersen (added) Comment: Was this tested on ARM? (see #15780) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14251#comment:21 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14251: LLVM Code Gen messes up registers -------------------------------------+------------------------------------- Reporter: angerman | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.2 Component: Compiler (LLVM) | Version: 8.3 Resolution: | 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): Phab:D5190 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * owner: kavon => (none) * status: closed => new * resolution: fixed => Comment: Sadly no; we currently don't have CI for ARM (although I am currently speaking with people to fix this). Regardless, Kavon is aware of the issue and will hopefully pop up soon with a patch. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14251#comment:22 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14251: LLVM Code Gen messes up registers -------------------------------------+------------------------------------- Reporter: angerman | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.2 Component: Compiler (LLVM) | Version: 8.3 Resolution: | 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): Phab:D5190 Wiki Page: | -------------------------------------+------------------------------------- Comment (by kavon): New fix is up: https://phabricator.haskell.org/D5254 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14251#comment:23 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14251: LLVM Code Gen messes up registers -------------------------------------+------------------------------------- Reporter: angerman | Owner: kavon Type: bug | Status: new Priority: highest | Milestone: 8.6.2 Component: Compiler (LLVM) | Version: 8.3 Resolution: | 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): Phab:D5190 Wiki Page: | -------------------------------------+------------------------------------- Changes (by kavon): * owner: (none) => kavon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14251#comment:24 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14251: LLVM Code Gen messes up registers
-------------------------------------+-------------------------------------
Reporter: angerman | Owner: kavon
Type: bug | Status: new
Priority: highest | Milestone: 8.6.2
Component: Compiler (LLVM) | Version: 8.3
Resolution: | 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): Phab:D5190
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#14251: LLVM Code Gen messes up registers -------------------------------------+------------------------------------- Reporter: angerman | Owner: kavon Type: bug | Status: closed Priority: highest | Milestone: 8.6.2 Component: Compiler (LLVM) | Version: 8.3 Resolution: fixed | 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): Phab:D5190 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed Comment: Merged to `ghc-8.6` with 2e23e1c7de01c92b038e55ce53d11bf9db993dd4. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14251#comment:26 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14251: LLVM Code Gen messes up registers -------------------------------------+------------------------------------- Reporter: angerman | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.3 Component: Compiler (LLVM) | Version: 8.3 Resolution: | 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): Phab:D5190 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * owner: kavon => (none) * status: closed => new * resolution: fixed => * milestone: 8.6.2 => 8.6.3 Comment: Sadly I had to back out both comment:25 and comment:18 on `ghc-8.6` due to breakage. This will likely need to wait for 8.6.3 at the earliest. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14251#comment:27 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14251: LLVM Code Gen messes up registers -------------------------------------+------------------------------------- Reporter: angerman | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.3 Component: Compiler (LLVM) | Version: 8.3 Resolution: | 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): Phab:D5190 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): I am backing out both fixes on `master` as well until we have a fix. Kavon, if you could find the time it would be amazing if we could have this for 8.8; it would be a shame if we had to ship yet another release with a broken LLVM backend. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14251#comment:28 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14251: LLVM Code Gen messes up registers -------------------------------------+------------------------------------- Reporter: angerman | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.8.1 Component: Compiler (LLVM) | Version: 8.3 Resolution: | 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): Phab:D5190 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.6.3 => 8.8.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14251#comment:29 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC