[GHC] #14833: QuantifiedConstraints: GHC can't deduce (() :: Constraint)?
GHC
ghc-devs at haskell.org
Fri Feb 23 23:02:50 UTC 2018
#14833: QuantifiedConstraints: GHC can't deduce (() :: Constraint)?
-------------------------------------+-------------------------------------
Reporter: Iceland_jack | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.5
Resolution: | Keywords:
| QuantifiedConstraints wipT2893
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by RyanGlScott):
Note that the `(:-)` part is not needed to trigger this:
{{{#!hs
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE QuantifiedConstraints #-}
{-# LANGUAGE UndecidableInstances #-}
module Bug where
data Dict c where
Dict :: c => Dict c
class (a => b) => Implies a b
instance (a => b) => Implies a b
iota1 :: (() => a) => Dict a
iota1 = Dict
iota2 :: Implies () a => Dict a
iota2 = Dict
}}}
Note that `iota1` typechecks but `iota2` does not.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14833#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list