characterization of subset of Monads that respect tail calls?

A S masaeedu at gmail.com
Tue Sep 27 21:24:43 UTC 2022


Hi Tom,

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.

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).

Thanks,
Asad

On Tue, Sept 27, 2022, 4:00 p.m. Tom Ellis <
tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk> wrote:

> On Tue, Sep 27, 2022 at 10:15:29AM +1000, Isaac Elliott wrote:
> >
> https://pursuit.purescript.org/packages/purescript-tailrec/6.1.0/docs/Control.Monad.Rec.Class
> > seems like a good starting point
>
> Seems like that package may have missed a trick to encode tail
> recursiveness through a distribution property:
>
>
>
> {-# LANGUAGE LambdaCase #-}
> {-# LANGUAGE DeriveFunctor #-}
>
> module RecExperiment where
>
> data Step a b = Loop a | Done b
>   deriving Functor
>
> tailRec :: (a -> Step a b) -> a -> b
> tailRec f = go . f
>   where
>   go (Loop a) = go (f a)
>   go (Done b) = b
>
> -- | This works for all monads
> tailRecM1 :: Monad m => (a -> m (Step a b)) -> a -> m b
> tailRecM1 f a = do
>   f a >>= \case
>     Loop a' -> tailRecM1 f a'
>     Done b -> pure b
>
> -- | This works for all monads with a "distribute" operation over
> -- @Step a@ and is guaranteed tail recursive via @tailRec at .
> tailRecM2 ::
>   Monad m =>
>   (m (Step a b) -> Step a (m b)) ->
>   (a -> m (Step a b)) ->
>   a ->
>   m b
> tailRecM2 distribute f = tailRec (distribute . f)
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/libraries/attachments/20220927/6c17f584/attachment.html>


More information about the Libraries mailing list