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:  Beginners Digest, Vol 106, Issue 7 (Francesco Ariis)
   2. Re:  Beginners Digest, Vol 106, Issue 7 (David McBride)
   3. Re:  how does hgearman-worker work? (i...@maximka.de)
   4. Re:  Beginners Digest, Vol 106, Issue 7 (Frank Lugala)


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

Message: 1
Date: Tue, 18 Apr 2017 14:48:06 +0200
From: Francesco Ariis <fa...@ariis.it>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] Beginners Digest, Vol 106, Issue 7
Message-ID: <20170418124806.ga9...@casa.casa>
Content-Type: text/plain; charset=utf-8

On Tue, Apr 18, 2017 at 03:39:28PM +0300, Andrey Klaus wrote:
> Hello everybody,
> 
> A small question.
> -----
> packageP = do
>     literal “package"
> -----
> 
> what is the "literal" in this code? My problem is
> 
> $ ghc ParserTest.hs
> [1 of 1] Compiling ParserTest       ( ParserTest.hs, ParserTest.o )

Hello Andrey,
    literal is not in scope, apparently. Did you forget to put an
import at the top of ParserTest.hs? E.g.:

    import SomeParserModule


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

Message: 2
Date: Tue, 18 Apr 2017 09:22:27 -0400
From: David McBride <toa...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Beginners Digest, Vol 106, Issue 7
Message-ID:
        <CAN+Tr407TmaCEHRZVWOGrUrh8=d3-mOtyed+t=zv0mdwkbr...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

That depends on what package you are using to parse.  If you are using
parsec, you can use the string function from Text.Parsec.Char.  If you
are using some other package, it probably has a different name for it.

