
#12526: regression in type inference with respect to type families -------------------------------------+------------------------------------- Reporter: Lemming | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.2 Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: 10634 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Here is a yet simpler version of the problem {{{ {-# LANGUAGE TypeFamilies, MonoLocalBinds #-} module T12526 where type family P (s :: * -> *) :: * -> * -> * type instance P Signal = Causal type family S (p :: * -> * -> *) :: * -> * type instance S Causal = Signal class (P (S p) ~ p) => CP p instance CP Causal data Signal a = Signal data Causal a b = Causal shapeModOsci :: CP p => p Float Float shapeModOsci = undefined f :: Causal Float Float -> Bool f = undefined -- This fails ping :: Bool ping = let osci = shapeModOsci in f osci -- This works -- ping :: Bool -- ping = f shapeModOsci }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12526#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler