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

Test.Credit.RandomAccess.Binary

Synopsis

Documentation

data Stream (m :: Type -> Type) a Source #

Constructors

SCons a (Stream m a) 
SNil 
SIndirect (Thunk m (Lazy m) (Stream m a)) 

Instances

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

Defined in Test.Credit.RandomAccess.Binary

Methods

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

indirect :: MonadCredit m => m (Stream m a) -> m (Stream m a) Source #

credit :: MonadCredit m => Credit -> Stream m a -> m () Source #

smatch Source #

Arguments

:: MonadCredit m 
=> Stream m a

Scrutinee

-> m b

Nil case

-> (a -> Stream m a -> m b)

Cons case

-> m b 

Smart destructor for streams, consuming one credit

data Tree a Source #

Constructors

Leaf a 
Node Int (Tree a) (Tree a) 

Instances

Instances details
MemoryCell m a => MemoryCell m (Tree a) Source # 
Instance details

Defined in Test.Credit.RandomAccess.Binary

Methods

prettyCell :: Tree a -> m Memory Source #

Show a => Show (Tree a) Source # 
Instance details

Defined in Test.Credit.RandomAccess.Binary

Methods

showsPrec :: Int -> Tree a -> ShowS #

show :: Tree a -> String #

showList :: [Tree a] -> ShowS #

Eq a => Eq (Tree a) Source # 
Instance details

Defined in Test.Credit.RandomAccess.Binary

Methods

(==) :: Tree a -> Tree a -> Bool #

(/=) :: Tree a -> Tree a -> Bool #

Ord a => Ord (Tree a) Source # 
Instance details

Defined in Test.Credit.RandomAccess.Binary

Methods

compare :: Tree a -> Tree a -> Ordering #

(<) :: Tree a -> Tree a -> Bool #

(<=) :: Tree a -> Tree a -> Bool #

(>) :: Tree a -> Tree a -> Bool #

(>=) :: Tree a -> Tree a -> Bool #

max :: Tree a -> Tree a -> Tree a #

min :: Tree a -> Tree a -> Tree a #

data Digit a Source #

Constructors

Zero 
One (Tree a) 
Two (Tree a) (Tree a) 

Instances

Instances details
MemoryCell m a => MemoryCell m (Digit a) Source # 
Instance details

Defined in Test.Credit.RandomAccess.Binary

Methods

prettyCell :: Digit a -> m Memory Source #

Show a => Show (Digit a) Source # 
Instance details

Defined in Test.Credit.RandomAccess.Binary

Methods

showsPrec :: Int -> Digit a -> ShowS #

show :: Digit a -> String #

showList :: [Digit a] -> ShowS #

Eq a => Eq (Digit a) Source # 
Instance details

Defined in Test.Credit.RandomAccess.Binary

Methods

(==) :: Digit a -> Digit a -> Bool #

(/=) :: Digit a -> Digit a -> Bool #

Ord a => Ord (Digit a) Source # 
Instance details

Defined in Test.Credit.RandomAccess.Binary

Methods

compare :: Digit a -> Digit a -> Ordering #

(<) :: Digit a -> Digit a -> Bool #

(<=) :: Digit a -> Digit a -> Bool #

(>) :: Digit a -> Digit a -> Bool #

(>=) :: Digit a -> Digit a -> Bool #

max :: Digit a -> Digit a -> Digit a #

min :: Digit a -> Digit a -> Digit a #

size :: Tree a -> Int Source #

link :: Tree a -> Tree a -> Tree a Source #

consTree :: MonadCredit m => Tree a -> Stream m (Digit a) -> m (Stream m (Digit a)) Source #

unconsTree :: MonadCredit m => Stream m (Digit a) -> m (Maybe (Tree a, Stream m (Digit a))) Source #

lookupTree :: MonadCredit m => Int -> Tree a -> m (Maybe a) Source #

updateTree :: MonadCredit m => Int -> a -> Tree a -> m (Tree a) Source #

newtype BinaryRA a (m :: Type -> Type) Source #

Constructors

BinaryRA 

Fields

Instances

Instances details
BoundedRandomAccess BinaryRA Source # 
Instance details

Defined in Test.Credit.RandomAccess.Binary

RandomAccess BinaryRA Source # 
Instance details

Defined in Test.Credit.RandomAccess.Binary

Methods

empty :: MonadCredit m => m (BinaryRA a m) Source #

cons :: MonadCredit m => a -> BinaryRA a m -> m (BinaryRA a m) Source #

uncons :: MonadCredit m => BinaryRA a m -> m (Maybe (a, BinaryRA a m)) Source #

lookup :: MonadCredit m => Int -> BinaryRA a m -> m (Maybe a) Source #

update :: MonadCredit m => Int -> a -> BinaryRA a m -> m (BinaryRA a m) Source #

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

Defined in Test.Credit.RandomAccess.Binary

Methods

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

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

Defined in Test.Credit.RandomAccess.Binary