Send Beginners mailing list submissions to beginners@haskell.org To subscribe or unsubscribe via the World Wide Web, visit http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners or, via email, send a message with subject or body 'help' to beginners-requ...@haskell.org
You can reach the person managing the list at beginners-ow...@haskell.org When replying, please edit your Subject line so it is more specific than "Re: Contents of Beginners digest..." Today's Topics: 1. how does hgearman-worker work? (i...@maximka.de) 2. Re: how does hgearman-worker work? (David McBride) 3. Re: how does hgearman-worker work? (i...@maximka.de) 4. State monad to help pass around game settings (Dave Martin) ---------------------------------------------------------------------- Message: 1 Date: Thu, 6 Apr 2017 17:37:22 +0200 (CEST) From: i...@maximka.de To: beginners@haskell.org Subject: [Haskell-beginners] how does hgearman-worker work? Message-ID: <1866905711.42388.1491493042...@communicator.strato.de> Content-Type: text/plain; charset=UTF-8 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 ------------------------------ Message: 2 Date: Thu, 6 Apr 2017 13:54:30 -0400 From: David McBride <toa...@gmail.com> To: Maxim 2001 <i...@maximka.de>, The Haskell-Beginners Mailing List - Discussion of primarily beginner-level topics related to Haskell <beginners@haskell.org> Subject: Re: [Haskell-beginners] how does hgearman-worker work? Message-ID: <can+tr418ckrpodreeqprmpsrul+zsd3oqxfnprbeee_kc3v...@mail.gmail.com> Content-Type: text/plain; charset=UTF-8 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, <i...@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@haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners ------------------------------ Message: 3 Date: Thu, 6 Apr 2017 23:43:19 +0200 (CEST) From: i...@maximka.de To: David McBride <toa...@gmail.com>, The Haskell-Beginners Mailing List - Discussion of primarily beginner-level topics related to Haskell <beginners@haskell.org> Subject: Re: [Haskell-beginners] how does hgearman-worker work? Message-ID: <1851063228.51296.1491514999...@communicator.strato.de> Content-Type: text/plain; charset=UTF-8 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 <toa...@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, <i...@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@haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners ------------------------------ Message: 4 Date: Thu, 6 Apr 2017 21:26:09 -0400 From: Dave Martin <davemartin...@aol.com> To: beginners@haskell.org Subject: [Haskell-beginners] State monad to help pass around game settings Message-ID: <15b4604c422-5e4f-8...@webprd-m51.mail.aol.com> Content-Type: text/plain; charset="utf-8" I'm trying to write a game with a "settings menu" where the user can adjust gameplay options. Right now I pass all the settings around as parameters. I'm trying to figure out how to use the State monad to simplify this task, but I can't figure out how to start. Or maybe my whole design approach is wrongheaded, and not in keeping with best practices. Haskell is my first language. This is the kind of thing I have now: mainM color shape = putStrLn "\n\nMain Menu" >> (putStrLn . unlines) [ "(1) Set", "(2) Display", "(3) Quit"] >> putStr "? " >> getChar >>= \c -> case c of '1' -> set color shape '2' -> display color shape '3' -> return () _ -> mainM color shape set color shape = putStrLn "\n\nSettings" >> (putStrLn . unlines) [ "(1) Color", "(2) Shape", "(3) Main Menu"] >> putStr "? " >> getChar >>= \c -> case c of '1' -> setColor color shape '2' -> setShape color shape '3' -> mainM color shape _ -> set color shape setColor color shape = putStr ("\n\nColor is " ++ color ++ ". New color? ") >> getLine >>= \cs -> set cs shape setShape color shape = putStr ("\n\nShape is " ++ shape ++ ". New shape? ") >> getLine >>= \cs -> set color cs display color shape = putStrLn ("\n\nColor is " ++ color ++ ". Shape is " ++ shape ++ ".") >> mainM color shape -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/beginners/attachments/20170406/a58f709c/attachment-0001.html> ------------------------------ Subject: Digest Footer _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners ------------------------------ End of Beginners Digest, Vol 106, Issue 2 *****************************************