creditmonad-1.0.0: Reasoning about amortized time complexity
Safe HaskellNone
LanguageGHC2021

Test.Credit.Heap.LazyPairing

Synopsis

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: - a is Empty and m has (log2 sm) credits - a is not Empty and m has (2 * log2 sm) credits - Right before forcing, m has (3 * log2 sm) credits

Instances

Instances details
BoundedHeap LazyPairing Source # 
Instance details

Defined in Test.Credit.Heap.LazyPairing

Methods

hcost :: Size -> HeapOp a -> Credit Source #

Heap LazyPairing Source # 
Instance details

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 # 
Instance details

Defined in Test.Credit.Heap.LazyPairing

Methods

prettyCell :: LazyPairing a m -> m Memory Source #

Pretty a => MemoryStructure (LazyPairing (PrettyCell a)) Source # 
Instance details

Defined in Test.Credit.Heap.LazyPairing

size :: forall a (s :: Type -> Type). LazyPairing a s -> Size Source #

data PLazyCon (m :: Type -> Type) a where Source #

Constructors

Em :: forall (m :: Type -> Type) a1. PLazyCon m (LazyPairing a1 m) 
Link 

Fields

  • :: 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)

    Merging 'h = Link(a, b, m)' costs one tick and performs two links, and assigns some credits to m. Because 'link a b' costs 'log2 (sa + sb)' credits, we have total costs of: 2 + 2*log2 (sa + sb + sm) + 2*log2 (sa + sb) + 2*log2 sm <= 6 * log2 sh (since sa + sb + sm <= sh)

Instances

Instances details
MonadCredit m => HasStep (PLazyCon m :: Type -> Type) (m :: Type -> Type) Source # 
Instance details

Defined in Test.Credit.Heap.LazyPairing

Methods

step :: PLazyCon m a -> m a Source #

(MonadMemory m, MemoryCell m a) => MemoryCell m (PLazyCon m a) Source # 
Instance details

Defined in Test.Credit.Heap.LazyPairing

Methods

prettyCell :: PLazyCon m a -> m Memory Source #

type PThunk (s :: Type -> Type) = Thunk s (PLazyCon s) 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