Initial Commit
[packages] / xemacs-packages / semantic / wisent / wisent-java-tags.wy
1 ;;; wisent-java-tags.wy -- Semantic LALR grammar for Java
2 ;;
3 ;; Copyright (C) 2002, 2007 David Ponce
4 ;; Copyright (C) 2007 Eric Ludlam
5 ;;
6 ;; Author: David Ponce <david@dponce.com>
7 ;; Maintainer: David Ponce <david@dponce.com>
8 ;; Created: 25 Feb 2002
9 ;; Keywords: syntax
10 ;; X-RCS: $Id: wisent-java-tags.wy,v 1.1 2007-11-26 15:12:32 michaels Exp $
11 ;;
12 ;; This file is not part of GNU Emacs.
13 ;;
14 ;; This program is free software; you can redistribute it and/or
15 ;; modify it under the terms of the GNU General Public License as
16 ;; published by the Free Software Foundation; either version 2, or (at
17 ;; your option) any later version.
18 ;;
19 ;; This software is distributed in the hope that it will be useful,
20 ;; but WITHOUT ANY WARRANTY; without even the implied warranty of
21 ;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
22 ;; General Public License for more details.
23 ;;
24 ;; You should have received a copy of the GNU General Public License
25 ;; along with GNU Emacs; see the file COPYING.  If not, write to the
26 ;; Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor,
27 ;; Boston, MA 02110-1301, USA.
28
29 ;;%package wisent-java-tags-wy
30
31 %languagemode  java-mode
32
33 ;; The default start symbol
34 %start compilation_unit
35 ;; Alternate entry points
36 ;;    - Needed by partial re-parse
37 %start package_declaration
38 %start import_declaration
39 %start class_declaration
40 %start field_declaration
41 %start method_declaration
42 %start formal_parameter
43 %start constructor_declaration
44 %start interface_declaration
45 ;;    - Needed by EXPANDFULL clauses
46 %start class_member_declaration
47 %start interface_member_declaration
48 %start formal_parameters
49
50 ;; -----------------------------
51 ;; Block & Parenthesis terminals
52 ;; -----------------------------
53 %type  <block>       ;;syntax "\\s(\\|\\s)" matchdatatype block
54
55 %token <block>       PAREN_BLOCK "(LPAREN RPAREN)"
56 %token <block>       BRACE_BLOCK "(LBRACE RBRACE)"
57 %token <block>       BRACK_BLOCK "(LBRACK RBRACK)"
58
59 %token <open-paren>  LPAREN      "("
60 %token <close-paren> RPAREN      ")"
61 %token <open-paren>  LBRACE      "{"
62 %token <close-paren> RBRACE      "}"
63 %token <open-paren>  LBRACK      "["
64 %token <close-paren> RBRACK      "]"
65
66 ;; ------------------
67 ;; Operator terminals
68 ;; ------------------
69 %type  <punctuation> ;;syntax "\\(\\s.\\|\\s$\\|\\s'\\)+" matchdatatype string
70
71 %token <punctuation> NOT         "!"
72 %token <punctuation> NOTEQ       "!="
73 %token <punctuation> MOD         "%"
74 %token <punctuation> MODEQ       "%="
75 %token <punctuation> AND         "&"
76 %token <punctuation> ANDAND      "&&"
77 %token <punctuation> ANDEQ       "&="
78 %token <punctuation> MULT        "*"
79 %token <punctuation> MULTEQ      "*="
80 %token <punctuation> PLUS        "+"
81 %token <punctuation> PLUSPLUS    "++"
82 %token <punctuation> PLUSEQ      "+="
83 %token <punctuation> COMMA       ","
84 %token <punctuation> MINUS       "-"
85 %token <punctuation> MINUSMINUS  "--"
86 %token <punctuation> MINUSEQ     "-="
87 %token <punctuation> DOT         "."
88 %token <punctuation> DIV         "/"
89 %token <punctuation> DIVEQ       "/="
90 %token <punctuation> COLON       ":"
91 %token <punctuation> SEMICOLON   ";"
92 %token <punctuation> LT          "<"
93 %token <punctuation> LSHIFT      "<<"
94 %token <punctuation> LSHIFTEQ    "<<="
95 %token <punctuation> LTEQ        "<="
96 %token <punctuation> EQ          "="
97 %token <punctuation> EQEQ        "=="
98 %token <punctuation> GT          ">"
99 %token <punctuation> GTEQ        ">="
100 %token <punctuation> RSHIFT      ">>"
101 %token <punctuation> RSHIFTEQ    ">>="
102 %token <punctuation> URSHIFT     ">>>"
103 %token <punctuation> URSHIFTEQ   ">>>="
104 %token <punctuation> QUESTION    "?"
105 %token <punctuation> XOR         "^"
106 %token <punctuation> XOREQ       "^="
107 %token <punctuation> OR          "|"
108 %token <punctuation> OREQ        "|="
109 %token <punctuation> OROR        "||"
110 %token <punctuation> COMP        "~"
111
112 ;; -----------------
113 ;; Literal terminals
114 ;; -----------------
115 %type  <symbol>      ;;syntax "\\(\\sw\\|\\s_\\)+"
116 %token <symbol>      IDENTIFIER
117
118 %type  <string>      ;;syntax "\\s\"" matchdatatype sexp
119 %token <string>      STRING_LITERAL
120
121 %type  <number>      ;;syntax semantic-lex-number-expression
122 %token <number>      NUMBER_LITERAL
123
124 %type <unicode>      syntax "\\\\u[0-9a-f][0-9a-f][0-9a-f][0-9a-f]"
125 %token <unicode>     unicodecharacter
126
127 ;; -----------------
128 ;; Keyword terminals
129 ;; -----------------
130
131 ;; Generate a keyword analyzer
132 %type  <keyword> ;;syntax "\\(\\sw\\|\\s_\\)+" matchdatatype keyword
133
134 %keyword ABSTRACT     "abstract"
135 %put     ABSTRACT summary
136 "Class|Method declaration modifier: abstract {class|<type>} <name> ..."
137
138 %keyword BOOLEAN      "boolean"
139 %put     BOOLEAN summary
140 "Primitive logical quantity type (true or false)"
141
142 %keyword BREAK        "break"
143 %put     BREAK summary
144 "break [<label>] ;"
145
146 %keyword BYTE         "byte"
147 %put     BYTE summary
148 "Integral primitive type (-128 to 127)"
149
150 %keyword CASE         "case"
151 %put     CASE summary
152 "switch(<expr>) {case <const-expr>: <stmts> ... }"
153
154 %keyword CATCH        "catch"
155 %put     CATCH summary
156 "try {<stmts>} catch(<parm>) {<stmts>} ... "
157
158 %keyword CHAR         "char"
159 %put     CHAR summary
160 "Integral primitive type ('\u0000' to '\uffff') (0 to 65535)"
161
162 %keyword CLASS        "class"
163 %put     CLASS summary
164 "Class declaration: class <name>"
165
166 %keyword CONST        "const"
167 %put     CONST summary
168 "Unused reserved word"
169
170 %keyword CONTINUE     "continue"
171 %put     CONTINUE summary
172 "continue [<label>] ;"
173
174 %keyword DEFAULT      "default"
175 %put     DEFAULT summary
176 "switch(<expr>) { ... default: <stmts>}"
177
178 %keyword DO           "do"
179 %put     DO summary
180 "do <stmt> while (<expr>);"
181
182 %keyword DOUBLE       "double"
183 %put     DOUBLE summary
184 "Primitive floating-point type (double-precision 64-bit IEEE 754)"
185
186 %keyword ELSE         "else"
187 %put     ELSE summary
188 "if (<expr>) <stmt> else <stmt>"
189
190 %keyword EXTENDS      "extends"
191 %put     EXTENDS summary
192 "SuperClass|SuperInterfaces declaration: extends <name> [, ...]"
193
194 %keyword FINAL        "final"
195 %put     FINAL summary
196 "Class|Member declaration modifier: final {class|<type>} <name> ..."
197
198 %keyword FINALLY      "finally"
199 %put     FINALLY summary
200 "try {<stmts>} ... finally {<stmts>}"
201
202 %keyword FLOAT        "float"
203 %put     FLOAT summary
204 "Primitive floating-point type (single-precision 32-bit IEEE 754)"
205
206 %keyword FOR          "for"
207 %put     FOR summary
208 "for ([<init-expr>]; [<expr>]; [<update-expr>]) <stmt>"
209
210 %keyword GOTO         "goto"
211 %put     GOTO summary
212 "Unused reserved word"
213
214 %keyword IF           "if"
215 %put     IF summary
216 "if (<expr>) <stmt> [else <stmt>]"
217
218 %keyword IMPLEMENTS   "implements"
219 %put     IMPLEMENTS summary
220 "Class SuperInterfaces declaration: implements <name> [, ...]"
221
222 %keyword IMPORT       "import"
223 %put     IMPORT summary
224 "Import package declarations: import <package>"
225
226 %keyword INSTANCEOF   "instanceof"
227
228 %keyword INT          "int"
229 %put     INT summary
230 "Integral primitive type (-2147483648 to 2147483647)"
231
232 %keyword INTERFACE    "interface"
233 %put     INTERFACE summary
234 "Interface declaration: interface <name>"
235
236 %keyword LONG         "long"
237 %put     LONG summary
238 "Integral primitive type (-9223372036854775808 to 9223372036854775807)"
239
240 %keyword NATIVE       "native"
241 %put     NATIVE summary
242 "Method declaration modifier: native <type> <name> ..."
243
244 %keyword NEW          "new"
245
246 %keyword PACKAGE      "package"
247 %put     PACKAGE summary
248 "Package declaration: package <name>"
249
250 %keyword PRIVATE      "private"
251 %put     PRIVATE summary
252 "Access level modifier: private {class|interface|<type>} <name> ..."
253
254 %keyword PROTECTED    "protected"
255 %put     PROTECTED summary
256 "Access level modifier: protected {class|interface|<type>} <name> ..."
257
258 %keyword PUBLIC       "public"
259 %put     PUBLIC summary
260 "Access level modifier: public {class|interface|<type>} <name> ..."
261
262 %keyword RETURN       "return"
263 %put     RETURN summary
264 "return [<expr>] ;"
265
266 %keyword SHORT        "short"
267 %put     SHORT summary
268 "Integral primitive type (-32768 to 32767)"
269
270 %keyword STATIC       "static"
271 %put     STATIC summary
272 "Declaration modifier: static {class|interface|<type>} <name> ..."
273
274 %keyword STRICTFP     "strictfp"
275 %put     STRICTFP summary
276 "Declaration modifier: strictfp {class|interface|<type>} <name> ..."
277
278 %keyword SUPER        "super"
279
280 %keyword SWITCH       "switch"
281 %put     SWITCH summary
282 "switch(<expr>) {[case <const-expr>: <stmts> ...] [default: <stmts>]}"
283
284
285 %keyword SYNCHRONIZED "synchronized"
286 %put     SYNCHRONIZED summary
287 "synchronized (<expr>) ... | Method decl. modifier: synchronized <type> <name> ..."
288
289 %keyword THIS         "this"
290
291 %keyword THROW        "throw"
292 %put     THROW summary
293 "throw <expr> ;"
294
295 %keyword THROWS       "throws"
296 %put     THROWS summary
297 "Method|Constructor declaration: throws <classType>, ..."
298
299 %keyword TRANSIENT    "transient"
300 %put     TRANSIENT summary
301 "Field declaration modifier: transient <type> <name> ..."
302
303 %keyword TRY          "try"
304 %put     TRY summary
305 "try {<stmts>} [catch(<parm>) {<stmts>} ...] [finally {<stmts>}]"
306
307 %keyword VOID         "void"
308 %put     VOID summary
309 "Method return type: void <name> ..."
310
311 %keyword VOLATILE     "volatile"
312 %put     VOLATILE summary
313 "Field declaration modifier: volatile <type> <name> ..."
314
315 %keyword WHILE        "while"
316 %put     WHILE summary
317 "while (<expr>) <stmt> | do <stmt> while (<expr>);"
318   
319 ;; --------------------------
320 ;; Official javadoc line tags
321 ;; --------------------------
322
323 ;; Javadoc tags are identified by a 'javadoc' keyword property.  The
324 ;; value of this property must be itself a property list where the
325 ;; following properties are recognized:
326 ;;
327 ;; - `seq' (mandatory) is the tag sequence number used to check if tags
328 ;;   are correctly ordered in a javadoc comment block.
329 ;;
330 ;; - `usage' (mandatory) is the list of token categories for which this
331 ;;   documentation tag is allowed.
332 ;;
333 ;; - `opt' (optional) if non-nil indicates this is an optional tag.
334 ;;   By default tags are mandatory.
335 ;;
336 ;; - `with-name' (optional) if non-nil indicates that this tag is
337 ;;   followed by an identifier like in "@param <var-name> description"
338 ;;   or "@exception <class-name> description".
339 ;;
340 ;; - `with-ref' (optional) if non-nil indicates that the tag is
341 ;;   followed by a reference like in "@see <reference>".
342
343 %keyword _AUTHOR      "@author"
344 %put     _AUTHOR      javadoc (seq 1 usage (type))
345 %keyword _VERSION     "@version"
346 %put     _VERSION     javadoc (seq 2 usage (type)) 
347 %keyword _PARAM       "@param"
348 %put     _PARAM       javadoc (seq 3 usage (function) with-name t) 
349 %keyword _RETURN      "@return"
350 %put     _RETURN      javadoc (seq 4 usage (function)) 
351 %keyword _EXCEPTION   "@exception"
352 %put     _EXCEPTION   javadoc (seq 5 usage (function) with-name t) 
353 %keyword _THROWS      "@throws"
354 %put     _THROWS      javadoc (seq 6 usage (function) with-name t) 
355 %keyword _SEE         "@see"
356 %put     _SEE         javadoc (seq 7 usage (type function variable) opt t with-ref t) 
357 %keyword _SINCE       "@since"
358 %put     _SINCE       javadoc (seq 8 usage (type function variable) opt t) 
359 %keyword _SERIAL      "@serial"
360 %put     _SERIAL      javadoc (seq 9 usage (variable) opt t) 
361 %keyword _SERIALDATA  "@serialData"
362 %put     _SERIALDATA  javadoc (seq 10 usage (function) opt t) 
363 %keyword _SERIALFIELD "@serialField"
364 %put     _SERIALFIELD javadoc (seq 11 usage (variable) opt t) 
365 %keyword _DEPRECATED  "@deprecated"
366 %put     _DEPRECATED  javadoc (seq 12 usage (type function variable) opt t) 
367
368 %%
369
370 ;; ------------
371 ;; LALR Grammar
372 ;; ------------
373
374 ;; This grammar is not designed to fully parse correct Java syntax.  It
375 ;; is optimized to work in an interactive environment to extract tokens
376 ;; (tags) needed by Semantic.  In some cases a syntax not allowed by
377 ;; the Java Language Specification will be accepted by this grammar.
378
379 compilation_unit
380   : package_declaration
381   | import_declaration
382   | type_declaration
383   ;
384
385 ;;; Package statement token
386 ;; ("NAME" package DETAIL "DOCSTRING")
387 package_declaration
388   : PACKAGE qualified_name SEMICOLON
389     (PACKAGE-TAG $2 nil)
390   ;
391
392 ;;; Include file token
393 ;; ("FILE" include SYSTEM "DOCSTRING") 
394 import_declaration
395   : IMPORT qualified_name SEMICOLON
396     (INCLUDE-TAG $2 nil)
397   | IMPORT qualified_name DOT MULT SEMICOLON
398     (INCLUDE-TAG (concat $2 $3 $4) nil)
399   ;
400
401 type_declaration
402   : SEMICOLON
403     ()
404   | class_declaration
405   | interface_declaration
406   ;
407
408 ;;; Type Declaration token
409 ;; ("NAME" type "TYPE" ( PART-LIST ) ( PARENTS ) EXTRA-SPEC "DOCSTRING")
410 class_declaration
411   : modifiers_opt CLASS qualified_name superc_opt interfaces_opt class_body
412     (TYPE-TAG $3 $2 $6 (if (or $4 $5) (cons $4 $5)) :typemodifiers $1)
413   ;
414
415 superc_opt
416   : ;;EMPTY
417   | EXTENDS qualified_name
418     (identity $2)
419   ;
420
421 interfaces_opt
422   : ;;EMPTY
423   | IMPLEMENTS qualified_name_list
424     (nreverse $2)
425   ;
426
427 class_body
428   : BRACE_BLOCK
429     (EXPANDFULL $1 class_member_declaration)
430   ;
431
432 class_member_declaration
433   : LBRACE
434     ()
435   | RBRACE
436     ()
437   | block
438     ()
439   | static_initializer
440     ()
441   | constructor_declaration
442   | interface_declaration
443   | class_declaration
444   | method_declaration
445   | field_declaration
446   ;
447
448 ;;; Type Declaration token
449 ;; ("NAME" type "TYPE" ( PART-LIST ) ( PARENTS ) EXTRA-SPEC "DOCSTRING")
450 interface_declaration
451   : modifiers_opt INTERFACE IDENTIFIER extends_interfaces_opt interface_body
452     (TYPE-TAG $3 $2 $5 (if $4 (cons nil $4)) :typemodifiers $1)
453   ;
454
455 extends_interfaces_opt
456   : ;;EMPTY
457   | EXTENDS qualified_name_list
458     (identity $2)
459   ;
460
461 interface_body
462   : BRACE_BLOCK
463     (EXPANDFULL $1 interface_member_declaration)
464   ;
465
466 interface_member_declaration
467   : LBRACE
468     ()
469   | RBRACE
470     ()
471   | interface_declaration
472   | class_declaration
473   | method_declaration
474   | field_declaration
475   ;
476
477 static_initializer
478   : STATIC block
479   ;
480
481 ;;; Function token
482 ;; ("NAME" function "TYPE" ( ARG-LIST ) EXTRA-SPEC "DOCSTRING") 
483 constructor_declaration
484   : modifiers_opt constructor_declarator throwsc_opt constructor_body
485     (FUNCTION-TAG (car $2) nil (cdr $2)
486                   :typemodifiers $1
487                   :throws $3
488                   :constructor-flag t)
489   ;
490
491 constructor_declarator
492   : IDENTIFIER formal_parameter_list
493     (cons $1 $2)
494   ;
495
496 constructor_body
497   : block 
498   ;
499
500 ;;; Function token
501 ;; ("NAME" function "TYPE" ( ARG-LIST ) EXTRA-SPEC "DOCSTRING") 
502 method_declaration
503   : modifiers_opt VOID method_declarator throwsc_opt method_body
504     (FUNCTION-TAG (car $3) $2 (cdr $3) :typemodifiers $1 :throws $4)
505   | modifiers_opt type method_declarator throwsc_opt method_body
506     (FUNCTION-TAG (car $3) $2 (cdr $3) :typemodifiers $1 :throws $4)
507   ;
508
509 method_declarator
510   : IDENTIFIER formal_parameter_list dims_opt
511     (cons (concat $1 $3) $2)
512   ;
513
514 throwsc_opt
515   : ;;EMPTY
516   | THROWS qualified_name_list
517     (nreverse $2)
518   ;
519
520 qualified_name_list
521   : qualified_name_list COMMA qualified_name
522     (cons $3 $1)
523   | qualified_name
524     (list $1)
525   ;
526
527 method_body
528   : SEMICOLON
529   | block
530   ;
531
532 ;; Just eat {...} block!
533 block
534   : BRACE_BLOCK
535   ;
536
537 formal_parameter_list
538   : PAREN_BLOCK
539     (EXPANDFULL $1 formal_parameters)
540   ;
541
542 formal_parameters
543   : LPAREN
544     ()
545   | RPAREN
546     ()
547   | formal_parameter COMMA
548   | formal_parameter RPAREN
549   ;
550
551 ;;; Variable token
552 ;; ("NAME" variable "TYPE" DEFAULT-VALUE EXTRA-SPEC "DOCSTRING")
553 formal_parameter
554   : formal_parameter_modifier_opt type variable_declarator_id
555     (VARIABLE-TAG $3 $2 nil :typemodifiers $1)
556   ;
557
558 formal_parameter_modifier_opt
559   : ;;EMPTY
560   | FINAL
561     (list $1)
562   ;
563
564 ;;; Variable token
565 ;; ("NAME" variable "TYPE" DEFAULT-VALUE EXTRA-SPEC "DOCSTRING")
566 field_declaration
567   : modifiers_opt type variable_declarators SEMICOLON
568     (VARIABLE-TAG $3 $2 nil :typemodifiers $1)
569   ;
570
571 variable_declarators
572   : variable_declarators COMMA variable_declarator
573     (progn
574       ;; Set the end of the compound declaration to the end of the
575       ;; COMMA delimiter.
576       (setcdr (cdr (car $1)) (cdr $region2))
577       (cons $3 $1))
578   | variable_declarator
579     (list $1)
580   ;
581
582 variable_declarator
583   : variable_declarator_id EQ variable_initializer
584     (cons $1 $region)
585   | variable_declarator_id
586     (cons $1 $region)
587   ;
588
589 variable_declarator_id
590   : IDENTIFIER dims_opt
591     (concat $1 $2)
592   ;
593
594 variable_initializer
595   : expression
596   ;
597
598 ;; Just eat expression!
599 expression
600   : expression term
601   | term
602   ;
603
604 term
605   : literal
606   | operator
607   | primitive_type
608   | IDENTIFIER
609   | BRACK_BLOCK
610   | PAREN_BLOCK
611   | BRACE_BLOCK
612   | NEW
613   | CLASS
614   | THIS
615   | SUPER
616   ;
617
618 literal
619 ;;   : NULL_LITERAL
620 ;;   | BOOLEAN_LITERAL
621   : STRING_LITERAL
622   | NUMBER_LITERAL
623   ;
624
625 operator
626   : NOT
627   | PLUS
628   | PLUSPLUS
629   | MINUS
630   | MINUSMINUS
631   | NOTEQ
632   | MOD
633   | MODEQ
634   | AND
635   | ANDAND
636   | ANDEQ
637   | MULT
638   | MULTEQ
639   | PLUSEQ
640   | MINUSEQ
641   | DOT
642   | DIV
643   | DIVEQ
644   | COLON
645   | LT
646   | LSHIFT
647   | LSHIFTEQ
648   | LTEQ
649   | EQ
650   | EQEQ
651   | GT
652   | GTEQ
653   | RSHIFT
654   | RSHIFTEQ
655   | URSHIFT
656   | URSHIFTEQ
657   | QUESTION
658   | XOR
659   | XOREQ
660   | OR
661   | OREQ
662   | OROR
663   | COMP
664   | INSTANCEOF
665   ;
666
667 primitive_type
668   : BOOLEAN
669   | CHAR
670   | LONG
671   | INT
672   | SHORT
673   | BYTE
674   | DOUBLE
675   | FLOAT
676   ;
677
678 modifiers_opt
679   : ;;EMPTY
680   | modifiers
681     (nreverse $1)
682   ;
683
684 modifiers
685   : modifiers modifier
686     (cons $2 $1)
687   | modifier
688     (list $1)
689   ;
690
691 modifier
692   : STRICTFP
693   | VOLATILE
694   | TRANSIENT
695   | SYNCHRONIZED
696   | NATIVE
697   | FINAL
698   | ABSTRACT
699   | STATIC
700   | PRIVATE
701   | PROTECTED
702   | PUBLIC
703   ;
704
705 type
706   : qualified_name dims_opt
707     (concat $1 $2)
708   | primitive_type dims_opt
709     (concat $1 $2)
710   ;
711
712 qualified_name
713   : qualified_name DOT IDENTIFIER
714     (concat $1 $2 $3)
715   | IDENTIFIER
716   ;
717
718 dims_opt
719   : ;;EMPTY
720     (identity "")
721   | dims
722   ;
723
724 dims
725   : dims BRACK_BLOCK
726     (concat $1 "[]")
727   | BRACK_BLOCK
728     (identity "[]")
729   ;
730
731 %%
732 ;; Define the lexer for this grammar
733 (define-lex wisent-java-tags-lexer
734   "Lexical analyzer that handles Java buffers.
735 It ignores whitespaces, newlines and comments."
736   semantic-lex-ignore-whitespace
737   semantic-lex-ignore-newline
738   semantic-lex-ignore-comments
739   ;;;; Auto-generated analyzers.
740   wisent-java-tags-wy--<number>-regexp-analyzer
741   wisent-java-tags-wy--<string>-sexp-analyzer
742   ;; Must detect keywords before other symbols
743   wisent-java-tags-wy--<keyword>-keyword-analyzer
744   wisent-java-tags-wy--<symbol>-regexp-analyzer
745   wisent-java-tags-wy--<punctuation>-string-analyzer
746   wisent-java-tags-wy--<block>-block-analyzer
747   ;; In theory, unicode chars should be turned into normal chars
748   ;; and then combined into regular ascii keywords and text.  This
749   ;; analyzer just keeps these things from making the lexer go boom.
750   wisent-java-tags-wy--<unicode>-regexp-analyzer
751   ;;;;
752   semantic-lex-default-action)
753
754 ;;; wisent-java-tags.wy ends here