[GHC] #11438: Code does not compile without ScopedTypeVariables

#11438: Code does not compile without ScopedTypeVariables -------------------------------------+------------------------------------- Reporter: wereHamster | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 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: -------------------------------------+------------------------------------- Feel free to change the summary, I have no idea how to summarize this issue. The code below fails to compile with `Couldn't match type A with B` and `The function X is applied to one argument, but its type Y has none` and some more (full output is attached below the code). However, simply enabling a language feature (`ScopedTypeVariable`) makes the code compile. If this is not a bug in the compiler then the message should be improved, because nothing in it points to the solution. I always thought of ScopedTypeVariables as allowing me to sprinkle `:: T` throughout the code, in more places than GHC would normally allow. I did not expect that merely enabling this language feature without any other changes in the source code would have any effect on the output. Dependencies: servant, servant-server {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE TypeOperators #-} -- {-# LANGUAGE ScopedTypeVariables #-} module Main where import Data.Proxy import Servant.API import Servant.Server data Credentials = Credential !String instance (HasServer sublayout) => HasServer (Credentials :> sublayout) where type ServerT (Credentials :> sublayout) m = Credentials -> ServerT sublayout m route Proxy subserver request respond = do let mbSessionIdString = lookup "cookie" [("cookie", "session id")] mbCredentials = fmap Credential mbSessionIdString case mbCredentials of Nothing -> error "No credentials supplied" Just cred -> route (Proxy :: Proxy sublayout) (subserver cred) request respond }}} {{{ [1 of 1] Compiling Main ( Bug.hs, interpreted ) Bug.hs:30:60: Couldn't match type ‘ServerT sublayout (either-4.4.1:Control.Monad.Trans.Either.EitherT ServantErr IO)’ with ‘ServerT layout0 (either-4.4.1:Control.Monad.Trans.Either.EitherT ServantErr IO)’ NB: ‘ServerT’ is a type function, and may not be injective The type variable ‘layout0’ is ambiguous Expected type: Credentials -> Server layout0 Actual type: ServerT (Credentials :> sublayout) (either-4.4.1:Control.Monad.Trans.Either.EitherT ServantErr IO) Relevant bindings include subserver :: Server (Credentials :> sublayout) (bound at Bug.hs:24:17) route :: Proxy (Credentials :> sublayout) -> Server (Credentials :> sublayout) -> Servant.Server.Internal.RoutingApplication (bound at Bug.hs:24:5) The function ‘subserver’ is applied to one argument, but its type ‘Server (Credentials :> sublayout)’ has none In the second argument of ‘route’, namely ‘(subserver cred)’ In the expression: route (Proxy :: Proxy sublayout) (subserver cred) request respond Failed, modules loaded: none. }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11438 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11438: Code does not compile without ScopedTypeVariables -------------------------------------+------------------------------------- Reporter: wereHamster | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): This is not a bug, but we could do much better in suggesting `ScopedTypeVariables`. The reason that the change makes a difference is that you refer to the type variable `sublayout` from within a method definition in your instance. You need `ScopedTypeVariables` to bring the instance's type variables into scope. An easy way of suggesting `ScopedTypeVariables` just came to mind: pretend the extension is always on. When looking up a type variable, if the extension is off but the variable would be in scope otherwise, suggest the extension, while returning a lookup failure (because the variable really isn't in scope!). Getting caught on `ScopedTypeVariables` is a fairly common occurrence in my experience, so I think it's worth putting in a bit of effort to do better here. (Even better would be to look for type variables in a signature that's missing a `forall` to suggest adding the `forall`, but that can be a separate task.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11438#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11438: Code does not compile without ScopedTypeVariables -------------------------------------+------------------------------------- Reporter: wereHamster | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): We should also mention in the users guide the fact that type variables in an instance head are brought into scope. [[http://downloads.haskell.org/~ghc/master/users- guide//glasgow_exts.html?highlight=scoped%20type%20variables#ghc-flag-- XScopedTypeVariables|Currently]] the text suggests that only variables introduced with an explicit `forall` are brought into scope. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11438#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11438: Code does not compile without ScopedTypeVariables -------------------------------------+------------------------------------- Reporter: wereHamster | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Oh, never mind, you just need to read farther than the first two paragraphs of the section. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11438#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11438: Code does not compile without ScopedTypeVariables -------------------------------------+------------------------------------- Reporter: wereHamster | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #1316, #9244, | Differential Rev(s): #3691 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => duplicate * related: => #1316, #9244, #3691 Comment: goldfire, hold that thought, but also subscribe to #9244. I'm closing this as a duplicate, so we can keep discussion in one place. #9244 has a nice test case (without dependencies), and some other suggestions for a better error message. wereHamster: thanks for reporting! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11438#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC