#5596: "f c = a $ b c", "f = a . b" does not.
-------------------------------+--------------------------------------------
    Reporter:  guest           |       Owner:                           
        Type:  bug             |      Status:  new                      
    Priority:  normal          |   Component:  Compiler (Type checker)  
     Version:  7.2.1           |    Keywords:                           
    Testcase:                  |   Blockedby:                           
          Os:  Linux           |    Blocking:                           
Architecture:  x86_64 (amd64)  |     Failure:  GHC rejects valid program
-------------------------------+--------------------------------------------
 the following code produces a type error, and i think it shouldn't:


 {{{
 {-# LANGUAGE ScopedTypeVariables, MultiParamTypeClasses #-}
 module Main
 where

 import Control.Monad.ST
 import Data.STRef
 import Text.Parsec


 type P v a = ParsecT TokStream () (ST v) a

 data TokStream = TokStream [Char]

 instance Stream TokStream (ST v) Char where
     uncons (TokStream []) = return Nothing
     uncons (TokStream (t:ts)) = return (Just (t, TokStream ts))

 c :: P v ()
 c = return ()

 works :: [Char] -> Either ParseError ()
 works toks = runST $ f $ TokStream toks
     where
       f :: forall v . TokStream -> ST v (Either ParseError ())
       f = runPT c () "<sourcefile>"

 doesnt :: [Char] -> Either ParseError ()
 doesnt = runST . f . TokStream
     where
       f :: forall v . TokStream -> ST v (Either ParseError ())
       f = runPT c () "<sourcefile>"
 }}}

 doesnt should be equivalent to works, but works works and doesnt doesn't.
 the type error:


 {{{

     Couldn't match expected type `forall s.
                                   ST s (Either ParseError ())'
                 with actual type `ST v0 (Either ParseError ())'
     Expected type: TokStream -> forall s. ST s (Either ParseError ())
       Actual type: TokStream -> ST v0 (Either ParseError ())
     In the first argument of `(.)', namely `f'
     In the second argument of `(.)', namely `f . TokStream'

 }}}

 I tried this on 7.2.1 and 7.0.3.  may be related to tickets 4347 or 4310,
 but I don't know enough about the ghc type engine to tell.

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