Code Monkey home page Code Monkey logo

Comments (6)

mitchellwrosen avatar mitchellwrosen commented on July 18, 2024 3

Updated benchmark code shows somewhat similar memory usage by all 3 libraries

Case                  Allocated    GCs
pqueue 1000000    5,278,798,384  5,037
psqueues 1000000  5,045,176,008  4,844
heaps 1000000     4,815,937,992  4,630
Benchmark code
{- cabal:
build-depends: base, chronos-bench, heaps, pqueue, psqueues, random, random-shuffle, weigh
ghc-options: -O
-}
{-# LANGUAGE BlockArguments #-}

import qualified Chronos.Bench as Chronos
import Control.Monad
import Data.Foldable
import Data.Function
import qualified Data.Heap as Heaps
import qualified Data.IntPSQ as Psqueues
import qualified Data.PQueue.Prio.Min as Pqueue
import System.Random (randomIO, randomRIO)
import System.Random.Shuffle (shuffleM)
import qualified Weigh

type Level = Int

type Node = Int

main :: IO ()
main = do
  benchmarkMemory
  benchmarkTime

benchmarkMemory :: IO ()
benchmarkMemory = do
  let n = 1000000

  nodes <- randomNodes n

  Weigh.mainWith do
    Weigh.func ("pqueue " ++ show n) (pqueueDrain . pqueueFromList) nodes
    Weigh.func ("psqueues " ++ show n) (psqueuesDrain . psqueuesFromList) nodes
    Weigh.func ("heaps " ++ show n) (heapsDrain . heapsFromList) nodes

benchmarkTime :: IO ()
benchmarkTime = do
  let n = 100

  nodes <- randomNodes n

  Chronos.defaultMain
    [ Chronos.bench ("pqueue insert/pop x" ++ show n) (pqueueDrain . pqueueFromList) nodes,
      Chronos.bench ("psqueues insert/pop x" ++ show n) (psqueuesDrain . psqueuesFromList) nodes,
      Chronos.bench ("heaps insert/pop x" ++ show n) (heapsDrain . heapsFromList) nodes
    ]

randomNodes :: Int -> IO [(Node, Level)]
randomNodes n =
  zip
    <$> (shuffleM =<< replicateM n randomIO)
    <*> replicateM n (randomRIO (1, 10))

pqueueDrain :: Pqueue.MinPQueue Level Node -> ()
pqueueDrain q =
  case Pqueue.minView q of
    Nothing -> ()
    Just (_, q') -> pqueueDrain q'

psqueuesDrain :: Psqueues.IntPSQ Level Node -> ()
psqueuesDrain q =
  case Psqueues.minView q of
    Nothing -> ()
    Just (_, _, _, q') -> psqueuesDrain q'

heapsDrain :: Heaps.Heap (Heaps.Entry Level Node) -> ()
heapsDrain q =
  case Heaps.viewMin q of
    Nothing -> ()
    Just (_, q') -> heapsDrain q'

pqueueFromList :: [(Node, Level)] -> Pqueue.MinPQueue Level Node
pqueueFromList =
  foldl' (\acc (node, level) -> Pqueue.insert level node acc) Pqueue.empty

psqueuesFromList :: [(Node, Level)] -> Psqueues.IntPSQ Level Node
psqueuesFromList =
  fst . foldl' step (Psqueues.empty, 1)
  where
    step (acc, counter) (node, level) =
      let counter' = counter + 1
       in counter' `seq` (Psqueues.insert counter level node acc, counter')

heapsFromList :: [(Node, Level)] -> Heaps.Heap (Heaps.Entry Level Node)
heapsFromList =
  foldl'
    (\acc (node, level) -> Heaps.insert (Heaps.Entry level node) acc)
    Heaps.empty

from reactive-banana.

konsumlamm avatar konsumlamm commented on July 18, 2024 1

Fyi, pqueue now supports GHC 9 (lspitzner/pqueue#43) and is actively maintained again (lspitzner/pqueue#41).

from reactive-banana.

HeinrichApfelmus avatar HeinrichApfelmus commented on July 18, 2024

Hm. I would also prefer to switch to a more maintained library, but the problem is that these libraries offer slightly different APIs that are subtly incompatible.

  • pqueue supports distinct elements with the same priority. That's what we want.
  • In psqueues, queue elements are distinguished not by themselves, but by unique keys. This would force us to equip the SomeNode type with a unique identifier, so that it can be used "as its own key".
  • In heaps, the Entry p a type makes it possible to attach elements (type a) to priorities. However, two Entry are considered identical if their priorities are equal — this is not what we want.

In the worst case, that is if pqueue will never be compatible with new versions of GHC 9, I would rather include parts of its code in reactive-banana, provided that the license allows this.

from reactive-banana.

mitchellwrosen avatar mitchellwrosen commented on July 18, 2024

Ah, interesting! Yes, I ran into that pecularity in psqueues when writing the benchmark. I ended up identifying each node by a counter that just gets incremented by one each insert, but I can see how threading that state through in the reactive-banana implementation would be a little bit clumsy.

Also, perhaps relevant, the last psqueues upload to hackage was actually in June 2019, whereas pqueue had a release in 2020. I'm not sure if psqueues is being actively maintained - if I had to guess, it is - but it's still interesting that it's gone untouched for over 2 years.

And finally, about heaps, could you clarify why the Entry Eq instance is problematic? Presumably it was done to make Eq/Ord agree with each other, but the data structure does permit duplicates, so (as long as we don't get tripped up comparing Entry to each other when we should be comparing the SomeNode inside) it does seem to me like it'd work. Unfortunately, it's a little bit slower than the others, at least in my benchmark.

from reactive-banana.

HeinrichApfelmus avatar HeinrichApfelmus commented on July 18, 2024

Yes, I ran into that pecularity in psqueues when writing the benchmark. I ended up identifying each node by a counter that just gets incremented by one each insert, but I can see how threading that state through in the reactive-banana implementation would be a little bit clumsy.

Yes, that would be clumsy. The very existence of the pqueue package demonstrates that it would also be unnecessary, which is a good argument not to do it.

Also, perhaps relevant, the last psqueues upload to hackage was actually in June 2019, whereas pqueue had a release in 2020.

It appears that pqueue has a co-maintainer as well. In any case, if it's just about relaxing version bounds, I think there are Hackage trustees who can publish package revisions. I'd say we wait for something like that? Again, in the worst case, I'd prefer including source code directly in reactive-banana.

Presumably it was done to make Eq/Ord agree with each other, but the data structure does permit duplicates.

Ah, I missed that the structures permits duplicates. Still, in this case, I think that the Eq instance is a bad idea, because I think that it's fair to expect that any Eq instance should satisfy the following property: If x == y, then this implies x = y for all intents and purposes. The Entry type violates that, and I feel very uneasy about using types where basic assumptions about equality are not satisfied. 😅

(PS: With "for all intents and purposes", I mean that "as far as the public API is concerned, no distinction can be made". For example, if two maps from Data.Map are equal according to ==, then the balanced trees used internally need not be equal, but this difference cannot be detected with the public API.)

from reactive-banana.

HeinrichApfelmus avatar HeinrichApfelmus commented on July 18, 2024

As pqeue is maintained again, I'd like to keep the status quo and close this issue. Please feel free to reopen.

from reactive-banana.

Related Issues (20)

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.