#5916: runST isn't free
---------------------------------+------------------------------------------
    Reporter:  tibbe             |       Owner:                  
        Type:  bug               |      Status:  new             
    Priority:  normal            |   Milestone:                  
   Component:  Compiler          |     Version:  7.4.1           
    Keywords:                    |          Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |     Failure:  None/Unknown    
  Difficulty:  Unknown           |    Testcase:                  
   Blockedby:                    |    Blocking:                  
     Related:                    |  
---------------------------------+------------------------------------------

Comment(by tibbe):

 I'm afraid I'm too stuck in my current use case to think of examples from
 some other domain. This is not a standalone test case, but hopefully it at
 least makes the problem clear.  Imagine
 we want to write a function:

 {{{
 -- | /O(n)/ Update the element at the given position in this array.
 update :: Array e -> Int -> e -> Array e
 }}}

 where Array is some simple wrapper around Array#.

 We can write this function using another function, `update'`, in `ST`.

 {{{
 -- | /O(n)/ Update the element at the given position in this array.
 update' :: Array e -> Int -> e -> ST s (Array e)
 update' ary idx b = do
     mary <- thaw ary 0 count  -- Copies all elements into a mutable array
     write mary idx b          -- Update the one element
     unsafeFreeze mary         -- Return as an immutable array
   where !count = length ary

 update ary idx b = runST (update' ary idx b)
 }}}

 Now, say we have a function that calls `update` many times in a loop:

 {{{
 data RoseTree a = Rose a (Array (Rose a)) | Nil

 insert :: a -> RoseTree a -> RoseTree a
 insert x Nil = Rose x ...
 insert x (Rose y subtrees)
     | x == y    = Rose x subtrees
     | otherwise = Rose y $ update subtrees idx (insert x subtreeToUpdate)
   where
     idx = subtreeIndex x y  -- Pick the right subtree to update
     subtreeToUpdate = index subtrees idx

 index :: Array a -> Int -> a
 index = ...
 }}}

 (If you find `insert` hard to understand, it might be helpful to consider
 what `insert` would look like if we were using a tuple of fixed size (e.g.
 2 for a binary tree) instead of an `Array`.)

 `insert` will end up calling `runST` many times.  If we want to avoid the
 cost of `runST` at each level of the tree, we could structure the code
 like so:

 {{{
 insert :: a -> RoseTree a -> RoseTree a
 insert x0 t0 = runST (go x0 t0)
     go x Nil = return $ Rose x ...
     go x (Rose y subtrees)
         | x == y    = return $ Rose x subtrees
         | otherwise = do
             st <- go x subtreeToUpdate
             ary <- update' subtrees idx st
             return $ Rose y ary
       where
         idx = subtreeIndex x y  -- Pick the right subtree to update
         subtreeToUpdate = index subtrees idx
 }}}

 N.B. We have replace the call to `update`, which embeds a call to `runST`,
 with a call to `update'`, which doesn't.

 We have now reduced the number of calls to `runST` from O(log n) to 1,
 which turns out to be a performance improvement since `runST` allocates.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5916#comment:3>
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