module Data.Heap.Internal
(
HeapT(..)
, isEmpty, rank, size
, empty, singleton, union, unions
, view
, partition
, splitAt, span
, fromList, toList
, fromDescList, toAscList
) where
import Control.Exception
import Data.Foldable ( Foldable(..), foldl' )
import Data.List ( groupBy, sortBy )
import Data.Monoid
import Data.Ord
import Data.Typeable
import Prelude hiding ( foldl, span, splitAt )
import Text.Read
data HeapT prio val
= Empty
| Tree { _rank :: !Int
, _size :: !Int
, _priority :: !prio
, _value :: val
, _left :: !(HeapT prio val)
, _right :: !(HeapT prio val)
}
deriving (Typeable)
instance (Read prio, Read val, Ord prio) => Read (HeapT prio val) where
readPrec = parens $ prec 10 $ do
Ident "fromList" <- lexP
fmap fromList readPrec
readListPrec = readListPrecDefault
instance (Show prio, Show val) => Show (HeapT prio val) where
showsPrec d heap = showParen (d > 10)
$ showString "fromList " . (showsPrec 11 (toList heap))
instance (Ord prio, Ord val) => Eq (HeapT prio val) where
heap1 == heap2 = size heap1 == size heap2 && EQ == compare heap1 heap2
instance (Ord prio, Ord val) => Ord (HeapT prio val) where
compare = comparing toPairAscList
instance (Ord prio) => Monoid (HeapT prio val) where
mempty = empty
mappend = union
mconcat = unions
instance Functor (HeapT prio) where
fmap _ Empty = Empty
fmap f heap = heap { _value = f (_value heap)
, _left = fmap f (_left heap)
, _right = fmap f (_right heap)
}
instance (Ord prio) => Foldable (HeapT prio) where
foldMap f = foldMap f . fmap snd . toAscList
foldr f z = foldl (flip f) z . fmap snd . reverse . toAscList
foldl f z = foldl f z . fmap snd . toAscList
isEmpty :: HeapT prio val -> Bool
isEmpty Empty = True
isEmpty _ = False
rank :: HeapT prio val -> Int
rank Empty = 0
rank heap = _rank heap
size :: HeapT prio val -> Int
size Empty = 0
size heap = _size heap
empty :: HeapT prio val
empty = Empty
singleton :: prio -> val -> HeapT prio val
singleton p v = Tree { _rank = 1
, _size = 1
, _priority = p
, _value = v
, _left = empty
, _right = empty
}
uncheckedCons :: (Ord prio) => prio -> val -> HeapT prio val -> HeapT prio val
uncheckedCons p v heap = assert (maybe True (\(p', _, _) -> p <= p') (view heap))
Tree { _rank = 1
, _size = 1 + size heap
, _priority = p
, _value = v
, _left = heap
, _right = empty
}
union :: (Ord prio) => HeapT prio val -> HeapT prio val -> HeapT prio val
union heap Empty = heap
union Empty heap = heap
union heap1 heap2 = let
p1 = _priority heap1
p2 = _priority heap2
in if p1 < p2
then makeT p1 (_value heap1) (_left heap1) (union (_right heap1) heap2)
else makeT p2 (_value heap2) (_left heap2) (union (_right heap2) heap1)
makeT :: (Ord prio) => prio -> val -> HeapT prio val -> HeapT prio val -> HeapT prio val
makeT p v a b = let
ra = rank a
rb = rank b
s = size a + size b + 1
in assert (checkPrio a && checkPrio b) $ if ra > rb
then Tree (rb + 1) s p v a b
else Tree (ra + 1) s p v b a
where
checkPrio = maybe True (\(p', _, _) -> p <= p') . view
unions :: (Ord prio) => [HeapT prio val] -> HeapT prio val
unions heaps = case tournamentFold' heaps of
[] -> empty
[h] -> h
hs -> unions hs
where
tournamentFold' :: (Monoid m) => [m] -> [m]
tournamentFold' (x1:x2:xs) = (: tournamentFold' xs) $! mappend x1 x2
tournamentFold' xs = xs
view :: (Ord prio) => HeapT prio val -> Maybe (prio, val, HeapT prio val)
view Empty = Nothing
view heap = Just (_priority heap, _value heap, union (_left heap) (_right heap))
partition :: (Ord prio) => ((prio, val) -> Bool) -> HeapT prio val
-> (HeapT prio val, HeapT prio val)
partition _ Empty = (empty, empty)
partition f heap
| f (p, v) = (makeT p v l1 r1, union l2 r2)
| otherwise = (union l1 r1, makeT p v l2 r2)
where
(p, v) = (_priority heap, _value heap)
(l1, l2) = partition f (_left heap)
(r1, r2) = partition f (_right heap)
splitAt :: (Ord prio) => Int -> HeapT prio val -> ([(prio, val)], HeapT prio val)
splitAt n heap
| n > 0 = case view heap of
Nothing -> ([], empty)
Just (p, v, hs) -> let (xs, heap') = splitAt (n1) hs in ((p, v):xs, heap')
| otherwise = ([], heap)
span :: (Ord prio) => ((prio, val) -> Bool) -> HeapT prio val
-> ([(prio, val)], HeapT prio val)
span f heap = case view heap of
Nothing -> ([], empty)
Just (p, v, hs) -> let pv = (p, v)
in if f pv
then let (xs, heap') = span f hs in (pv:xs, heap')
else ([], heap)
fromList :: (Ord prio) => [(prio, val)] -> HeapT prio val
fromList = fromDescList . sortBy (flip (comparing fst))
toList :: HeapT prio val -> [(prio, val)]
toList Empty = []
toList heap = let
left = _left heap
right = _right heap
in
(_priority heap, _value heap) : if (size right) < (size left)
then toList right ++ toList left
else toList left ++ toList right
fromDescList :: (Ord prio) => [(prio, val)] -> HeapT prio val
fromDescList = foldl' (\h (p, v) -> uncheckedCons p v h) empty
toAscList :: (Ord prio) => HeapT prio val -> [(prio, val)]
toAscList = fst . span (const True)
toPairAscList :: (Ord prio, Ord val) => HeapT prio val -> [(prio, val)]
toPairAscList = concat
. fmap (sortBy (comparing snd))
. groupBy (\x y -> fst x == fst y)
. toAscList