ANN: Updates in the monadic regions family

Dear all, I released new versions of some of my packages. Here are the changelogs: http://hackage.haskell.org/package/regions-0.9 http://hackage.haskell.org/package/regions-mtl-0.3.1.5 http://hackage.haskell.org/package/regions-monadstf-0.3.1.5 * Switch from monad-peel to monad-control. * Removed Control.Monad.Trans.Region.Concurrent. The fork functions contained bugs which could not be fixed. I'm working on a way to copy handles from one thread to another but the design has not settled yet. * Removed Data.RegionRef. I always considered this module a bit of a wart. * Added support for local regions. Primarily needed for the alloca functions from the regional-pointers package. More on that below. http://hackage.haskell.org/package/regional-pointers-0.6 * Switch from monad-peel to monad-control. * Major API change: Use the new local regions. This means that instead of: alloca ∷ (Storable α, MonadPeelIO pr) ⇒ (∀ s. RegionalPtr α (RegionT s pr) → RegionT s pr β) → pr β I now have: alloca ∷ (Storable α, MonadControlIO pr) ⇒ (∀ sl. LocalPtr α (LocalRegion sl s) → RegionT (Local s) pr β) → RegionT s pr β This allows my alloca to use the native alloca which is more efficient than doing a manual malloc and free as I did before. The type also allows to open resources in the continuation and use them outside the continuation and visa versa. * Have separate types for the three different pointers: - RegionalPtr: for pointers created using malloc. - LocalPtr: for pointers created using alloca. - NullPtr: for the nullPtr. * Add the type classes Pointer and AllocatedPointer to classify them. http://hackage.haskell.org/package/safer-file-handles-0.10 http://hackage.haskell.org/package/safer-file-handles-bytestring-0.2 http://hackage.haskell.org/package/safer-file-handles-text-0.2 * Switch from monad-peel to monad-control. * Support regional-pointers-0.6 and use its overloaded pointers. * Add separate types for standard handles: StdFileHandle and normal handles: RegionalFileHandle. * Add the type class FileHandle to group them. * Overload the filehandle in operations. http://hackage.haskell.org/package/usb-0.8 * getStrDesc and getStrDescFirstLang now return a Text instead of a String. This is a more efficient and cleaner interface. http://hackage.haskell.org/package/usb-enumerator-0.3 * Switch from monad-peel to monad-control. * Support iteratee-0.8.*. * Support usb-0.9. http://hackage.haskell.org/package/usb-safe-0.12 * Switched from monad-peel to monad-control. * Exported the ReadEndpoint, WriteEndpoint and EnumReadEndpoint type classes so you can refer to them in type signatures. * Support usb-0.8: getStrDesc and getStrDescFirstLang now return a Text instead of a String. * Support regions-0.9. * Support usb-enumerator-0.3. * Support iteratee-0.8.*. Regards, Bas

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
participants (1)
-
Bas van Dijk