#6015: "No instance" when using PolyKinds/DataKinds/FunDeps/Undecidable
---------------------------------------+------------------------------------
 Reporter:  atnnn                      |          Owner:                  
     Type:  feature request            |         Status:  new             
 Priority:  normal                     |      Component:  Compiler        
  Version:  7.4.1                      |       Keywords:                  
       Os:  Unknown/Multiple           |   Architecture:  Unknown/Multiple
  Failure:  GHC rejects valid program  |       Testcase:                  
Blockedby:                             |       Blocking:                  
  Related:                             |  
---------------------------------------+------------------------------------
 Consider this GHCi session:

 {{{
 > value (Proxy :: Proxy (Just True))
 No instance for (Value (Maybe Bool) (Just Bool 'True) t0)
 > :i Value
 instance Value Bool 'True Bool
 instance Value k a t => Value (Maybe k) (Just k a) (Maybe t)
 > value (Proxy :: Proxy (Just True)) :: Maybe Bool
 Just True
 }}}

 It would be helpful if GHC could use the instance (which seems suitable)
 or emit a better error message.

 {{{
 {-# LANGUAGE DataKinds, MultiParamTypeClasses, FunctionalDependencies,
              PolyKinds, UndecidableInstances, ScopedTypeVariables #-}

 data Proxy a = Proxy
 class Value a t | a -> t where value :: Proxy a -> t
 instance Value True Bool where value _ = True
 instance Value a t => Value (Just a) (Maybe t)
     where value _ = Just (value (Proxy :: Proxy a))

 -- main = print (value (Proxy :: Proxy (Just True)))
 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/6015>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler

_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to