capped-list-1.2: A list-like type for lazy sequences, with a user-defined termination value.

Portabilityportable
Maintainerjmillikin@gmail.com

Data.CappedList

Description

A list-like type for lazy sequences, with a user-defined termination value.

This module uses common names and so is designed to be imported qualified:

 import qualified Data.CappedList as CL

Synopsis

Documentation

data CappedList cap a Source

A list-like type for lazy sequences, with a user-defined termination value.

Constructors

Next a (CappedList cap a) 
Cap cap 

Instances

Typeable2 CappedList 
Monoid cap => Monad (CappedList cap) 
Functor (CappedList cap) 
Monoid cap => MonadFix (CappedList cap) 
Monoid cap => MonadPlus (CappedList cap) 
Monoid cap => Applicative (CappedList cap) 
Monoid cap => Foldable (CappedList cap) 
Monoid cap => Traversable (CappedList cap) 
Monoid cap => Alternative (CappedList cap) 
(Eq cap, Eq a) => Eq (CappedList cap a) 
(Data cap, Data a) => Data (CappedList cap a) 
(Show cap, Show a) => Show (CappedList cap a) 
Monoid cap => Monoid (CappedList cap a) 

toList :: CappedList cap a -> (cap, [a])Source

Convert a capped list to a standard list.

The cap is returned in the first value of the result tuple.

toList_ :: CappedList cap a -> [a]Source

Convert a capped list to a standard list, discarding the cap.

fromList :: [a] -> cap -> CappedList cap aSource

Convert a standard list and cap to a capped list.

null :: CappedList cap a -> BoolSource

Like the standard null function.

appendR :: CappedList cap1 a -> CappedList cap2 a -> (cap1, CappedList cap2 a)Source

Like the standard ++ function.

appendL :: CappedList cap1 a -> CappedList cap2 a -> (cap2, CappedList cap1 a)Source

Like the standard ++ function.

appendR_ :: CappedList cap1 a -> CappedList cap2 a -> CappedList cap2 aSource

Like the standard ++ function.

The first list's "cap" will be discarded; to preserve the cap, use appendR.

appendL_ :: CappedList cap1 a -> CappedList cap2 a -> CappedList cap1 aSource

Like the standard ++ function.

The second list's "cap" will be discarded; to preserve the cap, use appendL.

appendWith :: (c -> d -> e) -> CappedList c a -> CappedList d a -> CappedList e aSource

Append two capped lists, merging the caps together using a user-provided function.

map :: (a -> b) -> CappedList cap a -> CappedList cap bSource

Like the standard map function.

mapEither :: (a -> Either cap b) -> CappedList cap a -> CappedList cap bSource

Like the standard map function, but the mapping function may return a capping value.

concatMapM :: Monoid cap => (a -> CappedList cap b) -> CappedList cap a -> CappedList cap bSource

Like the standard concatMap function.

foldr :: (a -> b -> b) -> (cap -> b) -> CappedList cap a -> bSource

Like the standard foldr function, but accepting an extra parameter to handle Cap values.

foldl :: (b -> a -> b) -> (cap -> b) -> CappedList cap a -> bSource

Like the standard foldl function, but accepting an extra parameter to handle Cap values.

unfoldr :: (b -> Either cap (a, b)) -> b -> CappedList cap aSource

Like the standard Data.List.unfoldr function, but the step function must return a cap to terminate the unfold.

length :: CappedList cap a -> IntSource

Like the standard length function; Cap is considered 0-length.