[GHC] #12235: Wrong compilation of bang patterns

#12235: Wrong compilation of bang patterns -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.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 have this function: {{{#!haskell fn5 :: Int -> [T] -> Int fn5 i [] = i fn5 i (A : ts) = fn5 (i + 1) ts fn5 !i (B : ts) = fn5 (i + 2) ts fn5 i (C : ts) = fn5 0 ts }}} This function should only `seq` the int after seeing that head of the list is `B`. But this is the generated code: (desugar) {{{#!haskell Rec { -- RHS size: {terms: 64, types: 33, coercions: 0} fn5 [Occ=LoopBreaker] :: Int -> [T] -> Int [LclIdX, Str=DmdType] fn5 = \ (i_ayA :: Int) (ds_d1Zb :: [T]) -> let { fail_d1Zn :: GHC.Prim.Void# -> Int [LclId, Str=DmdType] fail_d1Zn = \ _ [Occ=Dead, OS=OneShot] -> Control.Exception.Base.patError @ 'GHC.Types.PtrRepLifted @ Int "Main.hs:(41,1)-(44,25)|function fn5"# } in case ds_d1Zb of _ [Occ=Dead] { [] -> i_ayA; : ds_d1Zk ts_ayC -> case ds_d1Zk of _ [Occ=Dead] { __DEFAULT -> (\ _ [Occ=Dead, OS=OneShot] -> let { fail_d1Zp :: GHC.Prim.Void# -> Int [LclId, Str=DmdType] fail_d1Zp = \ _ [Occ=Dead, OS=OneShot] -> case ds_d1Zb of _ [Occ=Dead] { __DEFAULT -> fail_d1Zn GHC.Prim.void#; : ds_d1Zm ts_ayG -> case ds_d1Zm of _ [Occ=Dead] { __DEFAULT -> fail_d1Zn GHC.Prim.void#; C -> fn5 (GHC.Types.I# 0#) ts_ayG } } } in case i_ayA of i_XyO { __DEFAULT -> case ds_d1Zb of _ [Occ=Dead] { __DEFAULT -> fail_d1Zp GHC.Prim.void#; : ds_d1Zl ts_ayE -> case ds_d1Zl of _ [Occ=Dead] { __DEFAULT -> fail_d1Zp GHC.Prim.void#; B -> fn5 (+ @ Int GHC.Num.$fNumInt i_XyO (GHC.Types.I# 2#)) ts_ayE } } }) GHC.Prim.void#; A -> fn5 (+ @ Int GHC.Num.$fNumInt i_ayA (GHC.Types.I# 1#)) ts_ayC } } end Rec } }}} This code evaluates the list, and evaluates the int unless head of the list is `A`. I don't know why there's special case in A? In any case, this is wrong behavior as it forces the int in wrong times. As an example, this fails: {{{#!haskell fn5 :: Int -> [T] -> Int fn5 i [] = i fn5 i (A : ts) = fn5 (i + 1) ts fn5 !i (B : ts) = fn5 (i + 2) ts fn5 i (C : ts) = fn5 0 ts main = print (fn5 undefined [C]) }}} Tried with: GHC HEAD, 8.0.1. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12235 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12235: Wrong compilation of bang patterns -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 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: | -------------------------------------+------------------------------------- Description changed by osa1: @@ -14,1 +14,1 @@ - {{{#!haskell + {{{ New description: I have this function: {{{#!haskell fn5 :: Int -> [T] -> Int fn5 i [] = i fn5 i (A : ts) = fn5 (i + 1) ts fn5 !i (B : ts) = fn5 (i + 2) ts fn5 i (C : ts) = fn5 0 ts }}} This function should only `seq` the int after seeing that head of the list is `B`. But this is the generated code: (desugar) {{{ Rec { -- RHS size: {terms: 64, types: 33, coercions: 0} fn5 [Occ=LoopBreaker] :: Int -> [T] -> Int [LclIdX, Str=DmdType] fn5 = \ (i_ayA :: Int) (ds_d1Zb :: [T]) -> let { fail_d1Zn :: GHC.Prim.Void# -> Int [LclId, Str=DmdType] fail_d1Zn = \ _ [Occ=Dead, OS=OneShot] -> Control.Exception.Base.patError @ 'GHC.Types.PtrRepLifted @ Int "Main.hs:(41,1)-(44,25)|function fn5"# } in case ds_d1Zb of _ [Occ=Dead] { [] -> i_ayA; : ds_d1Zk ts_ayC -> case ds_d1Zk of _ [Occ=Dead] { __DEFAULT -> (\ _ [Occ=Dead, OS=OneShot] -> let { fail_d1Zp :: GHC.Prim.Void# -> Int [LclId, Str=DmdType] fail_d1Zp = \ _ [Occ=Dead, OS=OneShot] -> case ds_d1Zb of _ [Occ=Dead] { __DEFAULT -> fail_d1Zn GHC.Prim.void#; : ds_d1Zm ts_ayG -> case ds_d1Zm of _ [Occ=Dead] { __DEFAULT -> fail_d1Zn GHC.Prim.void#; C -> fn5 (GHC.Types.I# 0#) ts_ayG } } } in case i_ayA of i_XyO { __DEFAULT -> case ds_d1Zb of _ [Occ=Dead] { __DEFAULT -> fail_d1Zp GHC.Prim.void#; : ds_d1Zl ts_ayE -> case ds_d1Zl of _ [Occ=Dead] { __DEFAULT -> fail_d1Zp GHC.Prim.void#; B -> fn5 (+ @ Int GHC.Num.$fNumInt i_XyO (GHC.Types.I# 2#)) ts_ayE } } }) GHC.Prim.void#; A -> fn5 (+ @ Int GHC.Num.$fNumInt i_ayA (GHC.Types.I# 1#)) ts_ayC } } end Rec } }}} This code evaluates the list, and evaluates the int unless head of the list is `A`. I don't know why there's special case in A? In any case, this is wrong behavior as it forces the int in wrong times. As an example, this fails: {{{#!haskell fn5 :: Int -> [T] -> Int fn5 i [] = i fn5 i (A : ts) = fn5 (i + 1) ts fn5 !i (B : ts) = fn5 (i + 2) ts fn5 i (C : ts) = fn5 0 ts main = print (fn5 undefined [C]) }}} Tried with: GHC HEAD, 8.0.1. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12235#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12235: Wrong compilation of bang patterns -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 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: | -------------------------------------+------------------------------------- Description changed by osa1: @@ -74,0 +74,2 @@ + data T = A | B | C + New description: I have this function: {{{#!haskell fn5 :: Int -> [T] -> Int fn5 i [] = i fn5 i (A : ts) = fn5 (i + 1) ts fn5 !i (B : ts) = fn5 (i + 2) ts fn5 i (C : ts) = fn5 0 ts }}} This function should only `seq` the int after seeing that head of the list is `B`. But this is the generated code: (desugar) {{{ Rec { -- RHS size: {terms: 64, types: 33, coercions: 0} fn5 [Occ=LoopBreaker] :: Int -> [T] -> Int [LclIdX, Str=DmdType] fn5 = \ (i_ayA :: Int) (ds_d1Zb :: [T]) -> let { fail_d1Zn :: GHC.Prim.Void# -> Int [LclId, Str=DmdType] fail_d1Zn = \ _ [Occ=Dead, OS=OneShot] -> Control.Exception.Base.patError @ 'GHC.Types.PtrRepLifted @ Int "Main.hs:(41,1)-(44,25)|function fn5"# } in case ds_d1Zb of _ [Occ=Dead] { [] -> i_ayA; : ds_d1Zk ts_ayC -> case ds_d1Zk of _ [Occ=Dead] { __DEFAULT -> (\ _ [Occ=Dead, OS=OneShot] -> let { fail_d1Zp :: GHC.Prim.Void# -> Int [LclId, Str=DmdType] fail_d1Zp = \ _ [Occ=Dead, OS=OneShot] -> case ds_d1Zb of _ [Occ=Dead] { __DEFAULT -> fail_d1Zn GHC.Prim.void#; : ds_d1Zm ts_ayG -> case ds_d1Zm of _ [Occ=Dead] { __DEFAULT -> fail_d1Zn GHC.Prim.void#; C -> fn5 (GHC.Types.I# 0#) ts_ayG } } } in case i_ayA of i_XyO { __DEFAULT -> case ds_d1Zb of _ [Occ=Dead] { __DEFAULT -> fail_d1Zp GHC.Prim.void#; : ds_d1Zl ts_ayE -> case ds_d1Zl of _ [Occ=Dead] { __DEFAULT -> fail_d1Zp GHC.Prim.void#; B -> fn5 (+ @ Int GHC.Num.$fNumInt i_XyO (GHC.Types.I# 2#)) ts_ayE } } }) GHC.Prim.void#; A -> fn5 (+ @ Int GHC.Num.$fNumInt i_ayA (GHC.Types.I# 1#)) ts_ayC } } end Rec } }}} This code evaluates the list, and evaluates the int unless head of the list is `A`. I don't know why there's special case in A? In any case, this is wrong behavior as it forces the int in wrong times. As an example, this fails: {{{#!haskell data T = A | B | C fn5 :: Int -> [T] -> Int fn5 i [] = i fn5 i (A : ts) = fn5 (i + 1) ts fn5 !i (B : ts) = fn5 (i + 2) ts fn5 i (C : ts) = fn5 0 ts main = print (fn5 undefined [C]) }}} Tried with: GHC HEAD, 8.0.1. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12235#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12235: Wrong compilation of bang patterns -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.1 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 rwbarton): * status: new => closed * resolution: => invalid Comment: It should fail. Pattern matching is top-to-bottom, left-to-right, and according to the user's guide
Matching an expression e against a pattern !p is done by first evaluating e (to WHNF) and then matching the result against p.
So on the third line, we evaluate `i` to WHNF before checking whether the head of the list is `B`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12235#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12235: Wrong compilation of bang patterns -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.1 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: | -------------------------------------+------------------------------------- Comment (by osa1): Where does it say that in the user manual? Because I checked the manual a couple of times before I decided that this is a bug.. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12235#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12235: Wrong compilation of bang patterns -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.1 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: | -------------------------------------+------------------------------------- Comment (by rwbarton): At https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/glasgow_exts... #ghc-flag--XBangPatterns, right after the first displayed bit of code. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12235#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12235: Wrong compilation of bang patterns -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.1 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: | -------------------------------------+------------------------------------- Comment (by osa1): OK, I figured this out. Haskell2010 section 4.4.3.1 says this about translating equation-style definitions to case expressions: A function binding binds a variable to a function value. The general form of a function binding for variable `x` is: x p11 … p1k match1 … x pn1 … pnk matchn where each `pij` is a pattern, and where each `matchi` is of the general form: <snip> Translation: The general binding form for functions is semantically equivalent to the equation (i.e. simple pattern binding): x = \ x1 … xk -> case (x1, …, xk) of (p11, …, p1k) match1 … (pn1, …, pnk) matchn where the xi are new identifiers. GHC user manual 9.28.1 says `-XBangPatterns` adds a new production to the pattern syntax: pat ::= !pat So now let's say I have this: {{{ fn5 :: Int -> [T] -> Int fn5 i [] = i fn5 i (A : ts) = fn5 (i + 1) ts fn5 !i (B : ts) = fn5 (i + 2) ts fn5 i (C : ts) = fn5 0 ts }}} According to the report, this should become: {{{ fn5 = \fresh_1 fresh_2 -> case (fresh_1, fresh_2) of (i, []) -> i (i, (A : ts)) -> fn5 (i + 1) ts (!i, (B : ts) -> fn5 (i + 2) ts (i, (C : ts) -> fn5 0 ts }}} The semantics is explained I think in this sentence (from the user manual): Matching an expression e against a pattern !p is done by first evaluating e (to WHNF) and then matching the result against p. in Haskell2010 "3.13 Case Expressions" A case expression is evaluated by pattern matching the expression e against the individual alternatives. The alternatives are tried sequentially, from top to bottom. ... So if we start matching these `i`s from top to bottom, for the third case we'd need to evaluate `i`. So when it finally came to matching `(i, (C : ts))` we've already evaluated `i` because we've tried the third pattern. Indeed, if I change the definition to {{{ fn5 :: Int -> [T] -> Int fn5 i [] = i fn5 i (A : ts) = fn5 (i + 1) ts fn5 i (C : ts) = fn5 0 ts fn5 !i (B : ts) = fn5 (i + 2) ts }}} It works as expected. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12235#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12235: Wrong compilation of bang patterns -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.1 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: | -------------------------------------+------------------------------------- Comment (by nomeata): I agree with rwbarton. When matching `(undefined, [C])` against the patterns, it will match it against `(i, [])` and fail, and then against `(i, (A : ts))` and fail. Now it will be matched against `(!i, (B : ts))`. Comparing a tuple requires matching the individual components, from left to right. So it matches `undefined` against `!i`. According to the docs for bang patterns, as you quote them, this is done by first evaluating the expression to WHNF, which triggers the `undefined`, and this happens before `[C]` is matched against `(B:ts)`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12235#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC