[GHC] #8705: Type inference regression with local dictionaries

#8705: Type inference regression with local dictionaries -------------------------------------------+------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type checker) | Version: 7.7 Keywords: | Operating System: Architecture: Unknown/Multiple | Unknown/Multiple Difficulty: Unknown | Type of failure: Blocked By: | None/Unknown Related Tickets: | Test Case: | Blocking: -------------------------------------------+------------------------------- Consider this code: {{{ {-# LANGUAGE ScopedTypeVariables, TypeOperators, DataKinds, MultiParamTypeClasses, GADTs, ConstraintKinds #-} import Data.Singletons.Prelude import GHC.Exts data Dict c where Dict :: c => Dict c -- A less-than-or-equal relation among naturals class a :<=: b sLeq :: Sing n -> Sing n2 -> Dict (n :<=: n2) sLeq = undefined insert_ascending :: forall n lst n1. (lst ~ '[n1]) => Proxy n1 -> Sing n -> SList lst -> Dict (n :<=: n1) insert_ascending _ n lst = case lst of -- If lst has one element... SCons h _ -> case sLeq n h of -- then check if n is <= h Dict -> Dict -- if so, we're done }}} (adapted from [https://github.com/goldfirere/singletons/blob/master/Test/InsertionSortImp.h... this file]) GHC 7.6.3 compiles without incident. When I run HEAD (with `-fprint- explicit-kinds`), I get {{{ Ins.hs:25:17: Could not deduce (n :<=: n1) arising from a use of ‛Dict’ from the context ((~) [*] lst ((':) * n1 ('[] *))) bound by the type signature for insert_ascending :: (~) [*] lst ((':) * n1 ('[] *)) => Proxy * n1 -> Sing * n -> SList * lst -> Dict (n :<=: n1) at Ins.hs:(20,21)-(21,70) or from ((~) [*] lst ((':) * n0 n2)) bound by a pattern with constructor SCons :: forall (a0 :: BOX) (z0 :: [a0]) (n0 :: a0) (n1 :: [a0]). (~) [a0] z0 ((':) a0 n0 n1) => Sing a0 n0 -> Sing [a0] n1 -> Sing [a0] z0, in a case alternative at Ins.hs:24:7-15 or from (n :<=: n0) bound by a pattern with constructor Dict :: forall (c :: Constraint). (c) => Dict c, in a case alternative at Ins.hs:25:9-12 Possible fix: add (n :<=: n1) to the context of the data constructor ‛Dict’ or the data constructor ‛SCons’ or the type signature for insert_ascending :: (~) [*] lst ((':) * n1 ('[] *)) => Proxy * n1 -> Sing * n -> SList * lst -> Dict (n :<=: n1) In the expression: Dict In a case alternative: Dict -> Dict In the expression: case sLeq n h of { Dict -> Dict } }}} If you stare at the type error long enough, you will see that GHC should be able to type-check this. The test case requires singletons-0.9.x, but is already much reduced. Interestingly, if all the "givens" are put in the top-level type signature, GHC does its job well. It seems that the act of unpacking the dictionaries is causing the problem. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8705 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8705: Type inference regression with local dictionaries --------------------------------------------+------------------------------ Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type checker) | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: --------------------------------------------+------------------------------ Changes (by jstolarek): * cc: jan.stolarek@… (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8705#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8705: Type inference regression with local dictionaries --------------------------------------------+------------------------------ Reporter: goldfire | Owner: Type: bug | Status: new Priority: high | Milestone: 7.8.1 Component: Compiler (Type checker) | Version: 7.8.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: --------------------------------------------+------------------------------ Changes (by goldfire): * priority: normal => high * version: 7.7 => 7.8.1-rc1 * milestone: => 7.8.1 Comment: Tweaking settings on the ticket to give it perhaps higher visibility. This bug is a type inference regression that I believe will hit the type system power users and would be embarrassing if we don't fix before the release. I've confirmed that the error happens in 7.8rc1. I haven't put time into looking for the source of the problem, but I think it will be in code I'm not (yet) deeply familiar with. If the release is approaching and this is still around, please ping me and I'll see what I can do. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8705#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8705: Type inference regression with local dictionaries --------------------------------------------+------------------------------ Reporter: goldfire | Owner: Type: bug | Status: new Priority: high | Milestone: 7.8.1 Component: Compiler (Type checker) | Version: 7.8.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: --------------------------------------------+------------------------------ Comment (by simonpj): Just to check, we have three givens: {{{ G1: lst ~ n1 : [] G2: lst ~ n0 : n2 G3: n :<=: n2 }}} From the G1,G2 we find `n1 ~ n0`, and from that and G3 we get `n :<=: n1`, which is what we want to prove. Is that the reasoning? Would it be difficult to drop the dependence on `singletons`, or include the code from there that's needed directly into this module? Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8705#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8705: Type inference regression with local dictionaries --------------------------------------------+------------------------------ Reporter: goldfire | Owner: Type: bug | Status: new Priority: high | Milestone: 7.8.1 Component: Compiler (Type checker) | Version: 7.8.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: --------------------------------------------+------------------------------ Comment (by goldfire): Your text is correct, but your code is not. I believe you meant {{{ G1: lst ~ n1 : [] G2: lst ~ n0 : n2 G3: n :<=: n0 }}} Note the `n0` in the last line. Otherwise, yes, I agree with your comment. I'll try to reduce the case more, yes. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8705#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8705: Type inference regression with local dictionaries --------------------------------------------+------------------------------ Reporter: goldfire | Owner: Type: bug | Status: new Priority: high | Milestone: 7.8.1 Component: Compiler (Type checker) | Version: 7.8.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: --------------------------------------------+------------------------------ Comment (by goldfire): Here is a version without the `singletons` dependency: {{{ {-# LANGUAGE TypeOperators, DataKinds, PolyKinds, MultiParamTypeClasses, GADTs, ConstraintKinds, TypeFamilies #-} module Bug where data family Sing (a :: k) data Proxy a = Proxy data instance Sing (a :: Maybe k) where SJust :: Sing h -> Sing (Just h) data Dict c where Dict :: c => Dict c -- A less-than-or-equal relation among naturals class a :<=: b sLeq :: Sing n -> Sing n2 -> Dict (n :<=: n2) sLeq = undefined insert_ascending :: (lst ~ Just n1) => Proxy n1 -> Sing n -> Sing lst -> Dict (n :<=: n1) insert_ascending _ n (SJust h) = case sLeq n h of Dict -> Dict }}} Interestingly, when I tried getting rid of the data family, the code started compiling. Perhaps there's a problem with normalisation somewhere? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8705#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8705: Type inference regression with local dictionaries --------------------------------------------+------------------------------ Reporter: goldfire | Owner: Type: bug | Status: new Priority: high | Milestone: 7.8.1 Component: Compiler (Type checker) | Version: 7.8.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: --------------------------------------------+------------------------------ Comment (by simonpj): Aha. Got it. Thank you. Patch coming -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8705#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8705: Type inference regression with local dictionaries
--------------------------------------------+------------------------------
Reporter: goldfire | Owner:
Type: bug | Status: new
Priority: high | Milestone: 7.8.1
Component: Compiler (Type checker) | Version: 7.8.1-rc1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: None/Unknown | Unknown/Multiple
Test Case: | Difficulty: Unknown
Blocking: | Blocked By:
| Related Tickets:
--------------------------------------------+------------------------------
Comment (by Simon Peyton Jones

#8705: Type inference regression with local dictionaries --------------------------------------------+------------------------------ Reporter: goldfire | Owner: Type: bug | Status: merge Priority: high | Milestone: 7.8.1 Component: Compiler (Type checker) | Version: 7.8.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Test Case: polykinds/T8705 | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: --------------------------------------------+------------------------------ Changes (by simonpj): * status: new => merge * testcase: => polykinds/T8705 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8705#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8705: Type inference regression with local dictionaries --------------------------------------------+------------------------------ Reporter: goldfire | Owner: Type: bug | Status: closed Priority: high | Milestone: 7.8.1 Component: Compiler (Type checker) | Version: 7.8.1-rc1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Test Case: polykinds/T8705 | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: --------------------------------------------+------------------------------ Changes (by thoughtpolice): * status: merge => closed * resolution: => fixed Comment: Merged. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8705#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC