#3586: Initialisation of unboxed arrays is too slow
-----------------------------------------+----------------------------------
    Reporter:  simonpj                   |        Owner:                  
        Type:  run-time performance bug  |       Status:  new             
    Priority:  high                      |    Milestone:  6.12.2          
   Component:  libraries (other)         |      Version:  6.10.4          
    Severity:  normal                    |   Resolution:                  
    Keywords:                            |   Difficulty:  Unknown         
    Testcase:                            |           Os:  Unknown/Multiple
Architecture:  Unknown/Multiple          |  
-----------------------------------------+----------------------------------
Comment (by simonpj):

 Concerning int-e's patch, why do you say that
 {{{
 }}}
 That should not happen. I've just tried it with this module:
 {{{
 module Seq where

 import Control.Monad
 import Data.Array.Base

 newArrayImplSeq (l,u) initialValue
   = do let n = safeRangeSize (l,u)
        marr <- unsafeNewArray_ (l,u)
        sequence_ [unsafeWrite marr i initialValue | i <- [0 .. n - 1]]
        return marr

 newArrayImplFor (l,u) initialValue
   = do let n = safeRangeSize (l,u)
        marr <- unsafeNewArray_ (l,u)
        forM_ [0 .. n - 1] (\i -> unsafeWrite marr i initialValue)
        return marr


 doSeq :: Monad m => (Int -> m ()) -> Int -> m ()
 doSeq f n = sequence_ [f i | i <- [1..n]]

 doFor :: Monad m => (Int -> m ()) -> Int -> m ()
 doFor f n = forM_ [1..n] f
 }}}
 Both versions yield identical code. So why do you think one is better than
 t'other?

 Secondly, it's absolutely true that GHC's current inlining of default
 methods is flaky, but that is something I'm fixing as part of a long
 running project called "the never-ending INLINE patch".  When I'm done,
 your work-around shouldn't be ncessary (although it's not harmful).  Stay
 tuned.

 Simon

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3586#comment:12>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to