[GHC] #12235: Wrong compilation of bang patterns

GHC ghc-devs at haskell.org
Mon Jun 27 09:57:52 UTC 2016


#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


More information about the ghc-tickets mailing list