#7026: Impredicative implicit parameters
---------------------------------------+------------------------------------
 Reporter:  Ashley Yakeley             |          Owner:                        
 
     Type:  bug                        |         Status:  new                   
 
 Priority:  normal                     |      Component:  Compiler (Type 
checker)
  Version:  7.4.2                      |       Keywords:                        
 
       Os:  Unknown/Multiple           |   Architecture:  Unknown/Multiple      
 
  Failure:  GHC rejects valid program  |       Testcase:                        
 
Blockedby:                             |       Blocking:                        
 
  Related:                             |  
---------------------------------------+------------------------------------
 There doesn't seem to be a way to make impredicative implicit parameters
 work in 7.4.2:

 {{{
 {-# LANGUAGE ImplicitParams, ImpredicativeTypes #-}
 module Bug where

     f1 :: Maybe ((?a :: Bool) => Char)
     f1 = Just 'C'

     f2 :: Maybe ((?a :: Bool) => Bool)
     f2 = Just ?a
 }}}


 {{{
 $ ghc -c Bug.hs

 Bug.hs:5:15:
     Couldn't match expected type `(?a::Bool) => Char'
                 with actual type `Char'
     In the first argument of `Just', namely 'C'
     In the expression: Just 'C'
     In an equation for `f1': f1 = Just 'C'

 Bug.hs:8:15:
     Unbound implicit parameter (?a::(?a::Bool) => Bool)
       arising from a use of implicit parameter `?a'
     In the first argument of `Just', namely `?a'
     In the expression: Just ?a
     In an equation for `f2': f2 = Just ?a
 }}}

 I believe this used to work?

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/7026>
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