
Hi Arie (and others who are interested in the regions library),
I would like to let you know that I'm working on a new version of my
regions package and its reverse dependencies:
regions-monadsfd, regions-monadstf,
safer-file-handles, regional-pointers and usb-safe.
The major change is that I removed the Resource class:
class Resource resource where
data Handle resource ∷ *
open ∷ resource → IO (Handle resource)
close ∷ Handle resource → IO ()
in favor of a much more simple interface, namely:
-- | An 'IO' computation that closes or finalizes a resource. For example
-- 'hClose' or 'free'.
type CloseAction = IO ()
-- | A handle to a 'CloseAction' that allows you to duplicate the action to a
-- parent region using 'dup'.
newtype CloseHandle (r ∷ * → *)
-- | Register the 'CloseAction' in the region. When the region terminates all
-- registered close actions will be perfomed if they're not duplicated to a
-- parent region.
register ∷ MonadIO pr ⇒ CloseAction → RegionT s pr (CloseHandle (RegionT s pr))
Here's an example how to use this new interface from my updated
regional-pointers package:
import qualified Foreign.Marshal.Alloc as FMA
-- | A regional handle to memory. This should provide a safer replacement for
-- Foreign.Ptr.Ptr
data RegionalPtr α (r ∷ * → *) = RegionalPtr (Ptr α) (CloseHandle r)
{-| Allocates the given number of bytes and returns a
regional pointer to them.
This should provide a safer replacement for:
Foreign.Marshal.Alloc.mallocBytes.
-}
mallocBytes ∷ MonadCatchIO pr
⇒ Int
→ RegionT s pr (RegionalPtr α (RegionT s pr))
mallocBytes size = block $ do
ptr ← liftIO $ FMA.mallocBytes size
let closeAction = free ptr
ch ← register closeAction
return $ RegionalPtr ptr ch
And here's an example from safer-file-handles:
-- | A regional handle to an opened file parameterized by the 'IOMode' in which
-- you opened the file and the region in which it was created.
data RegionalFileHandle ioMode (r ∷ * → *) =
RegionalFileHandle (Handle ioMode) (CloseHandle r)
openFile ∷ MonadCatchIO pr
⇒ FilePath
→ IOMode ioMode
→ RegionT s pr
(RegionalFileHandle ioMode (RegionT s pr))
openFile = openNormal E.openFile
-- | Opens a file in binary mode then yields a regional handle to it. This
-- provides a safer replacement for System.IO.openBinaryFile.
openBinaryFile ∷ MonadCatchIO pr
⇒ FilePath
→ IOMode ioMode
→ RegionT s pr
(RegionalFileHandle ioMode (RegionT s pr))
openBinaryFile = openNormal E.openBinaryFile
openNormal ∷ MonadCatchIO pr
⇒ (FilePath → IOMode ioMode → IO (E.Handle ioMode))
→ FilePath
→ IOMode ioMode
→ RegionT s pr
(RegionalFileHandle ioMode (RegionT s pr))
openNormal open filePath ioMode = block $ do
h ← liftIO $ open filePath ioMode
let closeAction = sanitizeIOError $ hClose h
ch ← register closeAction
return $ RegionalFileHandle h ch
I haven't released it yet because I need to write some more
documentation. However all the repositories contain the new code:
darcs get http://code.haskell.org/~basvandijk/code/regions
darcs get http://code.haskell.org/~basvandijk/code/regions-monadsfd
darcs get http://code.haskell.org/~basvandijk/code/regions-monadstf
darcs get http://code.haskell.org/~basvandijk/code/regional-pointers
darcs get http://code.haskell.org/~basvandijk/code/safer-file-handles
darcs get http://code.haskell.org/~basvandijk/code/usb-safe
and some examples:
darcs get http://code.haskell.org/~basvandijk/code/usb-safe-examples
darcs get http://code.haskell.org/~basvandijk/code/safer-file-handles-examples
darcs get http://code.haskell.org/~basvandijk/code/usb-safe-and-safer-file-handles-exa...
Regards,
Bas
On Wed, Jun 2, 2010 at 3:13 PM, Bas van Dijk
On Wed, Jun 2, 2010 at 2:57 PM, Arie Peterson
wrote: On Wed, Jun 2, 2010 at 2:28 PM, Bas van Dijk
wrote: Before answering your questions I would like to make sure I understand your Resource type. When I want to create a memory Resource for example is the following what you have in mind?
{-# LANGUAGE Rank2Types #-}
-- from base: import Foreign.Ptr ( Ptr ) import Foreign.Marshal.Alloc ( mallocBytes, free )
-- from transformers: import Control.Monad.IO.Class ( liftIO )
-- from MonadCatchIO-transformers: import Control.Monad.CatchIO ( MonadCatchIO, bracket )
newtype Resource cap m = Resource { with :: forall a. (cap -> m a) -> m a }
type Memory m a = Resource (Ptr a) m
memory :: MonadCatchIO m => Int -> Memory m a memory size = Resource $ bracket (liftIO $ mallocBytes size) (liftIO . free)
Yes, exactly. I also create type aliases for resources providing a specific capability.
On Wed, 2 Jun 2010 14:45:08 +0200, Bas van Dijk
wrote: The previous can also be generalized using my Resource class:
-- from regions: import qualified Control.Resource as C ( Resource(..) )
resource :: (MonadCatchIO m, C.Resource resource) => resource -> Resource (C.Handle resource) m resource r = Resource $ bracket (liftIO $ C.open r) (liftIO . C.close)
Yes, definitely.
(This is not a literal generalisation of the 'memory' function, unless you make 'Int' an instance of 'C.Resource'; one would probably create a special type 'data Memory = Memory Int' instead. This is the difference I alluded to in my earlier email.)
Indeed.
My regional-pointers package provides this Memory type and an instance for Resource: http://hackage.haskell.org/packages/archive/regional-pointers/0.1.0.2/doc/ht...
Now I'm beginning to understand the problem with your 'fallback' function. If I specialize the capability to Handles to Memory as in:
-- from regional-pointers: import Foreign.Ptr.Region ( Memory )
fallback :: Resource (C.Handle (Memory a)) IO -> Resource (C.Handle (Memory a)) IO -> Resource (C.Handle (Memory a)) IO fallback (Resource primary) (Resource backup) = Resource l where l c = primary c `catch` (\(SomeException _) -> backup c)
then the only way to create a value of type 'Resource (C.Handle (Memory a))' is to apply my previously posted 'resource' function to 'Memory nrOfBytes'. There's no other way to create Handles to Memory. Is that your problem?
The problem is that Handle is an associated _data_ type not an associated _type synonym_:
class Resource resource where data Handle resource ∷ * open ∷ resource → IO (Handle resource) close ∷ Handle resource → IO ()
So 'Handle' is an injective type function which means that every 'Handle resource' has only one 'resource'.
I could try turning 'Handle' into an associated type synonym.
Regards,
Bas
participants (1)
-
Bas van Dijk