characterization of subset of Monads that respect tail calls?

Hello everyone! a recent conversation I has having led to an interesting question: is there a good interface or something for Monads which guarantee tail calls are tail calls? (ideally via a stronger api assumption for tail position computations in a monad rather than "trustme" style api contracts) thx -Carter

https://pursuit.purescript.org/packages/purescript-tailrec/6.1.0/docs/Contro...
seems like a good starting point
On Tue, 27 Sept 2022, 6:39 am Carter Schonwald,
Hello everyone! a recent conversation I has having led to an interesting question: is there a good interface or something for Monads which guarantee tail calls are tail calls? (ideally via a stronger api assumption for tail position computations in a monad rather than "trustme" style api contracts)
thx -Carter _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Hey Isaac,
thats certainly an interesting approach, it seems like that solves it by
reframing the question as "can you implement a loop/trampoline in the
monad". It would be even cooler to have an approach that does proper tail
calls i think ..
On Mon, Sep 26, 2022 at 8:15 PM Isaac Elliott
https://pursuit.purescript.org/packages/purescript-tailrec/6.1.0/docs/Contro... seems like a good starting point
On Tue, 27 Sept 2022, 6:39 am Carter Schonwald, < carter.schonwald@gmail.com> wrote:
Hello everyone! a recent conversation I has having led to an interesting question: is there a good interface or something for Monads which guarantee tail calls are tail calls? (ideally via a stronger api assumption for tail position computations in a monad rather than "trustme" style api contracts)
thx -Carter _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

On Tue, Sep 27, 2022 at 10:15:29AM +1000, Isaac Elliott wrote:
https://pursuit.purescript.org/packages/purescript-tailrec/6.1.0/docs/Contro... 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@. 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)

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@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/Contro...
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@. 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@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

On Tue, Sep 27, 2022 at 05:24:43PM -0400, A S wrote:
The definition tailRecM1, while it typechecks, will not always operate in constant stack space
Correct.
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).
Correct, the distribution property is too strong to capture all MonadRec instances. However, it does capture Maybe, Either e and Identity. To capture (r ->)/Reader we need something more general (tailRecM3) which is sadly significantly less pleasant, but unless I am much mistaken it captures all instances of tailRecM that use tailRec. Maybe it's too unpleasant to be used in practice as an alternative of a direct implementation of tailRecM. Tom {-# LANGUAGE LambdaCase #-} module Rec where import Data.Functor.Identity (Identity(Identity)) data Step a b = Loop a | Done b onDone :: (b -> b') -> Step a b -> Step a b' onDone f = \case Loop a -> Loop a Done b -> Done (f b) 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 but is not necessarily stack safe. 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 particular distribution property -- and is stack safe through the use of @tailRec@. tailRecM3 :: Monad m => ((a -> m (Step a b)) -> m (a -> Step a l)) -> (l -> m b) -> (a -> m (Step a b)) -> a -> m b tailRecM3 distribute finish f a = do g <- distribute f finish (tailRec g a) tailRecReader :: (a -> r -> Step a b) -> a -> r -> b tailRecReader = tailRecM3 (\f r a -> f a r) (\b _ -> b) tailRecDistribute :: Monad m => (m (Step a b) -> Step a (m b)) -> (a -> m (Step a b)) -> a -> m b tailRecDistribute distribute = tailRecM3 (\f -> pure (\a -> distribute (f a))) id tailRecMaybe :: (a -> Maybe (Step a b)) -> a -> Maybe b tailRecMaybe = tailRecDistribute $ \case Nothing -> Done Nothing Just j -> onDone pure j tailRecEither :: (a -> Either e (Step a b)) -> a -> Either e b tailRecEither = tailRecDistribute $ \case Left e -> Done (Left e) Right r -> onDone pure r tailRecIdentity :: (a -> Identity (Step a b)) -> a -> Identity b tailRecIdentity = tailRecDistribute $ \case Identity i -> onDone pure i

On Mon, Sep 26, 2022 at 04:38:47PM -0400, Carter Schonwald wrote:
is there a good interface or something for Monads which guarantee tail calls are tail calls? (ideally via a stronger api assumption for tail position computations in a monad rather than "trustme" style api contracts)
*> is exactly for tail calls, isn't it? Consider its type (*>) :: m a -> m b -> m b It looks like it is saying that it doesn't need to save any of the context from the 'm a' call during evaluation of the 'm b' call, because the overall result is just the result of the 'm b' call. Is that what you were looking for, or was it something else? Tom
participants (4)
-
A S
-
Carter Schonwald
-
Isaac Elliott
-
Tom Ellis