foo :: Monad m => (m a -> m a) -> m a -> m a
foo kv m = m >>= kv . return
occurs a lot as a partial application foo kv (currently inline as (>>= kv . return) $ ...).
foo kv m is not the same as kv m; the latter performs effects in kv before performing effects in m and it is crucial for my use case to “squeeze dry” m of any effects before calling kv.
I can’t restrict kv to the more specific type a -> m a; so simply bind = flip (>>=) and writing bind kv $ ... is not an option.
So what would be an appropriate or established name for foo? It’s kind of like call-by-value, but for effects. (Of course it is nothing like actual call-by-value, because the a is not necessarily evaluated.)
(=<<) indeed seems like a good builtin way to make (>>= kv . return) $ bleh $ do ... blocks nicer.
Although I do wonder what kinds of kvs you have that cannot be rewritten to have the type a -> m a.
My kv is actually a parameter body to a type class method
class HasBind m v where
bind :: (m v -> m v) -> (m v -> m v) -> m v
instance HasBind M V where
bind rhs body = body . return =<< fix rhs -- can be much more complicated than a mere `fix rhs`
There are instances that just do bind rhs body = body (fix rhs) (“call-by-name”), hence I need this combinator.
An interesting combinator and perhaps more principled, but I think I prefer @jaror’s solution because I don’t want to parenthesize m (which can be quite big)
Edit: Of course, f =<< m needs parens as well when m = bleh $ do .... Sigh, won’t get much better, I guess.
# ghci
GHCi, version 9.4.4: https://www.haskell.org/ghc/ :? for help
ghci> :t \ kv m -> m >>= kv . return
\ kv m -> m >>= kv . return
:: (Monad m1, Monad m2) => (m2 a -> m1 b) -> m1 a -> m1 b
ghci>
Now if the type is limited to:
Monad m => (m a -> m b) -> m a -> m b
…it’s a monadic version of ($!):
ghci> :t ($!)
($!) :: (a -> b) -> a -> b
ghci>
Gofer had a primitive with that same type called strict, which suggests:
strictM :: Monad m => (m a -> m b) -> m a -> m b
strictM kv m = m >>= kv . return
For any law-respecting monad these two definitions of bind should be equivalent, due to the right identity law. Also note that bind is a common spoken name for the >>= operator, so your new method name could be confusing.
Mea culpa. What I said is still worth pointing out, but let me be more pedantic. The two instances will be equivalent if the following chain of two equations holds:
m >>= f . return == f (m >>= return) == f m
The second equation is implied by the right identity law, the first is true for most common f and m, but it doesn’t hold for f == const or for another example (>>=) = undefined. I take the OP’s question to be inspired by an industrial problem, so they may not be bothered by this.
Addendum: I think gofer’s strict function is actually just $! and that is not the same as \f x -> x >>= f . return. Forcing x does not have anything to do with forcing its effect. Think of m = putStrLn "foo"; forcing m is not the same as running the IO action. In general, forcing evaluation in the host language is not the same as forcing an effect encoded in the host language.