
I wanted a monadic unfoldr and couldn't see one so I thought I'd share two possibilities I'd been playing with: unfoldM_a :: Monad m => (b -> Maybe (m (a, b))) -> b -> m [a] unfoldM_a f base = case f base of Nothing -> return [] Just result -> do (a, b) <- result rest <- unfoldM_a f b return (a : rest) unfoldM_b :: Monad m => (b -> m (Maybe (a, b))) -> b -> m [a] unfoldM_b f base = do fb <- f base case fb of Nothing -> return [] Just (a, b) -> do rest <- unfoldM_b f b return (a : rest) test_case_a "" = Nothing test_case_a word@(_:xs) = Just (do a <- print (length word) return (a, xs)) test_case_b "" = return Nothing test_case_b word@(_:xs) = do a <- print (length word) return (Just (a, xs)) main = unfoldM_a test_case_a "foo" putStr "----\n" unfoldM_b test_case_b "foo" -- Mark

Mark T.B. Carroll writes: | I wanted a monadic unfoldr and couldn't see one so I thought I'd share two | possibilities I'd been playing with: | | | unfoldM_a :: Monad m => (b -> Maybe (m (a, b))) -> b -> m [a] : | unfoldM_b :: Monad m => (b -> m (Maybe (a, b))) -> b -> m [a] : Of those two, I prefer unfoldM_b because it gives you the opportunity to do some stuff in the monad before you decide between Just and Nothing. Here's a third, which merges the roles of Maybe and m. import Control.Monad.Error -- for instance MonadPlus IO -- and the reexport of MonadPlus unfoldM_c :: MonadPlus m => (b -> m (a, b)) -> b -> m [a] unfoldM_c f b = do (a, b) <- f b as <- unfoldM_c f b return (a:as) `mplus` return [] This has the (possibly undesirable) effect, when m is [], of generating all prefixes of the full unfolded list. - Tom
participants (2)
-
Mark T.B. Carroll
-
Tom Pledger