[GHC] #8739: ($) returning kind # no longer type checks

#8739: ($) returning kind # no longer type checks ------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.1-rc1 Keywords: | Operating System: Unknown/Multiple Architecture: Unknown/Multiple | Type of failure: None/Unknown Difficulty: Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | ------------------------------------+------------------------------------- Given: {{{ {-# LANGUAGE MagicHash #-} module InnerLoop(go) where import GHC.Exts go :: () -> Int# go () = go $ () }}} This type checks fine on GHC 7.2.3, and I have a similar version that works fine with 7.4 and 7.6. However, with GHC 7.8.20140130, I get: {{{ InnerLoop.hs:5:9: Kind incompatibility when matching types: s0 :: * Int# :: # In the expression: go $ () In an equation for `go': go () = go $ () }}} This code was reduced from [http://neilmitchell.blogspot.co.uk/2014/01 /optimising-haskell-for-tight-inner-loop.html this blog post], and code which triggers a similar bug can be [https://github.com/ndmitchell/shake/issues/94 found in Shake]. I know {{{$}}} has special type checking rules, were they removed or changed? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8739 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8739: ($) returning kind # no longer type checks -------------------------------------+------------------------------------ Reporter: NeilMitchell | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Changes (by jwlato): * cc: jwlato@… (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8739#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8739: ($) returning kind # no longer type checks -------------------------------------+------------------------------------ Reporter: NeilMitchell | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Changes (by nh2): * cc: mail@… (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8739#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8739: ($) returning kind # no longer type checks -------------------------------------+------------------------------------ Reporter: NeilMitchell | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Changes (by slyfox): * cc: slyfox@… (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8739#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8739: ($) returning kind # no longer type checks -------------------------------------+------------------------------------ Reporter: NeilMitchell | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: 7.8.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Changes (by thoughtpolice): * milestone: => 7.8.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8739#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8739: ($) returning kind # no longer type checks -------------------------------------+------------------------------------ Reporter: NeilMitchell | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: 7.8.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Changes (by goldfire): * status: new => infoneeded Comment: The fact that this code worked in <= 7.2 is a bug: #5570. I was unable to get the example above to compile on 7.4.2 or 7.6.3. Do you have an example that works with these versions but fails with 7.8? And, yes, the fix to #5570 did change the typing rules for `($)`, but seemingly in a good way. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8739#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8739: ($) returning kind # no longer type checks -------------------------------------+------------------------------------ Reporter: NeilMitchell | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: 7.8.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by simonpj): It's absolutely right that the second argument to `($)` must not have an unboxed kind. Because the code for `($)` must move that argument around (pass to the function), so it must know its width, pointerhood ect. But actually it would be ok for the ''result'' of the call `(f $ x)` to be unboxed, because the code for `($)` doesn't mess with the result; it just tail-calls `f`. It's a bit like the call `(error "foo")` which is allowed to have an unboxed type. So `error` has a rather magical type {{{ error :: forall (a:OpenKind). String -> a }}} where the funny quantifier `a:OpenKind` allows `a` to be instantiated to `Int#` as well as to `Int`. So we could regard `($)` as having the type {{{ ($) :: forall (a:*) (r:OpenKind). (a->r) -> a -> r }}} reflecting the fact that the result kind can range over unboxed types. Unless I'm being stupid here, the fix is simple in `TcExpr`, lines 329-ish: * Remove `b_ty <- newPolyFlexiTyVarTy` * Remove the `unifyType op_res_ty b_ty` * Replace the other reference to `b_ty` with `op_res_ty` Would someone like to try? Of course this deserves an elaboration of `Note [Typing rule for ($)]`, and a reference to this ticket. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8739#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8739: ($) returning kind # no longer type checks
-------------------------------------+------------------------------------
Reporter: NeilMitchell | Owner:
Type: bug | Status: infoneeded
Priority: normal | Milestone: 7.8.1
Component: Compiler | Version: 7.8.1-rc1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture: Unknown/Multiple
Type of failure: None/Unknown | Difficulty: Unknown
Test Case: | Blocked By:
Blocking: | Related Tickets:
-------------------------------------+------------------------------------
Comment (by Simon Peyton Jones

#8739: ($) returning kind # no longer type checks -----------------------------------------------+--------------------------- Reporter: NeilMitchell | Owner: Type: bug | Status: merge Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: Resolution: | 7.8.1-rc1 Operating System: Unknown/Multiple | Keywords: Type of failure: None/Unknown | Architecture: Test Case: typecheck/should_run/T8739 | Unknown/Multiple Blocking: | Difficulty: Unknown | Blocked By: | Related Tickets: -----------------------------------------------+--------------------------- Changes (by simonpj): * status: infoneeded => merge * testcase: => typecheck/should_run/T8739 Comment: OK I've done this. Since `($)` has a special typing rule anyway, it may as well be very special! Simon PS: Although 7.2 allowed it, if you used `-dcore-lint` it was rejected. I've fixed that too. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8739#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8739: ($) returning kind # no longer type checks -----------------------------------------------+--------------------------- Reporter: NeilMitchell | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: Resolution: fixed | 7.8.1-rc1 Operating System: Unknown/Multiple | Keywords: Type of failure: None/Unknown | Architecture: Test Case: typecheck/should_run/T8739 | Unknown/Multiple Blocking: | Difficulty: Unknown | Blocked By: | Related Tickets: -----------------------------------------------+--------------------------- Changes (by thoughtpolice): * status: merge => closed * resolution: => fixed Comment: Merged. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8739#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC