[GHC] #11753: Type hole(?) causes compiler failure

#11753: Type hole(?) causes compiler failure -------------------------------------+------------------------------------- Reporter: akfp | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Keywords: | Operating System: Linux Architecture: x86_64 | Type of failure: Compile-time (amd64) | crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I tried to understand soem Servant code, and added {{{#!hs bodyCheck :: _ }}} To the following code {{{#!hs -# LANGUAGE DataKinds #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} module Servant.Files ( FilesTmp , FilesMem , MultiPartData , MultiPartDataT , Tmp , Mem ) where import Control.Monad.Trans.Resource import Data.ByteString.Lazy (ByteString) import Network.Wai.Parse import Servant import Servant.Server.Internal -- Backends for file upload: in memory or in /tmp ? data Mem data Tmp class KnownBackend b where type Storage b :: * withBackend :: Proxy b -> (BackEnd (Storage b) -> IO r) -> IO r instance KnownBackend Mem where type Storage Mem = ByteString withBackend Proxy f = f lbsBackEnd instance KnownBackend Tmp where type Storage Tmp = FilePath withBackend Proxy f = runResourceT . withInternalState $ \s -> f (tempFileBackEnd s) -- * Files combinator, to get all of the uploaded files data Files b type MultiPartData b = ([Param], [File (Storage b)]) type MultiPartDataT b = ((MultiPartData b -> IO (MultiPartData b)) -> IO (MultiPartData b)) type FilesMem = Files Mem type FilesTmp = Files Tmp instance (KnownBackend b, HasServer sublayout config) => HasServer (Files b :> sublayout) config where type ServerT (Files b :> sublayout) m = MultiPartDataT b -> ServerT sublayout m route Proxy config subserver = WithRequest $ \request -> route (Proxy :: Proxy sublayout) config (addBodyCheck subserver (bodyCheck request)) where bodyCheck :: _ bodyCheck request = return $ Route (\f -> withBackend (Proxy :: Proxy b) $ \pb -> parseRequestBody pb request >>= f ) }}} Output: {{{
:load src/Servant/Test.hs [1 of 1] Compiling Servant.Files ( src/Servant/Test.hs, interpreted )
src/Servant/Test.hs:59:59: Couldn't match type ‘r’ with ‘([Param], [File (Storage b)])’ because type variable ‘b’ would escape its scope This (rigid, skolem) type variable is bound by the instance declaration at src/Servant/Test.hs:(53,10)-(54,80) Expected type: Delayed (((([Param], [File (Storage b)]) -> IO r) -> IO r) -> Server sublayout) Actual type: Delayed (Server (Files b :> sublayout)) Relevant bindings include bodyCheck :: Network.Wai.Internal.Request -> m (RouteResult ((([Param], [File (Storage b)]) -> IO r) -> IO r)) (bound at src/Servant/Test.hs:62:7) subserver :: Delayed (Server (Files b :> sublayout)) (bound at src/Servant/Test.hs:58:22) route :: Proxy (Files b :> sublayout) -> Context config -> Delayed (Server (Files b :> sublayout)) -> Router (bound at src/Servant/Test.hs:58:3) In the first argument of ‘addBodyCheck’, namely ‘subserver’ In the third argument of ‘route’, namely ‘(addBodyCheck subserver (bodyCheck request))’ src/Servant/Test.hs:59:70: Couldn't match type ‘m’ with ‘IO’ ‘m’ is untouchable inside the constraints (KnownBackend b, HasServer sublayout config) bound by the instance declaration at src/Servant/Test.hs:(53,10)-(54,80)ghc: panic! (the 'impossible' happened) (GHC version 7.10.3 for x86_64-unknown-linux): No skolem info: m_a5An[sk] Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11753 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11753: Type hole(?) causes compiler failure -------------------------------------+------------------------------------- Reporter: akfp | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by akfp: @@ -1,1 +1,1 @@ - I tried to understand soem Servant code, and added + I tried to understand some Servant code, and added @@ -10,1 +10,1 @@ - -# LANGUAGE DataKinds #-} + {-# LANGUAGE DataKinds #-} New description: I tried to understand some Servant code, and added {{{#!hs bodyCheck :: _ }}} To the following code {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} module Servant.Files ( FilesTmp , FilesMem , MultiPartData , MultiPartDataT , Tmp , Mem ) where import Control.Monad.Trans.Resource import Data.ByteString.Lazy (ByteString) import Network.Wai.Parse import Servant import Servant.Server.Internal -- Backends for file upload: in memory or in /tmp ? data Mem data Tmp class KnownBackend b where type Storage b :: * withBackend :: Proxy b -> (BackEnd (Storage b) -> IO r) -> IO r instance KnownBackend Mem where type Storage Mem = ByteString withBackend Proxy f = f lbsBackEnd instance KnownBackend Tmp where type Storage Tmp = FilePath withBackend Proxy f = runResourceT . withInternalState $ \s -> f (tempFileBackEnd s) -- * Files combinator, to get all of the uploaded files data Files b type MultiPartData b = ([Param], [File (Storage b)]) type MultiPartDataT b = ((MultiPartData b -> IO (MultiPartData b)) -> IO (MultiPartData b)) type FilesMem = Files Mem type FilesTmp = Files Tmp instance (KnownBackend b, HasServer sublayout config) => HasServer (Files b :> sublayout) config where type ServerT (Files b :> sublayout) m = MultiPartDataT b -> ServerT sublayout m route Proxy config subserver = WithRequest $ \request -> route (Proxy :: Proxy sublayout) config (addBodyCheck subserver (bodyCheck request)) where bodyCheck :: _ bodyCheck request = return $ Route (\f -> withBackend (Proxy :: Proxy b) $ \pb -> parseRequestBody pb request >>= f ) }}} Output: {{{
:load src/Servant/Test.hs [1 of 1] Compiling Servant.Files ( src/Servant/Test.hs, interpreted )
src/Servant/Test.hs:59:59: Couldn't match type ‘r’ with ‘([Param], [File (Storage b)])’ because type variable ‘b’ would escape its scope This (rigid, skolem) type variable is bound by the instance declaration at src/Servant/Test.hs:(53,10)-(54,80) Expected type: Delayed (((([Param], [File (Storage b)]) -> IO r) -> IO r) -> Server sublayout) Actual type: Delayed (Server (Files b :> sublayout)) Relevant bindings include bodyCheck :: Network.Wai.Internal.Request -> m (RouteResult ((([Param], [File (Storage b)]) -> IO r) -> IO r)) (bound at src/Servant/Test.hs:62:7) subserver :: Delayed (Server (Files b :> sublayout)) (bound at src/Servant/Test.hs:58:22) route :: Proxy (Files b :> sublayout) -> Context config -> Delayed (Server (Files b :> sublayout)) -> Router (bound at src/Servant/Test.hs:58:3) In the first argument of ‘addBodyCheck’, namely ‘subserver’ In the third argument of ‘route’, namely ‘(addBodyCheck subserver (bodyCheck request))’ src/Servant/Test.hs:59:70: Couldn't match type ‘m’ with ‘IO’ ‘m’ is untouchable inside the constraints (KnownBackend b, HasServer sublayout config) bound by the instance declaration at src/Servant/Test.hs:(53,10)-(54,80)ghc: panic! (the 'impossible' happened) (GHC version 7.10.3 for x86_64-unknown-linux): No skolem info: m_a5An[sk] Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11753#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11753: Type hole(?) causes compiler failure -------------------------------------+------------------------------------- Reporter: akfp | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: duplicate | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * status: new => closed * resolution: => duplicate Comment: This will be fixed in the next release. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11753#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11753: Type hole(?) causes compiler failure -------------------------------------+------------------------------------- Reporter: akfp | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: duplicate | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): What's it a duplicate of? Are you saying that you've tested with the 8.0 release candidate and it's fine there? If so, great, thanks. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11753#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11753: Type hole(?) causes compiler failure -------------------------------------+------------------------------------- Reporter: akfp | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: duplicate | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: #11059 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * related: => #11059 Comment: #11059 and quite a few others. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11753#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11753: Type hole(?) causes compiler failure -------------------------------------+------------------------------------- Reporter: akfp | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: duplicate | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: #11059 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): I have managed to test it now and it is indeed fixed. {{{ [1 of 1] Compiling Servant.Files ( test.hs, test.o ) test.hs:62:20: error: • Found type wildcard ‘_’ standing for ‘Network.Wai.Internal.Request -> IO (RouteResult ((([Param], [File (Storage b)]) -> IO r) -> IO r))’ Where: ‘r’ is a rigid type variable bound by the inferred type of bodyCheck :: Network.Wai.Internal.Request -> IO (RouteResult ((([Param], [File (Storage b)]) -> IO r) -> IO r)) at test.hs:63:7 ‘b’ is a rigid type variable bound by the instance declaration at test.hs:54:10 To use the inferred type, enable PartialTypeSignatures • In the type signature: bodyCheck :: _ In an equation for ‘route’: route Proxy config subserver = WithRequest $ \ request -> route (Proxy :: Proxy sublayout) config (addBodyCheck subserver (bodyCheck request)) where bodyCheck :: _ bodyCheck request = return $ Route (\ f -> withBackend (Proxy :: Proxy b) $ \ pb -> ...) In the instance declaration for ‘HasServer (Files b :> sublayout) config’ • Relevant bindings include bodyCheck :: Network.Wai.Internal.Request -> IO (RouteResult ((([Param], [File (Storage b)]) -> IO r) -> IO r)) (bound at test.hs:63:7) subserver :: Delayed (Server (Files b :> sublayout)) (bound at test.hs:59:22) config :: Config config (bound at test.hs:59:15) route :: Proxy (Files b :> sublayout) -> Config config -> Delayed (Server (Files b :> sublayout)) -> Router (bound at test.hs:59:3) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11753#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11753: Type hole(?) causes compiler failure -------------------------------------+------------------------------------- Reporter: akfp | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: duplicate | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: #11059 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Terrific thanks. I'm not sure it's worth adding as a regression test, as it's similar to others. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11753#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC