Safe Haskell | None |
---|---|
Language | GHC2021 |
Test.Credit.RandomAccess.Binary
Synopsis
- data Stream (m :: Type -> Type) a
- indirect :: MonadCredit m => m (Stream m a) -> m (Stream m a)
- credit :: MonadCredit m => Credit -> Stream m a -> m ()
- smatch :: MonadCredit m => Stream m a -> m b -> (a -> Stream m a -> m b) -> m b
- data Tree a
- data Digit a
- size :: Tree a -> Int
- link :: Tree a -> Tree a -> Tree a
- consTree :: MonadCredit m => Tree a -> Stream m (Digit a) -> m (Stream m (Digit a))
- unconsTree :: MonadCredit m => Stream m (Digit a) -> m (Maybe (Tree a, Stream m (Digit a)))
- lookupTree :: MonadCredit m => Int -> Tree a -> m (Maybe a)
- updateTree :: MonadCredit m => Int -> a -> Tree a -> m (Tree a)
- newtype BinaryRA a (m :: Type -> Type) = BinaryRA {
- unBinaryRA :: Stream m (Digit a)
Documentation
data Stream (m :: Type -> Type) a Source #
Instances
(MonadMemory m, MemoryCell m a) => MemoryCell m (Stream m a) Source # | |
Defined in Test.Credit.RandomAccess.Binary Methods prettyCell :: Stream m a -> m Memory 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
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
BoundedRandomAccess BinaryRA Source # | |
Defined in Test.Credit.RandomAccess.Binary | |
RandomAccess BinaryRA Source # | |
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 # | |
Defined in Test.Credit.RandomAccess.Binary Methods prettyCell :: BinaryRA a m -> m Memory Source # | |
Pretty a => MemoryStructure (BinaryRA (PrettyCell a)) Source # | |
Defined in Test.Credit.RandomAccess.Binary Methods prettyStructure :: MonadMemory m => BinaryRA (PrettyCell a) m -> m Memory Source # |