Parsec-Parser works alright, but could it be done better?

匆匆过客 提交于 2019-12-10 17:26:57

问题


I try to do this:

Parse a Text in the form:

Some Text #{0,0,0} some Text #{0,0,0}#{0,0,0} more Text #{0,0,0}

into a list of some data structure:

[Inside "Some Text ",Outside (0,0,0),Inside " some Text ",Outside (0,0,0),Outside (0,0,0),Inside " more Text ",Outside (0,0,0)]

So these #{a,b,c}-bits should turn into different things as the rest of the text.

I have this code:

module ParsecTest where

import Text.ParserCombinators.Parsec
import Monad

type Reference = (Int, Int, Int)

data Transc = Inside String | Outside Reference
              deriving (Show)

text :: Parser Transc
text =  do
         x <- manyTill anyChar ((lookAhead reference) <|> (eof >> return (Inside "")));
         return (Inside x)

transc = reference <|> text

alot :: Parser [Transc]
alot = do
        manyTill transc eof

reference :: Parser Transc
reference = try (do{ char '#';
                  char '{';
                  a <- number;
                char ',';
                b <- number;
                char ',';
                c <- number;
                char '}';
                return (Outside (a,b,c)) })

number :: Parser Int
number = do{ x <- many1 digit;
             return (read x) }

This works as expected. You can test this in ghci by typing

parseTest alot "Some Text #{0,0,0} some Text #{0,0,0}#{0,0,0} more Text #{0,0,0}"

But I think it's not nice.

1) Is the use of lookAhead really necessary for my problem?

2) Is the return (Inside "") an ugly hack?

3) Is there generally a more concise/smarter way to archieve the same?


回答1:


1) I think you do need lookAhead as you need the result of that parse. It would be nice to avoid running that parser twice by having a Parser (Transc,Maybe Transc) to indicate an Inside with an optional following Outside. If performance is an issue, then this is worth doing.

2) Yes.

3) Applicatives

number2 :: Parser Int
number2 = read <$> many1 digit

text2 :: Parser Transc
text2 = (Inside .) . (:) 
     <$> anyChar 
     <*> manyTill anyChar (try (lookAhead reference2) *> pure () <|> eof)


reference2 :: Parser Transc
reference2 = ((Outside .) .) . (,,) 
          <$> (string "#{" *> number2 <* char ',') 
          <*> number2 
          <*> (char ',' *> number2 <* char '}')

transc2 = reference2 <|> text2

alot2 = many transc2

You may want to rewrite the beginning of reference2 using a helper like aux x y z = Outside (x,y,z).

EDIT: Changed text to deal with inputs that don't end with an Outside.



来源:https://stackoverflow.com/questions/7852484/parsec-parser-works-alright-but-could-it-be-done-better

易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!