[GHC] #13748: Variables pretty-printed from -ddump-deriv are not scoped properly
GHC
ghc-devs at haskell.org
Tue May 23 17:02:56 UTC 2017
#13748: Variables pretty-printed from -ddump-deriv are not scoped properly
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
(Type checker) |
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
This bug is present on GHC 8.0.1, 8.0.2, 8.2.1 and HEAD, and originally
noted in https://ghc.haskell.org/trac/ghc/ticket/13738#comment:2. Take
this code:
{{{#!hs
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE PolyKinds #-}
{-# OPTIONS_GHC -ddump-deriv #-}
module Works where
newtype Wrap f a = Wrap (f a) deriving C
class C f where
c :: f a
}}}
When you compile it with GHC 8.0.2, you'll get this unsavory output:
{{{
GHCi, version 8.0.2: http://www.haskell.org/ghc/ :? for help
Loaded GHCi configuration from /home/rgscott/.ghci
[1 of 1] Compiling Works ( Works.hs, interpreted )
==================== Derived instances ====================
Derived instances:
instance forall k_a14U (f_a14V :: k_a14U -> *).
Works.C f_a14V =>
Works.C (Works.Wrap f_a14V) where
Works.c
= GHC.Prim.coerce
@(forall (a_a13F :: k_a14u). f_a13G a_a13F)
@(forall (a_a13F :: k_a14u). Works.Wrap f_a13G a_a13F)
Works.c
GHC.Generics representation types:
}}}
This is wrong, since the quantified variables in the instance head
(`k_a14U` and `f_a14V`) do not match the occurrences that they bind
(`k_a14u` and `f_a13G`). This is somewhat easier to see on GHC 8.2.1 or
HEAD, since the binding sites are printed without uniques:
{{{
GHCi, version 8.3.20170516: http://www.haskell.org/ghc/ :? for help
Loaded GHCi configuration from /home/rgscott/.ghci
[1 of 1] Compiling Works ( Works.hs, interpreted )
==================== Derived instances ====================
Derived class instances:
instance forall k (f :: k -> *).
Works.C f =>
Works.C (Works.Wrap f) where
Works.c
= GHC.Prim.coerce
@(forall (a_a1tD :: k_a1uE). f_a1tE a_a1tD)
@(forall (a_a1tD :: k_a1uE). Works.Wrap f_a1tE a_a1tD)
Works.c
Derived type family instances:
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13748>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list