tokenize parser combinators and free applicatives

Hi all on [1] it is said the following "Dealing with whitespace and comments is awkward in the parser; you need to wrap everything in a token combinator. (If you decide to do that, at least use a free applicative functor to ensure that you don’t forget to consume that whitespace)." Reading on `free` the def of Ap, frankly I don't see how can the free applicative be used for this. Anybody could drop a hint? I would appreciate it. [1]: https://ro-che.info/articles/2015-01-02-lexical-analysis -- Ruben

Hi Ruben,
I imagine, free applicative would allow you to easily insert
whitespace/comment eaters afterwards. For instance, say you have Parser
applicative for parsing. Then Ap Parser would represent the same parser,
but with parsing combinators separated with Ap constructors. You would use
Ap Parser when defining your grammar. Then you could "intersperse"
whitespace eaters in between the combinators and "retract" the resulting Ap
Parser into just Parser. That would probably be a cleaner approach compared
to having every combinator wrapped in trimWhiteSpacesAndComments combinator.
Kind regards,
Nick
On Tue, 18 Oct 2016 at 15:12 Ruben Astudillo
Hi all
on [1] it is said the following
"Dealing with whitespace and comments is awkward in the parser; you need to wrap everything in a token combinator. (If you decide to do that, at least use a free applicative functor to ensure that you don’t forget to consume that whitespace)."
Reading on `free` the def of Ap, frankly I don't see how can the free applicative be used for this. Anybody could drop a hint? I would appreciate it.
[1]: https://ro-che.info/articles/2015-01-02-lexical-analysis -- Ruben _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

On 18/10/16 09:29, Nickolay Kudasov wrote:
Hi Ruben,
I imagine, free applicative would allow you to easily insert whitespace/comment eaters afterwards. For instance, say you have Parser applicative for parsing. Then Ap Parser would represent the same parser, but with parsing combinators separated with Ap constructors. You would use Ap Parser when defining your grammar. Then you could "intersperse" whitespace eaters in between the combinators and "retract" the resulting Ap Parser into just Parser. That would probably be a cleaner approach compared to having every combinator wrapped in trimWhiteSpacesAndComments combinator.
I got the idea of what you said. Even if I want to intersperse `space` in the downgrade I end up with stuff on the wrong order. Probably has to do with the fact that Parsec already has a Applicative instance which I am using, instead of just Functor. import Text.Parsec import Control.Applicative hiding (many) import Control.Applicative.Free {- prints: Left (line 1, column 1): unexpected "h" expecting space -} main :: IO () main = print $ example2 -- Works example :: Either ParseError String example = parse query "" "hi number 5" where query = many letter *> space *> many letter *> space *> many digit -- Works in wrong order example2 :: Either ParseError String example2 = parse (down query) "" "hi number 5" where query = liftAp (many letter) *> liftAp (many letter) *> liftAp (many digit) down :: Ap (Parsec String u0) a -> Parsec String u0 a down (Pure a) = pure a down (Ap fa ap) = down ap <* space <*> fa {- to help understanding instance Applicative (Ap f) where pure = Pure Pure f <*> y = fmap f y Ap x y <*> z = Ap x (flip <$> y <*> z) Ap x y :: (Ap f (a -> b)) z :: (Ap f a) x :: (f c) y :: (Ap f (c -> a -> b)) flip <$> y <*> z :: Ap f (c -> b) flip <$> y :: Ap f (a -> c -> b) liftAp space :: Ap Parser Char liftAp space = Ap space (Pure id) liftAp letter :: Ap Parser Char liftAp letter = Ap letter (Pure id) liftAp space *> liftAp letter :: Ap Parser Char = (id <$ (Ap space (Pure id))) <*> Ap letter (Pure id) = Ap space (Pure (const id)) <*> Ap letter (Pure id) = Ap space (flip <$> (Pure (const id)) <*> Ap letter (Pure id)) = Ap space ( Pure (\a _ -> a)) <*> Ap letter (Pure id) ) = Ap space ( Ap letter (Pure (const id)) ) -} -- -- Ruben

On 18/10/16 18:06, Ruben Astudillo wrote:
-- Works in wrong order example2 :: Either ParseError String example2 = parse (down query) "" "hi number 5" where query = liftAp (many letter) *> liftAp (many letter) *> liftAp (many digit)
I got it! I had to use the `runAp` combinator that the `free` package offered. Changing to this version, of the function above in the previous code, makes it work as intend. Sorry for bothering you! example2 :: Either ParseError String example2 = parse (runAp (\f -> f <* skipMany space) query) "" "hi number 5" where query = liftAp (many letter) *> liftAp (many letter) *> liftAp (many digit) -- -- Ruben
participants (2)
-
Nickolay Kudasov
-
Ruben Astudillo