[Haskell-beginners] how does hgearman-client work?

David McBride toad3k at gmail.com
Thu Mar 16 12:25:41 UTC 2017


This library seems badly managed, but it does give you just enough to
work with, if you know how to use monad transformers.

someprocedure :: IO Bool
someprocedure = do
  res <- connectGearman somebs somehost someport
  case res of
    Left e -> undefined
    Right client -> do
      (res, _) <- flip runStateT client $ do
        res <- submitJob somefunc somebs
        case res of
          Left e -> undefined
          Right bs -> do
            -- do something with bs
            return True
      return res

If I were you I'd turn LambdaCase on to clean it up a bit, and do
something like this.

{-# LANGUAGE LambdaCase #-}

...

someprocedure :: IO Bool
someprocedure = do
  connectGearman somebs somehost someport >>= \case
    Left e -> return False
    Right client -> do
      flip evalStateT client $ do
        submitJob somefunc somebs >>= \case
          Left e -> return False
          Right bs -> do
            -- do something with bs
            return True

On Wed, Mar 15, 2017 at 4:18 PM,  <info at maximka.de> wrote:
> Hi,
> I repeat my unanswered question in hope to find here some help:
>
> Unfortunately the package hgearman does not provide any test or example and
> I can't work it out for myself how should be combined connectGearman and
> submitJob to put a job to the gearman job server.
>
> The result of connectGearman is:
>
> ghci> conn <- connectGearman (B.pack "x") ("localhost"::HostName)
> (4730::Port)
> ghci> :t conn
> conn :: Either GearmanError GearmanClient
>
> but submitJob uses private function submit which deals with StateT. So I can
> only guess the result of connectGearman should be wrapped into S.StateT
> GearmanClient IO without faintest idea how to do that.
>
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>


More information about the Beginners mailing list