[GHC] #14782: typeclass polymorphism defeats bang patterns

#14782: typeclass polymorphism defeats bang patterns -------------------------------------+------------------------------------- Reporter: dmwit | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 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: -------------------------------------+------------------------------------- I think the following program should crash, but it doesn't: {{{ {-# LANGUAGE BangPatterns #-} main = let n :: Num a => a; !n = undefined in return () }}} Interestingly, my attempt to translate this out of BangPatterns into standard Haskell according to the translation on the wiki page led to a compile-time error: {{{ main = let n :: Num a => a; x@n = undefined in x `seq` return () }}} Produces the error: {{{ test.hs:1:12: error: • Overloaded signature conflicts with monomorphism restriction n :: forall a. Num a => a • In the expression: let n :: Num a => a x@n = undefined in x `seq` return () In an equation for ‘main’: main = let n :: Num a => a x@n = undefined in x `seq` return () | 1 | main = let n :: Num a => a; x@n = undefined in x `seq` return () | ^^^^^^^^^^^^^^^ }}} Even giving `x` its own explicitly polymorphic type signature -- what I thought was the standard way to prevent the monomorphism restriction from being a problem -- doesn't help. I'm uncertain what to make of that, but it certainly seems related: earlier versions of the compiler both do not give that error and do produce a crashing program, as I expected. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14782 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14782: typeclass polymorphism defeats bang patterns -------------------------------------+------------------------------------- Reporter: dmwit | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by dmwit): * version: 8.2.1 => 8.2.2 Comment: (dminuoso confirmed that this applies to 8.2.2 as well, so I'm updating the version) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14782#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14782: typeclass polymorphism defeats bang patterns -------------------------------------+------------------------------------- Reporter: dmwit | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => invalid Comment: It is a bit confusing. See [http://downloads.haskell.org/~ghc/master/users- guide/glasgow_exts.html#recursive-and-polymorphic-let-bindings the manual entry for semantics of let bindings] {{{ let n :: Num a => a; !n = undefined in return () means let n :: Num a => a n = undefined in n `seq` return () which, after elaboration of dictionaries etc means let n = /\a. \(d::Num a). undefined in n `seq` return () }}} So the `seq` sees a lambda and does nothing. --------- As to the "conflicts with the MR" message, consider {{{ f :: forall a. Num a => a -> a Just f = e }}} and consult [https://www.haskell.org/onlinereport/haskell2010/haskellch4.html#x10-880004.... the Haskell report on the monomorphism restriction]. It says that the MR applies unless "an explicit type signature is given for every variable in the group that is bound by simple pattern binding"; and "Recall that ... a simple pattern binding is a pattern binding in which the pattern consists of only a single variable". So here `f` is not bound by a simple pattern binding and hence falls under the MR, signature or no signature. It's the same for your pattern binding `x@n`. You may say "but it's still simple" but that's not what the rules currently say. Incidentally, there's a bad typo in the Haskell 98 and Haskell 2010 reports. Under [https://www.haskell.org/onlinereport/haskell2010/haskellch4.html#x10-860004.... pattern bindings] both say "A simple pattern binding has form p = e"; but of course ''all'' pattern bindings have that form. It should say "A simple pattern binding has form x = e, where x is a variable". -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14782#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14782: typeclass polymorphism defeats bang patterns -------------------------------------+------------------------------------- Reporter: dmwit | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: invalid | Keywords: | MonomorphismRestriction Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: => MonomorphismRestriction -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14782#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14782: typeclass polymorphism defeats bang patterns -------------------------------------+------------------------------------- Reporter: dmwit | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: invalid | Keywords: | MonomorphismRestriction Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dmwit): Okay, I think I understand your explanation. But the more I think about this, the more it seems like there is still something a bit off in the current implementation. Here's an almost identical example, but with `Monoid` instead of `Num` to avoid having to think about defaulting: {{{ {-# LANGUAGE BangPatterns #-} main = let n :: Monoid a => a; !n = undefined in return () }}} Now that I have thought more carefully about what this means, I no longer understand why this is allowed to pass the type checker. If I'm following what you're saying, it seems like it ought to be an ambiguous type error, for exactly the same reason `main = seq (undefined :: Monoid a => a) (return ())` is. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14782#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14782: typeclass polymorphism defeats bang patterns -------------------------------------+------------------------------------- Reporter: dmwit | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: invalid | Keywords: | MonomorphismRestriction Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Let's look at your two examples: {{{#!hs main = seq (undefined :: Monoid a => a) (return ()) }}} The type-checker looks at the first argument of `seq` and sees something of `forall a. Monoid a => a`. So it instantiates this argument, providing a unification variable `t` and generating the constraint `Monoid t`. Later, the constraint solver discovers that it can't solve for `Monoid t`, and you've lost the game. {{{#!hs main = let n :: Monoid a => a; !n = undefined in return () }}} Here, the `undefined` is checked in an environment where we've quantified over `a` and can assume `Monoid a`, as is usual in the definition of a variable with a constrained type. No problem there. And, despite thinking of `!n` as desugaring to `seq n` somewhere, there is nowhere that GHC instantiates `n`. (Maybe you're arguing that we're not faithful to that desugaring... and you'd be right.) GHC just forces `n` right as it is, which exposes the lambda -- but not the `undefined` -- and then carries on. Does that help? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14782#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14782: typeclass polymorphism defeats bang patterns -------------------------------------+------------------------------------- Reporter: dmwit | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: | MonomorphismRestriction Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by dmwit): * status: closed => new * resolution: invalid => Comment: If you agree that you are not faithful to the desugaring, then I feel justified in reopening this as a genuine bug. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14782#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC