
#9190: Iface type variable out of scope: s -------------------------------------+------------------------------------ Reporter: nomeata | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by nomeata): Further reduced the problem: {{{ {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} module T9190b where import Language.Haskell.TH data family Family a b foo :: DecsQ foo = do s <- VarT `fmap` newName "s" return [ NewtypeInstD [] ''Family [s, ConT ''Double] (NormalC (mkName "Foo") [(NotStrict, TupleT 0) ]) [] ] }}} and {{{ {-# LANGUAGE TypeFamilies, TemplateHaskell #-} module T9190a where import T9190b foo }}} yields {{{ b179ce4def4d6d8b892ce82aab2d2a37 newtype instance T9190b.Family s GHC.Types.Double = Foo () RecFlag: Recursive b179ce4def4d6d8b892ce82aab2d2a37 axiom TFCo:R:FamilysDouble:: T9190b.Family s0 GHC.Types.Double = T9190a.R:FamilysDouble s0 family instance T9190b.Family [.], [GHC.Types.Double] = T9190a.TFCo:R:FamilysDouble }}} I’m off traveling to OPSLL, but I hope that this makes it easier for someone else to pick up the issue. (But maybe I’m completely off the track here, and the interface is actually fine – I just discovered that with `-fprint-explicit-foralls` this reads {{{ b179ce4def4d6d8b892ce82aab2d2a37 axiom TFCo:R:FamilysDouble:: forall s0. T9190b.Family s0 GHC.Types.Double = T9190a.R:FamilysDouble s0 }}} and this hiding of `forall` is new in 7.8 or 7.9 compared to 7.6, which had printed the `s0` directly. :-( ) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9190#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler