<div dir="ltr">The maintainers for bytestring are still listed as Don Stewart and Duncan Coutts on the package, and it doesn&#39;t seem to fall the list of core packages per <a href="http://www.haskell.org/haskellwiki/Library_submissions">http://www.haskell.org/haskellwiki/Library_submissions</a> so I suppose it would come down to talking one of them into taking the patch. <div>
<br></div><div>It seems odd that a fundamental package like this is omitted from the Library_submissions page though, as the older <a href="http://trac.haskell.org/haskell-platform/wiki/PackageMaintainers">http://trac.haskell.org/haskell-platform/wiki/PackageMaintainers</a> page on the trac shows it as maintained by GHC Central.</div>
<div><div><br></div><div>-Edward</div><div><br></div></div></div><div class="gmail_extra"><br><br><div class="gmail_quote">On Thu, Sep 5, 2013 at 4:38 PM, Artyom Kazak <span dir="ltr">&lt;<a href="mailto:yom@artyom.me" target="_blank">yom@artyom.me</a>&gt;</span> wrote:<br>
<blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">So, I have written several implementations of mapM_:<br>
    * bsMapM_gen   — generic, works for any monad<br>
    * bsMapM_short — essentially (\f s -&gt; mapM_ f $ unpack s)<br>
    * bsMapM_IO    — hand-written version specifically for IO<br>
<br>
Generic and hand-written versions don’t differ much. The overhead<br>
seems to be coming from inlinePerformIO (am I right here? Also, am<br>
I using inlinePerformIO legitimately?), which is only needed when<br>
we’re not in the IO monad.<br>
<br>
      {-# SPECIALISE ... IO #-}<br>
      {-# SPECIALISE ... ST #-}<br>
      bsMapM_gen :: Monad m =&gt; (Word8 -&gt; m a) -&gt; ByteString -&gt; m ()<br>
      bsMapM_gen f s = unsafePerformIO $ unsafeUseAsCStringLen s mapp<br>
        where<br>
          mapp (ptr, len) = return $ go 0<br>
            where<br>
              go i | i == len  = return ()<br>
                   | otherwise = let !b = inlinePerformIO $<br>
                                          peekByteOff ptr i<br>
                                 in  f b &gt;&gt; go (i+1)<br>
<br>
The short version relies on fusion of `unpack` and `mapM_`. Its<br>
advantage is that even when compiled without optimisations, it’s<br>
still fast. (Question: would the same happen to other versions,<br>
when put into Data.ByteString module? I suppose packages like<br>
bytestring are compiled with optimisations, so it probably would.)<br>
<br>
      {-# SPECIALISE ... IO #-}<br>
      {-# SPECIALISE ... ST #-}<br>
      bsMapM_shortIO :: (Word8 -&gt; IO a) -&gt; ByteString -&gt; IO ()<br>
      bsMapM_shortIO f s = mapM_ f (unpack s)<br>
<br>
Finally, the IO-specialised version. It’s faster than generic<br>
version (and, similarly, an ST-specialised version using<br>
unsafeIOToST would be just as fast), so I assume a SPECIALISE pragma<br>
involving bsMapM_IO and bsMapM_ST should be present.<br>
(Question: are there other monads for which unsafeIOToMonad exists?)<br>
<br>
      bsMapM_IO :: (Word8 -&gt; IO a) -&gt; ByteString -&gt; IO ()<br>
      bsMapM_IO f s = unsafeUseAsCStringLen s mapp<br>
        where<br>
          mapp (ptr, len) = go 0<br>
            where<br>
              go i | i == len  = return ()<br>
                   | otherwise = peekByteOff ptr i &gt;&gt;= f &gt;&gt; go (i+1)<br>
<br>
A-and here’s a table comparing performance of all three functions.<br>
All timings are in milliseconds.<br>
<br>
              ghci       ghc       ghc -O     ghc -O2<br>
          +----------+----------+-------<u></u>---+----------+<br>
    gen   |   380    |    85    |   4.1    |   4.0    |<br>
    short |    45    |    46    |  17.2    |  16.5    |<br>
    IO    |   434    |    92    |   2.4    |   2.4    |<br>
          +----------+----------+-------<u></u>---+----------+<br>
<br>
Here’s the code I used. (Question: have I messed up anything?)<br>
<br>
      import qualified Data.ByteString as BS<br>
      import Data.Random<br>
      import System.Random<br>
      import System.IO.Unsafe<br>
      import Control.Monad<br>
      import Data.IORef<br>
      import Criterion.Main<br>
      import BSMaps<br>
<br>
      --a bytestring consisting of 65536 random bytes<br>
      testCase = BS.pack $ fst $<br>
                 flip sampleState (mkStdGen 8) $<br>
                 replicateM (2^16) stdUniform<br>
<br>
      --sums elements of a bytestring, using given mapM_<br>
      sumIO :: ((Word8 -&gt; IO ()) -&gt; BS.ByteString -&gt; IO ()) -&gt;<br>
               BS.ByteString -&gt; Word8<br>
      sumIO f s = unsafePerformIO $ do<br>
        sm &lt;- newIORef 0<br>
        f (modifyIORef&#39; sm . (+)) s<br>
        readIORef sm<br>
<br>
      --runs the tests<br>
      main = defaultMain [<br>
        bench &quot;IO&quot;    $ whnf (sumIO bsMapM_IO)    testCase,<br>
        bench &quot;short&quot; $ whnf (sumIO bsMapM_short) testCase,<br>
        bench &quot;gen&quot;   $ whnf (sumIO bsMapM_gen)   testCase]<br>
<br>
Finally, if there isn’t anything wrong, what are my next steps to see<br>
this included into next version of bytestring?<div class="HOEnZb"><div class="h5"><br>
<br>
______________________________<u></u>_________________<br>
Libraries mailing list<br>
<a href="mailto:Libraries@haskell.org" target="_blank">Libraries@haskell.org</a><br>
<a href="http://www.haskell.org/mailman/listinfo/libraries" target="_blank">http://www.haskell.org/<u></u>mailman/listinfo/libraries</a><br>
</div></div></blockquote></div><br></div>