
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

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

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

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

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
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-Combinato... https://hackage.haskell.org/package/parsec-3.1.11/docs/Text-Parsec-Combinato... _______________________________________________ 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

Working it out for myself, it should be something like:
blah :: forall f. Applicative f => f PackageDec
blah = package *> Pkg . mconcat <$> ((:) <$> identifier <*> restOfIdentifiers)
where
restOfIdentifiers :: Applicative f => f [String]
restOfIdentifiers = many ((:) <$> char '.' <*> identifier)
On Fri, Apr 14, 2017 at 3:19 PM, mike h
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
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-Combinato... _______________________________________________ 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

Duh! I did have that - well clearly not exactly! What I’d done a couple of hours ago had the parens in the wrong place Earlier i had packageP' = literal "package" >> Pkg <$> (:) <$> identifier <*> many ((:) <$> char '.' <*> identifier) i.e. the first <$> (:) what I have now is (thanks David) packageP' = literal "package" >> Pkg <$> ((:) <$> identifier <*> many ((:) <$> char '.' <*> identifier)) :) Looking at it now what I first had is blindingly obviously wrong! Haskell often makes me feel stupid and makes me work for my code, thats why I love it! Cheers Mike
On 14 Apr 2017, at 20:27, David McBride
wrote: Working it out for myself, it should be something like:
blah :: forall f. Applicative f => f PackageDec blah = package *> Pkg . mconcat <$> ((:) <$> identifier <*> restOfIdentifiers) where restOfIdentifiers :: Applicative f => f [String] restOfIdentifiers = many ((:) <$> char '.' <*> identifier)
On Fri, Apr 14, 2017 at 3:19 PM, mike h
wrote: 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
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-Combinato... _______________________________________________ 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
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
participants (3)
-
David McBride
-
Francesco Ariis
-
mike h