<div dir="auto"><div dir="auto">Hi Tom,<div dir="auto"><br></div><div dir="auto">It's possible I'm misunderstanding what you're saying. The definition tailRecM1, while it typechecks, will not always operate in constant stack space (at least in PureScript). The paper "Stack Safety for Free" provides a pretty much analogous definition by way of illustration and says as much about it.</div><div dir="auto"><br></div><div dir="auto">As for tailRecM2, unfortunately this precludes many useful and nontrivial MonadRec instances such as Effect and Aff, which admit no such distributing natural transformation (if this is what you actually meant for the first argument to be).</div><div dir="auto"><br></div><div dir="auto">Thanks,</div><div dir="auto">Asad</div></div><br><div class="gmail_quote"><div dir="ltr" class="gmail_attr">On Tue, Sept 27, 2022, 4:00 p.m. Tom Ellis <<a href="mailto:tom-lists-haskell-cafe-2017@jaguarpaw.co.uk" target="_blank" rel="noreferrer">tom-lists-haskell-cafe-2017@jaguarpaw.co.uk</a>> wrote:<br></div><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">On Tue, Sep 27, 2022 at 10:15:29AM +1000, Isaac Elliott wrote:<br>
> <a href="https://pursuit.purescript.org/packages/purescript-tailrec/6.1.0/docs/Control.Monad.Rec.Class" rel="noreferrer noreferrer noreferrer" target="_blank">https://pursuit.purescript.org/packages/purescript-tailrec/6.1.0/docs/Control.Monad.Rec.Class</a><br>
> seems like a good starting point<br>
<br>
Seems like that package may have missed a trick to encode tail<br>
recursiveness through a distribution property:<br>
<br>
<br>
<br>
{-# LANGUAGE LambdaCase #-}<br>
{-# LANGUAGE DeriveFunctor #-}<br>
<br>
module RecExperiment where<br>
<br>
data Step a b = Loop a | Done b<br>
  deriving Functor<br>
<br>
tailRec :: (a -> Step a b) -> a -> b<br>
tailRec f = go . f<br>
  where<br>
  go (Loop a) = go (f a)<br>
  go (Done b) = b<br>
<br>
-- | This works for all monads<br>
tailRecM1 :: Monad m => (a -> m (Step a b)) -> a -> m b<br>
tailRecM1 f a = do<br>
  f a >>= \case<br>
    Loop a' -> tailRecM1 f a'<br>
    Done b -> pure b<br>
<br>
-- | This works for all monads with a "distribute" operation over<br>
-- @Step a@ and is guaranteed tail recursive via @tailRec@.<br>
tailRecM2 ::<br>
  Monad m =><br>
  (m (Step a b) -> Step a (m b)) -><br>
  (a -> m (Step a b)) -><br>
  a -><br>
  m b<br>
tailRecM2 distribute f = tailRec (distribute . f)<br>
_______________________________________________<br>
Libraries mailing list<br>
<a href="mailto:Libraries@haskell.org" rel="noreferrer noreferrer" target="_blank">Libraries@haskell.org</a><br>
<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries" rel="noreferrer noreferrer noreferrer" target="_blank">http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries</a><br>
</blockquote></div></div>