[GHC] #13506: Spurious extra error message due to functional dependencies
GHC
ghc-devs at haskell.org
Fri Mar 31 21:06:07 UTC 2017
#13506: Spurious extra error message due to functional dependencies
-------------------------------------+-------------------------------------
Reporter: gelisam | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.2
(Type checker) |
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: Incorrect
Unknown/Multiple | error/warning at compile-time
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
One call site is ill-typed, but GHC reports a type error at every call
site, not just the problematic one. In the original code, the problem
occurred with a very common function (`Data.Lens.view`), so the avalanche
of error messages made it difficult to find the problematic call site.
{{{#!hs
{-# LANGUAGE FlexibleInstances, FunctionalDependencies,
MultiParamTypeClasses #-}
module Bug where
class FunDep lista a | lista -> a
instance FunDep [a] a
singleton :: FunDep lista a => a -> lista
singleton _ = undefined
-- this error is expected:
-- Couldn't match type 'Char' with '()'
-- arising from a functional dependency between
-- constraint 'FunDep [Char] ()' arising from a use of 'singleton'
-- instance 'FunDep [a] a'
illTyped :: [Char]
illTyped = singleton ()
-- but this one is not:
-- Couldn't match type '()' with 'Char'
-- arising from a functional dependency between constraints:
-- 'FunDep [Char] Char' arising from a use of 'singleton' (in
'wellTyped')
-- 'FunDep [Char] ()' arising from a use of 'singleton' (in
'illTyped')
wellTyped :: [Char]
wellTyped = singleton 'a'
}}}
The spurious error disappears if `illTyped` is commented out or moved
after `wellTyped`.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13506>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list