Discussion: Add unboxed mutable references somewhere sensible

David Feuer david.feuer at gmail.com
Thu Feb 12 17:12:30 UTC 2015


Yes, this is the sort of thing I was looking for. One question: if I
understand it correctly, it looks like ArrayRef duplicates the logic
of vector's Unbox to allow more general types without piggybacking on
Vector with it (small) overhead. Am I reading this right? If so, what
are the arguments against this approach?

Finally, I can't seem to stop wondering if there might be some
fundamentally more pleasant approach to this whole thing. The
underlying basis for this suspicion comes from the fact that, as
strange as it looks, `StateT v (ST s) a` actually works very well. For
example, the source below produces very nice core with -O2.

module STST (countUp) where
import Control.Monad.ST
import Control.Monad.Trans.State.Strict
import Control.Monad.Trans (lift)
import Control.Monad (when)
import Data.Functor ((<$))
import qualified Data.Vector.Unboxed.Mutable as V
import Data.Vector.Unboxed.Mutable (MVector, unsafeWrite)

step :: V.MVector s Int -> StateT Int (ST s) Bool
step v = do
           i <- get
           if i == V.length v
           then return True
           else do
             lift (unsafeWrite v i i)
             put (i+1)
             return False

countUp :: V.MVector s Int -> ST s ()
countUp v = () <$ execStateT go 0
  where
    go = do
      done <- step v
      when (not done) go

On Wed, Feb 11, 2015 at 10:35 PM, Michael Snoyman <michael at snoyman.com> wrote:
> I added this to mutable-containers. It's easiest to see this by looking at
> three readme on
>
> http://www.stackage.org/package/mutable-containers
>
> I'd support something like this in primitive as well.
>
>
> On Thu, Feb 12, 2015, 4:36 AM Dan Doel <dan.doel at gmail.com> wrote:
>>
>> We could add something like this to primitive. It has a generalization of
>> things like STRef, under the name MutVar.
>>
>> On Wed, Feb 11, 2015 at 7:03 PM, David Feuer <david.feuer at gmail.com>
>> wrote:
>>>
>>> The problem they solve is perhaps not as well known as it should be:
>>>
>>> Code that frequently modifies an `STRef Int`, for example, will
>>> typically surprise the programmer by allocating a ton of memory. This
>>> happens because the reference holds a *boxed* Int. Code like
>>>
>>>     modifySTRef ref (+1)
>>>
>>> will allocate a new Int box every time. To the best of my knowledge,
>>> GHC makes no attempt to figure out if this is actually necessary and
>>> do something about it. The Data.Ref.Unboxed module in the ArrayRef
>>> package attempts to address this, but it doesn't seem to get much
>>> visibility, and its code hasn't been touched since 2009. What can we
>>> do about this?
>>> _______________________________________________
>>> Libraries mailing list
>>> Libraries at haskell.org
>>> http://www.haskell.org/mailman/listinfo/libraries
>>
>>
>> _______________________________________________
>> Libraries mailing list
>> Libraries at haskell.org
>> http://www.haskell.org/mailman/listinfo/libraries


More information about the Libraries mailing list