Bugs item #1200592, was opened at 2005-05-12 05:34
Message generated for change (Tracker Item Submitted) made by Item Submitter
You can respond by visiting: 
https://sourceforge.net/tracker/?func=detail&atid=108032&aid=1200592&group_id=8032

Category: Compiler
Group: None
Status: Open
Resolution: None
Priority: 5
Submitted By: Nobody/Anonymous (nobody)
Assigned to: Nobody/Anonymous (nobody)
Summary: GHC fails to pass dictionary in a rank-2 situation.

Initial Comment:
Hello,

The following code leads to a run- or compile-time error.
\begin{code}
{-# OPTIONS -fglasgow-exts #-}
module Main () where

foo :: (forall m. Monad m => m a) -> IO a
foo = id . id

main :: IO ()
main = foo (return ())
\end{code}

GHC translates `foo' effectively to an identity
function, failing to pass a dictionary to the argument.
  foo :: %forall a . (%forall (m::(*->*)) . ZCTMonad m ->
                                            m a)
                     -> IO a =
    \ @ a ->
        zi @ (IO a) @ (IO a)
        @ (IO a) (id @ (IO a))
        (id @ (IO a));

This doesn't typecheck, therefore 

$ ./ghc-6.5.20050510 -O IsolateBug.hs 
ghc-6.5.20050510: panic! (the `impossible' happened,
GHC version 6.5.20050510):
        No match in record selector Var.idInfo

Please report it as a compiler bug to
glasgow-haskell-bugs@haskell.org,
or http://sourceforge.net/projects/ghc/.

$ ghc-6.5.20050510 IsolateBug.hs 
$ ./a.out 
zsh: segmentation fault  ./a.out


The bug still occurs when we give the compiler a little
bit more type information
> foo = (id :: IO a -> IO a) . (id :: IO a -> IO a)
, however
> foo = id . id :: IO a -> IO a
and
> foo = id
behave correctly.

Tested with ghc-6.2.2, ghc-6.4 and the latest ghc-6.5
snapshot.

-- Thomas Jäger <[EMAIL PROTECTED]>

----------------------------------------------------------------------

You can respond by visiting: 
https://sourceforge.net/tracker/?func=detail&atid=108032&aid=1200592&group_id=8032
_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to