linear-base-0.5.0: Standard library for linear types.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Foreign.Heap

Description

Implementation of pairing heaps stored off-heap

Synopsis

Documentation

data Heap k a Source #

Constructors

Empty 
NonEmpty (Box (NEHeap k a)) 

data NEHeap k a Source #

Constructors

Heap k a (Box (List (NEHeap k a))) 

Instances

Instances details
(Representable k, Representable a) => Representable (NEHeap k a) Source # 
Instance details

Defined in Foreign.Heap

Associated Types

type AsKnown (NEHeap k a) #

Methods

toKnown :: NEHeap k a %1 -> AsKnown (NEHeap k a) #

ofKnown :: AsKnown (NEHeap k a) %1 -> NEHeap k a #

(Representable k, Representable a) => MkRepresentable (NEHeap k a) (k, a, Box (List (NEHeap k a))) Source # 
Instance details

Defined in Foreign.Heap

Methods

toRepr :: NEHeap k a %1 -> (k, a, Box (List (NEHeap k a))) #

ofRepr :: (k, a, Box (List (NEHeap k a))) %1 -> NEHeap k a #

type AsKnown (NEHeap k a) Source # 
Instance details

Defined in Foreign.Heap

type AsKnown (NEHeap k a) = AsKnown (k, a, Box (List (NEHeap k a)))

Non-empty heap primitives

singletonN :: (Representable k, Representable a) => k %1 -> a %1 -> Pool %1 -> NEHeap k a Source #

mergeN :: forall k a. (Representable k, Representable a, Movable k, Ord k) => NEHeap k a %1 -> NEHeap k a %1 -> Pool %1 -> NEHeap k a Source #

mergeN' :: forall k a. (Representable k, Representable a, Movable k, Ord k) => NEHeap k a %1 -> Heap k a %1 -> Pool %1 -> NEHeap k a Source #

extractMinN :: (Representable k, Representable a, Movable k, Ord k) => NEHeap k a %1 -> Pool %1 -> (k, a, Heap k a) Source #

pairUp :: forall k a. (Representable k, Representable a, Movable k, Ord k) => List (NEHeap k a) %1 -> Pool %1 -> Heap k a Source #

Heap primitives

singleton :: forall k a. (Representable k, Representable a) => k %1 -> a %1 -> Pool %1 -> Heap k a Source #

extractMin :: (Representable k, Representable a, Movable k, Ord k) => Heap k a %1 -> Pool %1 -> Maybe (k, a, Heap k a) Source #

merge :: forall k a. (Representable k, Representable a, Movable k, Ord k) => Heap k a %1 -> Heap k a %1 -> Pool %1 -> Heap k a Source #

Heap sort

foldl :: forall k a b. (Representable k, Representable a, Movable k, Ord k) => (b %1 -> k %1 -> a %1 -> b) -> b %1 -> Heap k a %1 -> Pool %1 -> b Source #

Guaranteed to yield pairs in ascending key order

unfold :: forall k a s. (Representable k, Representable a, Movable k, Ord k) => (s -> Maybe ((k, a), s)) -> s -> Pool %1 -> Heap k a Source #

Strict: stream must terminate.

ofList :: (Representable k, Representable a, Movable k, Ord k) => [(k, a)] -> Pool %1 -> Heap k a Source #

toList :: (Representable k, Representable a, Movable k, Ord k) => Heap k a %1 -> Pool %1 -> [(k, a)] Source #

sort :: forall k a. (Representable k, Representable a, Movable k, Ord k, Movable a) => [(k, a)] -> [(k, a)] Source #