[GHC] #13659: Bug report: "AThing evaluated unexpectedly tcTyVar a_alF"

#13659: Bug report: "AThing evaluated unexpectedly tcTyVar a_alF" -------------------------------------+------------------------------------- Reporter: costaparas | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Linux Architecture: x86_64 | Type of failure: Compile-time (amd64) | performance bug Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The following code: {{{#!hs {-# LANGUAGE GADTs, EmptyDataDecls, TypeFamilies, TypeOperators, DataKinds, FlexibleInstances #-} {- Defines a C-like printf function using DataKinds extensions. -} module Printf where -- format string parameterized by a list of types data Format (fmt :: [*]) where X :: Format '[] -- empty string, i.e. "" L :: a -> String -> Format '[] -- string literal, e.g. "hello" S :: a -> Format '[String] -- "%s" I :: Format a -> Format '[Int, a] -- "%d" }}} produces the following error: GHCi, version 7.10.3: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Printf ( Printf.hs, interpreted ) a.hs:12:27:ghc: panic! (the 'impossible' happened) (GHC version 7.10.3 for x86_64-unknown-linux): AThing evaluated unexpectedly tcTyVar a_alF Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug when run using **ghci Printf.hs** on Liunx Ubuntu 16.04 LTS 64-bit with Intel® Core™ i7-7500U CPU @ 2.70GHz -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13659 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13659: Bug report: "AThing evaluated unexpectedly tcTyVar a_alF" -------------------------------------+------------------------------------- Reporter: costaparas | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by costaparas: @@ -24,1 +24,1 @@ - a.hs:12:27:ghc: panic! (the 'impossible' happened) + Printf.hs:12:27:ghc: panic! (the 'impossible' happened) New description: The following code: {{{#!hs {-# LANGUAGE GADTs, EmptyDataDecls, TypeFamilies, TypeOperators, DataKinds, FlexibleInstances #-} {- Defines a C-like printf function using DataKinds extensions. -} module Printf where -- format string parameterized by a list of types data Format (fmt :: [*]) where X :: Format '[] -- empty string, i.e. "" L :: a -> String -> Format '[] -- string literal, e.g. "hello" S :: a -> Format '[String] -- "%s" I :: Format a -> Format '[Int, a] -- "%d" }}} produces the following error: GHCi, version 7.10.3: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Printf ( Printf.hs, interpreted ) Printf.hs:12:27:ghc: panic! (the 'impossible' happened) (GHC version 7.10.3 for x86_64-unknown-linux): AThing evaluated unexpectedly tcTyVar a_alF Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug when run using **ghci Printf.hs** on Liunx Ubuntu 16.04 LTS 64-bit with Intel® Core™ i7-7500U CPU @ 2.70GHz -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13659#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13659: Bug report: "AThing evaluated unexpectedly tcTyVar a_alF" -------------------------------------+------------------------------------- Reporter: costaparas | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I can't reproduce this bug on GHC 8.0.1 or later: {{{ $ /opt/ghc/8.0.1/bin/ghci Bug.hs GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Printf ( Bug.hs, interpreted ) Bug.hs:12:27: error: • Expected a type, but ‘a’ has kind ‘[*]’ • In the first argument of ‘Format’, namely ‘'[Int, a]’ In the type ‘Format '[Int, a]’ In the definition of data constructor ‘I’ Failed, modules loaded: none. }}} Commit 5955510e5f57464b1f4f42b510e3558d6e691380 was what fixed it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13659#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13659: Bug report: "AThing evaluated unexpectedly tcTyVar a_alF" -------------------------------------+------------------------------------- Reporter: costaparas | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I'll add a regression test -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13659#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13659: Bug report: "AThing evaluated unexpectedly tcTyVar a_alF"
-------------------------------------+-------------------------------------
Reporter: costaparas | Owner: (none)
Type: bug | Status: new
Priority: highest | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: | Keywords:
Operating System: Linux | Architecture: x86_64
Type of failure: Compile-time | (amd64)
performance bug | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#13659: Bug report: "AThing evaluated unexpectedly tcTyVar a_alF" -------------------------------------+------------------------------------- Reporter: costaparas | Owner: (none) Type: bug | Status: closed Priority: highest | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13659#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC