parsing - 使用秒差距解析命令式语言的奇怪行为

标签 parsing haskell parsec

我正在尝试用 Haskell 中的 Parsec 解析 Abap 语言的片段。 Abap 中的语句由点分隔。函数定义的语法为:

FORM <name> <arguments>.
    <statements>.
ENDFORM.

我将用它作为一个最小的例子。 这是我在 haskell 和解析器中编写相应类型的尝试。 GenStatement - 构造函数适用于除上述函数定义之外的所有其他语句。

module Main where

import Control.Applicative
import Data.Functor.Identity

import qualified Text.Parsec as P
import qualified Text.Parsec.String as S
import Text.Parsec.Language
import qualified Text.Parsec.Token as T

type Args = String
type Name = String

data AbapExpr -- ABAP Program
   = Form Name Args [AbapExpr]
   | GenStatement String [AbapExpr]
   deriving (Show, Read)

lexer :: T.TokenParser ()
lexer = T.makeTokenParser style
  where
    caseSensitive = False
    keys = ["form", "endform"]
    style = emptyDef
        { T.reservedNames = keys
        , T.identStart = P.alphaNum <|> P.char '_'
        , T.identLetter = P.alphaNum <|> P.char '_'
        }

dot :: S.Parser String
dot = T.dot lexer

reserved :: String -> S.Parser ()
reserved = T.reserved lexer

identifier :: S.Parser String
identifier = T.identifier lexer

argsP :: S.Parser String
argsP = P.manyTill P.anyChar (P.try (P.lookAhead dot))

genericStatementP :: S.Parser String
genericStatementP = P.manyTill P.anyChar (P.try dot)

abapExprP = P.try (P.between (reserved "form")
                             (reserved "endform" >> dot)
                             abapFormP)
    <|> abapStmtP
  where
    abapFormP = Form <$> identifier <*> argsP <* dot <*> many abapExprP
    abapStmtP = GenStatement <$> genericStatementP <*> many abapExprP

使用以下输入测试解析器会导致奇怪的行为。

-- a wrapper for convenience
parse :: S.Parser a -> String -> Either P.ParseError a
parse = flip P.parse "Test"

testParse1 = parse abapExprP "form foo arg1 arg2 arg2. form bar arg1. endform. endform."

结果

Right (GenStatement "form foo arg1 arg2 arg2" [GenStatement "form bar arg1" [GenStatement "endform" [GenStatement "endform" []]]])

所以看起来第一个分支总是失败,只有第二个通用分支成功。但是,如果第二个分支(解析通用语句)被注释,则解析表单突然成功:

abapExprP = P.try (P.between (reserved "form")
                             (reserved "endform" >> dot)
                             abapFormP)
    --    <|> abapStmtP
  where
    abapFormP = Form <$> identifier <*> argsP <* dot <*> many abapExprP
    -- abapStmtP = GenStatement <$> genericStatementP <*> many abapExprP

现在我们得到了

 Right (Form "foo" "arg1 arg2 arg2" [Form "bar" "arg1" []])

这怎么可能?看起来第一个分支成功了,为什么它在第一个示例中不起作用 - 我错过了什么?

非常感谢!

最佳答案

我发现您的解析器genericStatementP会解析任何字符,直到出现一个点(您正在使用P.anyChar)。因此,它无法识别您的词法分析器的保留关键字。

我认为你必须定义:

type Args = [String]

和:

argsP :: S.Parser [String]
argsP = P.manyTill identifier (P.try (P.lookAhead dot))

genericStatementP :: S.Parser String
genericStatementP = identifier

通过这些更改,我得到以下结果:

Right (Form "foo" ["arg1","arg2","arg2"] [Form "bar" ["arg1"] []])

关于parsing - 使用秒差距解析命令式语言的奇怪行为,我们在Stack Overflow上找到一个类似的问题: https://stackoverflow.com/questions/46745455/

相关文章:

haskell - 如何将失败的计算转换为成功的计算,反之亦然

haskell - 创建 Comonad 实例可以给我带来什么好处

haskell - 为什么这些 Haskell Parsec 组合器的顺序很重要?

解析 Haskell 自定义数据类型

haskell - 秒差距 vs Yacc/Bison/Antlr : Why and when to use Parsec?

javascript - 为什么在使用解析的字符串时出现错误 'Cannot read property ' name' of null'?

python - 用python解析常见的日志日期字符串

search - 确定一个词 "is"- 对标记进行分类

Android 4.0 Ice Cream Sandwich 解析器错误

visual-studio - 视觉 haskell 2008