tools/PascalParser.hs
changeset 6277 627b5752733a
parent 6275 f1b4f37dba22
child 6290 c6245ed6cbc0
equal deleted inserted replaced
6275:f1b4f37dba22 6277:627b5752733a
    12 
    12 
    13 data PascalUnit =
    13 data PascalUnit =
    14     Program Identifier Implementation
    14     Program Identifier Implementation
    15     | Unit Identifier Interface Implementation (Maybe Initialize) (Maybe Finalize)
    15     | Unit Identifier Interface Implementation (Maybe Initialize) (Maybe Finalize)
    16     deriving Show
    16     deriving Show
    17 
       
    18 data Interface = Interface Uses TypesAndVars
    17 data Interface = Interface Uses TypesAndVars
    19     deriving Show
    18     deriving Show
    20 data Implementation = Implementation Uses TypesAndVars
    19 data Implementation = Implementation Uses TypesAndVars
    21     deriving Show
    20     deriving Show
    22 data Identifier = Identifier String
    21 data Identifier = Identifier String
    23     deriving Show
    22     deriving Show
    24 data TypesAndVars = TypesAndVars [TypeVarDeclaration]
    23 data TypesAndVars = TypesAndVars [TypeVarDeclaration]
    25     deriving Show
    24     deriving Show
    26 data TypeVarDeclaration = TypeDeclaration TypeDecl
    25 data TypeVarDeclaration = TypeDeclaration Identifier TypeDecl
    27     | ConstDeclaration String
    26     | VarDeclaration Bool ([Identifier], TypeDecl) (Maybe Expression)
    28     | VarDeclaration Bool String
       
    29     | FunctionDeclaration Identifier Identifier (Maybe Phrase)
    27     | FunctionDeclaration Identifier Identifier (Maybe Phrase)
    30     deriving Show
    28     deriving Show
    31 data TypeDecl = SimpleType Identifier
    29 data TypeDecl = SimpleType Identifier
    32     | RangeType Range
    30     | RangeType Range
       
    31     | Sequence [Identifier]
    33     | ArrayDecl Range TypeDecl
    32     | ArrayDecl Range TypeDecl
    34     deriving Show
    33     | RecordType [TypeVarDeclaration]
    35 data Range = Range Identifier    
    34     | UnknownType
       
    35     deriving Show
       
    36 data Range = Range Identifier
       
    37            | RangeFromTo Expression Expression
    36     deriving Show
    38     deriving Show
    37 data Initialize = Initialize String
    39 data Initialize = Initialize String
    38     deriving Show
    40     deriving Show
    39 data Finalize = Finalize String
    41 data Finalize = Finalize String
    40     deriving Show
    42     deriving Show
    49         | Phrases [Phrase]
    51         | Phrases [Phrase]
    50         | SwitchCase Expression [(Expression, Phrase)] (Maybe Phrase)
    52         | SwitchCase Expression [(Expression, Phrase)] (Maybe Phrase)
    51         | Assignment Reference Expression
    53         | Assignment Reference Expression
    52     deriving Show
    54     deriving Show
    53 data Expression = Expression String
    55 data Expression = Expression String
    54     | FunCall Identifier [Expression]
    56     | FunCall Reference [Expression]
    55     | PrefixOp String Expression
    57     | PrefixOp String Expression
    56     | PostfixOp String Expression
    58     | PostfixOp String Expression
    57     | BinOp String Expression Expression
    59     | BinOp String Expression Expression
    58     | StringLiteral String
    60     | StringLiteral String
       
    61     | CharCode String
    59     | NumberLiteral String
    62     | NumberLiteral String
       
    63     | HexNumber String
       
    64     | Address Reference
    60     | Reference Reference
    65     | Reference Reference
    61     deriving Show
    66     deriving Show
    62 data Reference = ArrayElement Identifier Expression
    67 data Reference = ArrayElement Identifier Expression
    63     | SimpleReference Identifier
    68     | SimpleReference Identifier
    64     | RecordField Reference Reference
    69     | RecordField Reference Reference
    77             "begin", "end", "program", "unit", "interface"
    82             "begin", "end", "program", "unit", "interface"
    78             , "implementation", "and", "or", "xor", "shl"
    83             , "implementation", "and", "or", "xor", "shl"
    79             , "shr", "while", "do", "repeat", "until", "case", "of"
    84             , "shr", "while", "do", "repeat", "until", "case", "of"
    80             , "type", "var", "const", "out", "array"
    85             , "type", "var", "const", "out", "array"
    81             , "procedure", "function", "with", "for", "to"
    86             , "procedure", "function", "with", "for", "to"
    82             , "downto", "div", "mod"
    87             , "downto", "div", "mod", "record", "set"
    83             ]
    88             ]
    84     , reservedOpNames= [] 
    89     , reservedOpNames= [] 
    85     , caseSensitive  = False   
    90     , caseSensitive  = False   
    86     }
    91     }
    87     
    92     
    88 pas = patch $ makeTokenParser pascalLanguageDef
    93 pas = patch $ makeTokenParser pascalLanguageDef
    89     where
    94     where
    90     patch tp = tp {stringLiteral = between (char '\'') (char '\'') (many $ noneOf "'")}
    95     patch tp = tp {stringLiteral = sl}
       
    96     sl = do
       
    97         (char '\'')
       
    98         s <- (many $ noneOf "'")
       
    99         (char '\'')
       
   100         ss <- many $ do
       
   101             (char '\'')
       
   102             s' <- (many $ noneOf "'")
       
   103             (char '\'')
       
   104             return $ '\'' : s'
       
   105         comments    
       
   106         return $ concat (s:ss)
    91     
   107     
    92 comments = do
   108 comments = do
    93     spaces
   109     spaces
    94     skipMany $ do
   110     skipMany $ do
    95         comment
   111         comment
   134     table = [ 
   150     table = [ 
   135         [Postfix (char '^' >> return Dereference)]
   151         [Postfix (char '^' >> return Dereference)]
   136         , [Infix (char '.' >> return RecordField) AssocLeft]
   152         , [Infix (char '.' >> return RecordField) AssocLeft]
   137         ]
   153         ]
   138     
   154     
   139     
   155 varsDecl1 = varsParser many1    
   140 varsDecl endsWithSemi = do
   156 varsDecl = varsParser many
   141     vs <- many (try (aVarDecl >> semi pas) >> comments)
   157 varsParser m endsWithSemi = do
   142     when (not endsWithSemi) $ aVarDecl >> return ()
   158     vs <- m (aVarDecl >>= \i -> semi pas >> comments >> return i)
   143     comments
   159     v <- if not endsWithSemi then liftM (\a -> [a]) aVarDecl else return []
   144     return $ VarDeclaration False $ show vs
   160     comments
       
   161     return $ vs ++ v
   145     where
   162     where
   146     aVarDecl = do
   163     aVarDecl = do
   147         when (not endsWithSemi) $
   164         when (not endsWithSemi) $
   148             optional $ choice [
   165             optional $ choice [
   149                 try $ string "var"
   166                 try $ string "var"
   150                 , try $ string "const"
   167                 , try $ string "const"
   151                 , try $ string "out"
   168                 , try $ string "out"
   152                 ]
   169                 ]
   153         comments
   170         comments
   154         ids <- (commaSep1 pas) $ (iD <?> "variable declaration")
   171         ids <- try $ do
   155         char ':'
   172             i <- (commaSep1 pas) $ (iD <?> "variable declaration")
   156         comments
   173             char ':'
   157         t <- typeDecl
   174             return i
   158         comments
   175         comments
   159         return (ids, t)
   176         t <- typeDecl <?> "variable type declaration"
       
   177         comments
       
   178         init <- option Nothing $ do
       
   179             char '='
       
   180             comments
       
   181             e <- expression
       
   182             comments
       
   183             char ';'
       
   184             comments
       
   185             return (Just e)
       
   186         return $ VarDeclaration False (ids, t) init
   160 
   187 
   161 
   188 
   162 constsDecl = do
   189 constsDecl = do
   163     vs <- many (try (aConstDecl >> semi pas) >> comments)
   190     vs <- many (try (aConstDecl >>= \i -> semi pas >> return i) >>= \i -> comments >> return i)
   164     comments
   191     comments
   165     return $ VarDeclaration True $ show vs
   192     return vs
   166     where
   193     where
   167     aConstDecl = do
   194     aConstDecl = do
   168         comments
   195         comments
   169         ids <- iD <?> "const declaration"
   196         i <- iD <?> "const declaration"
   170         optional $ do
   197         optional $ do
   171             char ':'
   198             char ':'
   172             comments
   199             comments
   173             t <- typeDecl
   200             t <- typeDecl
   174             return ()
   201             return ()
   175         char '='
   202         char '='
   176         comments
   203         comments
   177         e <- expression
   204         e <- expression
   178         comments
   205         comments
   179         return (ids, e)
   206         return $ VarDeclaration False ([i], UnknownType) (Just e)
   180         
   207         
   181 typeDecl = choice [
   208 typeDecl = choice [
   182     arrayDecl
   209     arrayDecl
       
   210     , recordDecl
   183     , rangeDecl >>= return . RangeType
   211     , rangeDecl >>= return . RangeType
       
   212     , seqenceDecl >>= return . Sequence
   184     , identifier pas >>= return . SimpleType . Identifier
   213     , identifier pas >>= return . SimpleType . Identifier
   185     ] <?> "type declaration"
   214     ] <?> "type declaration"
   186     where
   215     where
   187     arrayDecl = do
   216     arrayDecl = do
   188         try $ string "array"
   217         try $ string "array"
   193         comments
   222         comments
   194         string "of"
   223         string "of"
   195         comments
   224         comments
   196         t <- typeDecl
   225         t <- typeDecl
   197         return $ ArrayDecl r t
   226         return $ ArrayDecl r t
   198 
   227     recordDecl = do
       
   228         try $ string "record"
       
   229         comments
       
   230         vs <- varsDecl True
       
   231         string "end"
       
   232         return $ RecordType vs
       
   233     seqenceDecl = (parens pas) $ (commaSep pas) iD
       
   234 
       
   235 typesDecl = many (aTypeDecl >>= \t -> comments >> return t)
       
   236     where
       
   237     aTypeDecl = do
       
   238         i <- try $ do
       
   239             i <- iD <?> "type declaration"
       
   240             comments
       
   241             char '='
       
   242             return i
       
   243         comments
       
   244         t <- typeDecl
       
   245         comments
       
   246         semi pas
       
   247         comments
       
   248         return $ TypeDeclaration i t
   199         
   249         
   200 rangeDecl = choice [
   250 rangeDecl = choice [
   201     iD >>= return . Range
   251     try $ rangeft
       
   252     , iD >>= return . Range
   202     ] <?> "range declaration"
   253     ] <?> "range declaration"
   203 
   254     where
   204     
   255     rangeft = do
   205 typeVarDeclaration isImpl = choice [
   256     e1 <- expression
       
   257     string ".."
       
   258     e2 <- expression
       
   259     return $ RangeFromTo e1 e2
       
   260     
       
   261 typeVarDeclaration isImpl = (liftM concat . many . choice) [
   206     varSection,
   262     varSection,
   207     constSection,
   263     constSection,
       
   264     typeSection,
   208     funcDecl,
   265     funcDecl,
   209     procDecl
   266     procDecl
   210     ]
   267     ]
   211     where
   268     where
   212     varSection = do
   269     varSection = do
   213         try $ string "var"
   270         try $ string "var"
   214         comments
   271         comments
   215         v <- varsDecl True
   272         v <- varsDecl1 True
   216         comments
   273         comments
   217         return v
   274         return v
   218 
   275 
   219     constSection = do
   276     constSection = do
   220         try $ string "const"
   277         try $ string "const"
   221         comments
   278         comments
   222         c <- constsDecl
   279         c <- constsDecl
   223         comments
   280         comments
   224         return c
   281         return c
       
   282 
       
   283     typeSection = do
       
   284         try $ string "type"
       
   285         comments
       
   286         t <- typesDecl
       
   287         comments
       
   288         return t
   225         
   289         
   226     procDecl = do
   290     procDecl = do
   227         string "procedure"
   291         string "procedure"
   228         comments
   292         comments
   229         i <- iD
   293         i <- iD
   234         comments
   298         comments
   235         char ';'
   299         char ';'
   236         b <- if isImpl then
   300         b <- if isImpl then
   237                 do
   301                 do
   238                 comments
   302                 comments
   239                 optional $ typeVarDeclaration isImpl
   303                 optional $ typeVarDeclaration True
   240                 comments
   304                 comments
   241                 liftM Just functionBody
   305                 liftM Just functionBody
   242                 else
   306                 else
   243                 return Nothing
   307                 return Nothing
   244         comments
   308         comments
   245         return $ FunctionDeclaration i (Identifier "") b
   309         return $ [FunctionDeclaration i (Identifier "") b]
   246         
   310         
   247     funcDecl = do
   311     funcDecl = do
   248         string "function"
   312         string "function"
   249         comments
   313         comments
   250         i <- iD
   314         i <- iD
   258         comments
   322         comments
   259         char ';'
   323         char ';'
   260         b <- if isImpl then
   324         b <- if isImpl then
   261                 do
   325                 do
   262                 comments
   326                 comments
   263                 typeVarDeclaration isImpl
   327                 optional $ typeVarDeclaration True
   264                 comments
   328                 comments
   265                 liftM Just functionBody
   329                 liftM Just functionBody
   266                 else
   330                 else
   267                 return Nothing
   331                 return Nothing
   268         return $ FunctionDeclaration i ret Nothing
   332         return $ [FunctionDeclaration i ret Nothing]
   269 
   333 
   270 program = do
   334 program = do
   271     string "program"
   335     string "program"
   272     comments
   336     comments
   273     name <- iD
   337     name <- iD
   280 interface = do
   344 interface = do
   281     string "interface"
   345     string "interface"
   282     comments
   346     comments
   283     u <- uses
   347     u <- uses
   284     comments
   348     comments
   285     tv <- many (typeVarDeclaration False)
   349     tv <- typeVarDeclaration False
   286     comments
   350     comments
   287     return $ Interface u (TypesAndVars tv)
   351     return $ Interface u (TypesAndVars tv)
   288 
   352 
   289 implementation = do
   353 implementation = do
   290     string "implementation"
   354     string "implementation"
   291     comments
   355     comments
   292     u <- uses
   356     u <- uses
   293     comments
   357     comments
   294     tv <- many (typeVarDeclaration True)
   358     tv <- typeVarDeclaration True
   295     string "end."
   359     string "end."
   296     comments
   360     comments
   297     return $ Implementation u (TypesAndVars tv)
   361     return $ Implementation u (TypesAndVars tv)
   298 
   362 
   299 expression = buildExpressionParser table term <?> "expression"
   363 expression = buildExpressionParser table term <?> "expression"
   300     where
   364     where
   301     term = comments >> choice [
   365     term = comments >> choice [
   302         parens pas $ expression 
   366         parens pas $ expression 
   303         , integer pas >>= return . NumberLiteral . show
   367         , integer pas >>= return . NumberLiteral . show
   304         , stringLiteral pas >>= return . StringLiteral
   368         , stringLiteral pas >>= return . StringLiteral
       
   369         , char '#' >> many digit >>= return . CharCode
       
   370         , char '$' >> many hexDigit >>= return . HexNumber
       
   371         , char '@' >> reference >>= return . Address
   305         , try $ funCall
   372         , try $ funCall
   306         , reference >>= return . Reference
   373         , reference >>= return . Reference
   307         ] <?> "simple expression"
   374         ] <?> "simple expression"
   308 
   375 
   309     table = [ 
   376     table = [ 
   449     i <- iD
   516     i <- iD
   450     p <- option [] $ (parens pas) parameters
   517     p <- option [] $ (parens pas) parameters
   451     return $ ProcCall i p
   518     return $ ProcCall i p
   452 
   519 
   453 funCall = do
   520 funCall = do
   454     i <- iD
   521     r <- reference
   455     p <- (parens pas) $ option [] parameters
   522     p <- (parens pas) $ option [] parameters
   456     return $ FunCall i p
   523     return $ FunCall r p
   457 
   524 
   458 parameters = (commaSep pas) expression <?> "parameters"
   525 parameters = (commaSep pas) expression <?> "parameters"
   459         
   526         
   460 functionBody = do
   527 functionBody = do
   461     p <- phrasesBlock
   528     p <- phrasesBlock