[Haskell-cafe] Resource module

Arie Peterson ariep at xs4all.nl
Wed Jun 2 08:57:06 EDT 2010


> On Wed, Jun 2, 2010 at 2:28 PM, Bas van Dijk <v.dijk.bas at gmail.com>
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 <v.dijk.bas at gmail.com>
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.)


Regards,

Arie



More information about the Haskell-Cafe mailing list