tools/PascalParser.hs
changeset 6272 a93cb9ca9fda
parent 6270 0a99f73dd8dd
child 6275 f1b4f37dba22
equal deleted inserted replaced
6271:9310cfe6bc37 6272:a93cb9ca9fda
     1 module PascalParser where
     1 module PascalParser where
     2 
     2 
     3 import Text.ParserCombinators.Parsec
     3 import Text.Parsec.Expr
     4 import Text.ParserCombinators.Parsec.Expr
     4 import Text.Parsec.Char
     5 import Text.ParserCombinators.Parsec.Token
     5 import Text.Parsec.Token
     6 import Text.ParserCombinators.Parsec.Language
     6 import Text.Parsec.Language
       
     7 import Text.Parsec.Prim
       
     8 import Text.Parsec.Combinator
       
     9 import Text.Parsec.String
     7 import Control.Monad
    10 import Control.Monad
     8 import Data.Char
    11 import Data.Char
     9 
    12 
    10 data PascalUnit =
    13 data PascalUnit =
    11     Program Identifier Implementation
    14     Program Identifier Implementation
    78     spaces
    81     spaces
    79     skipMany $ do
    82     skipMany $ do
    80         comment
    83         comment
    81         spaces
    84         spaces
    82 
    85 
    83 validIdChar = alphaNum <|> oneOf "_"    
       
    84 
       
    85 pascalUnit = do
    86 pascalUnit = do
    86     comments
    87     comments
    87     u <- choice [program, unit]
    88     u <- choice [program, unit]
    88     comments
    89     comments
    89     return u
    90     return u
   100     int <- interface
   101     int <- interface
   101     impl <- implementation
   102     impl <- implementation
   102     comments
   103     comments
   103     return $ Unit name int impl Nothing Nothing
   104     return $ Unit name int impl Nothing Nothing
   104     where
   105     where
   105         unitName = between (string "unit" >> comments) (char ';') (identifier pas)
   106         unitName = between (string "unit" >> comments) (semi pas) (identifier pas)
   106 
   107 
   107 varsDecl = do
   108 varsDecl endsWithSemi = do
   108     v <- aVarDecl `sepBy1` (char ';' >> comments)
   109     vs <- many (try (aVarDecl >> semi pas) >> comments)
   109     char ';'
   110     when (not endsWithSemi) $ aVarDecl >> return ()
   110     comments
   111     comments
   111     return $ VarDeclaration $ show v
   112     return $ VarDeclaration $ show vs
   112     where
   113     where
   113     aVarDecl = do
   114     aVarDecl = do
   114         ids <- (try (identifier pas) >>= \i -> comments >> return (Identifier i)) `sepBy1` (char ',' >> comments)
   115         ids <- (commaSep1 pas) $ ((identifier pas) <?> "variable declaration") >>= \i -> comments >> return (Identifier i)
   115         char ':'
   116         char ':'
   116         comments
   117         comments
   117         t <- typeDecl
   118         t <- typeDecl
   118         comments
   119         comments
   119         return (ids, t)
   120         return (ids, t)
   147     ]
   148     ]
   148     where
   149     where
   149     varSection = do
   150     varSection = do
   150         try $ string "var"
   151         try $ string "var"
   151         comments
   152         comments
   152         v <- varsDecl
   153         v <- varsDecl True
       
   154         comments
   153         return v
   155         return v
   154             
   156             
   155     procDecl = do
   157     procDecl = do
   156         string "procedure"
   158         string "procedure"
   157         comments
   159         comments
   158         i <- liftM Identifier $ identifier pas
   160         i <- liftM Identifier $ identifier pas
   159         optional $ do
   161         optional $ do
   160             char '('
   162             char '('
   161             varsDecl
   163             varsDecl False
   162             char ')'
   164             char ')'
   163         comments
   165         comments
   164         char ';'
   166         char ';'
   165         b <- if isImpl then
   167         b <- if isImpl then
   166                 do
   168                 do
   174         return $ FunctionDeclaration i (Identifier "") b
   176         return $ FunctionDeclaration i (Identifier "") b
   175         
   177         
   176     funcDecl = do
   178     funcDecl = do
   177         string "function"
   179         string "function"
   178         comments
   180         comments
   179         char '('
   181         optional $ do
   180         b <- manyTill anyChar (try $ char ')')
   182             char '('
   181         char ')'
   183             varsDecl False
       
   184             char ')'
   182         comments
   185         comments
   183         char ':'
   186         char ':'
   184         ret <- identifier pas
   187         ret <- identifier pas
   185         comments
   188         comments
   186         char ';'
   189         char ';'