[GHC] #11298: Implicit call stack empty in instance declarations

#11298: Implicit call stack empty in instance declarations -------------------------------------+------------------------------------- Reporter: pikajude | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Incorrect result Unknown/Multiple | at runtime Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Given the following code: {{{#!hs {-# LANGUAGE ImplicitParams #-} import GHC.Stack class Foo a where foo :: a -> String main = putStrLn $ foo () }}} In GHC 7.11.20151216, the following instances result in no output: {{{#!hs instance Foo () where foo () = prettyCallStack ?loc }}} {{{#!hs fooHelper = prettyCallStack ?loc instance Foo () where foo () = fooHelper }}} Though this one does: {{{#!hs fooHelper () = prettyCallStack ?loc instance Foo () where foo = fooHelper }}} The aforementioned instances all yield output with GHC 7.10.3 (after replacing `prettyCallStack` with `showCallStack`). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11298 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11298: Implicit call stack empty in instance declarations -------------------------------------+------------------------------------- Reporter: pikajude | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by pikajude: Old description:
Given the following code:
{{{#!hs {-# LANGUAGE ImplicitParams #-}
import GHC.Stack
class Foo a where foo :: a -> String
main = putStrLn $ foo () }}}
In GHC 7.11.20151216, the following instances result in no output:
{{{#!hs instance Foo () where foo () = prettyCallStack ?loc }}}
{{{#!hs fooHelper = prettyCallStack ?loc
instance Foo () where foo () = fooHelper }}}
Though this one does:
{{{#!hs fooHelper () = prettyCallStack ?loc
instance Foo () where foo = fooHelper }}}
The aforementioned instances all yield output with GHC 7.10.3 (after replacing `prettyCallStack` with `showCallStack`).
New description: Given the following code: {{{#!hs {-# LANGUAGE ImplicitParams #-} import GHC.Stack class Foo a where foo :: a -> String main = putStrLn $ foo () }}} In GHC 7.11.20151216, the following instances result in no output: {{{#!hs instance Foo () where foo () = prettyCallStack ?loc }}} {{{#!hs fooHelper = prettyCallStack ?loc instance Foo () where foo () = fooHelper }}} Though this one does: {{{#!hs fooHelper () = prettyCallStack ?loc instance Foo () where foo = fooHelper }}} Including explicit signatures with `-XInstanceSigs` has no effect. The aforementioned instances all yield output with GHC 7.10.3 (after replacing `prettyCallStack` with `showCallStack`). -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11298#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11298: Implicit call stack empty in instance declarations -------------------------------------+------------------------------------- Reporter: pikajude | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by pikajude: Old description:
Given the following code:
{{{#!hs {-# LANGUAGE ImplicitParams #-}
import GHC.Stack
class Foo a where foo :: a -> String
main = putStrLn $ foo () }}}
In GHC 7.11.20151216, the following instances result in no output:
{{{#!hs instance Foo () where foo () = prettyCallStack ?loc }}}
{{{#!hs fooHelper = prettyCallStack ?loc
instance Foo () where foo () = fooHelper }}}
Though this one does:
{{{#!hs fooHelper () = prettyCallStack ?loc
instance Foo () where foo = fooHelper }}}
Including explicit signatures with `-XInstanceSigs` has no effect.
The aforementioned instances all yield output with GHC 7.10.3 (after replacing `prettyCallStack` with `showCallStack`).
New description: Given the following code: {{{#!hs {-# LANGUAGE ImplicitParams #-} import GHC.Stack class Foo a where foo :: a -> String main = putStrLn $ foo () }}} In GHC 7.11.20151216, the following instances result in no output: {{{#!hs instance Foo () where foo () = prettyCallStack ?loc }}} {{{#!hs fooHelper = prettyCallStack ?loc instance Foo () where foo () = fooHelper }}} Though this one does: {{{#!hs fooHelper () = prettyCallStack ?loc instance Foo () where foo = fooHelper }}} Including explicit signatures with `-XInstanceSigs` has no effect. The aforementioned instances all yield output with GHC 7.10.3 (after replacing `prettyCallStack` with `showCallStack`): {{{ ?loc, called at implicit.hs:9:28 in main:Main }}} -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11298#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11298: Implicit call stack empty in instance declarations -------------------------------------+------------------------------------- Reporter: pikajude | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by pikajude: Old description:
Given the following code:
{{{#!hs {-# LANGUAGE ImplicitParams #-}
import GHC.Stack
class Foo a where foo :: a -> String
main = putStrLn $ foo () }}}
In GHC 7.11.20151216, the following instances result in no output:
{{{#!hs instance Foo () where foo () = prettyCallStack ?loc }}}
{{{#!hs fooHelper = prettyCallStack ?loc
instance Foo () where foo () = fooHelper }}}
Though this one does:
{{{#!hs fooHelper () = prettyCallStack ?loc
instance Foo () where foo = fooHelper }}}
Including explicit signatures with `-XInstanceSigs` has no effect.
The aforementioned instances all yield output with GHC 7.10.3 (after replacing `prettyCallStack` with `showCallStack`):
{{{ ?loc, called at implicit.hs:9:28 in main:Main }}}
New description: Given the following code: {{{#!hs {-# LANGUAGE ImplicitParams #-} import GHC.Stack class Foo a where foo :: a -> String main = putStrLn $ foo () }}} In GHC 7.11.20151216, the following instances result in no output: {{{#!hs instance Foo () where foo () = prettyCallStack ?loc }}} {{{#!hs fooHelper = prettyCallStack ?loc instance Foo () where foo () = fooHelper }}} Though this one does: {{{#!hs fooHelper () = prettyCallStack ?loc instance Foo () where foo = fooHelper {- CallStack (from ImplicitParams): fooHelper, called at implicit.hs:11:11 in main:Main -} }}} Including explicit signatures with `-XInstanceSigs` has no effect. The aforementioned instances all yield output with GHC 7.10.3 (after replacing `prettyCallStack` with `showCallStack`): {{{ ?loc, called at implicit.hs:9:28 in main:Main }}} -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11298#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11298: Implicit call stack empty in instance declarations -------------------------------------+------------------------------------- Reporter: pikajude | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * cc: gridaphobe (added) * milestone: => 8.0.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11298#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11298: Implicit call stack empty in instance declarations -------------------------------------+------------------------------------- Reporter: pikajude | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by gridaphobe): There are two things going on here. 1. We intentionally changed the meaning of a bare `?loc :: CallStack` in 8.0 to not include its own location, only function calls are appended to the stack now. So the first example is expected behavior in 8.0. 2. In your second example, GHC infers a CallStack parameter for fooHelper, thus it's occurrence in the instance declaration is appended to the stack. Why does GHC infer a CallStack for the 2nd fooHelper and not the 1st? Because the monomorphism restriction applies in the 1st declaration and prevents GHC from inferring a qualified type for fooHelper. So both cases are expected given the current implementation, but the difference is a bit annoying. The new implementation of the CallStack solver that allows GHC to infer CallStack parameters is essential to fix a terrible bug in the 7.10.2 solver, but it might make sense to prevent inferring CallStacks for top- level binders. I didn't do this originally since it would add another special case to the solver, and I don't want to do that without good reason. I'm not sure whether this qualifies, it's just another case of the monomorphism restriction. On the other hand, in this case we get different runtime behavior instead of an ambiguous type error, and this is definitely worse.. Thanks! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11298#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11298: Implicit call stack empty in instance declarations -------------------------------------+------------------------------------- Reporter: pikajude | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Is the user manual section about implicit call-stacks up to date? Does it mention that a bare `?loc::CallStack` makes an empty stack? Does it give the functions that work on call-stacks? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11298#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11298: Implicit call stack empty in instance declarations -------------------------------------+------------------------------------- Reporter: pikajude | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by gridaphobe): I updated the user guide as part of the rewrite, the current version is hosted [http://downloads.haskell.org/~ghc/master/users- guide//glasgow_exts.html#implicit-callstacks here]. It does mention that a bare `?loc :: CallStack` will be resolved to the empty stack ("GHC will never report an unbound implicit CallStack, and will instead default such occurrences to the empty CallStack.") It also describes `getCallStack` for extracting the list of call-sites, and `freezeCallStack` for preventing the addition of further call-sites. There are a couple other API functions (`push` and `pop`) that are only mentioned in the haddocks, but I think that's ok as they're pretty self- explanatory. Ack, I just noticed that the formatting is a bit screwy towards the end of the section, I'll send a patch to clean it up. If you have any comments/suggestions on the content itself I'd be happy to incorporate them. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11298#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11298: Implicit call stack empty in instance declarations -------------------------------------+------------------------------------- Reporter: pikajude | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed Comment: All of this has been merged. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11298#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11298: Implicit call stack empty in instance declarations -------------------------------------+------------------------------------- Reporter: pikajude | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by gridaphobe): FYI, we removed the inference of CallStacks so the resolution is that all of these examples should produce an empty CallStack. Adding an explicit signature, eg {{{ fooHelper :: ?loc :: CallStack => String fooHelper = prettyCallStack ?loc instance Foo () where foo () = fooHelper }}} will produce a singleton CallStack with the call-site of `fooHelper` inside `foo`. (Also, we're hiding the Implicit Parameter now and may move to a custom CallStack constraint in the future, so I'd suggest using the new `HasCallStack` synonym) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11298#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11298: Implicit call stack empty in instance declarations -------------------------------------+------------------------------------- Reporter: pikajude | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by saurabhnanda): * cc: saurabhnanda (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11298#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC