#4499: "skolem type variable" is bad for usability (and beginners)
----------------------------------------+-----------------------------------
    Reporter:  guest                    |        Owner:              
        Type:  bug                      |       Status:  new         
    Priority:  normal                   |    Milestone:              
   Component:  Compiler (Type checker)  |      Version:  7.0.1       
    Keywords:  skolem                   |     Testcase:              
   Blockedby:                           |   Difficulty:              
          Os:  Unknown/Multiple         |     Blocking:              
Architecture:  Unknown/Multiple         |      Failure:  None/Unknown
----------------------------------------+-----------------------------------

Comment(by simonpj):

 For this porgram
 {{{
 {-# LANGUAGE RankNTypes #-}
 module Foo where

 f :: (forall a. a->a) -> Int
 f = error "urk"

 g x = f (\v -> x)
 }}}
 currently we get
 {{{
 Foo.hs:8:7:
     Couldn't match type `t' with `a'
       because this skolem type variable would escape: `a'
     This skolem is bound by the polymorphic type `forall a. a -> a'
     The following variables have types that mention t
       x :: t (bound at Foo.hs:8:3)
 ...
 }}}
 what about
 {{{
     Couldn't match type `t' with `a'
       because the type variable 'a' would escape its scope
     The (rigid, skolem) type variable 'a' is is bound by
       the polymorphic type `forall a. a -> a'
     The following variables have types that mention t
       x :: t (bound at Foo.hs:8:3)}}}
 }}}

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