It’s not difficult for Bluefin. You just write the code you want to write, in a direct style, without thinking about ResourceT. You don’t even need to think about bracket because withFile does the bracket for you. (In the code below there is a bracket for observability reasons only.)
main :: IO ()
main = runEff $ \io -> do
let dir = "/tmp/test-dir"
forEach (firstThreeLinesOfEach dir io) $ \line ->
effIO io (putStrLn line)
firstThreeLinesOfEach ::
(e1 :> es, e2 :> es) =>
FilePath ->
IOE e1 ->
Stream String e2 ->
Eff es ()
firstThreeLinesOfEach dir io y = do
filenames <- effIO io (listDirectory dir)
let sortedFilenames = sort filenames
for_ sortedFilenames $ \filename -> do
let filepath = dir <> "/" <> filename
let firstThree = take 3 (linesOfFile filepath io)
forEach firstThree (yield y)
-- General purpose Bluefin function for streaming the
-- lines of a file. Perhaps it should be part of the
-- Bluefin standard library
linesOfFile ::
(e1 :> es, e2 :> es) =>
String ->
IOE e1 ->
Stream String e2 ->
Eff es ()
linesOfFile filename io y = do
withJump $ \onEOF -> do
withFile io filename ReadMode $ \h -> do
-- This bracket is only so we can observe the
-- prompt closing of the file.
bracket
(effIO io (putStrLn "File opened"))
(\() -> effIO io (putStrLn "File closed"))
( \() -> do
forever $ do
isEOF <- hIsEOF h
when isEOF $
jumpTo onEOF
yield y =<< hGetLine h
)
ghci> main
File opened
a1
a2
a3
File closed
File opened
b1
b2
b3
File closed
...
Full code
{-# LANGUAGE GHC2021 #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
import Bluefin.Compound (useImplUnder)
import Bluefin.Eff (Eff, bracket, (:&), (:>))
import Bluefin.IO (IOE, effIO, runEff)
import Bluefin.Jump (jumpTo, withJump)
import Bluefin.State (evalState, get, modify)
import Bluefin.Stream (Stream, forEach, yield)
import Bluefin.System.IO (Handle, unsafeWithHandle, withFile)
import Control.Monad (forever, when)
import Data.Foldable (for_)
import Data.List (sort)
import System.Directory
import System.IO (IOMode (ReadMode))
import System.IO qualified
import Prelude hiding (take)
main :: IO ()
main = runEff $ \io -> do
let dir = "/tmp/test-dir"
forEach (firstThreeLinesOfEach dir io) $ \line ->
effIO io (putStrLn line)
firstThreeLinesOfEach ::
(e1 :> es, e2 :> es) =>
FilePath ->
IOE e1 ->
Stream String e2 ->
Eff es ()
firstThreeLinesOfEach dir io y = do
filenames <- effIO io (listDirectory dir)
let sortedFilenames = sort filenames
for_ sortedFilenames $ \filename -> do
let filepath = dir <> "/" <> filename
let firstThree = take 3 (linesOfFile filepath io)
forEach firstThree (yield y)
-- General purpose Bluefin function for streaming the
-- lines of a file
linesOfFile ::
(e1 :> es, e2 :> es) =>
String ->
IOE e1 ->
Stream String e2 ->
Eff es ()
linesOfFile filename io y = do
withJump $ \onEOF -> do
withFile io filename ReadMode $ \h -> do
-- This bracket is only so we can observe the
-- prompt closing of the file.
bracket
(effIO io (putStrLn "File opened"))
(\() -> effIO io (putStrLn "File closed"))
( \() -> do
forever $ do
isEOF <- hIsEOF h
when isEOF $
jumpTo onEOF
yield y =<< hGetLine h
)
-- This should be part of the Bluefin standard library
take ::
(e1 :> es) =>
Integer ->
(forall e. Stream a e -> Eff (e :& es) ()) ->
Stream a e1 ->
Eff es ()
take n k y =
withJump $ \done -> do
evalState n $ \s -> do
forEach (useImplUnder . k) $ \a -> do
s' <- get s
when (s' <= 0) $
jumpTo done
modify s (subtract 1)
yield y a
-- This should be part of the Bluefin standard library
hGetLine :: (e1 :> es) => Handle e1 -> Eff es String
hGetLine h = unsafeWithHandle h System.IO.hGetLine
-- This should be part of the Bluefin standard library
hIsEOF :: (e1 :> es) => Handle e1 -> Eff es Bool
hIsEOF h = unsafeWithHandle h System.IO.hIsEOF