[Haskell-cafe] Resource module

Bas van Dijk v.dijk.bas at gmail.com
Wed Jun 2 09:13:29 EDT 2010


On Wed, Jun 2, 2010 at 2:57 PM, Arie Peterson <ariep at xs4all.nl> wrote:
>> 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.)

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/html/Foreign-Ptr-Region.html#t%3AMemory

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


More information about the Haskell-Cafe mailing list