Question

Is there a way to scope runResourceT to the lifetime of a single Sink?

I'm trying to build a Sink that wraps a potentially infinite number of Sinks. This works fine with threads but I'm trying to do it without threads. It seems like it should be possible. I've hit a road block due to the scoping of runResourceT: I get either too coarsely grained (but functional) or much too finely grained (totally broken) resource management.

{-# LANGUAGE FlexibleContexts #-}

import Control.Monad.Trans (lift)
import Control.Monad.Trans.Resource
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as BC8 (pack)
import Data.Conduit
import qualified Data.Conduit.Binary as Cb
import qualified Data.Conduit.List as Cl
import System.FilePath ((<.>))

test :: IO ()
test =
  runResourceT
      $ Cl.sourceList (fmap (BC8.pack . show) [(1 :: Int)..1000])
     $$ rotateResourceHog "/tmp/foo"

-- |
-- files are allocated on demand but handles are released at the same time
rotateResourceHog
  :: MonadResource m
  => FilePath -> Sink ByteString m ()
rotateResourceHog filePath = step 0 where
  step i = do
    x <- Cl.peek
    case x of
      Just _  -> do
        chunkWriter $ filePath <.> show (i :: Integer)
        -- loop
        step $ i+1

      Nothing -> return ()

-- |
-- files are allocated on demand but handles are released immediately
rotateUsingClosedHandles
  :: (MonadBaseControl IO m, MonadResource m)
  => FilePath -> Sink ByteString m ()
rotateUsingClosedHandles filePath = step 0 where
  step i = do
    x <- Cl.peek
    case x of
      Just _  -> do
        transPipe runResourceT . chunkWriter $ filePath <.> show (i :: Integer)
        -- loop
        step $ i+1

      Nothing -> return ()

chunkWriter
  :: MonadResource m
  => FilePath -> Sink ByteString m ()
chunkWriter filePath = do
  _ <- lift $ allocate (putStrLn "alloc") (\ _ -> putStrLn "free")

  -- the actual conduit chain is more complicated
  Cl.isolate 100 =$= Cb.sinkFile filePath
Was it helpful?

Solution

ResourceT is only intended to clean up resources in exceptional cases. It is not intended to provide prompt finalization, only guaranteed finalization. For promptness, conduit provides its own facilities for handling cleanup. In your case, you're looking for both: you want cleanup to happen as early as possible, and to occur even in the case of an exception being thrown. For this, you should use bracketP. For example:

chunkWriter
  :: MonadResource m
  => FilePath -> Sink ByteString m ()
chunkWriter filePath = bracketP
    (putStrLn "alloc")
    (\() -> putStrLn "free")
    (\() -> Cl.isolate 100 =$= Cb.sinkFile filePath)

This results in the desired interleaving of alloc and free outputs.

Licensed under: CC-BY-SA with attribution
Not affiliated with StackOverflow
scroll top