[GHC] #9844: Bang pattern doesn't work on a newtype constructor

GHC ghc-devs at haskell.org
Fri Nov 28 03:53:10 UTC 2014


#9844: Bang pattern doesn't work on a newtype constructor
-------------------------------------+-------------------------------------
       Reporter:  akio               |                   Owner:
           Type:  bug                |                  Status:  new
       Priority:  normal             |               Milestone:
      Component:  Compiler           |                 Version:  7.8.3
       Keywords:                     |        Operating System:
   Architecture:  Unknown/Multiple   |  Unknown/Multiple
     Difficulty:  Unknown            |         Type of failure:  Incorrect
     Blocked By:                     |  result at runtime
Related Tickets:                     |               Test Case:
                                     |                Blocking:
                                     |  Differential Revisions:
-------------------------------------+-------------------------------------
 According to the documentation, {{{f0}}} and {{{f1}}} in the following
 program should have the identical semantics:

 {{{#!hs
 {-# LANGUAGE BangPatterns #-}
 module Main where

 newtype N = N Int

 f0 :: N -> Int
 f0 n = case n of
   !(N _) -> 0
   _ -> 1

 f1 :: N -> Int
 f1 n = n `seq` case n of
   N _ -> 0
   _ -> 1

 main = do
   print $ f0 undefined
   print $ f1 undefined
 }}}

 However, ghc only compiles {{{f1}}} into a strict function:

 {{{
 % ./bang-newtype
 0
 bang-newtype: Prelude.undefined
 }}}

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9844>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list