| Copyright | (c) Luke Palmer 2008 |
|---|---|
| License | Public Domain |
| Maintainer | Luke Palmer <lrpalmer@gmail.com> |
| Stability | experimental |
| Portability | portable |
| Safe Haskell | Safe |
| Language | Haskell2010 |
Control.Monad.Omega
Description
A monad for enumerating sets: like the list monad, but impervious to infinite descent.
A depth-first search of a data structure can fail to give a full traversal if it has an infinitely deep path. Likewise, a breadth-first search of a data structure can fall short if it has an infinitely branching node. Omega addresses this problem by using a "diagonal" traversal that gracefully dissolves such data.
So while liftM2 (,) [0..] [0..] gets "stuck" generating tuples whose
first element is zero, "runOmega" $ liftM2 (,) ("each" [0..]) ("each"
[0..]) generates all pairs of naturals.
More precisely, if x appears at a finite index in
xs, and y appears at a finite index in f x,
then y will appear at a finite index in each xs >>= f.
This monad gets its name because it is a monad over sets of order type omega.
Warning: Omega is only a monad when the results of runOmega are
interpreted as a set; that is, a valid transformation according to the
monad laws may change the order of the results. However, the same
set of results will always be reachable. If you are using this as a monad,
I recommend that you use the newer weighted-search package instead
(it's also faster).
Documentation
diagonal :: [[a]] -> [a] Source #
This is the hinge algorithm of the Omega monad,
exposed because it can be useful on its own. Joins
a list of lists with the property that for every i j
there is an n such that xs !! i !! j == diagonal xs !! n.
In particular, n <= (i+j)*(i+j+1)/2 + j.
Instances
| Monad Omega Source # | |
| Functor Omega Source # | |
| MonadFail Omega Source # | |
Defined in Control.Monad.Omega | |
| Applicative Omega Source # | |
| Foldable Omega Source # | |
Defined in Control.Monad.Omega Methods fold :: Monoid m => Omega m -> m # foldMap :: Monoid m => (a -> m) -> Omega a -> m # foldr :: (a -> b -> b) -> b -> Omega a -> b # foldr' :: (a -> b -> b) -> b -> Omega a -> b # foldl :: (b -> a -> b) -> b -> Omega a -> b # foldl' :: (b -> a -> b) -> b -> Omega a -> b # foldr1 :: (a -> a -> a) -> Omega a -> a # foldl1 :: (a -> a -> a) -> Omega a -> a # elem :: Eq a => a -> Omega a -> Bool # maximum :: Ord a => Omega a -> a # minimum :: Ord a => Omega a -> a # | |
| Traversable Omega Source # | |
| Alternative Omega Source # | |
| MonadPlus Omega Source # | |