{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeSynonymInstances #-}
#ifdef __GLASGOW_HASKELL__
#define UNBOXED_COMPARISON_ARGUMENTS
#endif
#ifdef UNBOXED_COMPARISON_ARGUMENTS
{-# LANGUAGE MagicHash #-}
#endif
{-# OPTIONS_GHC -Wall #-}
{-# OPTIONS_HADDOCK show-extensions #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  ToySolver.Internal.Data.IndexedPriorityQueue
-- Copyright   :  (c) Masahiro Sakai 2012
-- License     :  BSD-style
--
-- Maintainer  :  masahiro.sakai@gmail.com
-- Stability   :  provisional
-- Portability :  non-portable
--
-- Priority queue implemented as array-based binary heap.
--
-----------------------------------------------------------------------------
module ToySolver.Internal.Data.IndexedPriorityQueue
  (
  -- * PriorityQueue type
    PriorityQueue
  , Value
  , Index

  -- * Constructors
  , newPriorityQueue
  , newPriorityQueueBy
  , NewFifo (..)

  -- * Operators
  , getElems
  , clear
  , clone
  , Enqueue (..)
  , Dequeue (..)
  , QueueSize (..)
  , member
  , update
  , rebuild
  , getHeapArray
  , getHeapVec

  -- * Misc operations
  , resizeHeapCapacity
  , resizeTableCapacity
  ) where

import Control.Loop
import Control.Monad
import qualified Data.Array.IO as A
import Data.Queue.Classes
import qualified ToySolver.Internal.Data.Vec as Vec
#ifdef UNBOXED_COMPARISON_ARGUMENTS
import GHC.Exts
#endif

type Index = Int
type Value = Int

-- | Priority queue implemented as array-based binary heap.
data PriorityQueue
  = PriorityQueue
#ifdef UNBOXED_COMPARISON_ARGUMENTS
  { PriorityQueue -> Int# -> Int# -> IO Bool
lt#  :: !(Int# -> Int# -> IO Bool)
#else
  { lt   :: !(Value -> Value -> IO Bool)
#endif
  , PriorityQueue -> UVec Index
heap :: !(Vec.UVec Value)
  , PriorityQueue -> UVec Index
table  :: !(Vec.UVec Index)
  }

-- | Build a priority queue with default ordering ('(<)' of 'Ord' class)
newPriorityQueue :: IO PriorityQueue
newPriorityQueue :: IO PriorityQueue
newPriorityQueue = (Index -> Index -> IO Bool) -> IO PriorityQueue
newPriorityQueueBy (\Index
a Index
b -> Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Index
a Index -> Index -> Bool
forall a. Ord a => a -> a -> Bool
< Index
b))

#ifdef UNBOXED_COMPARISON_ARGUMENTS

{-# INLINE newPriorityQueueBy #-}
-- | Build a priority queue with a given /less than/ operator.
newPriorityQueueBy :: (Value -> Value -> IO Bool) -> IO PriorityQueue
newPriorityQueueBy :: (Index -> Index -> IO Bool) -> IO PriorityQueue
newPriorityQueueBy Index -> Index -> IO Bool
cmp = (Int# -> Int# -> IO Bool) -> IO PriorityQueue
newPriorityQueueBy# Int# -> Int# -> IO Bool
cmp#
  where
    cmp# :: Int# -> Int# -> IO Bool
cmp# Int#
a Int#
b = Index -> Index -> IO Bool
cmp (Int# -> Index
I# Int#
a) (Int# -> Index
I# Int#
b)

-- | Build a priority queue with a given /less than/ operator.
newPriorityQueueBy# :: (Int# -> Int# -> IO Bool) -> IO PriorityQueue
newPriorityQueueBy# :: (Int# -> Int# -> IO Bool) -> IO PriorityQueue
newPriorityQueueBy# Int# -> Int# -> IO Bool
cmp# = do
  UVec Index
vec <- IO (UVec Index)
forall (a :: * -> * -> *) e. MArray a e IO => IO (GenericVec a e)
Vec.new
  UVec Index
idx <- IO (UVec Index)
forall (a :: * -> * -> *) e. MArray a e IO => IO (GenericVec a e)
Vec.new
  PriorityQueue -> IO PriorityQueue
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (PriorityQueue -> IO PriorityQueue)
-> PriorityQueue -> IO PriorityQueue
forall a b. (a -> b) -> a -> b
$ PriorityQueue{ lt# :: Int# -> Int# -> IO Bool
lt# = Int# -> Int# -> IO Bool
cmp#, heap :: UVec Index
heap = UVec Index
vec, table :: UVec Index
table = UVec Index
idx }

{-# INLINE lt #-}
lt :: PriorityQueue -> Value -> Value -> IO Bool
lt :: PriorityQueue -> Index -> Index -> IO Bool
lt PriorityQueue
q (I# Int#
a) (I# Int#
b) = PriorityQueue -> Int# -> Int# -> IO Bool
lt# PriorityQueue
q Int#
a Int#
b

#else

-- | Build a priority queue with a given /less than/ operator.
newPriorityQueueBy :: (Value -> Value -> IO Bool) -> IO PriorityQueue
newPriorityQueueBy cmp = do
  vec <- Vec.new
  idx <- Vec.new
  return $ PriorityQueue{ lt = cmp, heap = vec, table = idx }

#endif

-- | Return a list of all the elements of a priority queue. (not sorted)
getElems :: PriorityQueue -> IO [Value]
getElems :: PriorityQueue -> IO [Index]
getElems PriorityQueue
q = UVec Index -> IO [Index]
forall (a :: * -> * -> *) e.
MArray a e IO =>
GenericVec a e -> IO [e]
Vec.getElems (PriorityQueue -> UVec Index
heap PriorityQueue
q)

-- | Remove all elements from a priority queue.
clear :: PriorityQueue -> IO ()
clear :: PriorityQueue -> IO ()
clear PriorityQueue
q = do
  UVec Index -> IO ()
forall (a :: * -> * -> *) e.
MArray a e IO =>
GenericVec a e -> IO ()
Vec.clear (PriorityQueue -> UVec Index
heap PriorityQueue
q)
  UVec Index -> IO ()
forall (a :: * -> * -> *) e.
MArray a e IO =>
GenericVec a e -> IO ()
Vec.clear (PriorityQueue -> UVec Index
table PriorityQueue
q)

-- | Create a copy of a priority queue.
clone :: PriorityQueue -> IO PriorityQueue
clone :: PriorityQueue -> IO PriorityQueue
clone PriorityQueue
q = do
  UVec Index
h2 <- UVec Index -> IO (UVec Index)
forall (a :: * -> * -> *) e.
MArray a e IO =>
GenericVec a e -> IO (GenericVec a e)
Vec.clone (PriorityQueue -> UVec Index
heap PriorityQueue
q)
  UVec Index
t2 <- UVec Index -> IO (UVec Index)
forall (a :: * -> * -> *) e.
MArray a e IO =>
GenericVec a e -> IO (GenericVec a e)
Vec.clone (PriorityQueue -> UVec Index
table PriorityQueue
q)
  PriorityQueue -> IO PriorityQueue
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (PriorityQueue -> IO PriorityQueue)
-> PriorityQueue -> IO PriorityQueue
forall a b. (a -> b) -> a -> b
$ PriorityQueue
q{ heap = h2, table = t2 }

instance NewFifo PriorityQueue IO where
  newFifo :: IO PriorityQueue
newFifo = IO PriorityQueue
newPriorityQueue

instance Enqueue PriorityQueue IO Value where
  enqueue :: PriorityQueue -> Index -> IO ()
enqueue PriorityQueue
q Index
val = do
    Bool
m <- PriorityQueue -> Index -> IO Bool
member PriorityQueue
q Index
val
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
m (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
      Index
n <- UVec Index -> IO Index
forall (a :: * -> * -> *) e. GenericVec a e -> IO Index
Vec.getSize (PriorityQueue -> UVec Index
heap PriorityQueue
q)
      UVec Index -> Index -> IO ()
forall (a :: * -> * -> *) e.
MArray a e IO =>
GenericVec a e -> e -> IO ()
Vec.push (PriorityQueue -> UVec Index
heap PriorityQueue
q) Index
val
      UVec Index -> Index -> IO ()
forall (a :: * -> * -> *) e.
MArray a e IO =>
GenericVec a e -> Index -> IO ()
Vec.growTo (PriorityQueue -> UVec Index
table PriorityQueue
q) (Index
valIndex -> Index -> Index
forall a. Num a => a -> a -> a
+Index
1)
      UVec Index -> Index -> Index -> IO ()
forall (a :: * -> * -> *) e.
MArray a e IO =>
GenericVec a e -> Index -> e -> IO ()
Vec.unsafeWrite (PriorityQueue -> UVec Index
table PriorityQueue
q) Index
val Index
n
      PriorityQueue -> Index -> IO ()
up PriorityQueue
q Index
n

instance Dequeue PriorityQueue IO Value where
  dequeue :: PriorityQueue -> IO (Maybe Index)
dequeue PriorityQueue
q = do
    Index
n <- UVec Index -> IO Index
forall (a :: * -> * -> *) e. GenericVec a e -> IO Index
Vec.getSize (PriorityQueue -> UVec Index
heap PriorityQueue
q)
    case Index
n of
      Index
0 ->
        Maybe Index -> IO (Maybe Index)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Index
forall a. Maybe a
Nothing
      Index
_ -> do
        Index
val <- UVec Index -> Index -> IO Index
forall (a :: * -> * -> *) e.
MArray a e IO =>
GenericVec a e -> Index -> IO e
Vec.unsafeRead (PriorityQueue -> UVec Index
heap PriorityQueue
q) Index
0
        UVec Index -> Index -> Index -> IO ()
forall (a :: * -> * -> *) e.
MArray a e IO =>
GenericVec a e -> Index -> e -> IO ()
Vec.unsafeWrite (PriorityQueue -> UVec Index
table PriorityQueue
q) Index
val (-Index
1)
        if Index
n Index -> Index -> Bool
forall a. Eq a => a -> a -> Bool
== Index
1 then do
          UVec Index -> Index -> IO ()
forall (a :: * -> * -> *) e.
MArray a e IO =>
GenericVec a e -> Index -> IO ()
Vec.resize (PriorityQueue -> UVec Index
heap PriorityQueue
q) (Index
nIndex -> Index -> Index
forall a. Num a => a -> a -> a
-Index
1)
        else do
          Index
val1 <- UVec Index -> IO Index
forall (a :: * -> * -> *) e.
MArray a e IO =>
GenericVec a e -> IO e
Vec.unsafePop (PriorityQueue -> UVec Index
heap PriorityQueue
q)
          UVec Index -> Index -> Index -> IO ()
forall (a :: * -> * -> *) e.
MArray a e IO =>
GenericVec a e -> Index -> e -> IO ()
Vec.unsafeWrite (PriorityQueue -> UVec Index
heap PriorityQueue
q) Index
0 Index
val1
          UVec Index -> Index -> Index -> IO ()
forall (a :: * -> * -> *) e.
MArray a e IO =>
GenericVec a e -> Index -> e -> IO ()
Vec.unsafeWrite (PriorityQueue -> UVec Index
table PriorityQueue
q) Index
val1 Index
0
          PriorityQueue -> Index -> IO ()
down PriorityQueue
q Index
0
        Maybe Index -> IO (Maybe Index)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Index -> Maybe Index
forall a. a -> Maybe a
Just Index
val)

  dequeueBatch :: PriorityQueue -> IO [Index]
dequeueBatch PriorityQueue
q = [Index] -> IO [Index]
go []
    where
      go :: [Value] -> IO [Value]
      go :: [Index] -> IO [Index]
go [Index]
xs = do
        Maybe Index
r <- PriorityQueue -> IO (Maybe Index)
forall q (m :: * -> *) a. Dequeue q m a => q -> m (Maybe a)
dequeue PriorityQueue
q
        case Maybe Index
r of
          Maybe Index
Nothing -> [Index] -> IO [Index]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Index] -> [Index]
forall a. [a] -> [a]
reverse [Index]
xs)
          Just Index
x -> [Index] -> IO [Index]
go (Index
xIndex -> [Index] -> [Index]
forall a. a -> [a] -> [a]
:[Index]
xs)

instance QueueSize PriorityQueue IO where
  queueSize :: PriorityQueue -> IO Index
queueSize PriorityQueue
q = UVec Index -> IO Index
forall (a :: * -> * -> *) e. GenericVec a e -> IO Index
Vec.getSize (PriorityQueue -> UVec Index
heap PriorityQueue
q)

member :: PriorityQueue -> Value -> IO Bool
member :: PriorityQueue -> Index -> IO Bool
member PriorityQueue
q Index
v = do
  Index
n <- UVec Index -> IO Index
forall (a :: * -> * -> *) e. GenericVec a e -> IO Index
Vec.getSize (PriorityQueue -> UVec Index
table PriorityQueue
q)
  if Index
n Index -> Index -> Bool
forall a. Ord a => a -> a -> Bool
<= Index
v then
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
  else do
    Index
i <- UVec Index -> Index -> IO Index
forall (a :: * -> * -> *) e.
MArray a e IO =>
GenericVec a e -> Index -> IO e
Vec.unsafeRead (PriorityQueue -> UVec Index
table PriorityQueue
q) Index
v
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> IO Bool) -> Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$! Index
i Index -> Index -> Bool
forall a. Eq a => a -> a -> Bool
/= -Index
1

update :: PriorityQueue -> Value -> IO ()
update :: PriorityQueue -> Index -> IO ()
update PriorityQueue
q Index
v = do
  Index
i <- UVec Index -> Index -> IO Index
forall (a :: * -> * -> *) e.
MArray a e IO =>
GenericVec a e -> Index -> IO e
Vec.unsafeRead (PriorityQueue -> UVec Index
table PriorityQueue
q) Index
v
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Index
i Index -> Index -> Bool
forall a. Eq a => a -> a -> Bool
== -Index
1) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
    PriorityQueue -> Index -> IO ()
up PriorityQueue
q Index
i
    PriorityQueue -> Index -> IO ()
down PriorityQueue
q Index
i

up :: PriorityQueue -> Index -> IO ()
up :: PriorityQueue -> Index -> IO ()
up PriorityQueue
q !Index
i = do
  Index
val <- UVec Index -> Index -> IO Index
forall (a :: * -> * -> *) e.
MArray a e IO =>
GenericVec a e -> Index -> IO e
Vec.unsafeRead (PriorityQueue -> UVec Index
heap PriorityQueue
q) Index
i
  let loop :: Index -> IO Index
loop Index
0 = Index -> IO Index
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Index
0
      loop Index
j = do
        let p :: Index
p = Index -> Index
parent Index
j
        Index
val_p <- UVec Index -> Index -> IO Index
forall (a :: * -> * -> *) e.
MArray a e IO =>
GenericVec a e -> Index -> IO e
Vec.unsafeRead (PriorityQueue -> UVec Index
heap PriorityQueue
q) Index
p
        Bool
b <- PriorityQueue -> Index -> Index -> IO Bool
lt PriorityQueue
q Index
val Index
val_p
        if Bool
b
          then do
            UVec Index -> Index -> Index -> IO ()
forall (a :: * -> * -> *) e.
MArray a e IO =>
GenericVec a e -> Index -> e -> IO ()
Vec.unsafeWrite (PriorityQueue -> UVec Index
heap PriorityQueue
q) Index
j Index
val_p
            UVec Index -> Index -> Index -> IO ()
forall (a :: * -> * -> *) e.
MArray a e IO =>
GenericVec a e -> Index -> e -> IO ()
Vec.unsafeWrite (PriorityQueue -> UVec Index
table PriorityQueue
q) Index
val_p Index
j
            Index -> IO Index
loop Index
p
          else Index -> IO Index
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Index
j
  Index
j <- Index -> IO Index
loop Index
i
  UVec Index -> Index -> Index -> IO ()
forall (a :: * -> * -> *) e.
MArray a e IO =>
GenericVec a e -> Index -> e -> IO ()
Vec.unsafeWrite (PriorityQueue -> UVec Index
heap PriorityQueue
q) Index
j Index
val
  UVec Index -> Index -> Index -> IO ()
forall (a :: * -> * -> *) e.
MArray a e IO =>
GenericVec a e -> Index -> e -> IO ()
Vec.unsafeWrite (PriorityQueue -> UVec Index
table PriorityQueue
q) Index
val Index
j

down :: PriorityQueue -> Index -> IO ()
down :: PriorityQueue -> Index -> IO ()
down PriorityQueue
q !Index
i = do
  Index
n <- UVec Index -> IO Index
forall (a :: * -> * -> *) e. GenericVec a e -> IO Index
Vec.getSize (PriorityQueue -> UVec Index
heap PriorityQueue
q)
  Index
val <- UVec Index -> Index -> IO Index
forall (a :: * -> * -> *) e.
MArray a e IO =>
GenericVec a e -> Index -> IO e
Vec.unsafeRead (PriorityQueue -> UVec Index
heap PriorityQueue
q) Index
i
  let loop :: Index -> IO Index
loop !Index
j = do
        let !l :: Index
l = Index -> Index
left Index
j
            !r :: Index
r = Index -> Index
right Index
j
        if Index
l Index -> Index -> Bool
forall a. Ord a => a -> a -> Bool
>= Index
n
         then Index -> IO Index
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Index
j
         else do
           Index
child <- do
             if Index
r Index -> Index -> Bool
forall a. Ord a => a -> a -> Bool
>= Index
n
              then Index -> IO Index
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Index
l
              else do
                Index
val_l <- UVec Index -> Index -> IO Index
forall (a :: * -> * -> *) e.
MArray a e IO =>
GenericVec a e -> Index -> IO e
Vec.unsafeRead (PriorityQueue -> UVec Index
heap PriorityQueue
q) Index
l
                Index
val_r <- UVec Index -> Index -> IO Index
forall (a :: * -> * -> *) e.
MArray a e IO =>
GenericVec a e -> Index -> IO e
Vec.unsafeRead (PriorityQueue -> UVec Index
heap PriorityQueue
q) Index
r
                Bool
b <- PriorityQueue -> Index -> Index -> IO Bool
lt PriorityQueue
q Index
val_r Index
val_l
                if Bool
b
                  then Index -> IO Index
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Index
r
                  else Index -> IO Index
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Index
l
           Index
val_child <- UVec Index -> Index -> IO Index
forall (a :: * -> * -> *) e.
MArray a e IO =>
GenericVec a e -> Index -> IO e
Vec.unsafeRead (PriorityQueue -> UVec Index
heap PriorityQueue
q) Index
child
           Bool
b <- PriorityQueue -> Index -> Index -> IO Bool
lt PriorityQueue
q Index
val_child Index
val
           if Bool -> Bool
not Bool
b
             then Index -> IO Index
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Index
j
             else do
               UVec Index -> Index -> Index -> IO ()
forall (a :: * -> * -> *) e.
MArray a e IO =>
GenericVec a e -> Index -> e -> IO ()
Vec.unsafeWrite (PriorityQueue -> UVec Index
heap PriorityQueue
q) Index
j Index
val_child
               UVec Index -> Index -> Index -> IO ()
forall (a :: * -> * -> *) e.
MArray a e IO =>
GenericVec a e -> Index -> e -> IO ()
Vec.unsafeWrite (PriorityQueue -> UVec Index
table PriorityQueue
q) Index
val_child Index
j
               Index -> IO Index
loop Index
child
  Index
j <- Index -> IO Index
loop Index
i
  UVec Index -> Index -> Index -> IO ()
forall (a :: * -> * -> *) e.
MArray a e IO =>
GenericVec a e -> Index -> e -> IO ()
Vec.unsafeWrite (PriorityQueue -> UVec Index
heap PriorityQueue
q) Index
j Index
val
  UVec Index -> Index -> Index -> IO ()
forall (a :: * -> * -> *) e.
MArray a e IO =>
GenericVec a e -> Index -> e -> IO ()
Vec.unsafeWrite (PriorityQueue -> UVec Index
table PriorityQueue
q) Index
val Index
j

rebuild :: PriorityQueue -> IO ()
rebuild :: PriorityQueue -> IO ()
rebuild PriorityQueue
q = do
  Index
n <- UVec Index -> IO Index
forall (a :: * -> * -> *) e. GenericVec a e -> IO Index
Vec.getSize (PriorityQueue -> UVec Index
heap PriorityQueue
q)
  Index
-> (Index -> Bool) -> (Index -> Index) -> (Index -> IO ()) -> IO ()
forall (m :: * -> *) a.
Monad m =>
a -> (a -> Bool) -> (a -> a) -> (a -> m ()) -> m ()
forLoop Index
0 (Index -> Index -> Bool
forall a. Ord a => a -> a -> Bool
<Index
n) (Index -> Index -> Index
forall a. Num a => a -> a -> a
+Index
1) ((Index -> IO ()) -> IO ()) -> (Index -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Index
i -> do
    PriorityQueue -> Index -> IO ()
up PriorityQueue
q Index
i

-- | Get the internal representation of a given priority queue.
getHeapArray :: PriorityQueue -> IO (A.IOUArray Index Value)
getHeapArray :: PriorityQueue -> IO (IOUArray Index Index)
getHeapArray PriorityQueue
q = UVec Index -> IO (IOUArray Index Index)
forall (a :: * -> * -> *) e. GenericVec a e -> IO (a Index e)
Vec.getArray (PriorityQueue -> UVec Index
heap PriorityQueue
q)

-- | Get the internal representation of a given priority queue.
getHeapVec :: PriorityQueue -> IO (Vec.UVec Value)
getHeapVec :: PriorityQueue -> IO (UVec Index)
getHeapVec PriorityQueue
q = UVec Index -> IO (UVec Index)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (PriorityQueue -> UVec Index
heap PriorityQueue
q)

-- | Pre-allocate internal buffer for @n@ elements.
resizeHeapCapacity :: PriorityQueue -> Int -> IO ()
resizeHeapCapacity :: PriorityQueue -> Index -> IO ()
resizeHeapCapacity PriorityQueue
q Index
capa = UVec Index -> Index -> IO ()
forall (a :: * -> * -> *) e.
MArray a e IO =>
GenericVec a e -> Index -> IO ()
Vec.resizeCapacity (PriorityQueue -> UVec Index
heap PriorityQueue
q) Index
capa

-- | Pre-allocate internal buffer for @[0..n-1]@ values.
resizeTableCapacity :: PriorityQueue -> Int -> IO ()
resizeTableCapacity :: PriorityQueue -> Index -> IO ()
resizeTableCapacity PriorityQueue
q Index
capa = UVec Index -> Index -> IO ()
forall (a :: * -> * -> *) e.
MArray a e IO =>
GenericVec a e -> Index -> IO ()
Vec.resizeCapacity (PriorityQueue -> UVec Index
table PriorityQueue
q) Index
capa

{--------------------------------------------------------------------
  Index "traversal" functions
--------------------------------------------------------------------}

{-# INLINE left #-}
left :: Index -> Index
left :: Index -> Index
left Index
i = Index
iIndex -> Index -> Index
forall a. Num a => a -> a -> a
*Index
2 Index -> Index -> Index
forall a. Num a => a -> a -> a
+ Index
1

{-# INLINE right #-}
right :: Index -> Index
right :: Index -> Index
right Index
i = (Index
iIndex -> Index -> Index
forall a. Num a => a -> a -> a
+Index
1)Index -> Index -> Index
forall a. Num a => a -> a -> a
*Index
2;

{-# INLINE parent #-}
parent :: Index -> Index
parent :: Index -> Index
parent Index
i = (Index
iIndex -> Index -> Index
forall a. Num a => a -> a -> a
-Index
1) Index -> Index -> Index
forall a. Integral a => a -> a -> a
`div` Index
2

{--------------------------------------------------------------------
  test
--------------------------------------------------------------------}

{-
checkHeapProperty :: String -> PriorityQueue -> IO ()
checkHeapProperty str q = do
  (n,arr) <- readIORef (heap q)
  let go i = do
        val <- A.readArray arr i
        forM_ [left i, right i] $ \j ->
          when (j < n) $ do
            val2 <- A.readArray arr j
            b <- lt q val2 val
            when b $ do
              error (str ++ ": invalid heap " ++ show j)
            go j
  when (n > 0) $ go 0

  idx <- readIORef (table q)
  forM_ [0..n-1] $ \i -> do
    v <- A.readArray arr i
    i' <- A.readArray idx v
    when (i /= i') $ error $ str ++ ": invalid index " ++ show (i,v,i')
-}