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. Re:  how does hgearman-client work? (David McBride)
   2. Re:  how does hgearman-client work? (i...@maximka.de)


----------------------------------------------------------------------

Message: 1
Date: Thu, 16 Mar 2017 08:25:41 -0400
From: David McBride <toa...@gmail.com>
To: 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-client work?
Message-ID:
        <can+tr40zepo40uru4bcpax8kteztfsvn5jjenle1qmdcmob...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

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,  <i...@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@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>


------------------------------

Message: 2
Date: Thu, 16 Mar 2017 14:34:25 +0100 (CET)
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-client work?
Message-ID: <2017570301.11767.1489671266...@communicator.strato.de>
Content-Type: text/plain; charset=UTF-8

I'm really much obliged for your support, David.

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

It seems so. I tried to get some help by author at first: 
https://github.com/jperson/hgearman-client/issues/1

That's a reason why I'm working on PR to add some tests to the package.

Cheers,
Alexei

> On 16 March 2017 at 13:25 David McBride <toa...@gmail.com> wrote:
> 
> 
> 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,  <i...@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@haskell.org
> > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
> >


------------------------------

Subject: Digest Footer

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


------------------------------

End of Beginners Digest, Vol 105, Issue 6
*****************************************

Reply via email to