#344: arrow notation: incorrect scope of existential dictionaries
--------------------------------------+-------------------------------------
Reporter: nobody | Owner: ross
Type: bug | Status: new
Priority: lowest | Milestone: 7.6.1
Component: Compiler (Type checker) | Version: 6.4
Resolution: None | Keywords:
Os: Unknown/Multiple | Architecture: Unknown/Multiple
Failure: Compile-time crash | Difficulty: Unknown
Testcase: | Blockedby:
Blocking: | Related:
--------------------------------------+-------------------------------------
Changes (by danbst):
* cc: abcz2.uprola@… (added)
Comment:
Even smaller, which fails core-lint
{{{
{-# LANGUAGE Arrows, ExistentialQuantification #-}
{-# OPTIONS -dcore-lint #-}
module GHCbug where
class Foo a where foo :: a -> ()
data Bar = forall a. Foo a => Bar a
get :: Bar -> ()
get = proc x -> case x of Bar a -> id -< foo a
}}}
but I cannot figure, 1) what it should be desugared to:
{{{
get = arr (\x -> case x of Bar a -> foo a) >>> id
}}}
?
2) why does it compile without -dcore-lint? What part of GHC is bug hidden
in?
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/344#comment:22>
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