2

以下の例をSOから部分的に取り出し、必要に応じて変更しました。それはほぼ適合しますが、私がやりたいことは、commaSep expr の最初の文字列が常に識別子として解析され、後続のすべての文字列が文字列のみであることです。

現在、それらはすべて識別子として解析されます。

*Parser> parse expr "" "rd (isFib, test2, 100.1, ?BOOL)"
Right (FuncCall "rd" [Identifier "isFib",Identifier "test2",Number 100.1,Query "?BOOL"])

最終的にcommaSepを使用せずに入力全体を解析することになる解決策をいくつか試しました。構造を無視して、次のようなことをしなければならないことを意味します

expr_parse = do
    name <- resvd_cmd
    char '('
    skipMany space
    worker <- ident
    char ','
    skipMany1 space
    args <- commaSep expr --not fully worked this out yet
    query <- theQuery
    skipMany space
    char ')'
    return (name, worker, args, query)

それは私には最適ではなく、非常に不格好に見えます。expr以下のコードをリファクタリングし、必要なものを達成してシンプルに保つ方法はありますか?

module Parser where

import Control.Monad (liftM)
import Text.Parsec
import Text.Parsec.String (Parser)
import Lexer
import AST

expr = ident <|>  astring <|> number <|> theQuery <|> callOrIdent

astring = liftM String stringLiteral <?> "String"

number = liftM Number float <?> "Number"

ident = liftM Identifier identifier <?> "WorkerName"

questionm :: Parser Char
questionm = oneOf "?"

theQuery :: Parser AST
theQuery = do first <- questionm
              rest <- many1 letter
              let query = first:rest
              return ( Query query )

resvd_cmd = do { reserved "rd"; return ("rd") }
            <|> do { reserved "eval"; return ("eval") }
            <|> do { reserved "read"; return ("read") }
            <|> do { reserved "in"; return ("in") }
            <|> do { reserved "out"; return ("out") }
            <?> "LINDA-like Tuple"

callOrIdent = do
    name <- resvd_cmd
    liftM (FuncCall name)(parens $ commaSep expr) <|> return (Identifier name)

AST.hs

{-# LANGUAGE DeriveDataTypeable #-}

module AST where

import Data.Typeable

data AST
    = Number Double
    | Identifier String
    | String String
    | FuncCall String [AST]
    | Query String
    deriving (Show, Eq, Typeable)

Lexer.hs

module Lexer (
            identifier, reserved, operator, reservedOp, charLiteral, stringLiteral,
            natural, integer, float, naturalOrFloat, decimal, hexadecimal, octal,
            symbol, lexeme, whiteSpace, parens, braces, angles, brackets, semi,
            comma, colon, dot, semiSep, semiSep1, commaSep, commaSep1
    )where

import Text.Parsec
import qualified Text.Parsec.Token as P
import Text.Parsec.Language (haskellStyle)

lexer = P.makeTokenParser ( haskellStyle
                            {P.reservedNames = ["rd", "in", "out", "eval", "take"]}
                         )


identifier = P.identifier lexer
reserved = P.reserved lexer
operator = P.operator lexer
reservedOp = P.reservedOp lexer
charLiteral = P.charLiteral lexer
stringLiteral = P.stringLiteral lexer
natural = P.natural lexer
integer = P.integer lexer
float = P.float lexer
naturalOrFloat = P.naturalOrFloat lexer
decimal = P.decimal lexer
hexadecimal = P.hexadecimal lexer
octal = P.octal lexer
symbol = P.symbol lexer
lexeme = P.lexeme lexer
whiteSpace = P.whiteSpace lexer
parens = P.parens lexer
braces = P.braces lexer
angles = P.angles lexer
brackets = P.brackets lexer
semi = P.semi lexer
comma = P.comma lexer
colon = P.colon lexer
dot = P.dot lexer
semiSep = P.semiSep lexer
semiSep1 = P.semiSep1 lexer
commaSep = P.commaSep lexer
commaSep1 = P.commaSep1 lexer
4

1 に答える 1

4

lexeme最初に、パーサーが末尾の空白を食べるように変更する関数を紹介したいと思います。空白を明示的に食べるのではなく、使用することをお勧めします。食べて失敗するcommaSepので難点です。,あまり楽観的でない を書くのはいいことですがcommaSep、問題を直接解決しましょう。

に応募しよlexemecomma

acomma = lexeme comma

コードの問題の 1 つは、コードが として表示test2されることを期待してString "test2"いたのに、astringパーサーは文字列が で始まり、 で終わることを期待していたこと"です。はげた文字列用のパーサーを作成しましょう。ただし、最初に?スペースやコンマが含まれていないことを確認してください。

baldString = lexeme $ do
   x <- noneOf "? ,)"
   xs <- many (noneOf " ,)")   -- problematic - see comment below
   return . String $ x:xs

最後にクエリが必要なため、常に baldString の後にカンマがあることに気付いたとき、突破口が開かれました。

baldStringComma = do 
        s <- baldString
        acomma
        return s

タプルの最後にある 1 つ以上のクエリのパーサーを作成しましょう。

queries = commaSep1 (lexeme theQuery)

これで、識別子、baldStrings、およびクエリを取得できます

therest = do
   name <- lexeme ident 
   acomma
   args <- many baldStringComma
   qs <- queries
   return (name,args,qs)

最終的に与える

tuple = do
    name <- lexeme resvd_cmd
    stuff <- parens therest
    return (name,stuff)

だからあなたは得る

*Parser> parseTest tuple "rd (isFib, test2, 100.1, ?BOOL)"
("rd",(Identifier "isFib",[String "test2",String "100.1"],[Query "?BOOL"]))

ただし、クエリで文字列をまとめたい場合はreturn (name,args++qs)therest.

Applicative はあまり醜くない

<$>などの素敵なものがあるのに、モナドインターフェースに縛られるのはもどかしいと思った<*>ので、最初に

import Control.Applicative hiding (many, (<|>))

それで

baldString = lexeme . fmap String $
   (:) <$> noneOf "? ,)"   
       <*> many (noneOf " ,)")   -- problematic - see comment below

<$>これは の中置バージョンでfmapあるため(:)、 の出力に適用され、 のnoneOf "? ,"ようなものを返すパーサーが得られます('c':)。これは、必要な文字列を与えるためにmany (noneOf " ,")usingの出力に適用できます。<*>

baldStringComma = baldString <* acomma

の出力を無視し、の出力のみを返す<*>ように演算子を取得したので、これは便利です。逆の方法が必要な場合は、 を実行できますが、最初のパーサーの出力を既に無視している を使用することもできます。acommabaldString<**>>>

therest = (,,) <$> 
   lexeme ident <* acomma
   <*> many baldStringComma
   <*> queries

tuple = (,) <$> lexeme resvd_cmd 
            <*> parens therest

しかし、私たちがそうするなら、それはより良いことではないでしょうか

data Tuple = Tuple {cmd :: String, 
                    id :: AST,
                    argumentList :: [AST],
                    queryList :: [AST]} deriving Show

私たちができるように

niceTuple = Tuple <$> lexeme resvd_cmd <* lexeme (char '(')
                  <*> lexeme ident <* acomma
                  <*> many baldStringComma
                  <*> queries <* lexeme (char ')')

これにより(幅に収まるように手動できれいに印刷する必要があります)

*Parser> parseTest niceTuple "rd (isFib, test2, 100.1, ?BOOL)"
Tuple {cmd = "rd", 
       id = Identifier "isFib", 
       argumentList = [String "test2",String "100.1"], 
       queryList = [Query "?BOOL"]}

また、現在ASTは抽象構文ツリーというよりも抽象構文ストアであり、独自のタプル型を設計してそれを使用することでより多くのマイレージを得ることができると思います。使用する

newtype Command = Cmd String  deriving Show

など、型の安全性を確保し、パーサーを使用してそれらをタプル型にまとめて生成します。

于 2012-11-25T23:50:41.820 に答える