On Tue, Apr 18, 2017 at 8:39 AM, Andrey Klaus <deepminds...@gmail.com> wrote:
> Hello everybody,
>
> A small question.
> -----
> packageP = do
>     literal “package"
> -----
>
> what is the "literal" in this code? My problem is
>
> $ ghc ParserTest.hs
> [1 of 1] Compiling ParserTest       ( ParserTest.hs, ParserTest.o )
>
> ParserTest.hs:11:5: Not in scope: ‘literal’
>
> $ ghc --version
> The Glorious Glasgow Haskell Compilation System, version 7.10.3
>
> Is this because I use old version of software?
>
> Thanks,
> Andrey
>
>
>
> 2017-04-14 21:58 GMT+03:00 <beginners-requ...@haskell.org>:
>>
>> 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.  Parsing (mike h)
>>    2. Re:  Parsing (David McBride)
>>    3. Re:  Parsing (Francesco Ariis)
>>    4. Re:  Parsing (mike h)
>>    5. Re:  Parsing (mike h)
>>
>>
>> ----------------------------------------------------------------------
>>
>> Message: 1
>> Date: Fri, 14 Apr 2017 19:02:37 +0100
>> From: mike h <mike_k_hough...@yahoo.co.uk>
>> To: The Haskell-Beginners Mailing List - Discussion of primarily
>>         beginner-level topics related to Haskell <beginners@haskell.org>
>> Subject: [Haskell-beginners] Parsing
>> Message-ID: <2c66c9dc-30af-41c5-b9af-0d1da19e0...@yahoo.co.uk>
>> Content-Type: text/plain; charset=utf-8
>>
>> I have
>> data PackageDec = Pkg String deriving Show
>>
>> and a parser for it
>>
>> packageP :: Parser PackageDec
>> packageP = do
>>     literal “package"
>>     x  <- identifier
>>     xs <- many ((:) <$> char '.' <*> identifier)
>>     return $ Pkg . concat $ (x:xs)
>>
>> so I’m parsing for this sort  of string
>> “package some.sort.of.name”
>>
>> and I’m trying to rewrite the packageP parser in applicative style. As a
>> not quite correct start I have
>>
>> packageP' :: Parser PackageDec
>> packageP' = literal "package" >>  Pkg . concat <$> many ((:) <$> char '.'
>> <*> identifier)
>>
>> but I can’t see how to get the ‘first’ identifier into this sequence -
>> i.e. the bit that corresponds to  x <- identifier        in the
>> monadic version.
>>
>> in ghci
>> λ-> :t many ((:) <$> char '.' <*> identifier)
>> many ((:) <$> char '.' <*> identifier) :: Parser [[Char]]
>>
>> so I think that somehow I need to get the ‘first’ identifier into a list
>> just after  Pkg . concat  so that the whole list gets flattened and
>> everybody is happy!
>>
>> Any help appreciated.
>>
>> Thanks
>> Mike
>>
>>
>>
>>
>>
>>
>>
>> ------------------------------
>>
>> Message: 2
>> Date: Fri, 14 Apr 2017 14:17:42 -0400
>> From: David McBride <toa...@gmail.com>
>> To: The Haskell-Beginners Mailing List - Discussion of primarily
>>         beginner-level topics related to Haskell <beginners@haskell.org>
>> Subject: Re: [Haskell-beginners] Parsing
>> Message-ID:
>>
>> <can+tr42ifdf62sxo6wdq32rbaphq+eqtkjeuk-dnr8pdfrs...@mail.gmail.com>
>> Content-Type: text/plain; charset=UTF-8
>>
>> Try breaking it up into pieces.  There a literal "package" which is
>> dropped.  There is a first identifier, then there are the rest of the
>> identifiers (a list), then those two things are combined somehow (with
>> :).
>>
>> literal "package" *> (:) <$> identifier <*> restOfIdentifiers
>> where
>>   restOfIdentifiers :: Applicative f => f [String]
>>   restOfIdentifiers = many ((:) <$> char '.' <*> identifier
>>
>> I have not tested this code, but it should be close to what you are
>> looking for.
>>
>> On Fri, Apr 14, 2017 at 2:02 PM, mike h <mike_k_hough...@yahoo.co.uk>
>> wrote:
>> > I have
>> > data PackageDec = Pkg String deriving Show
>> >
>> > and a parser for it
>> >
>> > packageP :: Parser PackageDec
>> > packageP = do
>> >     literal “package"
>> >     x  <- identifier
>> >     xs <- many ((:) <$> char '.' <*> identifier)
>> >     return $ Pkg . concat $ (x:xs)
>> >
>> > so I’m parsing for this sort  of string
>> > “package some.sort.of.name”
>> >
>> > and I’m trying to rewrite the packageP parser in applicative style. As a
>> > not quite correct start I have
>> >
>> > packageP' :: Parser PackageDec
>> > packageP' = literal "package" >>  Pkg . concat <$> many ((:) <$> char
>> > '.' <*> identifier)
>> >
>> > but I can’t see how to get the ‘first’ identifier into this sequence -
>> > i.e. the bit that corresponds to  x <- identifier        in the
>> > monadic version.
>> >
>> > in ghci
>> > λ-> :t many ((:) <$> char '.' <*> identifier)
>> > many ((:) <$> char '.' <*> identifier) :: Parser [[Char]]
>> >
>> > so I think that somehow I need to get the ‘first’ identifier into a list
>> > just after  Pkg . concat  so that the whole list gets flattened and
>> > everybody is happy!
>> >
>> > Any help appreciated.
>> >
>> > Thanks
>> > Mike
>> >
>> >
>> >
>> >
>> >
>> > _______________________________________________
>> > Beginners mailing list
>> > Beginners@haskell.org
>> > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>>
>>
>> ------------------------------
>>
>> Message: 3
>> Date: Fri, 14 Apr 2017 20:35:32 +0200
>> From: Francesco Ariis <fa...@ariis.it>
>> To: beginners@haskell.org
>> Subject: Re: [Haskell-beginners] Parsing
>> Message-ID: <20170414183532.ga4...@casa.casa>
>> Content-Type: text/plain; charset=utf-8
>>
>> On Fri, Apr 14, 2017 at 07:02:37PM +0100, mike h wrote:
>> > I have
>> > data PackageDec = Pkg String deriving Show
>> >
>> > and a parser for it
>> >
>> > packageP :: Parser PackageDec
>> > packageP = do
>> >     literal “package"
>> >     x  <- identifier
>> >     xs <- many ((:) <$> char '.' <*> identifier)
>> >     return $ Pkg . concat $ (x:xs)
>> >
>> > so I’m parsing for this sort  of string
>> > “package some.sort.of.name”
>> >
>> > and I’m trying to rewrite the packageP parser in applicative style. As a
>> > not quite correct start I have
>>
>> Hello Mike,
>>
>>     I am not really sure what you are doing here? You are parsing a dot
>> separated list (like.this.one) but at the end you are concatenating all
>> together, why?
>> Are you sure you are not wanting [String] instead of String?
>>
>> If so, Parsec comes with some handy parser combinators [1], maybe one of
>> them could fit your bill:
>>
>>     -- should work
>>     packageP = literal "package" *> Pkg <$> sepEndBy1 identifier (char
>> '.')
>>
>> [1]
>> https://hackage.haskell.org/package/parsec-3.1.11/docs/Text-Parsec-Combinator.html
>>
>>
>> ------------------------------
>>
>> Message: 4
>> Date: Fri, 14 Apr 2017 20:12:14 +0100
>> From: mike h <mike_k_hough...@yahoo.co.uk>
>> To: The Haskell-Beginners Mailing List - Discussion of primarily
>>         beginner-level topics related to Haskell <beginners@haskell.org>
>> Subject: Re: [Haskell-beginners] Parsing
>> Message-ID: <ff162cde-e7e8-421b-a92e-057a643ee...@yahoo.co.uk>
>> Content-Type: text/plain; charset=utf-8
>>
>> Hi David,
>>
>> Thanks but I tried something like that before I posted. I’ll try again
>> maybe I mistyped.
>>
>> Mike
>> > On 14 Apr 2017, at 19:17, David McBride <toa...@gmail.com> wrote:
>> >
>> > Try breaking it up into pieces.  There a literal "package" which is
>> > dropped.  There is a first identifier, then there are the rest of the
>> > identifiers (a list), then those two things are combined somehow (with
>> > :).
>> >
>> > literal "package" *> (:) <$> identifier <*> restOfIdentifiers
>> > where
>> >  restOfIdentifiers :: Applicative f => f [String]
>> >  restOfIdentifiers = many ((:) <$> char '.' <*> identifier
>> >
>> > I have not tested this code, but it should be close to what you are
>> > looking for.
>> >
>> > On Fri, Apr 14, 2017 at 2:02 PM, mike h <mike_k_hough...@yahoo.co.uk>
>> > wrote:
>> >> I have
>> >> data PackageDec = Pkg String deriving Show
>> >>
>> >> and a parser for it
>> >>
>> >> packageP :: Parser PackageDec
>> >> packageP = do
>> >>    literal “package"
>> >>    x  <- identifier
>> >>    xs <- many ((:) <$> char '.' <*> identifier)
>> >>    return $ Pkg . concat $ (x:xs)
>> >>
>> >> so I’m parsing for this sort  of string
>> >> “package some.sort.of.name”
>> >>
>> >> and I’m trying to rewrite the packageP parser in applicative style. As
>> >> a not quite correct start I have
>> >>
>> >> packageP' :: Parser PackageDec
>> >> packageP' = literal "package" >>  Pkg . concat <$> many ((:) <$> char
>> >> '.' <*> identifier)
>> >>
>> >> but I can’t see how to get the ‘first’ identifier into this sequence -
>> >> i.e. the bit that corresponds to  x <- identifier        in the
>> >> monadic version.
>> >>
>> >> in ghci
>> >> λ-> :t many ((:) <$> char '.' <*> identifier)
>> >> many ((:) <$> char '.' <*> identifier) :: Parser [[Char]]
>> >>
>> >> so I think that somehow I need to get the ‘first’ identifier into a
>> >> list just after  Pkg . concat  so that the whole list gets flattened and
>> >> everybody is happy!
>> >>
>> >> Any help appreciated.
>> >>
>> >> Thanks
>> >> Mike
>> >>
>> >>
>> >>
>> >>
>> >>
>> >> _______________________________________________
>> >> Beginners mailing list
>> >> Beginners@haskell.org
>> >> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>> > _______________________________________________
>> > Beginners mailing list
>> > Beginners@haskell.org
>> > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>>
>>
>>
>> ------------------------------
>>
>> Message: 5
>> Date: Fri, 14 Apr 2017 20:19:40 +0100
>> From: mike h <mike_k_hough...@yahoo.co.uk>
>> To: The Haskell-Beginners Mailing List - Discussion of primarily
>>         beginner-level topics related to Haskell <beginners@haskell.org>
>> Subject: Re: [Haskell-beginners] Parsing
>> Message-ID: <d208c2b2-6e38-427d-9eaf-b9ea8532d...@yahoo.co.uk>
>> Content-Type: text/plain; charset="utf-8"
>>
>> Hi Francesco,
>> Yes, I think you are right with "Are you sure you are not wanting [String]
>> instead of String?”
>>
>> I could use Parsec but I’m building up a parser library from first
>> principles i.e.
>>
>> newtype Parser a = P (String -> [(a,String)])
>>
>> parse :: Parser a -> String -> [(a,String)]
>> parse (P p)  = p
>>
>> and so on….
>>
>> It’s just an exercise to see how far I can get. And its good fun. So maybe
>> I need add another combinator or to what I already have.
>>
>> Thanks
>>
>> Mike
>>
>>
>> > On 14 Apr 2017, at 19:35, Francesco Ariis <fa...@ariis.it> wrote:
>> >
>> > On Fri, Apr 14, 2017 at 07:02:37PM +0100, mike h wrote:
>> >> I have
>> >> data PackageDec = Pkg String deriving Show
>> >>
>> >> and a parser for it
>> >>
>> >> packageP :: Parser PackageDec
>> >> packageP = do
>> >>    literal “package"
>> >>    x  <- identifier
>> >>    xs <- many ((:) <$> char '.' <*> identifier)
>> >>    return $ Pkg . concat $ (x:xs)
>> >>
>> >> so I’m parsing for this sort  of string
>> >> “package some.sort.of.name”
>> >>
>> >> and I’m trying to rewrite the packageP parser in applicative style. As
>> >> a not quite correct start I have
>> >
>> > Hello Mike,
>> >
>> >    I am not really sure what you are doing here? You are parsing a dot
>> > separated list (like.this.one) but at the end you are concatenating all
>> > together, why?
>> > Are you sure you are not wanting [String] instead of String?
>> >
>> > If so, Parsec comes with some handy parser combinators [1], maybe one of
>> > them could fit your bill:
>> >
>> >    -- should work
>> >    packageP = literal "package" *> Pkg <$> sepEndBy1 identifier (char
>> > '.')
>> >
>> > [1]
>> > https://hackage.haskell.org/package/parsec-3.1.11/docs/Text-Parsec-Combinator.html
>> > <https://hackage.haskell.org/package/parsec-3.1.11/docs/Text-Parsec-Combinator.html>
>> > _______________________________________________
>> > Beginners mailing list
>> > Beginners@haskell.org <mailto:Beginners@haskell.org>
>> > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>> > <http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners>
>> -------------- next part --------------
>> An HTML attachment was scrubbed...
>> URL:
>> <http://mail.haskell.org/pipermail/beginners/attachments/20170414/66a17133/attachment.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 7
>> *****************************************
>
>
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>


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

