Hi @bruce-wayne
Do you mean like this? If not, could you say more about what you mean?
import Bluefin.EarlyReturn (returnEarly, withEarlyReturn)
import Bluefin.IO (effIO, runEff)
import Bluefin.Stream (yield, yieldToList)
import Data.Foldable (for_)
baz :: [Int] -> IO ([Int], Maybe Int)
baz count = runEff $ \io -> do
(as, ma) <- yieldToList $ \y -> do
withEarlyReturn $ \ret -> do
for_ count $ \a -> do
yield y a
if even a
then do
returnEarly ret (Just a)
else
effIO io (print a)
pure Nothing
let message = case ma of
Just a -> show a <> " is even!"
Nothing -> "There was no even element"
effIO io (putStrLn message)
pure (as, ma)
-- ghci> baz [1, 3, 5, 7]
-- 1
-- 3
-- 5
-- 7
-- There was no even element
-- ([1,3,5,7],Nothing)
-- ghci> baz [1, 3, 4, 5, 7]
-- 1
-- 3
-- 4 is even!
-- ([1,3,4],Just 4)
I take it this is a separate question? If so, yes, it works with foldM
, but there’s no real need for foldM
if you’re using Bluefin. It’s probably easier just to use for_
and evalState
:
import Control.Monad (foldM, when)
import Bluefin.EarlyReturn (returnEarly, withEarlyReturn)
import Bluefin.IO (effIO, runEff)
import Bluefin.Jump (jumpTo, withJump)
import Bluefin.State (evalState, get, put)
import Bluefin.Stream (yield, yieldToList)
import Data.Foldable (for_)
runningSumUntilNegativeFoldM l = runEff $ \io -> do
withJump $ \done -> do
(\f -> foldM f 0 l) $ \soFar i -> do
when (i < 0) $
jumpTo done
let next = soFar + i
effIO io (print next)
pure next
pure ()
-- ghci> runningSumUntilNegativeFoldM [1, 2, 3, 4, -1, 5]
-- 1
-- 3
-- 6
-- 10
runningSumUntilNegativeFor l = runEff $ \io -> do
withJump $ \done -> do
evalState 0 $ \total -> do
for_ l $ \i -> do
when (i < 0) $
jumpTo done
soFar <- get total
let next = soFar + i
effIO io (print next)
put total next
-- ghci> runningSumUntilNegativeFor [1, 2, 3, 4, -1, 5]
-- 1
-- 3
-- 6
-- 10