#4081: Strict constructor fields inspected in loop
---------------------------------+------------------------------------------
    Reporter:  rl                |        Owner:  benl                   
        Type:  bug               |       Status:  new                    
    Priority:  normal            |    Milestone:  7.2.1                  
   Component:  Compiler          |      Version:  6.13                   
    Keywords:                    |     Testcase:                         
   Blockedby:                    |   Difficulty:                         
          Os:  Unknown/Multiple  |     Blocking:                         
Architecture:  Unknown/Multiple  |      Failure:  Runtime performance bug
---------------------------------+------------------------------------------

Comment(by simonpj):

 Here are a couple more examples Max suggested, which I want to capture in
 this ticket.
 {{{
 module T4081a where

 ----------------
 data S1 = S1 !Product
 data Product = Product !Int

 foo :: S1 -> Int
 foo (S1 x) = go 0 10
   where
     go acc 0 = acc
     go acc y = case x of Product x -> go (acc + (y * x)) (y - 1)

 ---------------------
 data S2 = S2 !Int

 bar :: S2 -> Int
 bar (S2 x) = go 0 10
   where
     go acc 0 = acc
     go acc y = go (acc + (x * y)) (y - 1)

 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4081#comment:14>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler

_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to