
#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): And finally, the last dependency not in GHC reduced to this module {{{ {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} module T9190b (derivingUnbox) where import Control.Applicative import Data.Vector.Unboxed.Base (MVector (..)) import Language.Haskell.TH derivingUnbox :: String -> TypeQ -> DecsQ derivingUnbox name argsQ = do let mvName = mkName $ "MV_" ++ name args <- argsQ (_, typ, rep) <- case args of ForallT _ cxts (ArrowT `AppT` typ `AppT` rep) -> return (cxts, typ, rep) ArrowT `AppT` typ `AppT` rep -> return ([], typ, rep) _ -> fail "Expecting a type of the form: cxts => typ -> rep" s <- VarT <$> newName "s" let newtypeMVector = NewtypeInstD [] ''MVector [s, typ] (NormalC mvName [(NotStrict, ConT ''MVector `AppT` s `AppT` rep)]) [] return [ newtypeMVector] }}} to be used with {{{ {-# LANGUAGE MultiParamTypeClasses, TemplateHaskell, TypeFamilies #-} module T9190a where import T9190b data KBNSum = KBNSum Double Double derivingUnbox "KBNSum" [t| KBNSum -> (Double, Double) |] }}} There we see a new variable `s` being introduced and put in the type of the newtype declaration. Is it TH’s responsibility to abstract over `s` here, or GHCs -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9190#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler