[GHC] #13713: fdefer-type-errors makes missing import errors disappear

#13713: fdefer-type-errors makes missing import errors disappear -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: #12529 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I have this code {{{#!hs {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} import Data.Type.Equality ((:~:)(Refl)) import GHC.TypeLits import qualified Numeric.LinearAlgebra as LA import Numeric.LinearAlgebra.Static toVec :: forall n . (KnownNat n) => LA.Vector Double -> R n toVec vec = withVector vec $ \(v :: R n2) -> case sameNat (Proxy @n) (Proxy @n2) of Just Refl -> v Nothing -> error "wrong dimensions" }}} Notably I forgot to import `Proxy`. Without `-fdefer-type-errors` I get this error: {{{ ➤ nix-shell -p "haskellPackages.ghcWithPackages (pkgs:[pkgs.hmatrix])" --pure --run 'ghci ghc-8.0.2-proxy-confusing-error.hs' GHCi, version 8.0.2: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( ghc-8.0.2-proxy-confusing-error.hs, interpreted ) ghc-8.0.2-proxy-confusing-error.hs:12:60: error: Data constructor not in scope: Proxy ghc-8.0.2-proxy-confusing-error.hs:12:60: error: * Cannot apply expression of type `t1' to a visible type argument `n' * In the first argument of `sameNat', namely `(Proxy @n)' In the expression: sameNat (Proxy @n) (Proxy @n2) In the expression: case sameNat (Proxy @n) (Proxy @n2) of { Just Refl -> v Nothing -> error "wrong dimensions" } Failed, modules loaded: none. }}} but with `-fdefer-type-errors` the `Data constructor not in scope: Proxy` is gone! {{{ ➤ nix-shell -p "haskellPackages.ghcWithPackages (pkgs:[pkgs.hmatrix])" --pure --run 'ghci ghc-8.0.2-proxy-confusing-error.hs -fdefer-type-errors' GHCi, version 8.0.2: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( ghc-8.0.2-proxy-confusing-error.hs, interpreted ) ghc-8.0.2-proxy-confusing-error.hs:12:60: error: * Cannot apply expression of type `t1' to a visible type argument `n' * In the first argument of `sameNat', namely `(Proxy @n)' In the expression: sameNat (Proxy @n) (Proxy @n2) In the expression: case sameNat (Proxy @n) (Proxy @n2) of { Just Refl -> v Nothing -> error "wrong dimensions" } Failed, modules loaded: none. }}} This is probably related to #12529. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13713 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13713: fdefer-type-errors makes missing import errors disappear -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12529 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Simpler example {{{ {-# LANGUAGE TypeApplications #-} module T13713 where toVec = withVector (Proxy @Int) }}} The trouble is this: * The out-of-scope variables become deferred errors, which are reported as warnings * The "Cannot apply..." error is an error that we can't defer, so it stays as an error * When we have errors and warnings we report only the errors. So the out of scope variables are suppressed when (and only when) they are turned into warnings by `-fdefer-type-errors`. I'm not quite sure what to do here. I suppose the errors-that-become- warnings (via the defer mechanism) could somehow be made immune to suppression by errors that don't become warnings. That seems like the most plausible path to me, but someone would need to do it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13713#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13713: fdefer-type-errors makes missing import errors disappear -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12529 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): I seem to recall a conversation about not suppressing warnings when there are errors. I don't know where this was, however. gcc reports warnings alongside errors, for example, and I'd personally prefer to get all diagnostics instead of waiting only until I've fixed all the errors. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13713#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13713: fdefer-type-errors makes missing import errors disappear -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12529 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Yes, it'd also be possible just to stop suppressing warnings when there are errors. What do people think? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13713#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13713: fdefer-type-errors makes missing import errors disappear -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12529 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by vanto): It would seem logical that all the errors are reported if the flag {{{fdefer-type-errors}}} is active and the errors must be mentioned before the warning because they are superior to them without the flag or with the flag.\\ 1 - Show all errors , and after correction\\ 2 - Show warnings If an error can not be deffered, it must be reported first. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13713#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC