[GHC] #16115: Missing associated type instance not reported with error
GHC
ghc-devs at haskell.org
Mon Dec 31 16:24:32 UTC 2018
#16115: Missing associated type instance not reported with error
-------------------------------------+-------------------------------------
Reporter: dfeuer | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.10.1
Component: Compiler | Version: 8.6.3
(Type checker) |
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: Poor/confusing
Unknown/Multiple | error message
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
I noticed [https://stackoverflow.com/questions/53987924/haskell-couldnt-
match-expected-type-item-nat-with-actual-type this SO question] was caused
by a warning disappearing as a result of the error it caused.
{{{#!hs
{-# language TypeFamilies, DataKinds #-}
module NoWarning where
data Nat = Zero | Succ Nat deriving Show
class FromList a where
type Item a :: *
fromList :: [Item a] -> a
instance FromList Nat where
fromList [] = Zero
fromList (a:as) = Succ (fromList as :: Nat)
fish :: Nat
fish = fromList [(),(),()]
}}}
If you delete `fish`, you get a nice warning:
{{{
NoWarning.hs:8:1: warning: [-Wmissing-methods]
• No explicit associated type or default declaration for ‘Item’
• In the instance declaration for ‘FromList Nat’
|
8 | instance FromList Nat where
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^...
}}}
But with `fish`, all you get is
{{{
NoWarning.hs:13:18: error:
• Couldn't match expected type ‘Item Nat’ with actual type ‘()’
• In the expression: ()
In the first argument of ‘fromList’, namely ‘[(), (), ()]’
In the expression: fromList [(), (), ()]
|
13 | fish = fromList [(),(),()]
|
}}}
That warning is the proper explanation of the problem, and it's just
missing!
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/16115>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list