Lazy idempotent monadic actions

Say I have some function that accepts a monadic action, of type m a. I’ll use the result of this action zero or more times, to be determined at run time. If the action has a side effect, I want that effect to happen at most once, and not at all if the result isn’t needed.

It’d be nice to have an operator idem :: m a -> m (m a) that would wrap the action and provide that guarantee with laws in the spirit of:

  • idem ma $> () = pure ()
  • join (idem ma) = ma
  • idem ma >>= (\ma' -> ma' *> ma') = ma

Some monads (Either, e.g.) don’t have effects that can happen more than once; these actions are trivially idempotent, and idem = pure suffices for them.

Other monads (IO, e.g.) allow for creating refs of some variety, which I can use to memoize a result:

idem ma = newIORef Nothing <&> \ref ->
  readIORef ref >>= maybe (ma >>= \a -> writeIORef ref (Just a) $> a) pure

Still other monads ([], I think) probably can’t support this operator at all.

Is there a MonadIdem class or something that already contains this operator, or something equivalent? Or is this problem generally solved a different way, perhaps by wrapping any effectful actions with monad-specific logic outside of the code region that parameterizes over the application’s monad of choice?

4 Likes

For reference, here’s a discussion about a combinator to run an action exactly once (rather than at most once):

There is also an old discussion about “occult effects” on haskell cafe. The discussion is about monads m where idem = pure, in which case your first requirement can be more concisely written as a >> b = b. There are Haskell monads that have this property, but not many. The mathematicians call these the “affine” monads, the effect researchers call it a “discardable” effect.
My gut feeling is that idem can not be implemented for general m because it is undecidable in general whether a function is constant or not. (It would solve the halting problem.)

This sounds like lazy evaluation, i.e., memoisation of effectful computations.

I think you can turn any Monad into a memoised/“idempotent” monad by wrapping StateT (Heap m) around it, where Heap m can be implemented as IntMap (StateT (Heap m) m Any) (I realise that people would prefer to have some type foo to index this IntMap by a Tagged a that carries the return type a instead of Any), and the idem operation can be implemented very roughly as (didn’t type-check or anything, I hope you can make some sense of it)

type MemoT m = StateT (Heap m) m
type Heap m = IntMap (MemoT m Any)
type Addr = Int
idem :: MemoT m a -> MemoT m (MemoT m a)
idem ma = StateT (\h -> let a = nextFree h in (return (fetch a, IntMap.insert a h (memo a ma))))
fetch :: Addr -> MemoT m a -- Perhaps use `Tagged a Addr` for type safety; but doesn't matter much because it's all internal
fetch a = join (gets (\h -> IntMap.lookup a h))
memo :: Addr -> MemoT m a -> MemoT m a
memo a ma = ma >>= \v -> modify (\h -> IntMap.insert a (return v))

Of couse, you can also use IORefs to implement the Heap; seems simpler if you are in IO anyway.