
#14885: TH breaks the scoping of quoted default method implementations when spliced -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): It's not just class declarations that are broken. Pattern synonyms are similarly broken: {{{#!hs {-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TemplateHaskell #-} {-# OPTIONS_GHC -ddump-splices #-} module Bug where pattern P1 :: forall a. a -> Maybe a pattern P1 x <- Just x where P1 x = Just (x :: a) $([d| pattern P2 :: forall a. a -> Maybe a pattern P2 x <- Just x where P2 x = Just (x :: a) |]) }}} {{{ $ /opt/ghc/8.2.2/bin/ghci Bug.hs GHCi, version 8.2.2: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:(11,3)-(14,6): Splicing declarations [d| pattern P2_a1t7 :: forall a_a1t8. a_a1t8 -> Maybe a_a1t8 pattern P2_a1t7 x_a1t9 <- Just x_a1t9 where P2_a1t7 x_a1ta = Just (x_a1ta :: a_a1t8) |] ======> pattern P2_a4aA :: forall a_a4aB. a_a4aB -> Maybe a_a4aB pattern P2_a4aA x_a4aC <- Just x_a4aC where P2_a4aA x_a4aD = Just (x_a4aD :: a_a1t8) Bug.hs:11:3: error: • Couldn't match expected type ‘a1’ with actual type ‘a’ ‘a’ is a rigid type variable bound by the signature for pattern synonym ‘P2’ at Bug.hs:(11,3)-(14,6) ‘a1’ is a rigid type variable bound by an expression type signature: forall a1. a1 at Bug.hs:(11,3)-(14,6) • In the first argument of ‘Just’, namely ‘(x_a4aD :: a)’ In the expression: Just (x_a4aD :: a) In an equation for ‘P2’: P2 x_a4aD = Just (x_a4aD :: a) • Relevant bindings include x_a4aD :: a (bound at Bug.hs:11:3) $bP2 :: a -> Maybe a (bound at Bug.hs:11:3) | 11 | $([d| pattern P2 :: forall a. a -> Maybe a | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^... }}} As well as `DefaultSignatures`: {{{#!hs {-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TemplateHaskell #-} {-# OPTIONS_GHC -ddump-splices #-} module Bug where class Foo1 a where foo1 :: forall b. a -> b -> b default foo1 :: forall b. a -> b -> b foo1 _ x = (x :: b) $([d| class Foo2 a where foo2 :: forall b. a -> b -> b default foo2 :: forall b. a -> b -> b foo2 _ x = (x :: b) |]) }}} {{{ $ /opt/ghc/8.2.2/bin/ghci Bug.hs GHCi, version 8.2.2: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:(12,3)-(16,6): Splicing declarations [d| class Foo2_a1tO a_a1tQ where foo2_a1tP :: forall b_a1tR. a_a1tQ -> b_a1tR -> b_a1tR default foo2_a1tP :: forall b_a1tS. a_a1tQ -> b_a1tS -> b_a1tS foo2_a1tP _ x_a1tT = (x_a1tT :: b_a1tS) |] ======> class Foo2_a4bq a_a4bs where foo2_a4br :: forall b_a4bt. a_a4bs -> b_a4bt -> b_a4bt default foo2_a4br :: forall b_a4bu. a_a4bs -> b_a4bu -> b_a4bu foo2_a4br _ x_a4bv = x_a4bv :: b_a1tS Bug.hs:12:3: error: • Couldn't match expected type ‘b1’ with actual type ‘b’ ‘b’ is a rigid type variable bound by the type signature for: foo2 :: forall b. a0 -> b -> b at Bug.hs:(12,3)-(16,6) ‘b1’ is a rigid type variable bound by an expression type signature: forall b1. b1 at Bug.hs:(12,3)-(16,6) • In the expression: x_a4bv :: b In an equation for ‘foo2’: foo2 _ x_a4bv = x_a4bv :: b • Relevant bindings include x_a4bv :: b (bound at Bug.hs:12:3) foo2 :: a0 -> b -> b (bound at Bug.hs:12:3) | 12 | $([d| class Foo2 a where | ^^^^^^^^^^^^^^^^^^^^^^... }}} And `InstanceSigs`: {{{#!hs {-# LANGUAGE InstanceSigs #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TemplateHaskell #-} {-# OPTIONS_GHC -ddump-splices #-} module Bug where class Foo1 a where foo1 :: forall b. a -> b -> b instance Foo1 (Maybe a) where foo1 :: forall b. Maybe a -> b -> b foo1 _ x = (x :: b) $([d| class Foo2 a where foo2 :: forall b. a -> b -> b instance Foo2 (Maybe a) where foo2 :: forall b. Maybe a -> b -> b foo2 _ x = (x :: b) |]) }}} {{{ $ /opt/ghc/8.2.2/bin/ghci Bug.hs GHCi, version 8.2.2: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:(14,3)-(20,6): Splicing declarations [d| class Foo2_a1tR a_a1tT where foo2_a1tS :: forall b_a1tU. a_a1tT -> b_a1tU -> b_a1tU instance Foo2_a1tR (Maybe a_a1tV) where foo2_a1tS :: forall b_a1tW. Maybe a_a1tV -> b_a1tW -> b_a1tW foo2_a1tS _ x_a1tX = (x_a1tX :: b_a1tW) |] ======> class Foo2_a4c2 a_a4c4 where foo2_a4c3 :: forall b_a4c5. a_a4c4 -> b_a4c5 -> b_a4c5 instance Foo2_a4c2 (Maybe a_a4c6) where foo2_a4c3 :: forall b_a4c8. Maybe a_a4c6 -> b_a4c8 -> b_a4c8 foo2_a4c3 _ x_a4c7 = x_a4c7 :: b_a1tW Bug.hs:14:3: error: • Couldn't match expected type ‘b1’ with actual type ‘b’ ‘b’ is a rigid type variable bound by the type signature for: foo2 :: forall b. Maybe a -> b -> b at Bug.hs:(14,3)-(20,6) ‘b1’ is a rigid type variable bound by an expression type signature: forall b1. b1 at Bug.hs:(14,3)-(20,6) • In the expression: x_a4c7 :: b In an equation for ‘foo2’: foo2 _ x_a4c7 = x_a4c7 :: b In the instance declaration for ‘Foo2 (Maybe a)’ • Relevant bindings include x_a4c7 :: b (bound at Bug.hs:14:3) foo2 :: Maybe a -> b -> b (bound at Bug.hs:14:3) | 14 | $([d| class Foo2 a where | ^^^^^^^^^^^^^^^^^^^^^^... }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14885#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler