opened 11:25AM - 28 May 24 UTC
<!--
Thanks for raising a new CLC proposal.
Before proceeding, please make s…ure that you read and understand [`README.md`](https://github.com/haskell/core-libraries-committee#readme) and [`PROPOSALS.md`](https://github.com/haskell/core-libraries-committee/blob/main/PROPOSALS.md).
This is not a general bug tracker for `base`; it's expected that you not only describe a problem, but also offer a solution, which you are prepared to implement. If you want just to "file-and-forget", raise an issue at https://gitlab.haskell.org/ghc/ghc/-/issues.
-->
Data.List exposes `foldM`, but not `unfoldM`. `unfoldM` can be useful when producing a list whose size depends on a monadic context.
The only viable alternative I can think of to produce these kinds of lists, without depending on other libraries, is explicit recursion.
Other libraries *do* export this function: [hoogle search](https://hoogle.haskell.org/?hoogle=unfoldM&scope=set%3Astackage), albeit with some variation in signatures.
I think it would be reasonable to add `unfoldM` to `Data.List`, (and, for consistency, `Data.List.NonEmpty`).
I do not think this is adding undue mental burden on the user, as its name is consistent (`unfold` with a `M`onadic context, as is the naming scheme for many functions).
Here is the implementation of `Data.List.unfoldM` I think would be reasonable:
```haskell
unfoldM :: forall a seed m. Monad m => (seed -> m (Maybe (a, seed))) -> seed -> m [a]
unfoldM f initialSeed = f initialSeed >>= step
where
step :: Maybe (a, seed) -> m [a]
step mTup = case mTup of
Nothing -> pure []
Just (el, seed) -> (el :) <$> unfoldM f seed
```
And here's a version I think would be a reasonable addition to `Data.List.NonEmpty`:
```haskell
{-# LANGUAGE ScopedTypeVariables #-}
unfoldM :: forall a seed m. Monad m => (seed -> m (a, Maybe seed)) -> seed -> m (NonEmpty a)
unfoldM f initialSeed = do
(x, mSeed) <- f initialSeed
(x :|) <$> g mSeed
where
g :: Maybe seed -> m [a]
g mSeed = case mSeed of
Nothing -> pure []
Just seed -> f seed >>= h
h :: (a, Maybe seed) -> m [a]
h (x, mSeed) = (x :) <$> g mSeed
```
Open questions:
* Is there some kind of fusion possible? (I suspect not)
* Is there a more general form?[^1] (I suspect not)
* Do we need/want `l` and `r` variants?
* Do we need/want strict/lazy variants?
[^1]: This gets into the rabbit hold of whether the `Foldable` typeclass should have a dual...