Open expipiplus1 opened 4 years ago
You can do this, but getting the semantics right is incredibly difficult. I wouldn't document it, because I wouldn't recommend it.
It's possible to do something like this using only the safe parts of resourcet
. (At least the types match up and it passes some small amount of testing)
NestedResourceT
internally uses ReaderT
to pass around the deepest InternalState
(kept updated with local
), this 'ReaderT' is transforming a ResourceT
which keeps track of the 'InternalState's of the nested regions, making sure they're released properly.
newtype NestedResourceT m a = NestedResourceT
{ unNestedResourceT :: ReaderT InternalState (ResourceT m) a }
deriving newtype (Functor, Applicative, Monad, MonadIO)
instance MonadIO m => MonadResource (NestedResourceT m) where
liftResourceT (ResourceT r) = do
inner <- NestedResourceT ask
liftIO (r inner)
-- | An instance of MonadNestedResource must satisfy the following law
--
-- - @locally . liftResourceT = liftIO . runResourceT@
class MonadResource m => MonadNestedResource m where
locally :: m a -> m a
instance MonadIO m => MonadNestedResource (NestedResourceT m) where
locally (NestedResourceT r) = NestedResourceT $ do
(innerKey, inner) <- allocate createInternalState closeInternalState
ret <- local (const inner) r
release innerKey
pure ret
runNestedResourceT :: MonadUnliftIO m => NestedResourceT m a -> m a
runNestedResourceT (NestedResourceT r) = runResourceT $ do
(_, top) <- allocate createInternalState closeInternalState
runReaderT r top
I've not thought very hard about the law on MonadNestedResource
.
Even if the implementation is correct, it certainly requires a little more care on the part of the user to avoid passing resources outside the scope in which they're valid. Additionally the order in which destructors are called is no necessarily LIFO, for example locally $ allocate _ _ >> allocateGlobal _ _
will destroy the first allocation before destroying the global one.
Ah, my code above doesn't free locally
allocated resources promptly in the presence of exceptions.
Consider
test :: IO ()
test = runNestedResourceT $ do
(locally $ do
allocate (say "inner Create") (const (say "inner Destroy"))
throwIO (userError "hello")
)
`catchAny` sayErrShow
sayErr "Long running computation"
inner
is destroyed after the long running computation.
I suspect it's impossible to get the desired (and law abiding) behaviour here without a MonadUnliftIO
constraint on m
.
In which case one can dispense with NestedResourceT
and use ResourceT
directly:
instance MonadUnliftIO m => MonadNestedResource (ResourceT m) where
locally = ResourceT . const . runResourceT
Just to recap on my train of thought, the below seems like a reasonable implementation:
-- | An instance of MonadNestedResource must satisfy the following laws
--
-- - @locally . liftResourceT = liftIO . runResourceT@
-- - @locally . ($ f) =<< useCurrentScope = f@
class MonadResource m => MonadNestedResource m where
locally :: m a -> m a
useCurrentScope :: m (ResourceT n a -> n a)
instance MonadUnliftIO m => MonadNestedResource (ResourceT m) where
locally = ResourceT . const . runResourceT
useCurrentScope = flip runInternalState <$> getInternalState
-- MonadNestedResource instances for other transformers
instance MonadNestedResource m => MonadNestedResource (ReaderT r m) where
locally = mapReaderT locally
useCurrentScope = lift useCurrentScope
-- etc...
useCurrentScope
allows one to perform ResourceT
operations in any nested
scope. Obviously the same care must be taken with the ResourceT n a -> n a
value as with any allocated resource.
@snoyberg The definition in the preceding comment came out quite neat and tidy I think. How possible to you think it would be to get something like this included in the ResourceT package in Control.Monad.Trans.Resource
or Control.Monad.Trans.Resource.Nested
? (Obviously with some more documentation and thinking about the below)
Perhaps it would be best to wrap the output of useCurrentScope
in data Scope = Scope (forall n a. ResourceT n a -> n a)
or equivalently have it typed as ((forall n b. ResourceT n b -> n b) -> m a) -> m a
(similarly to unliftio and MonadBaseControl)
In fact, useCurrentScope
doesn't even have to be a member of MonadNestedResource
, it can be run anywhere with a MonadResource
constraint.
Highly unlikely. Like I mentioned in the first place: this kind of interface is highly likely to end up getting misused.
locally :: MonadResource m => m a -> m a
I would also like this function... I'm not sure in what way it could be misused :thinking: my use case is that I have hierarchical threads that cancel
their children upon termination. Giving each thread an empty release map and using allocate
to register children as resources solves this very nicely.
What's the recommended way of nesting several layers of ResourceT? It would be very handy to have some function
locally :: MonadResource m => m a -> m a
which deallocates any allocated resources at the end of the call tolocally
instead of deallocating them at the end ofrunResourceT
which may be in the far future.The use case is any time one wants to use a scarce resource and clean it up promptly and automatically as part of a larger computation.
Without the automatic part it would of course be possible to just keep track of the
ReleaseKey
s and release early.One nice way of doing this may be to run things in an environment where instead of a single
InternalState
one has a stack of them where the top of the stack is popped and closed at the end of the call tolocally
. Another way of doing this may be to simply nest calls torunResourceT
although this does change the type of the monad in which things are running.The documentation doesn't mention anything about this.
On top of this, a way to either allocate resources in an enclosing scope (not sure how the scope would be specified though (perhaps
locally
could provide a value of typeIO a -> (a -> IO ()) -> m (ReleaseKey, a)
which allocates in the parent region)) or to promote resources to an enclosing scope so they could be returned safely throughlocally
might be desirable.Such a feature would help bring ResourceT a little closer to the very nice object lifetime behaviour of Rust and C++, one could wrap all
do
blocks withlocally
(where appropriate) to approximate their behaviour.