mirror of
https://github.com/haskell-effectful/effectful.git
synced 2024-11-23 06:22:28 +03:00
More HasCallStack stuff
This commit is contained in:
parent
1f1f351d73
commit
f2bdfc344f
@ -11,7 +11,8 @@
|
||||
* Fix a bug in `stateM` and `modifyM` of thread local `State` effect that
|
||||
might've caused dropped state updates
|
||||
([#237](https://github.com/haskell-effectful/effectful/issues/237)).
|
||||
* Add `HasCallStack` constraints for easier debugging.
|
||||
* Add `HasCallStack` constraints where appropriate for better debugging
|
||||
experience.
|
||||
* **Breaking changes**:
|
||||
- `localSeqLend`, `localLend`, `localSeqBorrow` and `localBorrow` now take a
|
||||
list of effects instead of a single one.
|
||||
|
@ -13,6 +13,8 @@
|
||||
* Fix a bug in `stateM` and `modifyM` of thread local `State` effect that
|
||||
might've caused dropped state updates
|
||||
([#237](https://github.com/haskell-effectful/effectful/issues/237)).
|
||||
* Add `HasCallStack` constraints where appropriate for better debugging
|
||||
experience.
|
||||
* **Breaking changes**:
|
||||
- `localSeqLend`, `localLend`, `localSeqBorrow` and `localBorrow` now take a
|
||||
list of effects instead of a single one.
|
||||
|
@ -81,14 +81,14 @@ myThreadId :: Concurrent :> es => Eff es C.ThreadId
|
||||
myThreadId = unsafeEff_ C.myThreadId
|
||||
|
||||
-- | Lifted 'C.forkIO'.
|
||||
forkIO :: Concurrent :> es => Eff es () -> Eff es C.ThreadId
|
||||
forkIO :: (HasCallStack, Concurrent :> es) => Eff es () -> Eff es C.ThreadId
|
||||
forkIO k = unsafeEff $ \es -> do
|
||||
esF <- cloneEnv es
|
||||
C.forkIO $ unEff k esF
|
||||
|
||||
-- | Lifted 'C.forkFinally'.
|
||||
forkFinally
|
||||
:: Concurrent :> es
|
||||
:: (HasCallStack, Concurrent :> es)
|
||||
=> Eff es a
|
||||
-> (Either SomeException a -> Eff es ())
|
||||
-> Eff es C.ThreadId
|
||||
@ -98,7 +98,7 @@ forkFinally k cleanup = unsafeEff $ \es -> do
|
||||
|
||||
-- | Lifted 'C.forkIOWithUnmask'.
|
||||
forkIOWithUnmask
|
||||
:: Concurrent :> es
|
||||
:: (HasCallStack, Concurrent :> es)
|
||||
=> ((forall a. Eff es a -> Eff es a) -> Eff es ())
|
||||
-> Eff es C.ThreadId
|
||||
forkIOWithUnmask = liftForkWithUnmask C.forkIOWithUnmask
|
||||
@ -115,14 +115,14 @@ throwTo tid = unsafeEff_ . C.throwTo tid
|
||||
-- Threads with affinity
|
||||
|
||||
-- | Lifted 'C.forkOn'.
|
||||
forkOn :: Concurrent :> es => Int -> Eff es () -> Eff es C.ThreadId
|
||||
forkOn :: (HasCallStack, Concurrent :> es) => Int -> Eff es () -> Eff es C.ThreadId
|
||||
forkOn n k = unsafeEff $ \es -> do
|
||||
esF <- cloneEnv es
|
||||
C.forkOn n (unEff k esF)
|
||||
|
||||
-- | Lifted 'C.forkOnWithUnmask'.
|
||||
forkOnWithUnmask
|
||||
:: Concurrent :> es
|
||||
:: (HasCallStack, Concurrent :> es)
|
||||
=> Int
|
||||
-> ((forall a. Eff es a -> Eff es a) -> Eff es ())
|
||||
-> Eff es C.ThreadId
|
||||
@ -180,14 +180,14 @@ threadWaitWriteSTM fd = unsafeEff_ $ do
|
||||
-- Bound threads
|
||||
|
||||
-- | Lifted 'C.forkOS'.
|
||||
forkOS :: Concurrent :> es => Eff es () -> Eff es C.ThreadId
|
||||
forkOS :: (HasCallStack, Concurrent :> es) => Eff es () -> Eff es C.ThreadId
|
||||
forkOS k = unsafeEff $ \es -> do
|
||||
esF <- cloneEnv es
|
||||
C.forkOS $ unEff k esF
|
||||
|
||||
-- | Lifted 'E.forkOSWithUnmask'.
|
||||
forkOSWithUnmask
|
||||
:: Concurrent :> es
|
||||
:: (HasCallStack, Concurrent :> es)
|
||||
=> ((forall a. Eff es a -> Eff es a) -> Eff es ())
|
||||
-> Eff es C.ThreadId
|
||||
forkOSWithUnmask = liftForkWithUnmask C.forkOSWithUnmask
|
||||
@ -197,13 +197,13 @@ isCurrentThreadBound :: Concurrent :> es => Eff es Bool
|
||||
isCurrentThreadBound = unsafeEff_ C.isCurrentThreadBound
|
||||
|
||||
-- | Lifted 'C.runInBoundThread'.
|
||||
runInBoundThread :: Concurrent :> es => Eff es a -> Eff es a
|
||||
runInBoundThread :: (HasCallStack, Concurrent :> es) => Eff es a -> Eff es a
|
||||
runInBoundThread k = unsafeEff $ \es -> do
|
||||
esF <- cloneEnv es
|
||||
C.runInBoundThread $ unEff k esF
|
||||
|
||||
-- | Lifted 'C.runInUnboundThread'.
|
||||
runInUnboundThread :: Concurrent :> es => Eff es a -> Eff es a
|
||||
runInUnboundThread :: (HasCallStack, Concurrent :> es) => Eff es a -> Eff es a
|
||||
runInUnboundThread k = unsafeEff $ \es -> do
|
||||
esF <- cloneEnv es
|
||||
C.runInUnboundThread $ unEff k esF
|
||||
@ -219,7 +219,8 @@ mkWeakThreadId = unsafeEff_ . C.mkWeakThreadId
|
||||
-- Helpers
|
||||
|
||||
liftForkWithUnmask
|
||||
:: (((forall c. IO c -> IO c) -> IO a) -> IO C.ThreadId)
|
||||
:: HasCallStack
|
||||
=> (((forall c. IO c -> IO c) -> IO a) -> IO C.ThreadId)
|
||||
-> ((forall c. Eff es c -> Eff es c) -> Eff es a)
|
||||
-> Eff es C.ThreadId
|
||||
liftForkWithUnmask fork action = unsafeEff $ \es -> do
|
||||
|
@ -91,27 +91,27 @@ import Effectful.Dispatch.Static.Primitive
|
||||
import Effectful.Dispatch.Static.Unsafe
|
||||
|
||||
-- | Lifted 'A.async'.
|
||||
async :: Concurrent :> es => Eff es a -> Eff es (Async a)
|
||||
async :: (HasCallStack, Concurrent :> es) => Eff es a -> Eff es (Async a)
|
||||
async = liftAsync A.async
|
||||
|
||||
-- | Lifted 'A.asyncBound'.
|
||||
asyncBound :: Concurrent :> es => Eff es a -> Eff es (Async a)
|
||||
asyncBound :: (HasCallStack, Concurrent :> es) => Eff es a -> Eff es (Async a)
|
||||
asyncBound = liftAsync A.asyncBound
|
||||
|
||||
-- | Lifted 'A.asyncOn'.
|
||||
asyncOn :: Concurrent :> es => Int -> Eff es a -> Eff es (Async a)
|
||||
asyncOn :: (HasCallStack, Concurrent :> es) => Int -> Eff es a -> Eff es (Async a)
|
||||
asyncOn cpu = liftAsync (A.asyncOn cpu)
|
||||
|
||||
-- | Lifted 'A.asyncWithUnmask'.
|
||||
asyncWithUnmask
|
||||
:: Concurrent :> es
|
||||
:: (HasCallStack, Concurrent :> es)
|
||||
=> ((forall b. Eff es b -> Eff es b) -> Eff es a)
|
||||
-> Eff es (Async a)
|
||||
asyncWithUnmask = liftAsyncWithUnmask A.asyncWithUnmask
|
||||
|
||||
-- | Lifted 'A.asyncOnWithUnmask'.
|
||||
asyncOnWithUnmask
|
||||
:: Concurrent :> es
|
||||
:: (HasCallStack, Concurrent :> es)
|
||||
=> Int
|
||||
-> ((forall b. Eff es b -> Eff es b) -> Eff es a)
|
||||
-> Eff es (Async a)
|
||||
@ -119,7 +119,7 @@ asyncOnWithUnmask cpu = liftAsyncWithUnmask (A.asyncOnWithUnmask cpu)
|
||||
|
||||
-- | Lifted 'A.withAsync'.
|
||||
withAsync
|
||||
:: Concurrent :> es
|
||||
:: (HasCallStack, Concurrent :> es)
|
||||
=> Eff es a
|
||||
-> (Async a -> Eff es b)
|
||||
-> Eff es b
|
||||
@ -127,7 +127,7 @@ withAsync = liftWithAsync A.withAsync
|
||||
|
||||
-- | Lifted 'A.withAsyncBound'.
|
||||
withAsyncBound
|
||||
:: Concurrent :> es
|
||||
:: (HasCallStack, Concurrent :> es)
|
||||
=> Eff es a
|
||||
-> (Async a -> Eff es b)
|
||||
-> Eff es b
|
||||
@ -135,7 +135,7 @@ withAsyncBound = liftWithAsync A.withAsyncBound
|
||||
|
||||
-- | Lifted 'A.withAsyncOn'.
|
||||
withAsyncOn
|
||||
:: Concurrent :> es
|
||||
:: (HasCallStack, Concurrent :> es)
|
||||
=> Int
|
||||
-> Eff es a
|
||||
-> (Async a -> Eff es b)
|
||||
@ -144,7 +144,7 @@ withAsyncOn cpu = liftWithAsync (A.withAsyncOn cpu)
|
||||
|
||||
-- | Lifted 'A.withAsyncWithUnmask'.
|
||||
withAsyncWithUnmask
|
||||
:: Concurrent :> es
|
||||
:: (HasCallStack, Concurrent :> es)
|
||||
=> ((forall c. Eff es c -> Eff es c) -> Eff es a)
|
||||
-> (Async a -> Eff es b)
|
||||
-> Eff es b
|
||||
@ -152,7 +152,7 @@ withAsyncWithUnmask = liftWithAsyncWithUnmask A.withAsyncWithUnmask
|
||||
|
||||
-- | Lifted 'A.withAsyncOnWithUnmask'.
|
||||
withAsyncOnWithUnmask
|
||||
:: Concurrent :> es
|
||||
:: (HasCallStack, Concurrent :> es)
|
||||
=> Int
|
||||
-> ((forall c. Eff es c -> Eff es c) -> Eff es a)
|
||||
-> (Async a -> Eff es b)
|
||||
@ -268,22 +268,22 @@ link2Only :: Concurrent :> es => (SomeException -> Bool) -> Async a -> Async b -
|
||||
link2Only f a b = unsafeEff_ $ A.link2Only f a b
|
||||
|
||||
-- | Lifted 'A.race'.
|
||||
race :: Concurrent :> es => Eff es a -> Eff es b -> Eff es (Either a b)
|
||||
race :: (HasCallStack, Concurrent :> es) => Eff es a -> Eff es b -> Eff es (Either a b)
|
||||
race ma mb = unsafeEff $ \es -> do
|
||||
A.race (unEff ma =<< cloneEnv es) (unEff mb =<< cloneEnv es)
|
||||
|
||||
-- | Lifted 'A.race_'.
|
||||
race_ :: Concurrent :> es => Eff es a -> Eff es b -> Eff es ()
|
||||
race_ :: (HasCallStack, Concurrent :> es) => Eff es a -> Eff es b -> Eff es ()
|
||||
race_ ma mb = unsafeEff $ \es -> do
|
||||
A.race_ (unEff ma =<< cloneEnv es) (unEff mb =<< cloneEnv es)
|
||||
|
||||
-- | Lifted 'A.concurrently'.
|
||||
concurrently :: Concurrent :> es => Eff es a -> Eff es b -> Eff es (a, b)
|
||||
concurrently :: (HasCallStack, Concurrent :> es) => Eff es a -> Eff es b -> Eff es (a, b)
|
||||
concurrently ma mb = unsafeEff $ \es -> do
|
||||
A.concurrently (unEff ma =<< cloneEnv es) (unEff mb =<< cloneEnv es)
|
||||
|
||||
-- | Lifted 'A.concurrently_'.
|
||||
concurrently_ :: Concurrent :> es => Eff es a -> Eff es b -> Eff es ()
|
||||
concurrently_ :: (HasCallStack, Concurrent :> es) => Eff es a -> Eff es b -> Eff es ()
|
||||
concurrently_ ma mb = unsafeEff $ \es -> do
|
||||
A.concurrently_ (unEff ma =<< cloneEnv es) (unEff mb =<< cloneEnv es)
|
||||
|
||||
@ -293,7 +293,7 @@ concurrently_ ma mb = unsafeEff $ \es -> do
|
||||
|
||||
-- | Lifted 'A.mapConcurrently'.
|
||||
mapConcurrently
|
||||
:: (Traversable f, Concurrent :> es)
|
||||
:: (HasCallStack, Traversable f, Concurrent :> es)
|
||||
=> (a -> Eff es b)
|
||||
-> f a
|
||||
-> Eff es (f b)
|
||||
@ -302,7 +302,7 @@ mapConcurrently f t = unsafeEff $ \es -> do
|
||||
|
||||
-- | Lifted 'A.mapConcurrently_'.
|
||||
mapConcurrently_
|
||||
:: (Foldable f, Concurrent :> es)
|
||||
:: (HasCallStack, Foldable f, Concurrent :> es)
|
||||
=> (a -> Eff es b)
|
||||
-> f a
|
||||
-> Eff es ()
|
||||
@ -311,7 +311,7 @@ mapConcurrently_ f t = unsafeEff $ \es -> do
|
||||
|
||||
-- | Lifted 'A.forConcurrently'.
|
||||
forConcurrently
|
||||
:: (Traversable f, Concurrent :> es)
|
||||
:: (HasCallStack, Traversable f, Concurrent :> es)
|
||||
=> f a
|
||||
-> (a -> Eff es b)
|
||||
-> Eff es (f b)
|
||||
@ -320,7 +320,7 @@ forConcurrently t f = unsafeEff $ \es -> do
|
||||
|
||||
-- | Lifted 'A.forConcurrently_'.
|
||||
forConcurrently_
|
||||
:: (Foldable f, Concurrent :> es)
|
||||
:: (HasCallStack, Foldable f, Concurrent :> es)
|
||||
=> f a
|
||||
-> (a -> Eff es b)
|
||||
-> Eff es ()
|
||||
@ -328,12 +328,20 @@ forConcurrently_ t f = unsafeEff $ \es -> do
|
||||
U.forConcurrently_ t (\a -> unEff (f a) =<< cloneEnv es)
|
||||
|
||||
-- | Lifted 'A.replicateConcurrently'.
|
||||
replicateConcurrently :: Concurrent :> es => Int -> Eff es a -> Eff es [a]
|
||||
replicateConcurrently
|
||||
:: (HasCallStack, Concurrent :> es)
|
||||
=> Int
|
||||
-> Eff es a
|
||||
-> Eff es [a]
|
||||
replicateConcurrently n f = unsafeEff $ \es -> do
|
||||
U.replicateConcurrently n (unEff f =<< cloneEnv es)
|
||||
|
||||
-- | Lifted 'A.replicateConcurrently_'.
|
||||
replicateConcurrently_ :: Concurrent :> es => Int -> Eff es a -> Eff es ()
|
||||
replicateConcurrently_
|
||||
:: (HasCallStack, Concurrent :> es)
|
||||
=> Int
|
||||
-> Eff es a
|
||||
-> Eff es ()
|
||||
replicateConcurrently_ n f = unsafeEff $ \es -> do
|
||||
U.replicateConcurrently_ n (unEff f =<< cloneEnv es)
|
||||
|
||||
@ -342,7 +350,7 @@ replicateConcurrently_ n f = unsafeEff $ \es -> do
|
||||
|
||||
-- | Lifted 'U.pooledMapConcurrentlyN'.
|
||||
pooledMapConcurrentlyN
|
||||
:: (Concurrent :> es, Traversable t)
|
||||
:: (HasCallStack, Concurrent :> es, Traversable t)
|
||||
=> Int
|
||||
-> (a -> Eff es b)
|
||||
-> t a
|
||||
@ -352,7 +360,7 @@ pooledMapConcurrentlyN threads f t = unsafeEff $ \es -> do
|
||||
|
||||
-- | Lifted 'U.pooledMapConcurrently'.
|
||||
pooledMapConcurrently
|
||||
:: (Concurrent :> es, Traversable t)
|
||||
:: (HasCallStack, Concurrent :> es, Traversable t)
|
||||
=> (a -> Eff es b)
|
||||
-> t a
|
||||
-> Eff es (t b)
|
||||
@ -361,7 +369,7 @@ pooledMapConcurrently f t = unsafeEff $ \es -> do
|
||||
|
||||
-- | Lifted 'U.pooledMapConcurrentlyN'.
|
||||
pooledMapConcurrentlyN_
|
||||
:: (Concurrent :> es, Foldable f)
|
||||
:: (HasCallStack, Concurrent :> es, Foldable f)
|
||||
=> Int
|
||||
-> (a -> Eff es b)
|
||||
-> f a
|
||||
@ -371,7 +379,7 @@ pooledMapConcurrentlyN_ threads f t = unsafeEff $ \es -> do
|
||||
|
||||
-- | Lifted 'U.pooledMapConcurrently_'.
|
||||
pooledMapConcurrently_
|
||||
:: (Concurrent :> es, Foldable f)
|
||||
:: (HasCallStack, Concurrent :> es, Foldable f)
|
||||
=> (a -> Eff es b)
|
||||
-> f a
|
||||
-> Eff es ()
|
||||
@ -380,7 +388,7 @@ pooledMapConcurrently_ f t = unsafeEff $ \es -> do
|
||||
|
||||
-- | Lifted 'U.pooledForConcurrentlyN'.
|
||||
pooledForConcurrentlyN
|
||||
:: (Concurrent :> es, Traversable t)
|
||||
:: (HasCallStack, Concurrent :> es, Traversable t)
|
||||
=> Int
|
||||
-> t a
|
||||
-> (a -> Eff es b)
|
||||
@ -390,7 +398,7 @@ pooledForConcurrentlyN threads t f = unsafeEff $ \es -> do
|
||||
|
||||
-- | Lifted 'U.pooledForConcurrently'.
|
||||
pooledForConcurrently
|
||||
:: (Concurrent :> es, Traversable t)
|
||||
:: (HasCallStack, Concurrent :> es, Traversable t)
|
||||
=> t a
|
||||
-> (a -> Eff es b)
|
||||
-> Eff es (t b)
|
||||
@ -399,7 +407,7 @@ pooledForConcurrently t f = unsafeEff $ \es -> do
|
||||
|
||||
-- | Lifted 'U.pooledForConcurrentlyN'.
|
||||
pooledForConcurrentlyN_
|
||||
:: (Concurrent :> es, Foldable f)
|
||||
:: (HasCallStack, Concurrent :> es, Foldable f)
|
||||
=> Int
|
||||
-> f a
|
||||
-> (a -> Eff es b)
|
||||
@ -409,7 +417,7 @@ pooledForConcurrentlyN_ threads t f = unsafeEff $ \es -> do
|
||||
|
||||
-- | Lifted 'U.pooledForConcurrently_'.
|
||||
pooledForConcurrently_
|
||||
:: (Concurrent :> es, Foldable f)
|
||||
:: (HasCallStack, Concurrent :> es, Foldable f)
|
||||
=> f a
|
||||
-> (a -> Eff es b)
|
||||
-> Eff es ()
|
||||
@ -417,22 +425,40 @@ pooledForConcurrently_ t f = unsafeEff $ \es -> do
|
||||
U.pooledForConcurrently_ t (\a -> unEff (f a) =<< cloneEnv es)
|
||||
|
||||
-- | Lifted 'U.pooledReplicateConcurrentlyN'.
|
||||
pooledReplicateConcurrentlyN :: Concurrent :> es => Int -> Int -> Eff es a -> Eff es [a]
|
||||
pooledReplicateConcurrentlyN
|
||||
:: (HasCallStack, Concurrent :> es)
|
||||
=> Int
|
||||
-> Int
|
||||
-> Eff es a
|
||||
-> Eff es [a]
|
||||
pooledReplicateConcurrentlyN threads n f = unsafeEff $ \es -> do
|
||||
U.pooledReplicateConcurrentlyN threads n (unEff f =<< cloneEnv es)
|
||||
|
||||
-- | Lifted 'U.pooledReplicateConcurrently'.
|
||||
pooledReplicateConcurrently :: Concurrent :> es => Int -> Eff es a -> Eff es [a]
|
||||
pooledReplicateConcurrently
|
||||
:: (HasCallStack, Concurrent :> es)
|
||||
=> Int
|
||||
-> Eff es a
|
||||
-> Eff es [a]
|
||||
pooledReplicateConcurrently n f = unsafeEff $ \es -> do
|
||||
U.pooledReplicateConcurrently n (unEff f =<< cloneEnv es)
|
||||
|
||||
-- | Lifted 'U.pooledReplicateConcurrentlyN_'.
|
||||
pooledReplicateConcurrentlyN_ :: Concurrent :> es => Int -> Int -> Eff es a -> Eff es ()
|
||||
pooledReplicateConcurrentlyN_
|
||||
:: (HasCallStack, Concurrent :> es)
|
||||
=> Int
|
||||
-> Int
|
||||
-> Eff es a
|
||||
-> Eff es ()
|
||||
pooledReplicateConcurrentlyN_ threads n f = unsafeEff $ \es -> do
|
||||
U.pooledReplicateConcurrentlyN_ threads n (unEff f =<< cloneEnv es)
|
||||
|
||||
-- | Lifted 'U.pooledReplicateConcurrently_'.
|
||||
pooledReplicateConcurrently_ :: Concurrent :> es => Int -> Eff es a -> Eff es ()
|
||||
pooledReplicateConcurrently_
|
||||
:: (HasCallStack, Concurrent :> es)
|
||||
=> Int
|
||||
-> Eff es a
|
||||
-> Eff es ()
|
||||
pooledReplicateConcurrently_ n f = unsafeEff $ \es -> do
|
||||
U.pooledReplicateConcurrently_ n (unEff f =<< cloneEnv es)
|
||||
|
||||
@ -472,7 +498,7 @@ conc :: Eff es a -> Conc es a
|
||||
conc = Action
|
||||
|
||||
-- | Lifted 'U.runConc'.
|
||||
runConc :: Concurrent :> es => Conc es a -> Eff es a
|
||||
runConc :: (HasCallStack, Concurrent :> es) => Conc es a -> Eff es a
|
||||
runConc m = unsafeEff $ \es -> U.runConc (unliftConc es m)
|
||||
where
|
||||
unliftConc :: Env es -> Conc es a -> U.Conc IO a
|
||||
@ -513,7 +539,8 @@ instance (Concurrent :> es, Monoid a) => Monoid (Concurrently es a) where
|
||||
-- Helpers
|
||||
|
||||
liftAsync
|
||||
:: (IO a -> IO (Async a))
|
||||
:: HasCallStack
|
||||
=> (IO a -> IO (Async a))
|
||||
-> Eff es a
|
||||
-> Eff es (Async a)
|
||||
liftAsync fork action = unsafeEff $ \es -> do
|
||||
@ -521,7 +548,8 @@ liftAsync fork action = unsafeEff $ \es -> do
|
||||
fork $ unEff action esA
|
||||
|
||||
liftAsyncWithUnmask
|
||||
:: (((forall b. IO b -> IO b) -> IO a) -> IO (Async a))
|
||||
:: HasCallStack
|
||||
=> (((forall b. IO b -> IO b) -> IO a) -> IO (Async a))
|
||||
-> ((forall b. Eff es b -> Eff es b) -> Eff es a)
|
||||
-> Eff es (Async a)
|
||||
liftAsyncWithUnmask fork action = unsafeEff $ \es -> do
|
||||
@ -530,7 +558,8 @@ liftAsyncWithUnmask fork action = unsafeEff $ \es -> do
|
||||
fork $ \unmask -> unEff (action $ reallyUnsafeLiftMapIO unmask) esA
|
||||
|
||||
liftWithAsync
|
||||
:: (IO a -> (Async a -> IO b) -> IO b)
|
||||
:: HasCallStack
|
||||
=> (IO a -> (Async a -> IO b) -> IO b)
|
||||
-> Eff es a
|
||||
-> (Async a -> Eff es b)
|
||||
-> Eff es b
|
||||
@ -540,7 +569,8 @@ liftWithAsync withA action k = unsafeEff $ \es -> do
|
||||
(\a -> unEff (k a) es)
|
||||
|
||||
liftWithAsyncWithUnmask
|
||||
:: (((forall c. IO c -> IO c) -> IO a) -> (Async a -> IO b) -> IO b)
|
||||
:: HasCallStack
|
||||
=> (((forall c. IO c -> IO c) -> IO a) -> (Async a -> IO b) -> IO b)
|
||||
-> ((forall c. Eff es c -> Eff es c) -> Eff es a)
|
||||
-> (Async a -> Eff es b)
|
||||
-> Eff es b
|
||||
|
@ -78,7 +78,7 @@ type instance DispatchOf Concurrent = Static WithSideEffects
|
||||
data instance StaticRep Concurrent = Concurrent
|
||||
|
||||
-- | Run the 'Concurrent' effect.
|
||||
runConcurrent :: IOE :> es => Eff (Concurrent : es) a -> Eff es a
|
||||
runConcurrent :: (HasCallStack, IOE :> es) => Eff (Concurrent : es) a -> Eff es a
|
||||
runConcurrent = evalStaticRep Concurrent
|
||||
|
||||
-- $setup
|
||||
|
@ -117,7 +117,11 @@ modifyMVarMasked var f = reallyUnsafeUnliftIO $ \unlift -> do
|
||||
--
|
||||
-- /Note:/ the finalizer will run a cloned environment, so any changes it makes
|
||||
-- to thread local data will not be visible outside of it.
|
||||
mkWeakMVar :: Concurrent :> es => MVar a -> Eff es () -> Eff es (Weak (MVar a))
|
||||
mkWeakMVar
|
||||
:: (HasCallStack, Concurrent :> es)
|
||||
=> MVar a
|
||||
-> Eff es ()
|
||||
-> Eff es (Weak (MVar a))
|
||||
mkWeakMVar var f = unsafeEff $ \es -> do
|
||||
-- The finalizer can run at any point and in any thread.
|
||||
M.mkWeakMVar var . unEff f =<< cloneEnv es
|
||||
|
@ -119,7 +119,10 @@ modifyMVar'Masked var f = reallyUnsafeUnliftIO $ \unlift -> do
|
||||
--
|
||||
-- /Note:/ the finalizer will run a cloned environment, so any changes it makes
|
||||
-- to thread local data will not be visible outside of it.
|
||||
mkWeakMVar' :: Concurrent :> es => MVar' a -> Eff es () -> Eff es (Weak (MVar' a))
|
||||
mkWeakMVar'
|
||||
:: (HasCallStack, Concurrent :> es)
|
||||
=> MVar' a -> Eff es ()
|
||||
-> Eff es (Weak (MVar' a))
|
||||
mkWeakMVar' var f = unsafeEff $ \es -> do
|
||||
-- The finalizer can run at any point and in any thread.
|
||||
M.mkWeakMVar' var . unEff f =<< cloneEnv es
|
||||
|
@ -128,7 +128,11 @@ modifyMVarMasked var f = reallyUnsafeUnliftIO $ \unlift -> do
|
||||
--
|
||||
-- /Note:/ the finalizer will run a cloned environment, so any changes it makes
|
||||
-- to thread local data will not be visible outside of it.
|
||||
mkWeakMVar :: Concurrent :> es => MVar a -> Eff es () -> Eff es (Weak (MVar a))
|
||||
mkWeakMVar
|
||||
:: (HasCallStack, Concurrent :> es)
|
||||
=> MVar a
|
||||
-> Eff es ()
|
||||
-> Eff es (Weak (MVar a))
|
||||
mkWeakMVar var f = unsafeEff $ \es -> do
|
||||
-- The finalizer can run at any point and in any thread.
|
||||
M.mkWeakMVar var . unEff f =<< cloneEnv es
|
||||
|
@ -119,7 +119,11 @@ registerDelay = unsafeEff_ . STM.registerDelay
|
||||
--
|
||||
-- /Note:/ the finalizer will run a cloned environment, so any changes it makes
|
||||
-- to thread local data will not be visible outside of it.
|
||||
mkWeakTVar :: Concurrent :> es => TVar a -> Eff es () -> Eff es (Weak (TVar a))
|
||||
mkWeakTVar
|
||||
:: (HasCallStack, Concurrent :> es)
|
||||
=> TVar a
|
||||
-> Eff es ()
|
||||
-> Eff es (Weak (TVar a))
|
||||
mkWeakTVar var f = unsafeEff $ \es -> do
|
||||
-- The finalizer can run at any point and in any thread.
|
||||
STM.mkWeakTVar var . unEff f =<< cloneEnv es
|
||||
@ -136,7 +140,11 @@ newEmptyTMVarIO = unsafeEff_ STM.newEmptyTMVarIO
|
||||
--
|
||||
-- /Note:/ the finalizer will run a cloned environment, so any changes it makes
|
||||
-- to thread local data will not be visible outside of it.
|
||||
mkWeakTMVar :: Concurrent :> es => TMVar a -> Eff es () -> Eff es (Weak (TMVar a))
|
||||
mkWeakTMVar
|
||||
:: (HasCallStack, Concurrent :> es)
|
||||
=> TMVar a
|
||||
-> Eff es ()
|
||||
-> Eff es (Weak (TMVar a))
|
||||
mkWeakTMVar var f = unsafeEff $ \es -> do
|
||||
-- The finalizer can run at any point and in any thread.
|
||||
STM.mkWeakTMVar var . unEff f =<< cloneEnv es
|
||||
|
@ -17,5 +17,5 @@ type instance DispatchOf Console = Static WithSideEffects
|
||||
data instance StaticRep Console = Console
|
||||
|
||||
-- | Run the 'Console' effect.
|
||||
runConsole :: IOE :> es => Eff (Console : es) a -> Eff es a
|
||||
runConsole :: (HasCallStack, IOE :> es) => Eff (Console : es) a -> Eff es a
|
||||
runConsole = evalStaticRep Console
|
||||
|
@ -32,7 +32,7 @@ type instance DispatchOf Environment = Static WithSideEffects
|
||||
data instance StaticRep Environment = Environment
|
||||
|
||||
-- | Run the 'Environment' effect.
|
||||
runEnvironment :: IOE :> es => Eff (Environment : es) a -> Eff es a
|
||||
runEnvironment :: (HasCallStack, IOE :> es) => Eff (Environment : es) a -> Eff es a
|
||||
runEnvironment = evalStaticRep Environment
|
||||
|
||||
-- | Lifted 'E.getArgs'.
|
||||
|
@ -16,5 +16,5 @@ type instance DispatchOf FileSystem = Static WithSideEffects
|
||||
data instance StaticRep FileSystem = FileSystem
|
||||
|
||||
-- | Run the 'FileSystem' effect.
|
||||
runFileSystem :: IOE :> es => Eff (FileSystem : es) a -> Eff es a
|
||||
runFileSystem :: (HasCallStack, IOE :> es) => Eff (FileSystem : es) a -> Eff es a
|
||||
runFileSystem = evalStaticRep FileSystem
|
||||
|
@ -69,7 +69,11 @@ atomicWriteIORef var = unsafeEff_ . Ref.atomicWriteIORef var
|
||||
--
|
||||
-- /Note:/ the finalizer will run a cloned environment, so any changes it makes
|
||||
-- to thread local data will not be visible outside of it.
|
||||
mkWeakIORef :: Prim :> es => IORef a -> Eff es () -> Eff es (Weak (IORef a))
|
||||
mkWeakIORef
|
||||
:: (HasCallStack, Prim :> es)
|
||||
=> IORef a
|
||||
-> Eff es ()
|
||||
-> Eff es (Weak (IORef a))
|
||||
mkWeakIORef var f = unsafeEff $ \es -> do
|
||||
-- The finalizer can run at any point and in any thread.
|
||||
Ref.mkWeakIORef var . unEff f =<< cloneEnv es
|
||||
|
@ -56,7 +56,11 @@ atomicWriteIORef' var = unsafeEff_ . Ref.atomicWriteIORef' var
|
||||
--
|
||||
-- /Note:/ the finalizer will run a cloned environment, so any changes it makes
|
||||
-- to thread local data will not be visible outside of it.
|
||||
mkWeakIORef' :: Prim :> es => IORef' a -> Eff es () -> Eff es (Weak (IORef' a))
|
||||
mkWeakIORef'
|
||||
:: (HasCallStack, Prim :> es)
|
||||
=> IORef' a
|
||||
-> Eff es ()
|
||||
-> Eff es (Weak (IORef' a))
|
||||
mkWeakIORef' var f = unsafeEff $ \es -> do
|
||||
-- The finalizer can run at any point and in any thread.
|
||||
Ref.mkWeakIORef' var . unEff f =<< cloneEnv es
|
||||
|
@ -62,7 +62,7 @@ data Process :: Effect
|
||||
type instance DispatchOf Process = Static WithSideEffects
|
||||
data instance StaticRep Process = Process
|
||||
|
||||
runProcess :: IOE :> es => Eff (Process : es) a -> Eff es a
|
||||
runProcess :: (HasCallStack, IOE :> es) => Eff (Process : es) a -> Eff es a
|
||||
runProcess = evalStaticRep Process
|
||||
|
||||
----------------------------------------
|
||||
|
@ -25,7 +25,7 @@ type instance DispatchOf Temporary = Static WithSideEffects
|
||||
data instance StaticRep Temporary = Temporary
|
||||
|
||||
-- | Run the 'Temporary' effect.
|
||||
runTemporary :: IOE :> es => Eff (Temporary : es) a -> Eff es a
|
||||
runTemporary :: (HasCallStack, IOE :> es) => Eff (Temporary : es) a -> Eff es a
|
||||
runTemporary = evalStaticRep Temporary
|
||||
|
||||
-- | Lifted 'T.withSystemTempFile'.
|
||||
|
@ -21,7 +21,7 @@ type instance DispatchOf Timeout = Static WithSideEffects
|
||||
data instance StaticRep Timeout = Timeout
|
||||
|
||||
-- | Run the 'Timeout' effect.
|
||||
runTimeout :: IOE :> es => Eff (Timeout : es) a -> Eff es a
|
||||
runTimeout :: (HasCallStack, IOE :> es) => Eff (Timeout : es) a -> Eff es a
|
||||
runTimeout = evalStaticRep Timeout
|
||||
|
||||
-- | Lifted 'T.timeout'.
|
||||
|
Loading…
Reference in New Issue
Block a user