[Haskell-cafe] Problem with lifted-async
Lana Black
lanablack at amok.cc
Fri Sep 4 12:26:20 UTC 2015
Hello,
I'm writing a thread supervisor that allows implicitly passing some
monadic context (e.g. ReaderT) using MonadBaseControl from
monad-control. The problem is that I don't know how to tackle this
error.
GHCi, version 7.10.2: http://www.haskell.org/ghc/ :? for help
[1 of 1] Compiling Main ( ex.hs, interpreted )
ex.hs:20:20:
Couldn't match type ‘StM t a0’ with ‘StM t a’
NB: ‘StM’ is a type function, and may not be injective
The type variable ‘a0’ is ambiguous
Expected type: Async (StM t a0)
Actual type: Async (StM t a)
Relevant bindings include
as :: Async (StM t a) (bound at ex.hs:19:30)
t :: Task t a (bound at ex.hs:19:28)
td :: TaskDescriptor t (bound at ex.hs:19:10)
pollTask :: TaskDescriptor t
-> TaskDescriptor t -> t (TaskDescriptor t)
(bound at ex.hs:19:1)
In the first argument of ‘poll’, namely ‘as’
In a stmt of a 'do' block: st <- poll as
Failed, modules loaded: none.
This minimal code snippet would be
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleContexts #-}
import Control.Concurrent.Async.Lifted (Async,async,asyncBound,poll,cancel)
import Control.Monad.Trans.Control (MonadBaseControl,StM)
data Task m a = Task {
taskVal :: m a
}
data TaskDescriptor m = forall a. TaskDescriptor {
task :: Task m a,
asyncThread :: Async (StM m a)
}
runTask :: forall a m. (MonadBaseControl IO m) => Task m a -> m (TaskDescriptor m)
runTask = undefined
pollTask td(TaskDescriptor t as) = do
st <- poll as
case st of
Nothing -> pure td
Just r -> runTask t
main = undefined
StM is a type from MonadBaseControl typeclass, the definition is
class MonadBase b m => MonadBaseControl b m | m -> b where
type StM m a :: *
liftBaseWith :: (RunInBase m b -> b a) -> m a
restoreM :: StM m a -> m a
type RunInBase m b = forall a. m a -> b (StM m a)
I stripped the comments, the full version is here
https://hackage.haskell.org/package/monad-control-1.0.0.4/docs/src/Control-Monad-Trans-Control.html#MonadBaseControl
More information about the Haskell-Cafe
mailing list