簡體   English   中英

在語義分析階段獲取行號信息(使用Alex,Happy)

[英]Getting line number information in the Semantic Analysis Phase (using Alex,Happy)

我正在為實驗語言進行語義分析。 我正在使用Alex和Happy來生成詞法分析器和解析器(實際上我正在使用BNFC工具來生成Alex和Happy文件)。 每當出現語義錯誤(比如類型錯誤)時,我都想收到包含行號和列號的錯誤消息。

似乎我必須在構建符號表或AST時存儲行號信息。 如果我可以以某種方式訪問​​Happy文件的規則部分中的位置信息,我的問題就會解決。

任何有關這方面的建議都將受到高度贊賞。

我嘗試實現下面建議的答案,但遺憾的是沒有取得任何成功。 讓我們考慮一個非常簡單的語法: -

Expr -> Expr + Term
       | Term
Term -> Int

我的詞法分析器如下所示。

%wrapper "posn"

$digit = 0-9            -- digits
$alpha = [a-zA-Z]       -- alphabetic characters

tokens :-

  $white+               ;
  "--".*                ;
  $digit+               { \p s -> L {getPos = p , unPos = Tok_Int (read s) }}
  \+                    { \p s -> L {getPos = p , unPos = Tok_Plus} }


{
data L a = L{ getPos :: AlexPosn, unPos :: a } deriving (Eq,Show)

data Token =
      Tok_Plus 
    | Tok_Int Int 
    deriving (Eq,Show)


getToken :: IO [L Token]
getToken = do 
    args <- getArgs
    case length args == 0 of
        True  -> do 
               error $ "\n****************Error: Expecting file name as an argument.\n" 
        False -> do
            let fname  = args !! 0 
            conts <- readFile fname
            let tokens = alexScanTokens conts 
            return tokens 

}

我的Yacc文件如下,這是我正在努力的地方。 如何在我的語法樹中嵌入位置信息。

{
{-# OPTIONS_GHC -fno-warn-incomplete-patterns -fno-warn-overlapping-patterns #-}
module Parser where
import Lexer

}

%name pExpr Exp 
%name pTerm Term 

%tokentype {L Token}
%error { parseError }

%token
      int             { L { getPos = _,unPos = Tok_Int $$ } }
      '+'             { L { getPos = _,unPos = Tok_Plus } }

%%
Exp :: {L Expr} 
Exp  : Exp '+' Term           { L { getPos =  getPos $1 , unPos = EAdd (unPos $1) (unPos $3) } }
     | Term                   { $1 }

Term :: {L Expr}
Term : int                   { L {getPos =  getPos $1, unPos =  EInt (unPos $1) } } 

{

data Expr =  EAdd Expr Expr 
            | EInt Int 
            deriving (Eq,Show)


returnM :: a -> Err a
returnM = return

thenM :: Err a -> (a -> Err b) -> Err b
thenM = (>>=)


parseError :: [L Token] -> a
parseError _ = error "Parse error"

}

嘗試編譯生成的Haskell文件時,我收到以下類型錯誤。

Parser.hs:109:39:
    Couldn't match expected type `L a0' with actual type `Int'
    In the first argument of `getPos', namely `happy_var_1'
    In the `getPos' field of a record
    In the first argument of `HappyAbsSyn5', namely
      `(L {getPos = getPos happy_var_1,
           unPos = EInt (unPos happy_var_1)})'

Parser.hs:109:73:
    Couldn't match expected type `L Int' with actual type `Int'
    In the first argument of `unPos', namely `happy_var_1'
    In the first argument of `EInt', namely `(unPos happy_var_1)'
    In the `unPos' field of a record

你們能告訴我如何使這件事有效嗎?

如果您的詞法分析器輸出中有位置信息,則可以訪問快樂規則中的位置信息。 這正是GHC本身如何將SrcLoc放入其自己的Haskell代碼內部表示中的方式。

基本上,您將使用posn Alex包裝器將位置信息注入您的令牌類型:

data L a = L{ getPos :: AlexPosn, unPos :: a }

(所以你的Alex標記L Token會返回L Token值); 然后你將快樂規則中的各個令牌位置組合到非終結符的位置(例如,你可以從Expr + ExprL (combinedPosn [getPos $1, getPos $2, getPos $3] $ PlusExpr (unPos $1) (unPos $3)的規則L (combinedPosn [getPos $1, getPos $2, getPos $3] $ PlusExpr (unPos $1) (unPos $3)

暫無
暫無

聲明:本站的技術帖子網頁,遵循CC BY-SA 4.0協議,如果您需要轉載,請注明本站網址或者原文地址。任何問題請咨詢:yoyou2525@163.com.

 
粵ICP備18138465號  © 2020-2024 STACKOOM.COM