[Haskell-cafe] ANN: Updates in the monadic regions family
Bas van Dijk
v.dijk.bas at gmail.com
Thu Mar 10 14:03:03 CET 2011
In regions-0.9 I removed support for forking threads because it
allowed you to use a closed handle in a forked thread. Unfortunately I
just realized that it's still possible to fork threads in a region.
The reason is that I've derived a MonadControlIO instance for RegionT
which enables you to use forkIO as demonstrated by the following
program:
---------------------------------------------------------------------
{-# LANGUAGE UnicodeSyntax, NoImplicitPrelude, KindSignatures #-}
module Main where
-- from base:
import Data.Function ( ($) )
import Control.Concurrent ( ThreadId, forkIO, threadDelay )
import Control.Monad ( (>>=), liftM, void )
import System.IO ( IO )
-- from transformers:
import Control.Monad.IO.Class ( liftIO )
-- from regions:
import Control.Monad.Trans.Region ( RegionT, runRegionT )
-- from safer-file-handles:
import System.IO.SaferFileHandles ( openFile
, IOMode(ReadMode)
, hGetContents
, putStrLn
)
-- from pathtype:
import System.Path.Posix ( asAbsFile )
-- from monad-control:
import Control.Exception.Control ( mask_ )
import Control.Monad.IO.Control ( MonadControlIO, liftControlIO )
main ∷ IO ()
main = do runRegionT region
threadDelay 1500000
region ∷ MonadControlIO pr ⇒ RegionT s pr ()
region = do
putStrLn "Running region"
h ← openFile (asAbsFile "/etc/passwd") ReadMode
_ ← liftForkIO $ do
putStrLn "Forked region"
liftIO $ threadDelay 1000000
hGetContents h >>= putStrLn
liftIO $ threadDelay 500000
putStrLn "Exiting region"
liftForkIO ∷ MonadControlIO m ⇒ m α → m ThreadId
liftForkIO m = liftControlIO $ \runInIO →
forkIO $ void $ runInIO m
---------------------------------------------------------------------
Executing main yields the following error:
> main
Running region
Forked region
Exiting region
<interactive>: /etc/passwd: hGetContents: illegal operation (handle is closed)
I think the only solution is to drop the derived MonadControlIO and
MonadTransControl instances. Unfortunately the packages that use
regions require this instance because they need to use mask_ when
opening resources. Here an example from safer-file-handles:
openFile ∷ (MonadControlIO pr, AbsRelClass ar)
⇒ FilePath ar
→ IOMode ioMode
→ RegionT s pr
(RegionalFileHandle ioMode (RegionT s pr))
openFile = openNormal E.openFile
openNormal open = \filePath ioMode → mask_ $ do
h ← liftIO $ open (getPathString filePath) ioMode
ch ← onExit $ sanitizeIOError $ hClose h
return $ RegionalFileHandle h ch
I guess I have to solve this by providing a custom mask_ function or
using MonadCatchIO-transformers as I did before.
I'm going to think about the best solution. In the mean time just
don't use something like liftForkIO.
Regards,
Bas
More information about the Haskell-Cafe
mailing list