[GHC] #13952: Liberal coverage condition fails if TypeInType is enabled
GHC
ghc-devs at haskell.org
Mon Jul 10 14:20:48 UTC 2017
#13952: Liberal coverage condition fails if TypeInType is enabled
-------------------------------------+-------------------------------------
Reporter: mpickering | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.2.1-rc2
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
The following program compiles with 8.0.2 but fails with 8.2.1-rc2. It
succeeds if the `TypeInType` extension is disabled.
{{{#!hs
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE DataKinds,
FlexibleContexts, FlexibleInstances, FunctionalDependencies,
MultiParamTypeClasses, TypeFamilies, TypeOperators #-}
-- Removing TypeInType causes compilation to succeed
{-# LANGUAGE TypeInType #-}
module Bookkeeper.Internal where
import GHC.Generics
import GHC.TypeLits (Symbol, KnownSymbol, TypeError, ErrorMessage(..))
class FromGeneric a book | a -> book where
fromGeneric :: a x -> book
type family Expected a where
Expected (l :+: r) = TypeError ('Text "Cannot convert sum types into
Books")
Expected U1 = TypeError ('Text "Cannot convert non-record types
into Books")
instance (book ~ Expected U1) => FromGeneric U1 book where
fromGeneric = error "impossible"
}}}
{{{
src/Bookkeeper/Internal.hs:18:10: error:
• Illegal instance declaration for ‘FromGeneric U1 book’
The coverage condition fails in class ‘FromGeneric’
for functional dependency: ‘a -> book’
Reason: lhs type ‘U1’ does not determine rhs type ‘book’
Un-determined variable: book
• In the instance declaration for ‘FromGeneric U1 book’
|
18 | instance (book ~ Expected U1) => FromGeneric U1 book where
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
}}}
Perhaps this is related to #12803 but I made another ticket so that it can
be diagnosed separately.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13952>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list