
#12040: Code that builds on 7.8.4 and 7.10.3 but fails with requiring UndecidableInstances on 8.0.1-rc4 -------------------------------------+------------------------------------- Reporter: dmcclean | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): It has something to do with the polykindedness of `Proxy`. This further- reduced version displays the same behavior but after replacing `Proxy` by `Maybe`, both versions of ghc accept the program. {{{ {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE KindSignatures #-} module T12040 where import Data.Proxy newtype Dimensional c d a = Quantity a class HasDimension a class Demotable (q :: * -> *) instance (HasDimension (Proxy d)) => Demotable (Dimensional Int d) where }}} Maybe a consequence of kind and type arguments being treated uniformly in GHC's Core language now? Arguably neither behavior is wrong, since the instance termination checker is necessarily a conservative approximation. There's no real harm in just turning on UndecidableInstances. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12040#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler