[GHC] #11167: Fixity of field-deconstructors incorrect
GHC
ghc-devs at haskell.org
Fri Dec 4 23:25:14 UTC 2015
#11167: Fixity of field-deconstructors incorrect
-------------------------------------+-------------------------------------
Reporter: hvr | Owner:
Type: bug | Status: new
Priority: highest | Milestone: 8.0.1
Component: Compiler | Version: 7.10.2
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
The example below
{{{#!hs
module Foo where
data SomeException
newtype ContT r m a = ContT {runContT :: (a -> m r) -> m r}
runContT' :: ContT r m a -> (a -> m r) -> m r
runContT' = runContT
catch_ :: IO a -> (SomeException -> IO a) -> IO a
catch_ = undefined
-- has type error
foo :: IO ()
foo = (undefined :: ContT () IO a) `runContT` (undefined :: a -> IO ())
`catch_` (undefined :: SomeException -> IO ())
-- typechecks
foo' :: IO ()
foo' = (undefined :: ContT () IO a) `runContT'` (undefined :: a -> IO ())
`catch_` (undefined :: SomeException -> IO ())
}}}
works with GHC 7.10 but breaks with GHC HEAD currently with:
{{{
foo.hs:15:47: error:
• Couldn't match expected type ‘a0 -> IO ()’
with actual type ‘IO ()’
• In the second argument of ‘runContT’, namely
‘(undefined :: a -> IO ())
`catch_` (undefined :: SomeException -> IO ())’
In the expression:
runContT
(undefined :: ContT () IO a)
(undefined :: a -> IO ())
`catch_` (undefined :: SomeException -> IO ())
In an equation for ‘foo’:
foo
= runContT
(undefined :: ContT () IO a)
(undefined :: a -> IO ())
`catch_` (undefined :: SomeException -> IO ())
foo.hs:15:48: error:
• Couldn't match expected type ‘IO ()’
with actual type ‘a1 -> IO ()’
• In the first argument of ‘catch_’, namely
‘(undefined :: a -> IO ())’
In the second argument of ‘runContT’, namely
‘(undefined :: a -> IO ())
`catch_` (undefined :: SomeException -> IO ())’
In the expression:
runContT
(undefined :: ContT () IO a)
(undefined :: a -> IO ())
`catch_` (undefined :: SomeException -> IO ())
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11167>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list