とりあえず Vparsecという名前で書いています


とりあえず Parsecをちゃんと使えてるかどうかをチェックしたいので
semantic valueの処理は全然作り込んでいなくて
パースした文字列を表示する処理だけ書いています。


declarationを書いているのだけど、どんどん繋がっていってキリがないので
一旦 module_itemで切ってソースを貼っておこうと思います。


portのシンタックスってこんなに複雑だったっけ。
あと、BNFに明示されてないけど spaceの扱いをちゃんとやろうとすると
記述が長くなってしまいます。
それから、いまのところ tryをふんだんに使っています。

module Vparsec where

import Text.ParserCombinators.Parsec
import Text.ParserCombinators.Parsec.Expr

{-- File input version --}
parseVerilog :: FilePath -> IO ()
parseVerilog fname
    = do { input <- readFile fname
         ; putStr input
         ; case parse verilog1995 fname input of
                Left err -> do { putStr "Error parsing at : " ; print err }
                Right x -> print x }


-- Verilog 1995 parser
verilog1995 :: Parser String
verilog1995 = do { a <- description ; return a }
            <?> "source text!!"

description :: Parser String
description = do { mod <- moduleDeclaration ; return mod }
          <|> do { udp <- udp_declaration ; return udp }
          <?> "description"
                
-- XXX MEMO : letters, digits, dollar, _ :: first must be a letter or the underscore.
-- XXX size is up to 1024. (this consraint is not implemented yet)
identifier :: Parser String
identifier = do { c <- char '_' <|> letter
                ; cs <- many (try(alphaNum) <|> try(char '_') <|> char '$')
                ; return (c:cs) }
          <?> "identifier"

moduleDeclaration :: Parser String
moduleDeclaration = do { a <- try(string "module")
                       ; b <- moduleDeclaration_
                       ; return $ a ++ b }
                <|> do { a <- try(string "macromodule")
                       ; b <- moduleDeclaration_
                       ; return $ a ++ b }
                <?> "moduleDeclaration"
    where
        moduleDeclaration_ :: Parser String
        moduleDeclaration_
            = do { many1 space
                 ; a <- nameOfModule
                 ; spaces
                 ; b <- listOfPorts <|> string ""
                 ; spaces
                 ; c <- string ";"
--               ; spaces
--               ; d <- many moduleItem     -- XXX not yet
                 ; many1 space
                 ; e <- string "endmodule"
                 ; return $ a ++ b ++ c {- ++ (concat d) -} ++ e }

nameOfModule :: Parser String
nameOfModule = identifier <?> "nameOfModule"

listOfPorts :: Parser String
listOfPorts = do { a <- string "("
                 ; spaces
                 ; b <- port
                 ; spaces
                 ; c <- many commaPorts
                 ; spaces
                 ; d <- string ")"
                 ; return $ a ++ b ++ (concat c) ++ d } 
            <?> "listOfPorts"

port :: Parser String
port = do { a <- try(port') ; return a }
   <|> do { a <- try(portExpression) ; return a }
   <|> string ""
   <?> "port"
        where
            port' :: Parser String
            port' = do { a <- string "."
                       ; spaces
                       ; b <- nameOfPort
                       ; spaces
                       ; c <- string "("
                       ; spaces
                       ; d <- try(portExpression) <|> string ""
                       ; spaces
                       ; e <- string ")"
                       ; return $ a ++ b ++ c ++ d ++ e }

commaPorts :: Parser String
commaPorts = do { a <- string ","
                ; spaces 
                ; b <- port
                ; return $ a ++ b; }
          <?> "commaPorts"

portExpression :: Parser String
portExpression = do { a <- try(portReference) ; return a }
             <|> do { a <- try(portExpression') ; return a }
             <?> "portExpression"
                where
                    portExpression' :: Parser String 
                    portExpression'
                        = do { a <- string "{"
                             ; spaces
                             ; b <- portReference
                             ; spaces
                             ; c <- many commaPortReference
                             ; spaces
                             ; d <- string "}"
                             ; return $ a ++ b ++ (concat c) ++ d }

commaPortReference :: Parser String
commaPortReference = do { a <- string ","
                        ; spaces
                        ; b <- portReference
                        ; return $ a ++ b }
                  <?> "commaPortReference"

portReference :: Parser String
portReference = do { a <- nameOfVariable
                   ; b <- portConstantExpression
                   ; return $ a ++ b }
             <?> "portReference"
    where
        portConstantExpression :: Parser String
        portConstantExpression = do { a <- try(portConstantExpression') ; return a }
                             <|> do { a <- try(portConstantExpression'') ; return a }
                             <|> do { a <- string ""; return a }
                             <?> "portConstantExpression"

        portConstantExpression' :: Parser String
        portConstantExpression' = do { a <- string "["
                                     ; spaces
                                     ; b <- constantExpression
                                     ; spaces
                                     ; c <- string "]"
                                     ; return $ a ++ b ++ c } 

        portConstantExpression'' :: Parser String
        portConstantExpression'' = do { a <- string "["
                                      ; spaces
                                      ; b <- constantExpression
                                      ; spaces
                                      ; c <- string ":"
                                      ; spaces
                                      ; d <- string "]"
                                      ; return $ a ++ b ++ c ++ d }

nameOfPort :: Parser String
nameOfPort = identifier <?> "nameOfPort"

nameOfVariable :: Parser String
nameOfVariable = identifier <?> "nameOfVariable"



{--------- XXX TODO impl. ---------}
udp_declaration :: Parser String
udp_declaration = string ""
             <?> "udp_declaration"

constantExpression :: Parser String
--constantExpression = expression   -- temp. 
constantExpression = string ""      -- dummy
                 <?> "constantExpression"