Safe Haskell | None |
---|---|
Language | GHC2021 |
Test.Credit.Heap.LazyPairing
Synopsis
- data LazyPairing a (s :: Type -> Type)
- = Empty
- | Heap Size a (LazyPairing a s) (PThunk s (LazyPairing a s))
- size :: forall a (s :: Type -> Type). LazyPairing a s -> Size
- data PLazyCon (m :: Type -> Type) a where
- Em :: forall (m :: Type -> Type) a1. PLazyCon m (LazyPairing a1 m)
- Link :: forall a1 (m :: Type -> Type). Ord a1 => Size -> LazyPairing a1 m -> LazyPairing a1 m -> Thunk m (PLazyCon m) (LazyPairing a1 m) -> PLazyCon m (LazyPairing a1 m)
- type PThunk (s :: Type -> Type) = Thunk s (PLazyCon s)
- data NEHeap (s :: Type -> Type) a = NEHeap Size a (LazyPairing a s) (PThunk s (LazyPairing a s))
- mergePairs :: (MonadCredit m, Ord a) => NEHeap m a -> LazyPairing a m -> m (LazyPairing a m)
- link :: (MonadCredit m, Ord a) => LazyPairing a m -> LazyPairing a m -> m (LazyPairing a m)
Documentation
data LazyPairing a (s :: Type -> Type) Source #
Constructors
Empty | |
Heap Size a (LazyPairing a s) (PThunk s (LazyPairing a s)) | Changed from Okasaki is that we annotate the size of the thunk.
Invariant: For 'Heap sm x a m', we have either:
- |
Instances
BoundedHeap LazyPairing Source # | |
Heap LazyPairing Source # | |
Defined in Test.Credit.Heap.LazyPairing Methods empty :: MonadCredit m => m (LazyPairing a m) Source # insert :: (MonadCredit m, Ord a) => a -> LazyPairing a m -> m (LazyPairing a m) Source # merge :: (MonadCredit m, Ord a) => LazyPairing a m -> LazyPairing a m -> m (LazyPairing a m) Source # splitMin :: (MonadCredit m, Ord a) => LazyPairing a m -> m (Maybe (a, LazyPairing a m)) Source # | |
(MonadMemory m, MemoryCell m a) => MemoryCell m (LazyPairing a m) Source # | |
Defined in Test.Credit.Heap.LazyPairing Methods prettyCell :: LazyPairing a m -> m Memory Source # | |
Pretty a => MemoryStructure (LazyPairing (PrettyCell a)) Source # | |
Defined in Test.Credit.Heap.LazyPairing Methods prettyStructure :: MonadMemory m => LazyPairing (PrettyCell a) m -> m Memory Source # |
data PLazyCon (m :: Type -> Type) a where Source #
Constructors
Em :: forall (m :: Type -> Type) a1. PLazyCon m (LazyPairing a1 m) | |
Link | |
Fields
|
Instances
MonadCredit m => HasStep (PLazyCon m :: Type -> Type) (m :: Type -> Type) Source # | |
Defined in Test.Credit.Heap.LazyPairing | |
(MonadMemory m, MemoryCell m a) => MemoryCell m (PLazyCon m a) Source # | |
Defined in Test.Credit.Heap.LazyPairing Methods prettyCell :: PLazyCon m a -> m Memory Source # |
data NEHeap (s :: Type -> Type) a Source #
Constructors
NEHeap Size a (LazyPairing a s) (PThunk s (LazyPairing a s)) |
mergePairs :: (MonadCredit m, Ord a) => NEHeap m a -> LazyPairing a m -> m (LazyPairing a m) Source #
mergePairs
costs up to 'log2 (sz + sa)' credits
link :: (MonadCredit m, Ord a) => LazyPairing a m -> LazyPairing a m -> m (LazyPairing a m) Source #
link
costs up to 'log2 (sz + sa) + 1' credits