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) Regards, Bas On Wed, Jun 2, 2010 at 2:28 PM, Bas van Dijk <v.dijk....@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) > > Regards, > > Bas > > On Wed, Jun 2, 2010 at 1:11 AM, Arie Peterson <ar...@xs4all.nl> wrote: >> On Tue, 1 Jun 2010 21:10:40 +0200, Bas van Dijk <v.dijk....@gmail.com> >> wrote: >> | [...] >> | Hi Arie, I would love to see some examples of these resources for >> | which you can't define a Resource[1] instance. >> | [...] >> | >> | [1] >> | >> http://hackage.haskell.org/packages/archive/regions/0.5/doc/html/Control-Resource.html >> >> >> I had this involved example of a function that takes a resource, and >> returns a similar resource, which performs the relevant IO actions in a >> separate thread, receiving its instructions over a concurrent channel. >> However, in the course of explaining why it doesn't fit in the simple >> open/Handle/close framework, I actually helped myself to see that it is >> possible (and not difficult) :-). >> >> >> A different scenario where the open/Handle/close framework may actually >> not suffice is the following: >> >>> fallback :: Resource cap IO -> Resource cap IO -> Resource cap IO >>> fallback (Resource primary) (Resource backup) = Resource l where >>> l c = primary c `catch` (\ ProblemWithMainResource -> backup c) >> >> ; the fact that @c@, the "continuation" (which describes how the >> capability is used), is mentioned twice in the body of @l@ makes this a >> weird case. >> >> >> By the way, Bas, I'm not quite sure how to properly use your Resource >> class. Should one create different datatypes for different resources, if >> they have different handle types or open/close functions, even though they >> provide the same "capability"? I would like to avoid this, if possible, to >> make life easier for users of these resources (they just want a resource >> providing a certain capability, and don't care about its internal state). I >> suppose one can create a class of resources giving a certain capability >> instead. >> >> >> Kind regards, >> >> Arie >> >> > _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe