Feeding a monad into itself

I have a function f :: a -> Maybe a that I want to feed into itself with some initial input until it returns Nothing. untilNothing :: (a -> Maybe a) -> a -> a untilNothing f x = case f x of Just x' -> untilNothing f x' Nothing -> x Is there a better way to do this? I feel like there is something more general going on with Monads being fed into themselves, but maybe I'm wrong. Thoughts?

This is about as good as you can do. The monad-loops package provides a
variety of similar combinators, generally implemented in similar ways, but
not this specific combinator. The downside of this combinator is that it is
partial: it will run forever without producing anything if f never gives a
Nothing.
On Thu, Jul 20, 2017 at 10:27 AM Jake
I have a function f :: a -> Maybe a that I want to feed into itself with some initial input until it returns Nothing.
untilNothing :: (a -> Maybe a) -> a -> a untilNothing f x = case f x of Just x' -> untilNothing f x' Nothing -> x
Is there a better way to do this? I feel like there is something more general going on with Monads being fed into themselves, but maybe I'm wrong. Thoughts? _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Also this pattern does seem Maybe-specific, in that for the general Monad case there's not an obvious termination condition. JEff
On Jul 20, 2017, at 11:03 AM, Rein Henrichs
wrote: This is about as good as you can do. The monad-loops package provides a variety of similar combinators, generally implemented in similar ways, but not this specific combinator. The downside of this combinator is that it is partial: it will run forever without producing anything if f never gives a Nothing.
On Thu, Jul 20, 2017 at 10:27 AM Jake
wrote: I have a function f :: a -> Maybe a that I want to feed into itself with some initial input until it returns Nothing. untilNothing :: (a -> Maybe a) -> a -> a untilNothing f x = case f x of Just x' -> untilNothing f x' Nothing -> x
Is there a better way to do this? I feel like there is something more general going on with Monads being fed into themselves, but maybe I'm wrong. Thoughts? _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Could MonadPlus (with mzero) or Alternative (with empty) provide the
termination condition, if this pattern turned out to be more generally
useful?
Joshua Grosso
On Thu, Jul 20, 2017 at 7:16 PM, Jeff Clites
Also this pattern does seem Maybe-specific, in that for the general Monad case there's not an obvious termination condition.
JEff
On Jul 20, 2017, at 11:03 AM, Rein Henrichs
wrote: This is about as good as you can do. The monad-loops package provides a variety of similar combinators, generally implemented in similar ways, but not this specific combinator. The downside of this combinator is that it is partial: it will run forever without producing anything if f never gives a Nothing.
On Thu, Jul 20, 2017 at 10:27 AM Jake
wrote: I have a function f :: a -> Maybe a that I want to feed into itself with some initial input until it returns Nothing.
untilNothing :: (a -> Maybe a) -> a -> a untilNothing f x = case f x of Just x' -> untilNothing f x' Nothing -> x
Is there a better way to do this? I feel like there is something more general going on with Monads being fed into themselves, but maybe I'm wrong. Thoughts? _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

That's what I was thinking, but I couldn't figure out if I wanted
MonadPlus, Alternative or maybe Monoid because they all have zero elements.
On Thu, Jul 20, 2017, 21:52 Joshua Grosso
Could MonadPlus (with mzero) or Alternative (with empty) provide the termination condition, if this pattern turned out to be more generally useful?
Joshua Grosso
On Thu, Jul 20, 2017 at 7:16 PM, Jeff Clites
wrote: Also this pattern does seem Maybe-specific, in that for the general Monad case there's not an obvious termination condition.
JEff
On Jul 20, 2017, at 11:03 AM, Rein Henrichs
wrote: This is about as good as you can do. The monad-loops package provides a variety of similar combinators, generally implemented in similar ways, but not this specific combinator. The downside of this combinator is that it is partial: it will run forever without producing anything if f never gives a Nothing.
On Thu, Jul 20, 2017 at 10:27 AM Jake
wrote: I have a function f :: a -> Maybe a that I want to feed into itself with some initial input until it returns Nothing.
untilNothing :: (a -> Maybe a) -> a -> a untilNothing f x = case f x of Just x' -> untilNothing f x' Nothing -> x
Is there a better way to do this? I feel like there is something more general going on with Monads being fed into themselves, but maybe I'm wrong. Thoughts? _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Another possibility is to use Either for an early exit.
iterateM :: Monad m => (a -> m a) -> a -> m b
iterateM f a = f a >>= iterateM f
exitOnNothing :: (a -> Maybe a) -> a -> Either a a
exitOnNothing f a = maybe (Left a) Right (f a)
Now, your untilNothing is iterateM . exitOnNothing, but you can easily
extend it to use IO or whatever pattern you like.
On Thu, Jul 20, 2017 at 11:17 PM, Jake
That's what I was thinking, but I couldn't figure out if I wanted MonadPlus, Alternative or maybe Monoid because they all have zero elements.
On Thu, Jul 20, 2017, 21:52 Joshua Grosso
wrote: Could MonadPlus (with mzero) or Alternative (with empty) provide the termination condition, if this pattern turned out to be more generally useful?
Joshua Grosso
On Thu, Jul 20, 2017 at 7:16 PM, Jeff Clites
wrote: Also this pattern does seem Maybe-specific, in that for the general Monad case there's not an obvious termination condition.
JEff
On Jul 20, 2017, at 11:03 AM, Rein Henrichs
wrote: This is about as good as you can do. The monad-loops package provides a variety of similar combinators, generally implemented in similar ways, but not this specific combinator. The downside of this combinator is that it is partial: it will run forever without producing anything if f never gives a Nothing.
On Thu, Jul 20, 2017 at 10:27 AM Jake
wrote: I have a function f :: a -> Maybe a that I want to feed into itself with some initial input until it returns Nothing.
untilNothing :: (a -> Maybe a) -> a -> a untilNothing f x = case f x of Just x' -> untilNothing f x' Nothing -> x
Is there a better way to do this? I feel like there is something more general going on with Monads being fed into themselves, but maybe I'm wrong. Thoughts? _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
--
Dave Menendez

Another interesting thought: although all of those give you a way to obtain a zero, I don't think any give you a way to test whether something is that zero. Hmm. JEff
On Jul 20, 2017, at 8:17 PM, Jake
wrote: That's what I was thinking, but I couldn't figure out if I wanted MonadPlus, Alternative or maybe Monoid because they all have zero elements.
On Thu, Jul 20, 2017, 21:52 Joshua Grosso
wrote: Could MonadPlus (with mzero) or Alternative (with empty) provide the termination condition, if this pattern turned out to be more generally useful? Joshua Grosso
On Thu, Jul 20, 2017 at 7:16 PM, Jeff Clites
wrote: Also this pattern does seem Maybe-specific, in that for the general Monad case there's not an obvious termination condition. JEff
On Jul 20, 2017, at 11:03 AM, Rein Henrichs
wrote: This is about as good as you can do. The monad-loops package provides a variety of similar combinators, generally implemented in similar ways, but not this specific combinator. The downside of this combinator is that it is partial: it will run forever without producing anything if f never gives a Nothing.
On Thu, Jul 20, 2017 at 10:27 AM Jake
wrote: I have a function f :: a -> Maybe a that I want to feed into itself with some initial input until it returns Nothing. untilNothing :: (a -> Maybe a) -> a -> a untilNothing f x = case f x of Just x' -> untilNothing f x' Nothing -> x
Is there a better way to do this? I feel like there is something more general going on with Monads being fed into themselves, but maybe I'm wrong. Thoughts? _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

On 2017-07-21 23:33, Jeff Clites wrote:
Another interesting thought: although all of those give you a way to obtain a zero, I don't think any give you a way to test whether something is that zero. Hmm.
Well you could always use Eq. Or Foldable's null. That would generalize the loop to all foldable monads. Is that useful? I doubt it, but it's interesting. Cheers.

Well you can usually replace a recursion with a fix and a case Maybe with a maybe. Then you would get something like this. untilNothing f = fix (\f' a -> maybe a f' (f a)) But it's really unreadable. Or at least I can't read it. Though it's fun to think up. Also no connection to monads. Cheers Silvio

Another perfectly cromulent definition is:
untilNothing f = fromJust . last . takeWhile isJust . iterate (f =<<) . Just
This has 2 advantages:
1. It illustrates the haskellism that "A list is a loop is a list."
2. It composes much-beloved list combinators into a reasonable pipeline.
-- Kim-Ee
On Fri, Jul 21, 2017 at 12:26 AM, Jake
I have a function f :: a -> Maybe a that I want to feed into itself with some initial input until it returns Nothing.
untilNothing :: (a -> Maybe a) -> a -> a untilNothing f x = case f x of Just x' -> untilNothing f x' Nothing -> x
Is there a better way to do this? I feel like there is something more general going on with Monads being fed into themselves, but maybe I'm wrong. Thoughts?
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Very interesting! What do you mean by a "better" unfold?
On Fri, Jul 21, 2017, 13:06 MarLinn
On 2017-07-21 17:57, Kim-Ee Yeoh wrote:
Another perfectly cromulent definition is:
untilNothing f = fromJust . last . takeWhile isJust . iterate (f =<<) . Just
This has 2 advantages:
1. It illustrates the haskellism that "A list is a loop is a list." 2. It composes much-beloved list combinators into a reasonable pipeline.
Note that
fromJust . last . takeWhile isJust . iterate (f =<<) . Just ≡ last . catMaybes . takeWhile isJust . iterate (f =<<) . Just
Note further that that with duplicate x = (x,x),
\initialElement -> catMaybes . takeWhile isJust . iterate (f =<<) . Just $ initialElement ≡ \initialElement -> initialElement: unfoldr (fmap duplicate . f) initialElement
In other words, the pipeline is basically equivalent to a simple unfoldr modulo the first step. Therefore,
untilNothing f initialElement = last $ initialElement : unfoldr (fmap duplicate . f) initialElement
Which reveals the relation to anamorphisms and makes it possible to drop two of the three pain-inducing functions (isJust and fromJust).
This further hints at the fact that loops are a combination of anamorphisms/unfolds (here: unfoldr) and catamorphisms/folds (here: last). As last can easily be replaced with better options like foldMap Last, the search for a "better" implementation should basically consist of a search for a more suitable unfold. A simple hoogle seems to reveal several options.
Cheers, MarLinn
PS: The relation to lists still remains in my version, but it may be easier to see that the "haskellism" is just an unfortunate result of both their prominence in the standard libraries and the specialised syntax we have for them. That's why it's a "haskellism", and not a universal relation.

Very interesting! What do you mean by a "better" unfold?
Well you asked the original question, so I'll leave that up to you to define. ;) Your original version is relatively specialised, but simple and efficient. The one I adapted uses quite a bit of intermediate wrapping and unwrapping and needs to move parts around on every iteration. Only because of list fusion does it have a chance to compete. It's also quite indirect and uses up cognitive energy when trying to understand it. So yours is "better" in several ways. Maybe there's a general unfold that is easier to understand. Or more efficient. Or easier to adapt to more situations. It depends highly on what your actual goals are…
participants (8)
-
David Menendez
-
Jake
-
Jeff Clites
-
Joshua Grosso
-
Kim-Ee Yeoh
-
MarLinn
-
Rein Henrichs
-
Silvio Frischknecht