{-# language Safe #-}

module LazyAsync.Types.Resource where

import LazyAsync.Prelude (Functor)

{- | A resource and an action that releases it

A /resource/ is something that can be /acquired/ and then /released/, where
releasing an object once it is no longer needed is important because the supply
is exhaustible.

-}
data Resource m a = Resource{ Resource m a -> m ()
release :: m (), Resource m a -> a
resource :: a }
    deriving a -> Resource m b -> Resource m a
(a -> b) -> Resource m a -> Resource m b
(forall a b. (a -> b) -> Resource m a -> Resource m b)
-> (forall a b. a -> Resource m b -> Resource m a)
-> Functor (Resource m)
forall a b. a -> Resource m b -> Resource m a
forall a b. (a -> b) -> Resource m a -> Resource m b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
forall (m :: * -> *) a b. a -> Resource m b -> Resource m a
forall (m :: * -> *) a b. (a -> b) -> Resource m a -> Resource m b
<$ :: a -> Resource m b -> Resource m a
$c<$ :: forall (m :: * -> *) a b. a -> Resource m b -> Resource m a
fmap :: (a -> b) -> Resource m a -> Resource m b
$cfmap :: forall (m :: * -> *) a b. (a -> b) -> Resource m a -> Resource m b
Functor