[GHC] #11220: Stack overflow instead of type check failure in Servant route

#11220: Stack overflow instead of type check failure in Servant route -------------------------------------+------------------------------------- Reporter: sopvop | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 (Type checker) | 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: -------------------------------------+------------------------------------- GHC 7.10.3 eats a lot of memory and segfaults compiling this. {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE EmptyDataDecls #-} {-# LANGUAGE TypeOperators #-} module Main where import Data.Proxy import Servant.API -- requires servant data A apiP :: Proxy Api apiP = Proxy -- Users type Api = "variants" :> Get '[JSON] () routeL :: URI routeL = safeLink apiP (Proxy :: Proxy ("variants" :> Get '[A] ())) -- Should result in type error -- '[JSON] in route but '[A] here main = print routeL }}} There is '[ JSON ] in Api type, but '[A] in Proxy type passed to safeLink, so it should result in type error. Correct program compiles without problems. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11220 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11220: Stack overflow instead of type check failure in Servant route -------------------------------------+------------------------------------- Reporter: sopvop | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler (Type | Version: 7.10.3 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * priority: normal => high * failure: None/Unknown => Compile-time crash * milestone: => 8.0.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11220#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11220: Stack overflow instead of type check failure in Servant route -------------------------------------+------------------------------------- Reporter: sopvop | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler (Type | Version: 7.10.3 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): On GHC 8.0 this fails with, {{{ $ ghc Hi.hs [1 of 1] Compiling SmAssetMan.Routes ( Hi.hs, Hi.o ) Hi.hs:40:22: error: • Reduction stack overflow; size = 201 When simplifying the following type: Servant.Utils.Links.And (Servant.Utils.Links.IsSubList '[HALJSON] '[]) (Servant.Utils.Links.IsSubList '[] '[]) Use -freduction-depth=0 to disable this check (any upper bound you could choose might fail unpredictably with minor updates to GHC, so disabling the check is recommended if you're sure that type checking should terminate) • In the expression: safeLink apiP (Proxy :: Proxy ("projects" :> (Capture "project_id" ProjectId :> ("variants" :> Get Mimes ())))) In an equation for ‘variantsByProjectL’: variantsByProjectL = safeLink apiP (Proxy :: Proxy ("projects" :> (Capture "project_id" ProjectId :> ("variants" :> Get Mimes ())))) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11220#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11220: Stack overflow instead of type check failure in Servant route -------------------------------------+------------------------------------- Reporter: sopvop | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler (Type | Version: 7.10.3 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * cc: goldfire (added) Old description:
GHC 7.10.3 eats a lot of memory and segfaults compiling this.
{{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE EmptyDataDecls #-} {-# LANGUAGE TypeOperators #-} module Main where
import Data.Proxy
import Servant.API -- requires servant
data A
apiP :: Proxy Api apiP = Proxy
-- Users
type Api = "variants" :> Get '[JSON] ()
routeL :: URI routeL = safeLink apiP (Proxy :: Proxy ("variants" :> Get '[A] ())) -- Should result in type error -- '[JSON] in route but '[A] here
main = print routeL
}}}
There is '[ JSON ] in Api type, but '[A] in Proxy type passed to safeLink, so it should result in type error.
Correct program compiles without problems.
New description: GHC 7.10.3 eats a lot of memory and segfaults compiling this. {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE EmptyDataDecls #-} {-# LANGUAGE TypeOperators #-} module Main where import Data.Proxy import Servant.API -- requires servant data A apiP :: Proxy Api apiP = Proxy -- Users type Api = "variants" :> Get '[JSON] () routeL :: URI routeL = safeLink apiP (Proxy :: Proxy ("variants" :> Get '[A] ())) -- Should result in type error -- '[JSON] in route but '[A] here main = print routeL }}} There is `'[ JSON ]` in `Api` type, but `'[A]` in `Proxy` type passed to `safeLink`, so it should result in type error. Correct program compiles without problems. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11220#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11220: Stack overflow instead of type check failure in Servant route -------------------------------------+------------------------------------- Reporter: sopvop | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler (Type | Version: 7.10.3 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by sopvop): #10806 may be related, but is marked as fixed in master -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11220#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11220: Stack overflow instead of type check failure in Servant route -------------------------------------+------------------------------------- Reporter: sopvop | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler (Type | Version: 7.10.3 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): The new error is actually somewhat informative. I don't have the definitions of `IsSubList` and `And` to hand (though they're easy to imagine). Could they loop? If they are the simple definitions I imagine, this is indeed a GHC bug. If they reasonably can loop, on the other hand, then this error message might be acceptable. Need feedback from the original poster, and a test case that doesn't depend on all of `servant` would be great. (Just inline the definitions into this module?) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11220#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11220: Stack overflow instead of type check failure in Servant route -------------------------------------+------------------------------------- Reporter: sopvop | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler (Type | Version: 7.10.3 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by sopvop): * Attachment "Main.hs" added. With relevant parts of servant inlined. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11220 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11220: Stack overflow instead of type check failure in Servant route -------------------------------------+------------------------------------- Reporter: sopvop | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler (Type | Version: 7.10.3 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): You have this definition: {{{ type family IsSubList a b :: Constraint where IsSubList '[] b = () IsSubList '[x] (x ': xs) = () IsSubList '[x] (y ': ys) = IsSubList '[x] ys IsSubList (x ': xs) y = IsSubList '[x] y `And` IsSubList xs y }}} But `IsSubList '[Int] '[]` loops by triggering the fourth equation (and being apart from all previous ones). Note that the left conjunct of the `And` is the exact same thing that we started with. So I think GHC's behavior here is quite reasonable. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11220#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11220: Stack overflow instead of type check failure in Servant route -------------------------------------+------------------------------------- Reporter: sopvop | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler (Type | Version: 7.10.3 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by sopvop): I'll report this to servant devs then. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11220#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11220: Stack overflow instead of type check failure in Servant route -------------------------------------+------------------------------------- Reporter: sopvop | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.0.1 Component: Compiler (Type | Version: 7.10.3 checker) | Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * status: new => closed * resolution: => invalid Comment: OK. I'm closing this as invalid. Do reopen if you disagree. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11220#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC