
Dear list, For some time, I have maintained a small private module centred around the following type of "resource":
newtype Resource cap m = Resource { with :: forall a. (cap -> m a) -> m a }
Interpretation: @Resource cap m@ is a resource, providing a "capability" of type @cap@, which does administration (like opening and closing handles) in the monad @m@. I would like to use a standard module instead of this howe-grown one, so I can publish things that depend on it. Does anyone know a package that provides this? Things I tried: - The type is suspiciously similar to the continuation monad transformer; in fact @Resource cap m@ is isomorphic to @forall t. ContT t m cap@. However, I can't use this latter type directly, because I would like functions on Resources like the instance
instance (Monoid cap) => Monoid (Resource cap m)
, which is not possible without a newtype wrapper. - I tried using the "regions" package, since it has a very similar purpose, but this seems impossible: some resources I could not express in the form required for its class 'Resource' (methods 'open' and 'close'). If something like this is not yet around, I'll upload my version, but I'd like to reuse, if possible. Regards, Arie

On Mon, May 31, 2010 at 12:08 PM, Arie Peterson
- I tried using the "regions" package, since it has a very similar purpose, but this seems impossible: some resources I could not express in the form required for its class 'Resource' (methods 'open' and 'close').
Hi Arie, I would love to see some examples of these resources for which you can't define a Resource[1] instance. Regards, Bas [1] http://hackage.haskell.org/packages/archive/regions/0.5/doc/html/Control-Res...

On Tue, 1 Jun 2010 21:10:40 +0200, Bas van Dijk
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

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
On Tue, 1 Jun 2010 21:10:40 +0200, Bas van Dijk
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-Res... 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

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
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
wrote: On Tue, 1 Jun 2010 21:10:40 +0200, Bas van Dijk
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-Res... 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

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
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

On Wed, Jun 2, 2010 at 2:57 PM, Arie Peterson
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 (2)
-
Arie Peterson
-
Bas van Dijk