data-list-zigzag-0.1.1.1: A list but with a balanced enumeration of Cartesian product.

Safe HaskellNone
LanguageHaskell2010

Data.List.ZigZag

Description

The feature of this module is ZigZag and its class instances. It is an abstract data type and can be constructed / deconstructed by fromList / toList or fromDiagonals / toDiagonals. See the associated documentation for more information.

Synopsis

Documentation

diagonals :: [[a]] -> [[a]] Source #

Finds the diagonals through a ragged list of lists.

For example, the diagonals of:

   [ [0,1,2]
   , []
   , [3,4]
   , [5,6,7]
   ]
 

Are:

   [ [0]
   , [1]
   , [3,2]
   , [5,4]
   , [6]
   , [7]
   ]
 

Which can be seen intuitively.

This algorithm works by storing a list of tails of rows already seen. To find the next diagonal we take the head of the next row plus the head of each stored tail. The tail remainders are stored plus the remainder of the new row.

If there are no more rows but some remaining tails we then iteratively form diagonals from the heads of each tail until there are no tails remaining.

Applied to the example:

   Row     | Output | Remaining
   --------+--------+----------------
   [0,1,2] | [0]    | [[1,2]]
   []      | [1]    | [[2]]
   [3,4]   | [3,2]  | [[4]]
   [5,6,7] | [5,4]  | [[6,7]]
   x       | [6]    | [[7]]
   x       | [7]    | []
 

fromDiagonals :: [[a]] -> ZigZag a Source #

Convert a list of diagonals to a ZigZag.

   fromDiagonals . toDiagonals = id
   toDiagonals . fromDiagonals = id
 

fromList :: [a] -> ZigZag a Source #

Convert a list to a ZigZag.

   fromList . toList = id
   toList . fromList = id
 

toDiagonals :: ZigZag a -> [[a]] Source #

Convert a ZigZag to a list of diagonals.

   fromDiagonals . toDiagonals = id
   toDiagonals . fromDiagonals = id
 

toList :: ZigZag a -> [a] Source #

Convert a ZigZag to a list.

   fromList . toList = id
   toList . fromList = id
 

data ZigZag a Source #

A list but with a balanced enumeration of Cartesian product such that

   fmap sum (sequence (replicate n (fromList [0..])))
 

is monotonically increasing.

Example:

   sequence [fromList [0,1], fromList [0,1,2]]
   = fromDiagonals
     [ [[0,0]]
     , [[1,0],[0,1]]
     , [[1,1],[0,2]]
     , [[1,2]]
     ]
 

This variation is useful in at least two ways. One, it is not stuck on infinite factors. Two, if the factors are ordered then the product is similarly ordered; this can lend to efficient searching of product elements.

Note that this method fails for the infinitary product even if every factor is known to be non-empty. The first element is known but following it are infinite elements that each draw a second element from one of the infinite factors. A product element drawing a third factor element is never reached.

Instances

Monad ZigZag Source # 

Methods

(>>=) :: ZigZag a -> (a -> ZigZag b) -> ZigZag b #

(>>) :: ZigZag a -> ZigZag b -> ZigZag b #

return :: a -> ZigZag a #

fail :: String -> ZigZag a #

Functor ZigZag Source # 

Methods

fmap :: (a -> b) -> ZigZag a -> ZigZag b #

(<$) :: a -> ZigZag b -> ZigZag a #

Applicative ZigZag Source # 

Methods

pure :: a -> ZigZag a #

(<*>) :: ZigZag (a -> b) -> ZigZag a -> ZigZag b #

liftA2 :: (a -> b -> c) -> ZigZag a -> ZigZag b -> ZigZag c #

(*>) :: ZigZag a -> ZigZag b -> ZigZag b #

(<*) :: ZigZag a -> ZigZag b -> ZigZag a #

Foldable ZigZag Source # 

Methods

fold :: Monoid m => ZigZag m -> m #

foldMap :: Monoid m => (a -> m) -> ZigZag a -> m #

foldr :: (a -> b -> b) -> b -> ZigZag a -> b #

foldr' :: (a -> b -> b) -> b -> ZigZag a -> b #

foldl :: (b -> a -> b) -> b -> ZigZag a -> b #

foldl' :: (b -> a -> b) -> b -> ZigZag a -> b #

foldr1 :: (a -> a -> a) -> ZigZag a -> a #

foldl1 :: (a -> a -> a) -> ZigZag a -> a #

toList :: ZigZag a -> [a] #

null :: ZigZag a -> Bool #

length :: ZigZag a -> Int #

elem :: Eq a => a -> ZigZag a -> Bool #

maximum :: Ord a => ZigZag a -> a #

minimum :: Ord a => ZigZag a -> a #

sum :: Num a => ZigZag a -> a #

product :: Num a => ZigZag a -> a #

Traversable ZigZag Source # 

Methods

traverse :: Applicative f => (a -> f b) -> ZigZag a -> f (ZigZag b) #

sequenceA :: Applicative f => ZigZag (f a) -> f (ZigZag a) #

mapM :: Monad m => (a -> m b) -> ZigZag a -> m (ZigZag b) #

sequence :: Monad m => ZigZag (m a) -> m (ZigZag a) #

Eq1 ZigZag Source # 

Methods

liftEq :: (a -> b -> Bool) -> ZigZag a -> ZigZag b -> Bool #

Ord1 ZigZag Source # 

Methods

liftCompare :: (a -> b -> Ordering) -> ZigZag a -> ZigZag b -> Ordering #

Read1 ZigZag Source # 

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (ZigZag a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [ZigZag a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (ZigZag a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [ZigZag a] #

Show1 ZigZag Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> ZigZag a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [ZigZag a] -> ShowS #

Alternative ZigZag Source # 

Methods

empty :: ZigZag a #

(<|>) :: ZigZag a -> ZigZag a -> ZigZag a #

some :: ZigZag a -> ZigZag [a] #

many :: ZigZag a -> ZigZag [a] #

MonadPlus ZigZag Source # 

Methods

mzero :: ZigZag a #

mplus :: ZigZag a -> ZigZag a -> ZigZag a #

IsList (ZigZag a) Source # 

Associated Types

type Item (ZigZag a) :: * #

Methods

fromList :: [Item (ZigZag a)] -> ZigZag a #

fromListN :: Int -> [Item (ZigZag a)] -> ZigZag a #

toList :: ZigZag a -> [Item (ZigZag a)] #

Eq a => Eq (ZigZag a) Source # 

Methods

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

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

Data a => Data (ZigZag a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ZigZag a -> c (ZigZag a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ZigZag a) #

toConstr :: ZigZag a -> Constr #

dataTypeOf :: ZigZag a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (ZigZag a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ZigZag a)) #

gmapT :: (forall b. Data b => b -> b) -> ZigZag a -> ZigZag a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ZigZag a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ZigZag a -> r #

gmapQ :: (forall d. Data d => d -> u) -> ZigZag a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ZigZag a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ZigZag a -> m (ZigZag a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ZigZag a -> m (ZigZag a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ZigZag a -> m (ZigZag a) #

Ord a => Ord (ZigZag a) Source # 

Methods

compare :: ZigZag a -> ZigZag a -> Ordering #

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

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

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

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

max :: ZigZag a -> ZigZag a -> ZigZag a #

min :: ZigZag a -> ZigZag a -> ZigZag a #

Read a => Read (ZigZag a) Source # 
Show a => Show (ZigZag a) Source # 

Methods

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

show :: ZigZag a -> String #

showList :: [ZigZag a] -> ShowS #

Generic (ZigZag a) Source # 

Associated Types

type Rep (ZigZag a) :: * -> * #

Methods

from :: ZigZag a -> Rep (ZigZag a) x #

to :: Rep (ZigZag a) x -> ZigZag a #

Semigroup (ZigZag a) Source # 

Methods

(<>) :: ZigZag a -> ZigZag a -> ZigZag a #

sconcat :: NonEmpty (ZigZag a) -> ZigZag a #

stimes :: Integral b => b -> ZigZag a -> ZigZag a #

Monoid (ZigZag a) Source # 

Methods

mempty :: ZigZag a #

mappend :: ZigZag a -> ZigZag a -> ZigZag a #

mconcat :: [ZigZag a] -> ZigZag a #

Generic1 * ZigZag Source # 

Associated Types

type Rep1 ZigZag (f :: ZigZag -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 ZigZag f a #

to1 :: Rep1 ZigZag f a -> f a #

type Rep (ZigZag a) Source # 
type Rep (ZigZag a)
type Item (ZigZag a) Source # 
type Item (ZigZag a) = a
type Rep1 * ZigZag Source #