[GHC] #16115: Missing associated type instance not reported with error

#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

#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 (Type | Version: 8.6.3 checker) | Resolution: | 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: | -------------------------------------+------------------------------------- Comment (by simonpj): Yes, that's true. But it's generally reasonable for errors to suppress warnings. And the error isn't too bad. The user thinks "Why doesn't `Item Nat` equal `()`? Oh, I'd better look in `instance FromList Nat`, since `Item` is an associate type of `FromList`; and sure enough there is no `type instance`. So it's not too bad. If we wanted to change, I can imagine various things we could do: * Never suppress warnings, even if there are errors. * Make it compulsory to give an instance for an associated type, if there is no default in the class. That'd be a language change. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16115#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 (Type | Version: 8.6.3 checker) | Resolution: | 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: | -------------------------------------+------------------------------------- Comment (by dfeuer): I think there's a much more conservative option that would be much better. When we come down to wanting `Item Nat ~ ()`, the type checker ''knows'' that `Item Nat` is a stuck type, and it ''knows'' that `()` is not the same stuck type. So the problem can immediately be narrowed down to {{{ Could not match expected type `Item Nat' with actual type `()'. The type family application `Item Nat' is stuck. [etc.] }}} We presumably ''also'' know that `Item` is an associated type of `FromList`, so we should be able to do a bit better, incorporating the information from the suppressed warning: {{{ Could not match expected type `Item Nat' with actual type `()'. No explicit associated type or default declaration for ‘Item’ in the instance declaration for ‘FromList Nat’ [etc.] }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16115#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC