[Haskell-cafe] Help Improving Conduit Performance

Matthew Leach matthew at mattleach.net
Tue Jun 29 10:54:21 UTC 2021


Hi there!

I'm currently trying to write a program for the creation of IQ samples
from various sound files; AM is my current focus. This seems like a
really good application for the conduit library. I've so far got:

--8<---------------cut here---------------start------------->8---
run :: AMOptions -> IO ()
run opts = do
  (info, Just (aSamps :: SV.Buffer Float)) <- SF.readFile $ inputFile opts

  putStr "Processing samples... "
  hFlush stdout

  runConduitRes $ yieldMany (SV.fromBuffer aSamps)
               .| modulateAM (modIndex opts)
               .| zeroStuff (upsample opts)
               .| mapC renderSample
               .| unsafeBuilderToByteString
               .| sinkFile (outputFile opts)
--8<---------------cut here---------------end--------------->8---

However, this is *slow*. It takes over 40 seconds to run; I've
previously implemented the above without using streaming and this code
took approx 3 seconds to run with the same input.

I compiled the code for profiling and it appears as though the main
culprit is the function `injectLeftovers':

--8<---------------cut here---------------start------------->8---
        Mon Jun 28 22:55 2021 Time and Allocation Profiling Report  (Final)

           ayeQ +RTS -p -RTS am -i /Users/matthew/40.flac -o /Users/matthew/out.cfile -u 15 -m 150

        total time  =       76.32 secs   (76322 ticks @ 1000 us, 1 processor)
        total alloc = 445,275,685,456 bytes  (excludes profiling overheads)

COST CENTRE     MODULE                        SRC                                                    %time %alloc

injectLeftovers Data.Conduit.Internal.Pipe    src/Data/Conduit/Internal/Pipe.hs:(410,1)-(418,38)      79.5   81.6
runPipe         Data.Conduit.Internal.Pipe    src/Data/Conduit/Internal/Pipe.hs:(395,1)-(399,33)       7.1    5.0
awaitForever    Data.Conduit.Internal.Conduit src/Data/Conduit/Internal/Conduit.hs:(950,1)-(952,10)    5.3    3.7
run             AM                            AM.hs:(62,1)-(77,88)                                     4.4    7.0
renderSample    Render                        Render.hs:8:1-58                                         3.5    2.5
--8<---------------cut here---------------end--------------->8---

I'm at a bit of a loss as to where to start looking for why this
particlar function is using so many resources, or which part of the
pipeline is causing the issue. The custom pieces of code that I've got
in the pipeline are:

--8<---------------cut here---------------start------------->8---
modulateAM' :: Int -> Float -> IQ
modulateAM' modIdx s = (base + amp) :+ 0.0
  where x = fromIntegral modIdx / 200
        amp = s * x
        base = 1 - x

modulateAM :: Monad m => Int -> ConduitT Float IQ m ()
modulateAM = mapC . modulateAM'
--8<---------------cut here---------------end--------------->8---

--8<---------------cut here---------------start------------->8---
zeroStuff :: Monad m => Int -> ConduitT IQ  IQ  m ()
zeroStuff factor = awaitForever (\v -> yield v >>
                                  replicateM_ (factor - 1) (yield zero))
  where zero = 0 :+ 0
--8<---------------cut here---------------end--------------->8---

--8<---------------cut here---------------start------------->8---
renderSample :: IQ -> Builder
renderSample (real :+ imag) = floatLE real <> floatLE imag
--8<---------------cut here---------------end--------------->8---

Any help would be appreciated!

Regards,
-- 
Matt


More information about the Haskell-Cafe mailing list