[GHC] #13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in 8.2

#13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Try running this code in GHCi: {{{ λ> :set -XBangPatterns -XRankNTypes -XTypeFamilies λ> let x :: forall a . a ~ Integer => forall b. b ~ Integer => (a, b); !x = (1, 2) }}} In GHC 8.0.1 and 8.0.2, this works. But in GHC 8.2.1: {{{ <interactive>:3:74: Couldn't match expected type ‘forall a. (a ~ Integer) => forall b. (b ~ Integer) => (a, b)’ with actual type ‘(Integer, Integer)’ In the expression: (1, 2) In a pattern binding: !x = (1, 2) }}} If you put this code into a source file: {{{#!hs {-# LANGUAGE BangPatterns #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE RankNTypes #-} module Bug where x :: forall a . a ~ Integer => forall b. b ~ Integer => (a, b) !x = (1, 2) }}} Then it also works in GHC 8.0.1. and 8.0.2, but it errors on GHC 8.2 (this time with a different error): {{{ GHCi, version 8.2.0.20170413: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:6:1: error: Overloaded signature conflicts with monomorphism restriction x :: forall a. a ~ Integer => forall b. b ~ Integer => (a, b) | 6 | x :: forall a . a ~ Integer => forall b. b ~ Integer => (a, b) | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13594 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Gah! GHC has two sorts of bindings: `FunBind` and `PatBind`: * `FunBind` is used for function bindings, obviously, but also for bindings of form `x = e`. As the comments in `HsBinds.hs` say: {{{ -- FunBind is used for both functions @f x = e@ -- and variables @f = \x -> e@ -- -- Reason 1: Special case for type inference: see 'TcBinds.tcMonoBinds'. -- -- Reason 2: Instance decls can only have FunBinds, which is convenient. -- If you change this, you'll need to change e.g. rnMethodBinds }}} * `PatBind` is used for all other pattern bindings So `!x = e` is treated as a `PatBind`. And that means that it will take the `InferGen` patch (see `TcBinds.decideGeneralisationPlan`); and that means that it will behave differently type-inference-wise than `x = e; x :: sig`. And that is bad: bangs aren't supposed to affect typing. Best solution (I think): add a bang-flag to `FunRhs` (c.f. the `LexicalFixity` flag) in `HsExpr.HsMatchContext`. Then * `!x = e` would be a "simple" pattern binding * `FunBind` would handle all simple pattern bindings (as well as true function binding) NB: `(x) = e` would not be a "simple" pattern binding, and would still go via `PatBind`. Maybe that's even a feature. We could instead put the flag in `FunBind` itself, but I'm influenced by that `LexicalFixity` flag, which Alan migraed from `FunBind` to the `HsMatchContext` place (I forget why). I'm too swamped work on this, but I'll happily offer guidance. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13594#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: BangPatterns, Resolution: | RankNTypes Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: => BangPatterns, RankNTypes -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13594#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: BangPatterns, Resolution: | RankNTypes Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * owner: (none) => bgamari * priority: normal => high * milestone: => 8.2.1 Comment: I have a patch validating for this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13594#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: BangPatterns, Resolution: | RankNTypes Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Where is the patch? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13594#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: BangPatterns, Resolution: | RankNTypes Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): It is the `wip/T13594` branch but sadly validation failed. I'll need to look into why. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13594#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: BangPatterns, Resolution: | RankNTypes Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by asr): * cc: asr (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13594#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: BangPatterns, Resolution: | RankNTypes Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Ben: can you put this on Phab? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13594#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: BangPatterns, Resolution: | RankNTypes Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3525 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * differential: => Phab:D3525 Comment: See Phab:D3525. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13594#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in
8.2
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: bgamari
Type: bug | Status: new
Priority: high | Milestone: 8.2.1
Component: Compiler (Type | Version: 8.2.1-rc2
checker) | Keywords: BangPatterns,
Resolution: | RankNTypes
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D3525
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: merge Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: BangPatterns, Resolution: | RankNTypes Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3525 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => merge -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13594#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: merge Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: BangPatterns, Resolution: | RankNTypes Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3525 Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Erm, the commit in 372995364c52eef15066132d7d1ea8b6760034e6 doesn't actually fix either of the programs I reported, does it? I get the same errors on a recent GHC HEAD build: {{{ $ inplace/bin/ghc-stage2 --interactive GHCi, version 8.3.20170511: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci λ> :set -XBangPatterns -XRankNTypes -XTypeFamilies λ> let x :: forall a . a ~ Integer => forall b. b ~ Integer => (a, b); !x = (1, 2) <interactive>:2:74: error: • Couldn't match expected type ‘forall b. b ~ Integer => (a, b)’ with actual type ‘(Integer, Integer)’ • In the expression: (1, 2) In a pattern binding: !x = (1, 2) • Relevant bindings include x :: forall b. b ~ Integer => (a, b) (bound at <interactive>:2:70) }}} {{{ $ inplace/bin/ghc-stage2 ../Bug.hs [1 of 1] Compiling Bug ( ../Bug.hs, ../Bug.o ) ../Bug.hs:6:1: error: Overloaded signature conflicts with monomorphism restriction x :: forall a. a ~ Integer => forall b. b ~ Integer => (a, b) | 6 | x :: forall a . a ~ Integer => forall b. b ~ Integer => (a, b) | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13594#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: BangPatterns, Resolution: | RankNTypes Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3525 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * owner: bgamari => (none) * status: merge => new Comment: Yes, it seems you are right; I should have reviewed the ticket summary before concluding that the issue was fixed. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13594#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in
8.2
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: high | Milestone: 8.2.1
Component: Compiler (Type | Version: 8.2.1-rc2
checker) | Keywords: BangPatterns,
Resolution: | RankNTypes
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D3525
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: BangPatterns, Resolution: | RankNTypes Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3525 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Ahhh, I see what happened here. It looks like I must have dropped the critical hunk from my patch somewhere along the line. Validating fix currently. Thanks for catching this Ryan! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13594#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in
8.2
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: high | Milestone: 8.2.1
Component: Compiler (Type | Version: 8.2.1-rc2
checker) | Keywords: BangPatterns,
Resolution: | RankNTypes
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D3525
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: BangPatterns, Resolution: | RankNTypes Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3525 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * owner: (none) => bgamari -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13594#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: patch Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: BangPatterns, Resolution: | RankNTypes Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3661 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch * differential: Phab:D3525 => Phab:D3661 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13594#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in
8.2
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: bgamari
Type: bug | Status: patch
Priority: high | Milestone: 8.2.1
Component: Compiler (Type | Version: 8.2.1-rc2
checker) | Keywords: BangPatterns,
Resolution: | RankNTypes
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D3661
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: merge Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: BangPatterns, Resolution: | RankNTypes Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3661 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => merge -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13594#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: merge Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: BangPatterns, Resolution: | RankNTypes Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3661 Wiki Page: | -------------------------------------+------------------------------------- Comment (by alanz): I can confirm that the API Annotations work fine with ghc-exactprint, as at https://github.com/alanz/ghc- exactprint/commit/bcc41d3ffd295312e05eb745a63464b505786cc1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13594#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: closed Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: BangPatterns, Resolution: fixed | RankNTypes Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3661 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged with c7ed911f1b102f85ba89fe2ccce9ecf8231d1b8c. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13594#comment:21 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: closed Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: BangPatterns, Resolution: fixed | RankNTypes Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3661 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Hmm. In `Match.hs` this patch did {{{ - ; let upats = map (unLoc . decideBangHood dflags) pats + ; let add_bang + | FunRhs {mc_strictness=SrcStrict} <- ctx + = pprTrace "addBang" empty addBang + | otherwise + = decideBangHood dflags + upats = map (unLoc . add_bang) pats }}} I don't think that's right. I claim the if `mc_strictness` is True then `pats` is empty, so this change is a no-op. Do you agree? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13594#comment:22 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: closed Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: BangPatterns, Resolution: fixed | RankNTypes Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3661 Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Furthermore, I thought top-level bangs were disallowed, regardless of types. The existence of a top-level bang causes an assertion failure in a debug compiler. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13594#comment:23 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in
8.2
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: bgamari
Type: bug | Status: closed
Priority: high | Milestone: 8.2.1
Component: Compiler (Type | Version: 8.2.1-rc2
checker) | Keywords: BangPatterns,
Resolution: fixed | RankNTypes
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D3661
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in
8.2
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: bgamari
Type: bug | Status: closed
Priority: high | Milestone: 8.2.1
Component: Compiler (Type | Version: 8.2.1-rc2
checker) | Keywords: BangPatterns,
Resolution: fixed | RankNTypes
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D3661
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: closed Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: BangPatterns, Resolution: fixed | RankNTypes Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3661 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): OK I fixed both comment:22 and the wrongly-accepted program. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13594#comment:26 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC