
#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