[GHC] #8540: Template Haskell handling bug in ghc-7.7.20131115 under windows
#8540: Template Haskell handling bug in ghc-7.7.20131115 under windows ----------------------------+---------------------------------- Reporter: awson | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.7 Keywords: | Operating System: Windows Architecture: x86 | Type of failure: Runtime crash Difficulty: Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | ----------------------------+---------------------------------- Compiling this: {{{ {-# LANGUAGE TemplateHaskell #-} module Foo where import Data.Aeson import Data.Aeson.TH data Test = Test $(deriveFromJSON defaultOptions ''Test) }}} ghc-7.7.20131115 crashes with {{{ Foo.hs:10:3: Can't find interface-file declaration for variable Data.Aeson.TH.parseTypeMismatch' Probable cause: bug in .hi-boot file, or inconsistent .hi file Use -ddump-if-trace to get an idea of which file caused the error In the expression: Data.Aeson.TH.parseTypeMismatch' "Test" "Foo.Test" "an empty Array" ("Array of length " ++ ((show . Data.Vector.length) arr_a3BM)) In a case alternative: Array arr_a3BM | Data.Vector.null arr_a3BM -> Control.Applicative.pure Test | otherwise -> Data.Aeson.TH.parseTypeMismatch' "Test" "Foo.Test" "an empty Array" ("Array of length " ++ ((show . Data.Vector.length) arr_a3BM)) In the expression: case value_a3BL of { Array arr_a3BM | Data.Vector.null arr_a3BM -> Control.Applicative.pure Test | otherwise -> Data.Aeson.TH.parseTypeMismatch' "Test" "Foo.Test" "an empty Array" ("Array of length " ++ ((show . Data.Vector.length) arr_a3BM)) other_a3BN -> Data.Aeson.TH.parseTypeMismatch' "Test" "Foo.Test" "Array" (Data.Aeson.TH.valueConName other_a3BN) } }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8540 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
#8540: Template Haskell handling bug in ghc-7.7.20131115 -------------------------------------+------------------------------------ Reporter: awson | Owner: Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: Runtime crash | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Changes (by awson): * priority: high => highest * os: Windows => Unknown/Multiple * architecture: x86 => Unknown/Multiple Comment: Both windows x86 and linux x86_64 GHCs have this bug. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8540#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
#8540: Template Haskell handling bug in ghc-7.7.20131115 ? -------------------------------------+------------------------------------ Reporter: awson | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: Runtime crash | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Changes (by awson): * priority: highest => normal Comment: Ok, it seems adding a bunch of explicit exports to Data.Aeson.TH makes the problem go. It looks like previously TH implicitly exposed all variables referenced in exported functions and this is no longer the case. Which behaviour is erroneous then? Probably, current behaviour is not a bug at all but quite contrary - the fix of looong-standing bug? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8540#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
#8540: Template Haskell handling bug in ghc-7.7.20131115 ? -------------------------------------+------------------------------------ Reporter: awson | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: Runtime crash | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by simonpj): Might it be possible to make a small test case? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8540#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
#8540: Template Haskell handling bug in ghc-7.7.20131115 ? -------------------------------------+------------------------------------ Reporter: awson | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: Runtime crash | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by simonpj): I did install aeson, but go this when compiling your program {{{ simonpj@cam-05-unx:~/tmp$ /home/simonpj/5builds/validate-HEAD/inplace/bin /ghc-stage2 -c T8540.hs Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. Loading package array-0.5.0.0 ... linking ... done. Loading package deepseq-1.3.0.2 ... linking ... done. Loading package primitive-0.5.1.0 ... linking ... done. Loading package vector-0.10.9.1 ... linking ... done. Loading package pretty-1.1.1.1 ... linking ... done. Loading package old-locale-1.0.0.6 ... linking ... done. Loading package time-1.4.1 ... linking ... done. Loading package containers-0.5.3.1 ... linking ... done. Loading package bytestring-0.10.4.0 ... linking ... done. Loading package text-0.11.3.1 ... <command line>: can't load .so/.DLL for: libHStext-0.11.3.1.so (libHStext-0.11.3.1.so: cannot open shared object file: No such file or directory) simonpj@cam-05-unx:~/tmp$ }}} Something to do with dynamic linking, I suppose, but I don't know how to fix it. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8540#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
#8540: Template Haskell handling bug in ghc-7.7.20131115 ? -------------------------------------+------------------------------------ Reporter: awson | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: Runtime crash | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by awson): Here is the simplest test case: Foo.hs {{{ {-# LANGUAGE TemplateHaskell #-} module Foo (foo) where import Language.Haskell.TH foo :: Q Exp foo = [| bar |] bar :: Int bar = 5 }}} Baz.hs {{{ {-# LANGUAGE TemplateHaskell #-} module Baz where import Foo baz :: Int baz = $foo }}} Current GHC gives {{{ Baz.hs:8:7: Can't find interface-file declaration for variable Foo.bar Probable cause: bug in .hi-boot file, or inconsistent .hi file Use -ddump-if-trace to get an idea of which file caused the error In the expression: Foo.bar In an equation for `baz': baz = Foo.bar }}} when compiling Baz.hs. But if I explicitly export bar from Foo.hs: {{{ {-# LANGUAGE TemplateHaskell #-} module Foo (foo, bar) where import Language.Haskell.TH foo :: Q Exp foo = [| bar |] bar :: Int bar = 5 }}} current GHC gets happy. Older GHCs were able to live without this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8540#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
#8540: Template Haskell handling bug in ghc-7.7.20131115 ? -------------------------------------+------------------------------------ Reporter: awson | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: Runtime crash | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by simonpj): Thanks. I understand now. I'm on it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8540#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
#8540: Template Haskell handling bug in ghc-7.7.20131115 ?
-------------------------------------+------------------------------------
Reporter: awson | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.7
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture: Unknown/Multiple
Type of failure: Runtime crash | Difficulty: Unknown
Test Case: | Blocked By:
Blocking: | Related Tickets:
-------------------------------------+------------------------------------
Comment (by Simon Peyton Jones
#8540: Template Haskell handling bug in ghc-7.7.20131115 ?
-------------------------------------+------------------------------------
Reporter: awson | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.7
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture: Unknown/Multiple
Type of failure: Runtime crash | Difficulty: Unknown
Test Case: | Blocked By:
Blocking: | Related Tickets:
-------------------------------------+------------------------------------
Comment (by Simon Peyton Jones
#8540: Template Haskell handling bug in ghc-7.7.20131115 ? -------------------------------------+------------------------------------ Reporter: awson | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: Runtime crash | Difficulty: Unknown Test Case: th/T8540 | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Changes (by simonpj): * status: new => closed * testcase: => th/T8540 * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8540#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
#8540: Template Haskell handling bug in ghc-7.7.20131115 ?
-------------------------------------+------------------------------------
Reporter: awson | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.7
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture: Unknown/Multiple
Type of failure: Runtime crash | Difficulty: Unknown
Test Case: th/T8540 | Blocked By:
Blocking: | Related Tickets:
-------------------------------------+------------------------------------
Changes (by nomeata):
* status: closed => new
* resolution: fixed =>
Comment:
I believe this change causes test failures to fail with assertions (at
least it touches the location of the assertion):
{{{
=====> print019(ghci) 2936 of 3831 [0, 0, 0]
cd ./ghci.debugger/scripts && HC='/home/jojo/build/haskell/ghc/inplace/bin
/ghc-stage2' HC_OPTS='-dcore-lint -dcmm-lint -dno-debug-output -no-user-
package-db -rtsopts -fno-ghci-history '
'/home/jojo/build/haskell/ghc/inplace/bin/ghc-stage2' --interactive -v0
-ignore-dot-ghci -dcore-lint -dcmm-lint -dno-debug-output -no-user-
package-db -rtsopts -fno-ghci-history -ignore-dot-ghci print019.run.stdout 2>print019.run.stderr
Actual stderr output differs from expected:
--- ./ghci.debugger/scripts/print019.stderr 2013-09-13
20:58:44.089042446 +0100
+++ ./ghci.debugger/scripts/print019.run.stderr 2013-11-22
21:47:09.304630865 +0000
@@ -1,12 +1,9 @@
+ghc-stage2: panic! (the 'impossible' happened)
+ (GHC version 7.7.20131108 for x86_64-unknown-linux):
+ ASSERT failed!
+ file compiler/typecheck/TcEnv.lhs line 467
+ it{v a1C8} [lid]
+ a1{tv a1w5} [rt]
+
+Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
-:11:1:
- No instance for (Show a1) arising from a use of ‛print’
- Cannot resolve unknown runtime type ‛a1’
- Use :print or :force to determine these types
- Relevant bindings include it :: a1 (bound at :11:1)
- Note: there are several potential instances:
- instance Show a => Show (List1 a) -- Defined at ../Test.hs:11:12
- instance Show MyInt -- Defined at ../Test.hs:14:16
- instance Show a => Show (MkT a) -- Defined at ../Test.hs:17:13
- ...plus 32 others
- In a stmt of an interactive GHCi command: print it
*** unexpected failure for print019(ghci)
=====> break003(ghci) 2955 of 3831 [0, 1, 0]
cd ./ghci.debugger/scripts && HC='/home/jojo/build/haskell/ghc/inplace/bin
/ghc-stage2' HC_OPTS='-dcore-lint -dcmm-lint -dno-debug-output -no-user-
package-db -rtsopts -fno-ghci-history '
'/home/jojo/build/haskell/ghc/inplace/bin/ghc-stage2' --interactive -v0
-ignore-dot-ghci -dcore-lint -dcmm-lint -dno-debug-output -no-user-
package-db -rtsopts -fno-ghci-history -ignore-dot-ghci break003.run.stdout 2>break003.run.stderr
Actual stderr output differs from expected:
--- ./ghci.debugger/scripts/break003.stderr 2013-09-02
15:07:33.148355402 +0100
+++ ./ghci.debugger/scripts/break003.run.stderr 2013-11-22
21:47:09.528630856 +0000
@@ -1,4 +1,9 @@
+ghc-stage2: panic! (the 'impossible' happened)
+ (GHC version 7.7.20131108 for x86_64-unknown-linux):
+ ASSERT failed!
+ file compiler/typecheck/TcEnv.lhs line 467
+ it{v aR1} [lid]
+ t{tv IQD} [rt] -> t1{tv IQE} [rt]
+
+Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
-:5:1:
- No instance for (Show (t -> t1)) arising from a use of ‛print’
- In a stmt of an interactive GHCi command: print it
*** unexpected failure for break003(ghci)
=====> break006(ghci) 2957 of 3831 [0, 2, 0]
cd ./ghci.debugger/scripts && HC='/home/jojo/build/haskell/ghc/inplace/bin
/ghc-stage2' HC_OPTS='-dcore-lint -dcmm-lint -dno-debug-output -no-user-
package-db -rtsopts -fno-ghci-history '
'/home/jojo/build/haskell/ghc/inplace/bin/ghc-stage2' --interactive -v0
-ignore-dot-ghci -dcore-lint -dcmm-lint -dno-debug-output -no-user-
package-db -rtsopts -fno-ghci-history -ignore-dot-ghci break006.run.stdout 2>break006.run.stderr
Actual stderr output differs from expected:
--- ./ghci.debugger/scripts/break006.stderr 2013-09-13
20:58:44.085042446 +0100
+++ ./ghci.debugger/scripts/break006.run.stderr 2013-11-22
21:47:09.764630848 +0000
@@ -1,26 +1,33 @@
+ghc-stage2: panic! (the 'impossible' happened)
+ (GHC version 7.7.20131108 for x86_64-unknown-linux):
+ ASSERT failed!
+ file compiler/typecheck/TcEnv.lhs line 467
+ it{v aX8} [lid]
+ t1{tv IWQ} [rt]
+
+Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
+
+ghc-stage2: panic! (the 'impossible' happened)
+ (GHC version 7.7.20131108 for x86_64-unknown-linux):
+ ASSERT failed!
+ file compiler/typecheck/TcEnv.lhs line 467
+ y{v aYb} [lid]
+ t1{tv IWQ} [rt]
+
+Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
+
+
+:8:1: Not in scope: ‛y’
+
+Top level: Not in scope: ‛y’
+
+Top level: Not in scope: ‛y’
+ghc-stage2: panic! (the 'impossible' happened)
+ (GHC version 7.7.20131108 for x86_64-unknown-linux):
+ ASSERT failed!
+ file compiler/typecheck/TcEnv.lhs line 467
+ it{v aYm} [lid]
+ t1{tv IWQ} [rt]
+
+Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
-:6:1:
- No instance for (Show t1) arising from a use of ‛print’
- Cannot resolve unknown runtime type ‛t1’
- Use :print or :force to determine these types
- Relevant bindings include it :: t1 (bound at :6:1)
- Note: there are several potential instances:
- instance Show Double -- Defined in ‛GHC.Float’
- instance Show Float -- Defined in ‛GHC.Float’
- instance (Integral a, Show a) => Show (GHC.Real.Ratio a)
- -- Defined in ‛GHC.Real’
- ...plus 24 others
- In a stmt of an interactive GHCi command: print it
-
-:8:1:
- No instance for (Show t1) arising from a use of ‛print’
- Cannot resolve unknown runtime type ‛t1’
- Use :print or :force to determine these types
- Relevant bindings include it :: t1 (bound at :8:1)
- Note: there are several potential instances:
- instance Show Double -- Defined in ‛GHC.Float’
- instance Show Float -- Defined in ‛GHC.Float’
- instance (Integral a, Show a) => Show (GHC.Real.Ratio a)
- -- Defined in ‛GHC.Real’
- ...plus 24 others
- In a stmt of an interactive GHCi command: print it
Actual stdout output differs from expected:
--- ./ghci.debugger/scripts/break006.stdout 2013-09-02
15:07:33.148355402 +0100
+++ ./ghci.debugger/scripts/break006.run.stdout 2013-11-22
21:47:09.760630848 +0000
@@ -9,12 +9,7 @@
x :: Integer = 1
f :: Integer -> t1 = _
_result :: [t1] = _
-y = (_t1::t1)
-y = 2
xs :: [Integer] = [2,3]
x :: Integer = 1
-f :: Integer -> Integer = _
-_result :: [Integer] = _
-y :: Integer = 2
-_t1 :: Integer = 2
-2
+f :: Integer -> t1 = _
+_result :: [t1] = _
*** unexpected failure for break006(ghci)
Unexpected results from:
TEST="break006 break003 print019"
}}}
(I hope this “but it breaks my `-DDEBUG`” barfing is not too annoying...)
--
Ticket URL:
GHC
The Glasgow Haskell Compiler
#8540: Template Haskell handling bug in ghc-7.7.20131115 ?
-------------------------------------+------------------------------------
Reporter: awson | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.7
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture: Unknown/Multiple
Type of failure: Runtime crash | Difficulty: Unknown
Test Case: th/T8540 | Blocked By:
Blocking: | Related Tickets:
-------------------------------------+------------------------------------
Comment (by Joachim Breitner
#8540: Template Haskell handling bug in ghc-7.7.20131115 ? -------------------------------------+------------------------------------ Reporter: awson | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: Runtime crash | Difficulty: Unknown Test Case: th/T8540 | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by simonpj): I have `-DDEBUG` on too (certainly in `TcEnv`), and these tests work fine for me. I don't know how to account for this. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8540#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
#8540: Template Haskell handling bug in ghc-7.7.20131115 ? -------------------------------------+------------------------------------ Reporter: awson | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: Runtime crash | Difficulty: Unknown Test Case: th/T8540 | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by nomeata): I just reproduced it here again, starting from a clean tree, and the build host on travis has it. Have you tried running `make clean` first? And are you sure there is no `mk/are-validating.mk` overriding your settings? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8540#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
#8540: Template Haskell handling bug in ghc-7.7.20131115 ?
-------------------------------------+------------------------------------
Reporter: awson | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.7
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture: Unknown/Multiple
Type of failure: Runtime crash | Difficulty: Unknown
Test Case: th/T8540 | Blocked By:
Blocking: | Related Tickets:
-------------------------------------+------------------------------------
Comment (by Simon Peyton Jones
#8540: Template Haskell handling bug in ghc-7.7.20131115 ?
-------------------------------------+------------------------------------
Reporter: awson | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.7
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture: Unknown/Multiple
Type of failure: Runtime crash | Difficulty: Unknown
Test Case: th/T8540 | Blocked By:
Blocking: | Related Tickets:
-------------------------------------+------------------------------------
Comment (by Simon Peyton Jones
#8540: Template Haskell handling bug in ghc-7.7.20131115 ? -------------------------------------+------------------------------------ Reporter: awson | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: Runtime crash | Difficulty: Unknown Test Case: th/T8540 | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Changes (by simonpj): * status: new => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8540#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC