[GHC] #14816: Missed Called Arity opportunity?

GHC ghc-devs at haskell.org
Tue Feb 20 04:41:16 UTC 2018


#14816: Missed Called Arity opportunity?
-------------------------------------+-------------------------------------
        Reporter:  dfeuer            |                Owner:  (none)
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:  8.6.1
       Component:  Compiler          |              Version:  8.2.2
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
 Type of failure:  Runtime           |  Unknown/Multiple
  performance bug                    |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by dfeuer):

 nomeata, I finally came up with a standalone test case that exhibits the
 same (apparent) peculiarity. I don't really understand what you're asking,
 so I'm hoping this will help.

 {{{#!hs
 {-# language UnboxedTuples #-}
 module Fish where
 import Data.Array.ST
 import Control.Monad.ST.Strict
 import Control.Monad

 blink :: (a -> b) -> a -> (# b #)
 blink g a = (# g a #)

 test :: Int -> a -> (a -> a -> a) -> STArray s Int a -> ST s (STArray s
 Int a)
 test k a f m = insertModifyingArr k (blink (f a)) m
 {-# NOINLINE test #-}

 insertModifyingArr :: Int -> (a -> (# a #))
                    -> STArray s Int a -> ST s (STArray s Int a)
 insertModifyingArr i0 f arr0 = do
    rng <- range <$> getBounds arr0
    go i0 rng arr0
   where
     go i [] arr = pure arr
     go i (k : ks) arr
       | i == k = do
           old <- readArray arr i
           case f old of (# new #) -> writeArray arr i new
           return arr
       | otherwise = go i ks arr
 }}}

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


More information about the ghc-tickets mailing list