[Haskell-beginners] how does hgearman-worker work?
info at maximka.de
info at maximka.de
Thu Apr 6 21:43:19 UTC 2017
Thank you very much, David.
> If you want to run it from within StateT GearmanClient IO, you must
> use liftIO.
The execution of the worker implementation below shows the ThreadId but the worker doesn't grab any job from gearmand as expected. GRAB_JOB, wich sends gmLoop (https://github.com/jperson/hgearman-client/blob/master/Network/Gearman/Worker.hs#L29), appears in gearmand logs but the worker close the connection before gearmand sends GEARMAN_COMMAND_JOB_ASSIGN replay. It looks like the worker does not execute gmWait.
{-# LANGUAGE LambdaCase #-}
import qualified Control.Monad.State as S
import qualified Data.ByteString.Char8 as B
import qualified Network.Gearman.Client as C
import qualified Network.Gearman.Worker as W
import Network.Gearman.Internal (Function, Port)
import Network.Socket (HostName)
import GHC.Conc.Sync (ThreadId)
main :: IO ()
main = do
work >>= \ case
Nothing -> putStrLn "nothing"
Just t -> putStrLn $ show t
return ()
work :: IO (Maybe ThreadId)
work = do
connect >>= \case
Left e -> error $ B.unpack e
Right gc -> do
(res, _) <- flip S.runStateT gc $ do
g <- W.registerWorker ((B.pack "foo")::Function) (\_ -> B.pack "bar")
t <- S.liftIO $ W.runWorker gc (return g)
return $ Just t
return res
where
connect = C.connectGearman (B.pack "worker-id-123") ("localhost"::HostName) (4730::Port)
> This is just a guess based on what I know about gearman and that
> particular api choice. He may have intended you to use runWorker
> outside of the setup phase. He certainly doesn't prevent it.
>
> someprocedure' :: IO ()
> someprocedure' = do
> gs <- connectGearman >>= \case
> Left e -> return []
> Right gc -> do
> (res, _) <- flip runStateT gc $ do
> g <- registerWorker undefined undefined
> g2 <- registerWorker undefined undefined
> return $ [g,g2]
> return res
>
> mapM_ (\g -> runWorker g (return ())) gs
>
I'm not sure it could work in this way because runWorker :: GearmanClient -> Gearman () -> IO ThreadId and connectGearman result is of type IO (Either GearmanError GearmanClient)
Best regards,
Alexei
> On 06 April 2017 at 19:54 David McBride <toad3k at gmail.com> wrote:
>
>
> There are a couple problems. One is that runWorker has a type of IO
> ThreadId. I have no idea why he would write it that way in his API.
> If you want to run it from within StateT GearmanClient IO, you must
> use liftIO.
>
> liftIO :: (MonadIO m) => IO a -> StateT s IO
>
> instance MonadIO (StateT s IO) where
> liftIO :: IO a -> StateT s IO a
>
> liftIO $ runWorker gc whatever.
>
> When you are working in monadic code, you connect monadic components
> based on their types. If you are a procedure
>
> someprocedure :: IO ???
>
> Then every statement you used must some form of ???. runWorker
> returns (IO ThreadId), return () returns (IO ()), return res returns
> IO (whatever type res is). I'm not sure what you intend to do with
> the threadId, save it or ignore it, but you might try something like
> this.
>
> someprocedure' :: IO (Maybe ThreadId)
> someprocedure' = do
> connectGearman >>= \case
> Left e -> return Nothing
> Right gc -> do
> (res, _) <- flip runStateT gc $ do
> g <- registerWorker undefined undefined
> t <- liftIO $ runWorker gc undefined
> return $ Just t
> return res
>
> This is just a guess based on what I know about gearman and that
> particular api choice. He may have intended you to use runWorker
> outside of the setup phase. He certainly doesn't prevent it.
>
> someprocedure' :: IO ()
> someprocedure' = do
> gs <- connectGearman >>= \case
> Left e -> return []
> Right gc -> do
> (res, _) <- flip runStateT gc $ do
> g <- registerWorker undefined undefined
> g2 <- registerWorker undefined undefined
> return $ [g,g2]
> return res
>
> mapM_ (\g -> runWorker g (return ())) gs
>
>
>
> On Thu, Apr 6, 2017 at 11:37 AM, <info at maximka.de> wrote:
> > A while ago I asked similar question about hgearman client. With help I got in the List (https://mail.haskell.org/pipermail/beginners/2017-March/017435.html) and I implemented a gearman client in Haskell. (here the implementation http://stackoverflow.com/questions/42774191/how-does-hgearman-client-work)
> >
> > Unfortunately I need again some help be implementation of gearman worker.
> >
> > I post here only the snippet with the badly implemented code in hope to find again some help. (Complete implementation: http://stackoverflow.com/questions/43155857/how-does-hgearman-worker-work)
> >
> > Right gc -> do
> > (res, _) <- flip S.runStateT gc $ do
> > g <- (W.registerWorker name func)
> > t <- W.runWorker gc (return ())
> > return t >> return ()
> >
> > return res
> >
> > This throws exception:
> > Couldn't match expected type `S.StateT
> > Network.Gearman.Internal.GearmanClient IO a0'
> > with actual type `IO GHC.Conc.Sync.ThreadId'
> > In a stmt of a 'do' block: t <- W.runWorker gc (return ())
> > In the second argument of `($)', namely
> > `do { g <- (W.registerWorker name func);
> > t <- W.runWorker gc (return ());
> > return t >> return () }
> >
> >
> > What do I wrong with W.runWorker gc (return ())?
> >
> > runWorker :: GearmanClient -> Gearman () -> IO ThreadId
> > https://hackage.haskell.org/package/hgearman-0.1.0.2/docs/Network-Gearman-Worker.html
> >
> > Best regards,
> > Alexei
> > _______________________________________________
> > Beginners mailing list
> > Beginners at haskell.org
> > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
More information about the Beginners
mailing list