Message: 3
Date: Tue, 18 Apr 2017 16:27:18 +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: <1163641822.368480.1492525638...@communicator.strato.de>
Content-Type: text/plain; charset=UTF-8

Finally I implemented a hgearman based worker. The code is posted on 
stackoverflow:
http://stackoverflow.com/a/43474542/2789312

> > 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.

I can't justify it with my less state transformer experiences. But it doesn't 
work for me.
Both registerWorker and runWorker should use the same StateT instance because
registerWorker puts a function to be executed during runWorker into StateT 
https://github.com/p-alik/hgearman-client/blob/master/Network/Gearman/Worker.hs#L19
and runWorker fetch and execute it 
https://github.com/p-alik/hgearman-client/blob/master/Network/Gearman/Worker.hs#L42
 

Alexei

> On 06 April 2017 at 23:43 i...@maximka.de wrote:
> 
> 
> 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
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


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

Message: 4
Date: Wed, 19 Apr 2017 00:11:14 +0000
From: Frank Lugala <officia...@live.in>
To: "The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell" <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Beginners Digest, Vol 106, Issue 7
Message-ID:
        
<am4pr02mb32525fef4a96e4c9841a0bd8cc...@am4pr02mb3252.eurprd02.prod.outlook.com>
        
Content-Type: text/plain; charset="cp1253"

Can   anyone  suggest a good Haskell  IDE  for  windows?


________________________________
From: Beginners <beginners-boun...@haskell.org> on behalf of David McBride 
<toa...@gmail.com>
Sent: Tuesday, April 18, 2017 4:22 PM
To: The Haskell-Beginners Mailing List - Discussion of primarily beginner-level 
topics related to Haskell
Subject: Re: [Haskell-beginners] Beginners Digest, Vol 106, Issue 7

That depends on what package you are using to parse.  If you are using
parsec, you can use the string function from Text.Parsec.Char.  If you
are using some other package, it probably has a different name for it.

On Tue, Apr 18, 2017 at 8:39 AM, Andrey Klaus <deepminds...@gmail.com> wrote:
> Hello everybody,
>
> A small question.
> -----
> packageP = do
>     literal “package"
> -----
>
> what is the "literal" in this code? My problem is
>
> $ ghc ParserTest.hs
> [1 of 1] Compiling ParserTest       ( ParserTest.hs, ParserTest.o )
>
> ParserTest.hs:11:5: Not in scope: ‘literal’
>
> $ ghc --version
> The Glorious Glasgow Haskell Compilation System, version 7.10.3
>
> Is this because I use old version of software?
>
> Thanks,
> Andrey
>
>
>
> 2017-04-14 21:58 GMT+03:00 <beginners-requ...@haskell.org>:
>>
>> 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
Haskell-Beginners Info 
Page<http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners>
mail.haskell.org
Haskell-Beginners -- The Haskell-Beginners Mailing List - Discussion of 
primarily beginner-level topics related to Haskell About Haskell-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.  Parsing (mike h)
>>    2. Re:  Parsing (David McBride)
>>    3. Re:  Parsing (Francesco Ariis)
>>    4. Re:  Parsing (mike h)
>>    5. Re:  Parsing (mike h)
>>
>>
>> ----------------------------------------------------------------------
>>
>> Message: 1
>> Date: Fri, 14 Apr 2017 19:02:37 +0100
>> From: mike h <mike_k_hough...@yahoo.co.uk>
>> To: The Haskell-Beginners Mailing List - Discussion of primarily
>>         beginner-level topics related to Haskell <beginners@haskell.org>
>> Subject: [Haskell-beginners] Parsing
>> Message-ID: <2c66c9dc-30af-41c5-b9af-0d1da19e0...@yahoo.co.uk>
>> Content-Type: text/plain; charset=utf-8
>>
>> I have
>> data PackageDec = Pkg String deriving Show
>>
>> and a parser for it
>>
>> packageP :: Parser PackageDec
>> packageP = do
>>     literal “package"
>>     x  <- identifier
>>     xs <- many ((:) <$> char '.' <*> identifier)
>>     return $ Pkg . concat $ (x:xs)
>>
>> so I’m parsing for this sort  of string
>> “package some.sort.of.name”
>>
>> and I’m trying to rewrite the packageP parser in applicative style. As a
>> not quite correct start I have
>>
>> packageP' :: Parser PackageDec
>> packageP' = literal "package" >>  Pkg . concat <$> many ((:) <$> char '.'
>> <*> identifier)
>>
>> but I can’t see how to get the ‘first’ identifier into this sequence -
>> i.e. the bit that corresponds to  x <- identifier        in the
>> monadic version.
>>
>> in ghci
>> λ-> :t many ((:) <$> char '.' <*> identifier)
>> many ((:) <$> char '.' <*> identifier) :: Parser [[Char]]
>>
>> so I think that somehow I need to get the ‘first’ identifier into a list
>> just after  Pkg . concat  so that the whole list gets flattened and
>> everybody is happy!
>>
>> Any help appreciated.
>>
>> Thanks
>> Mike
>>
>>
>>
>>
>>
>>
>>
>> ------------------------------
>>
>> Message: 2
>> Date: Fri, 14 Apr 2017 14:17:42 -0400
>> From: David McBride <toa...@gmail.com>
>> To: The Haskell-Beginners Mailing List - Discussion of primarily
>>         beginner-level topics related to Haskell <beginners@haskell.org>
>> Subject: Re: [Haskell-beginners] Parsing
>> Message-ID:
>>
>> <can+tr42ifdf62sxo6wdq32rbaphq+eqtkjeuk-dnr8pdfrs...@mail.gmail.com>
>> Content-Type: text/plain; charset=UTF-8
>>
>> Try breaking it up into pieces.  There a literal "package" which is
>> dropped.  There is a first identifier, then there are the rest of the
>> identifiers (a list), then those two things are combined somehow (with
>> :).
>>
>> literal "package" *> (:) <$> identifier <*> restOfIdentifiers
>> where
>>   restOfIdentifiers :: Applicative f => f [String]
>>   restOfIdentifiers = many ((:) <$> char '.' <*> identifier
>>
>> I have not tested this code, but it should be close to what you are
>> looking for.
>>
>> On Fri, Apr 14, 2017 at 2:02 PM, mike h <mike_k_hough...@yahoo.co.uk>
>> wrote:
>> > I have
>> > data PackageDec = Pkg String deriving Show
>> >
>> > and a parser for it
>> >
>> > packageP :: Parser PackageDec
>> > packageP = do
>> >     literal “package"
>> >     x  <- identifier
>> >     xs <- many ((:) <$> char '.' <*> identifier)
>> >     return $ Pkg . concat $ (x:xs)
>> >
>> > so I’m parsing for this sort  of string
>> > “package some.sort.of.name”
>> >
>> > and I’m trying to rewrite the packageP parser in applicative style. As a
>> > not quite correct start I have
>> >
>> > packageP' :: Parser PackageDec
>> > packageP' = literal "package" >>  Pkg . concat <$> many ((:) <$> char
>> > '.' <*> identifier)
>> >
>> > but I can’t see how to get the ‘first’ identifier into this sequence -
>> > i.e. the bit that corresponds to  x <- identifier        in the
>> > monadic version.
>> >
>> > in ghci
>> > λ-> :t many ((:) <$> char '.' <*> identifier)
>> > many ((:) <$> char '.' <*> identifier) :: Parser [[Char]]
>> >
>> > so I think that somehow I need to get the ‘first’ identifier into a list
>> > just after  Pkg . concat  so that the whole list gets flattened and
>> > everybody is happy!
>> >
>> > Any help appreciated.
>> >
>> > Thanks
>> > Mike
>> >
>> >
>> >
>> >
>> >
>> > _______________________________________________
>> > Beginners mailing list
>> > Beginners@haskell.org
>> > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
Haskell-Beginners Info 
Page<http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners>
mail.haskell.org
Haskell-Beginners -- The Haskell-Beginners Mailing List - Discussion of 
primarily beginner-level topics related to Haskell About Haskell-Beginners



>>
>>
>> ------------------------------
>>
>> Message: 3
>> Date: Fri, 14 Apr 2017 20:35:32 +0200
>> From: Francesco Ariis <fa...@ariis.it>
>> To: beginners@haskell.org
>> Subject: Re: [Haskell-beginners] Parsing
>> Message-ID: <20170414183532.ga4...@casa.casa>
>> Content-Type: text/plain; charset=utf-8
>>
>> On Fri, Apr 14, 2017 at 07:02:37PM +0100, mike h wrote:
>> > I have
>> > data PackageDec = Pkg String deriving Show
>> >
>> > and a parser for it
>> >
>> > packageP :: Parser PackageDec
>> > packageP = do
>> >     literal “package"
>> >     x  <- identifier
>> >     xs <- many ((:) <$> char '.' <*> identifier)
>> >     return $ Pkg . concat $ (x:xs)
>> >
>> > so I’m parsing for this sort  of string
>> > “package some.sort.of.name”
>> >
>> > and I’m trying to rewrite the packageP parser in applicative style. As a
>> > not quite correct start I have
>>
>> Hello Mike,
>>
>>     I am not really sure what you are doing here? You are parsing a dot
>> separated list (like.this.one) but at the end you are concatenating all
>> together, why?
>> Are you sure you are not wanting [String] instead of String?
>>
>> If so, Parsec comes with some handy parser combinators [1], maybe one of
>> them could fit your bill:
>>
>>     -- should work
>>     packageP = literal "package" *> Pkg <$> sepEndBy1 identifier (char
>> '.')
>>
>> [1]
>> https://hackage.haskell.org/package/parsec-3.1.11/docs/Text-Parsec-Combinator.html
>>
>>
>> ------------------------------
>>
>> Message: 4
>> Date: Fri, 14 Apr 2017 20:12:14 +0100
>> From: mike h <mike_k_hough...@yahoo.co.uk>
>> To: The Haskell-Beginners Mailing List - Discussion of primarily
>>         beginner-level topics related to Haskell <beginners@haskell.org>
>> Subject: Re: [Haskell-beginners] Parsing
>> Message-ID: <ff162cde-e7e8-421b-a92e-057a643ee...@yahoo.co.uk>
>> Content-Type: text/plain; charset=utf-8
>>
>> Hi David,
>>
>> Thanks but I tried something like that before I posted. I’ll try again
>> maybe I mistyped.
>>
>> Mike
>> > On 14 Apr 2017, at 19:17, David McBride <toa...@gmail.com> wrote:
>> >
>> > Try breaking it up into pieces.  There a literal "package" which is
>> > dropped.  There is a first identifier, then there are the rest of the
>> > identifiers (a list), then those two things are combined somehow (with
>> > :).
>> >
>> > literal "package" *> (:) <$> identifier <*> restOfIdentifiers
>> > where
>> >  restOfIdentifiers :: Applicative f => f [String]
>> >  restOfIdentifiers = many ((:) <$> char '.' <*> identifier
>> >
>> > I have not tested this code, but it should be close to what you are
>> > looking for.
>> >
>> > On Fri, Apr 14, 2017 at 2:02 PM, mike h <mike_k_hough...@yahoo.co.uk>
>> > wrote:
>> >> I have
>> >> data PackageDec = Pkg String deriving Show
>> >>
>> >> and a parser for it
>> >>
>> >> packageP :: Parser PackageDec
>> >> packageP = do
>> >>    literal “package"
>> >>    x  <- identifier
>> >>    xs <- many ((:) <$> char '.' <*> identifier)
>> >>    return $ Pkg . concat $ (x:xs)
>> >>
>> >> so I’m parsing for this sort  of string
>> >> “package some.sort.of.name”
>> >>
>> >> and I’m trying to rewrite the packageP parser in applicative style. As
>> >> a not quite correct start I have
>> >>
>> >> packageP' :: Parser PackageDec
>> >> packageP' = literal "package" >>  Pkg . concat <$> many ((:) <$> char
>> >> '.' <*> identifier)
>> >>
>> >> but I can’t see how to get the ‘first’ identifier into this sequence -
>> >> i.e. the bit that corresponds to  x <- identifier        in the
>> >> monadic version.
>> >>
>> >> in ghci
>> >> λ-> :t many ((:) <$> char '.' <*> identifier)
>> >> many ((:) <$> char '.' <*> identifier) :: Parser [[Char]]
>> >>
>> >> so I think that somehow I need to get the ‘first’ identifier into a
>> >> list just after  Pkg . concat  so that the whole list gets flattened and
>> >> everybody is happy!
>> >>
>> >> Any help appreciated.
>> >>
>> >> Thanks
>> >> Mike
>> >>
>> >>
>> >>
>> >>
>> >>
>> >> _______________________________________________
>> >> Beginners mailing list
>> >> Beginners@haskell.org
>> >> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>> > _______________________________________________
>> > Beginners mailing list
>> > Beginners@haskell.org
>> > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>>
>>
>>
>> ------------------------------
>>
>> Message: 5
>> Date: Fri, 14 Apr 2017 20:19:40 +0100
>> From: mike h <mike_k_hough...@yahoo.co.uk>
>> To: The Haskell-Beginners Mailing List - Discussion of primarily
>>         beginner-level topics related to Haskell <beginners@haskell.org>
>> Subject: Re: [Haskell-beginners] Parsing
>> Message-ID: <d208c2b2-6e38-427d-9eaf-b9ea8532d...@yahoo.co.uk>
>> Content-Type: text/plain; charset="utf-8"
>>
>> Hi Francesco,
>> Yes, I think you are right with "Are you sure you are not wanting [String]
>> instead of String?”
>>
>> I could use Parsec but I’m building up a parser library from first
>> principles i.e.
>>
>> newtype Parser a = P (String -> [(a,String)])
>>
>> parse :: Parser a -> String -> [(a,String)]
>> parse (P p)  = p
>>
>> and so on….
>>
>> It’s just an exercise to see how far I can get. And its good fun. So maybe
>> I need add another combinator or to what I already have.
>>
>> Thanks
>>
>> Mike
>>
>>
>> > On 14 Apr 2017, at 19:35, Francesco Ariis <fa...@ariis.it> wrote:
>> >
>> > On Fri, Apr 14, 2017 at 07:02:37PM +0100, mike h wrote:
>> >> I have
>> >> data PackageDec = Pkg String deriving Show
>> >>
>> >> and a parser for it
>> >>
>> >> packageP :: Parser PackageDec
>> >> packageP = do
>> >>    literal “package"
>> >>    x  <- identifier
>> >>    xs <- many ((:) <$> char '.' <*> identifier)
>> >>    return $ Pkg . concat $ (x:xs)
>> >>
>> >> so I’m parsing for this sort  of string
>> >> “package some.sort.of.name”
>> >>
>> >> and I’m trying to rewrite the packageP parser in applicative style. As
>> >> a not quite correct start I have
>> >
>> > Hello Mike,
>> >
>> >    I am not really sure what you are doing here? You are parsing a dot
>> > separated list (like.this.one) but at the end you are concatenating all
>> > together, why?
>> > Are you sure you are not wanting [String] instead of String?
>> >
>> > If so, Parsec comes with some handy parser combinators [1], maybe one of
>> > them could fit your bill:
>> >
>> >    -- should work
>> >    packageP = literal "package" *> Pkg <$> sepEndBy1 identifier (char
>> > '.')
>> >
>> > [1]
>> > https://hackage.haskell.org/package/parsec-3.1.11/docs/Text-Parsec-Combinator.html
>> > <https://hackage.haskell.org/package/parsec-3.1.11/docs/Text-Parsec-Combinator.html>
>> > _______________________________________________
>> > Beginners mailing list
>> > Beginners@haskell.org <mailto:Beginners@haskell.org>
>> > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>> > <http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners>
>> -------------- next part --------------
>> An HTML attachment was scrubbed...
>> URL:
>> <http://mail.haskell.org/pipermail/beginners/attachments/20170414/66a17133/attachment.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 7
>> *****************************************
>
>
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>
_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20170419/994632a3/attachment.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 12
******************************************

Reply via email to