some progress
[yu.git] / yu / parser.lua
blobb7b7235ce6195d0e97f976b463e90a555c950f06
1 require "lpeg"
3 local L=lpeg
5 local p,s,r,b,lpegv =L.P,L.S,L.R,L.B,L.V
6 local c,carg,cb,cc,cp,cs,ct,cg,cmt,cf= L.C,L.Carg,L.Cb,L.Cc,L.Cp,L.Cs,L.Ct,L.Cg,L.Cmt,L.Cf
8 local v=setmetatable({},{__index=function(t,k) return lpegv(k) end})
9 local ipairs,pairs=ipairs,pairs
10 local io,type=io,type
11 local print,error,assert=print,error,assert
12 local setmetatable=setmetatable
14 module ("yu" ,package.seeall)
15 setmetatable(_M,{__index=function(t,k) error("undefined symbol:"..k,2) end})
17 local currentParseLine=1
18 local currentParseOffset=1
20 local currentLine=1
21 local currentLineOffset=0
22 local currentOffsetTable={0}
24 local currentTokenLine=1
25 local currentTokenLineOffset=0
27 local currentPos0=0
28 local currentPos1=0
29 local line0=1
30 local line1=1
31 local pos0=0
32 local pos1=0
34 local lineInfo={}
36 local function newline(off)
37 currentLine=currentLine+1
38 currentLineOffset=off
39 lineInfo[currentLine]=off
40 currentOffsetTable[currentLine]=off
41 end
43 local function newParseLine(a,s)
44 currentParseLine=currentParseLine+1
45 currentParseOffset=s
46 print("l",currentParseLine,s)
47 return s
48 end
50 local function parseErr(msg,pos)
51 local lpos=pos-currentLineOffset
52 return error("parse error<"..currentLine..":"..lpos..">:"..msg)
53 end
54 --cmt(p(1),f
56 -- local function tagpos(tag) return cg(cp(),tag) end
58 local function cnot(patt,f) return cg(cp(),'p0')*(patt+(cb'p0'*cp()/f)) end
60 local function cerr(patt,msg) return cnot(patt,function(s0,s1)
61 return parseErr(msg,s1)
62 end) end
65 local function c1 (s, o) return s end
67 local function t0(tag) return function() return {tag=tag} end end
70 -- local I0=cp()/function(pos)
71 -- pos0=pos
72 -- line0=currentLine
73 -- end
75 -- local I1=cp()/function(pos)
76 -- if pos0>pos1 then
77 -- currentTokenLine=line1
78 -- currentTokenLineOffset=currentOffsetTable[currentTokenLine]
79 -- currentPos0=pos1
80 -- currentPos1=pos0
81 -- end
82 -- pos1=pos
83 -- line1=currentLine
84 -- end
87 -- local function tpos()
88 -- return nil and {line=currentLine,
89 -- pos=currentPos0,
90 -- lpos=currentPos0-currentTokenLineOffset,
91 -- len=currentPos1-currentPos0}
92 -- end
94 local function t1(tag,a)
95 return function(v) return {tag=tag,[a]=v} end
96 end
98 local function t2(tag,k1,k2)
99 assert(k1 and k2)
100 return function(v1,v2) return {tag=tag,[k1]=v1,[k2]=v2} end
103 local function t3(tag,k1,k2,k3)
104 assert(k1 and k2 and k3)
105 return function(v1,v2,v3) return {tag=tag,[k1]=v1,[k2]=v2,[k3]=v3} end
108 local function t4(tag,k1,k2,k3,k4)
109 assert(k1 and k2 and k3 and k4)
110 return function(v1,v2,v3,v4) return {tag=tag,[k1]=v1,[k2]=v2,[k3]=v3,[k4]=v4} end
113 local function t5(tag,k1,k2,k3,k4,k5)
114 assert(k1 and k2 and k3 and k4 and k5)
115 return function(v1,v2,v3,v4,v5) return {tag=tag,[k1]=v1,[k2]=v2,[k3]=v3,[k4]=v4,[k5]=v5} end
118 local function tt(tag,t)
119 return function(...) return {tag=tag,[t]={...}} end
122 local function tc(tag,c)
123 c.tag=tag
124 return function() return c end
127 local function cpos(patt)
128 return (cp()*patt*cp()/function(p0,t,p1)
129 -- if type(t)~="table" then print(t) end
130 t.p0=p0
131 t.p1=p1
132 return t
133 end)
136 --------------TERMINAL
138 local DIGIT=r'09'
139 local _=s' \t'^0
141 local ALPHA=r'AZ'+r'az'+'_'
142 local ALPHADIGIT=ALPHA+DIGIT
143 local Name=ALPHA*ALPHADIGIT^0
146 local EOL= (p'\n'+p'\r\n'+p'\r')*cp()/newline
149 local LESSEQ=p'<='
150 local NOTEQ=p'~='
151 local LESS=p'<'
152 local GREATEQ=p'>='
153 local GREATER=p'>'
154 local EQ=p'=='
155 local NOTEQ1=p'<>'
157 local ASSIGN=p'='
158 local ASSDEF=p':='
159 local ASSCAST=p'=:'
161 local ASSADD=p'+='
162 local ASSSUB=p'-='
163 local ASSMUL=p'*='
164 local ASSDIV=p'/='
165 local ASSPOW=p'^='
166 local ASSMOD=p'%='
167 local ASSCON=p'..='
168 local ASSAND=p'or='
169 local ASSOR=p'and='
171 local ARROWE=p'=>'
172 local ARROW=p'->'
173 local STICK=p'|'
175 local POPEN,PCLOSE=p'(',p')'
176 local BOPEN,BCLOSE=p'{',p'}'
177 local SOPEN,SCLOSE=p'[',p']'
179 local SLASH=p'/'
180 local STAR=p'*'
181 local MINUS=p'-'
182 local PLUS=p'+'
183 local POW=p'^'
185 local COMMA=p','
186 local COLON=p':'
187 local DOT=p'.'
188 local DOLLAR=p'$'
189 local NUM=p'#'
190 local QUES=p'?'
191 local AT=p'@'
192 local PERCENT=p'%'
194 local DOTDOT=p'..'
195 local DOUBLECOLON=p'::'
196 local SEMI=p';'
199 -- #--------------------Kw-----------------------
200 local TRUE=p"true"
201 local FALSE=p"false"
202 local NIL=p"nil"
204 local END=p"end"
205 local DO=p"do"
207 local WHILE=p"while"
208 local FOR=p"for"
209 local IN=p"in"
211 local BREAK=p"break"
212 local CONTINUE=p"continue"
213 local RETURN=p"return"
214 local YIELD=p"yield"
215 local SPAWN=p"spawn"
218 local IF=p"if"
219 local THEN=p"then"
220 local ELSE=p"else"
221 local ELSEIF=p"elseif"
223 local SELECT=p"select"
224 local CASE=p"case"
225 local DEFAULT=p"default"
227 local CLASS=p"class"
228 local EXTENDS=p"extends"
229 local ABSTRACT=p"abstract"
230 local NEW=p"new"
231 local FINALIZE=p"finalize"
232 local METHOD=p"method"
233 local INHERIT=p"inherit"
234 local FIELD=p"field"
235 local GET=p"get"
236 local SET=p"set"
237 local SELF=p"self"
238 local SUPER=p"super"
239 local IS=p"is"
242 local FUNCTION=p"function"
243 local FUNC=p"func"
245 local FUNCKW = FUNCTION+FUNC
247 local OPERATOR=p"operator"
248 local GLOBAL=p"global"
249 local LOCAL=p"local"
250 local CONST=p"const"
251 local ENUM=p"enum"
252 local NAMESPACE=p"namespace"
254 local PRIVATE=p"private"
255 local PUBLIC=p"public"
256 local EXTERN=p"extern"
258 local TRY=p"try"
259 local CATCH=p"catch"
260 local THROW=p"throw"
262 local IMPORT=p"import"
263 local USING=p"using"
265 local NUMBER=p"number"
266 local BOOL=p"bool"
267 local STRING=p"string"
268 local ANY=p"any"
270 local AND=p"and"
271 local OR=p"or"
272 local NOT_KW=p"not"
273 local AS=p"as"
275 local LT2=p'<<'
276 local GT2=p'>>'
277 local LT=p'<'
278 local GT=p'>'
279 local RAWLUA=p'__Lua'
281 local Keyword= TRUE+FALSE+NIL
282 + END+DO
283 + WHILE+FOR+IN
284 + BREAK+CONTINUE+RETURN+YIELD+SPAWN
285 + IF+THEN+ELSEIF+ELSE
286 + SELECT+CASE+DEFAULT
287 + CLASS+EXTENDS+ABSTRACT+NEW
288 + FIELD+PRIVATE+PUBLIC+EXTERN
289 + SELF+SUPER
290 + FUNCTION+FUNC+METHOD+OPERATOR+INHERIT
291 + GLOBAL+LOCAL+CONST+ENUM
292 + TRY+CATCH+THROW
293 + IMPORT+USING
294 + AND+OR+NOT_KW
295 + AS
296 + RAWLUA
299 local QUOTE=p'"'
300 local QUOTES=p"'"
302 ------------------------CONSTANT
304 local StringS= QUOTES * c( (1-QUOTES-EOL)^0 ) * cerr(QUOTES, "broken string")
305 local StringD= QUOTE * c( (1-QUOTE-EOL)^0 ) * cerr(QUOTE, "broken string")
308 local StringLOpen = "[" * cg(p'='^0, "init") * "[" * EOL^-1
309 local StringLClose = "]" * c(p'='^0) * "]"
310 local StringLCloseEQ = cmt(StringLClose * cb("init"), function (s, i, a, b) return a == b end)
311 local StringL = StringLOpen * c((1 - StringLCloseEQ)^0) * cerr(StringLClose,"mismatched long string/block comment") / c1
313 local StringCore=StringL+StringD+StringS
315 local NegativeSymbol=(MINUS * _ )^-1
316 local IntegerCore=NegativeSymbol * DIGIT^1
317 local RationalCore=NegativeSymbol * DIGIT^0 * '.' * #DIGIT* cerr(DIGIT^1,"malformed rational")
319 local Integer= c( IntegerCore ) * _
320 local Rational=c( RationalCore) * _
321 local Exponetional=c( (RationalCore+IntegerCore) * 'e' * cerr(IntegerCore, "malformed exponetional") ) * _
323 local Number = Exponetional+Rational+Integer
324 local Boolean= c(TRUE+FALSE)
326 local cnil = cc(nil)
328 local LineCmt=p'--'*(1-EOL)^0*EOL
329 local BlockCmt=p'--'*StringL/function() end --drop captured string
331 local COMMENT=BlockCmt+LineCmt
333 local __= v.WS
334 local _NA=v.NotAlpha
335 local SemiEOL=(__ * SEMI * __)^0
336 local IdentCore=Name - ( Keyword * -ALPHADIGIT )
338 local Ident=v.Ident
339 local String=v.String
341 local function foldexpr(l,e,...)
342 if e then
343 e.l=l
344 return foldexpr(e,...)
346 return l
349 local function w(p) return __*p*__ end
351 local pdepth,pstack=0,{}
353 POpen= w(POPEN)*cp()/function(pos)
354 pdepth=pdepth+1
355 pstack[pdepth]=pos
358 PClose= cnot(w(PCLOSE),function(pos0,pos1)
359 parseErr("unclosed parenthesis ->"..pstack[pdepth],pos1)
360 end)
362 --GRAMMAR
364 local Module=p{
365 'M',
367 WS=(s' \t'+COMMENT+EOL)^0;
368 NotAlpha= #(-ALPHA); --not alpha
369 Ident= c(IdentCore)* __;
371 String=StringCore * __;
373 M= ct(w(v.HeadStmt)^0) * w(v.Block) * cerr(-p(1),"syntax error") / t2('module','heads','block');
375 HeadStmt=v.Import;
377 Import= w(IMPORT) *__* String / t1('import','src');
379 Block= ct((__ * v.Stmt * SemiEOL )^0 )/function(a) a.tag="block" return a end ;
381 -------------END STATEMENTS
382 EndStmt=cpos(v.ReturnStmt
383 +v.BreakStmt
384 +v.ContinueStmt
385 +v.ThrowStmt)
388 ReturnStmt= (RETURN * __ * (v.ExprList+cnil)) /t1('returnstmt','values');
390 BreakStmt=w(BREAK) /t0'breakstmt';
392 ContinueStmt=w(CONTINUE) /t0'continuestmt';
394 ThrowStmt=THROW * __ * v.ExprList /t1('throwstmt','values');
397 -- #--------------------STATMENTS-------------------
399 Stmt =cpos(
400 v.AssignStmt
401 + v.ExprStmt
402 + v.BlockInnerDecls
403 + v.ExternBlock
404 + v.FlowStmt
405 + v.EndStmt
409 CommonDirective=PRIVATE * cerr(w(COLON),"':' expected")/t0('private')
410 + PUBLIC * cerr(w(COLON),"':' expected")/t0('public')
411 + RAWLUA * cerr(w(StringL),"long string expected")/t1('rawlua','src')
414 ExprStmt= v.Expr /t1('exprstmt','expr');
416 -----------------------EXTERN BLOCK
417 ExternBlock=EXTERN * __ *
418 ct((v.ExternDecl*SemiEOL)^0)*
419 cerr(END*__, "unclosed extern block")/t1('extern','decls')
422 ExternDecl= v.ConstDecl
423 + v.GlobalDecl
424 + v.EnumDecl
425 + v.ExternFuncDecl
426 + v.ExternClassDecl
427 + v.CommonDirective
430 ExternFuncDecl=FUNCKW *__* v.ExternFuncBody;
432 ExternFuncBody= (v.FuncAlias *AS*__ * Ident
433 +cnil*Ident)*
434 v.FuncType/t3('externfunc','alias','name','type')
437 FuncAlias =(StringS+StringD+IdentCore)*__;
439 ExternClassDecl=CLASS *__* Ident *
440 (ct(v.ExternClassItemDecl^0)/
441 function(t) t.tag="block" return t end) *
442 END *__ /t2('externclass','name','block')
445 ExternClassItemDecl=
446 v.GlobalDecl
447 + v.FieldDecl
448 + v.ConstDecl
449 + v.EnumDecl
450 + v.ExternFuncDecl
451 + v.ExternMethodDecl
452 + v.CommonDirective
455 ExternMethodDecl=METHOD *__* v.ExternFuncBody/function(f) f.tag='externmethod' return f end;
458 -- #--------------------Flow Control-------------------
459 FlowStmt= v.IfStmt
460 + v.WhileStmt
461 + v.ForStmt
462 + v.ForEachStmt
463 + v.SwitchStmt
464 + v.DoStmt
465 + v.TryStmt
466 + v.YieldStmt
468 YieldStmt= YIELD *__ * v.ExprList / t1('yieldstmt','values');
470 DoStmt = DO * __ * v.Block * cerr(END*__, "unclosed do block") /t1('dostmt','block');
472 IfStmt = IF *__ * cerr(v.Expr,"condition expression expected") *
473 v.ThenBody / t2('ifstmt','cond','body')
476 ThenBody= cerr(THEN*__,"'then' expected") *
477 v.Block *
479 v.ElseIfBody
481 (ELSE * __ * v.Block)^-1 *
482 cerr(END * __ , "unclosed if-then block")
483 )/t2(nil,'thenbody','elsebody')
486 ElseIfBody= ELSEIF * __ * cerr(v.Expr,"condition expression expected") *
487 v.ThenBody / t2('ifstmt','cond','body') ;
490 SwitchStmt= SELECT *__ * cerr(v.Expr,"condition expression expected") *
491 ct((CASE * __ * cerr(v.ExprList,"case condition expressions expected") *
492 cerr(DO*__,"'do' expected for 'case'") *
493 v.Block/t2('case','conds','block')
494 )^0) *
495 (DEFAULT *__ * v.Block) ^-1 *
496 cerr(END*__, "unclosed switch block")/t3('switchstmt','cond','cases','default')
499 WhileStmt= WHILE * __ * cerr(v.Expr, "condition expression expected") *
500 cerr(DO*__,"'do' expected for 'while'") *
501 v.Block *
502 cerr(END * __, "unclosed while block") / t2('whilestmt','cond','block')
505 TryStmt = TRY * __ *
506 v.Block *
507 ct( cerr(v.CatchBody^1, "catch block expected" ) ) *
508 cerr(END * __ , "unclosed try-catch block") / t2('trystmt','block','catches')
511 CatchBody= w(CATCH) * cerr(v.TypedVarList, "catch variable expected") *
512 cerr( DO *__ , "'do' expected for 'catch'" ) *
513 cerr(v.Block,"syntax error in catch block") /t2('catch','vars','block')
516 ForStmt = FOR *__ * Ident/t1('var','name') *
517 #(-IN-COMMA) * cerr(ASSIGN,"'=' expected in for-loop") * __ *
518 ct(cerr(
519 v.Expr * COMMA *__ * v.Expr *
520 (COMMA * __ * v.Expr )^-1
521 ,"for loop range error")) *
522 cerr(DO*__,"'do' expected for 'for'") *
523 v.Block*
524 cerr(END*__, "unclosed for-loop block")/t3('forstmt','var','range','block')
527 ForEachStmt= FOR *__ *
528 v.TypedVarList *
529 cerr(IN,"for-loop syntax error") *__* cerr(v.Expr,"enumerator expression expected") *
530 cerr(DO*__,"'do' expected for 'for'") *
531 v.Block *
532 cerr(END*__, "unclosed foreach-loop block")
533 /t3('foreachstmt','vars','enumerator','block')
536 TypedVar =Ident * v.TypeTag^-1 / t2('var','name','type');
537 TypedVarList=ct((v.TypedVar * ( COMMA *__* cerr(v.TypedVar,"variable expected"))^0)^-1);
539 ---------------------------ASSIGN----------------------
540 AssignStmt = v.AssOpStmt + v.Assign + v.BatchAssign;
542 AssOpStmt = v.Expr *
543 c(ASSADD + ASSSUB + ASSMUL + ASSDIV+ ASSMOD + ASSPOW + ASSAND + ASSOR + ASSCON) *__ *
544 cerr(v.Expr, "expression expected") / t3('assopstmt','var','op','value')
546 Assign = v.ExprList *__* v.AssignSymbol *__* cerr(v.ExprList , "values expected")
547 / t3('assignstmt','vars','autocast','values');
549 BatchAssign= v.Expr * DOT *__*
550 POpen* ct(cerr(Ident* (COMMA * __ * Ident)^0 ,"member names expected")) *PClose *
551 v.AssignSymbol * v.ExprList / t4('batchassign','var','members','autocast','values') ;
553 AssignSymbol= w(ASSCAST*cc(true)+ASSIGN*cc(nil));
555 --------------------------Declaration--------------------
557 BlockInnerDecls= v.LocalDecl
558 + v.ConstDecl
559 + v.FuncDecl
560 + v.GlobalDecl
561 + v.ClassDecl
562 + v.EnumDecl
563 + v.CommonDirective
566 -------------------Class Declaration-------------------
568 ClassInnerDecls=cpos(
569 v.FuncDecl
570 + v.MethodDecl
571 + v.FieldDecl
572 + v.ConstDecl
573 + v.GlobalDecl
574 + v.EnumDecl
575 + v.CommonDirective)
578 ClassDecl= CLASS * __ *
579 cerr(Ident*
580 (ct(LT*__*
581 cerr(v.TVar*(COMMA*__*v.TVar)^0,"template variable expected")*
582 cerr(GT*__,"'>' expected"))
583 +cnil)
584 ,"class name expected") *
585 (EXTENDS * __ * cerr(v.SuperName,'super class name expected')+cnil) *
586 v.MetaData *
587 ct(v.ClassInnerDecls^0)*
588 cerr(END *__, "unclosed class block")
589 /t5('classdecl','name','template','super','meta','decls');
591 TVar = Ident/t1('tvar','name');
593 SuperName= Ident*
594 (ct(LT*__*
595 cerr(v.Type*(COMMA*__*v.Type)^0,"type expected")*
596 cerr(GT*__,"'>' expected"))
597 +cnil)
598 /t2('supername','id','template')
601 -- #-------------------Symbol Delcaration-------------------
603 EnumDecl= ENUM *__* cerr(Ident,"enumeration name expected") *
604 cerr(BOPEN *__*
605 ct( v.EnumItem* ( COMMA *__* v.EnumItem )^0 ) *
606 BCLOSE *__ , "enum items expected")
607 /t2('enumdecl','name','items')
610 EnumItem= cerr(Ident,"enum item name expected") *
611 (ASSIGN *__ * cerr(v.Expr,"expression expected") + cnil)
612 /t2('enumitem','name','value')
615 LocalDecl= LOCAL *__* cerr(v.VarDecl,"variable declaration expected")
616 / function(vd) vd.type='local' return vd end;
618 GlobalDecl= GLOBAL *__* cerr(v.VarDecl,"variable declaration expected")
619 / function(vd) vd.type='global' return vd end;
621 ConstDecl= CONST *__* cerr(v.VarDecl,"variable declaration expected")
622 / function(vd) vd.type='const' return vd end;
624 FieldDecl= FIELD *__* cerr(v.VarDecl, "variable declaration expected" ) * v.MetaData
625 / function(vd,meta) vd.type='field' vd.meta=meta return vd end
627 ( v.GetterBody*v.SetterBody
628 + v.SetterBody*v.GetterBody *cc(true))
629 /function(fd,g,s,setterFirst)
630 if setterFirst then g,s=s,g end
631 fd.getter=g
632 fd.setter=s
633 return fd
637 GetterBody= p'::get' *__* cerr(v.FuncBlock,"property getter block expected") +cnil;
638 SetterBody= p'::set' *__* cerr(v.FuncBlock,"property setter block expected") +cnil;
640 VarDecl= ct(v.VarDeclBody * (COMMA *__* cerr(v.VarDeclBody ,"variable expected"))^0)*
641 ( w(ASSIGN) * v.ExprList
642 + w(ASSDEF) * v.ExprList*cc(true)
643 + cnil
644 )/ t3('vardecl','vars','values','def')
647 VarDeclBody= cpos((Ident* (v.TypeTag + cnil) )/t2('var','name','type'));
649 MethodDecl =(METHOD*cnil+INHERIT*cc(true)) * __ *
650 cerr(v.MethodName,"method name/operator expected") *
651 v.FuncType
652 /t3('methoddecl','inherit','name','type')
654 ( ABSTRACT * cc(true) * __ * v.MetaData
655 + cnil* v.MetaData * v.FuncBlock
656 )/function(head,ab,meta,block)
657 head.meta=meta
658 head.abstract=ab
659 head.block=block
660 return head
664 MethodName= (c(v.Operators + NEW + FINALIZE) + Ident) *__;
666 Operators =s('+-*/%^<>')+ p'>='+p'<='+p'=='+p'~='+p'as'+p'[]'+p'[]=';
668 FuncDecl= FUNCKW * __ * cerr(Ident ,"function name expected") * __ *
669 ( AS *__ * cerr(v.FuncAlias, "function alias expected")+cnil ) *
670 cerr(v.FuncType,"function type expected")* __ *
671 v.FuncBlock / t4('funcdecl','name','alias','type','block');
673 FuncBlock= ARROWE *__* v.Expr/t1('exprbody','expr')
674 + v.Block * cerr(END *__,"unclosed function block");
676 FuncType= (v.TypeSymbol+cnil) *
677 POpen *
678 ct((v.ArgDef * (w(COMMA)* cerr(v.ArgDef, "argument expected"))^0 )^-1) *
679 PClose *
680 (w(ARROW) * ct(cerr(
681 POpen* v.RetTypeItem * (w(COMMA) * cerr(v.RetTypeItem,"return type expected"))^0 *PClose
682 + v.RetTypeItem * cerr(0-w(COMMA),"multiple return type must be inside parenthesis")
683 ,"return type syntax error"))
684 + cnil
686 /function(ret0,args,rettype)
687 if ret0 and rettype then
688 return parseErr('duplicated return type declaration')
690 return {tag='functype', rettype=ret0 and {ret0} or rettype or nil, args=args}
694 ArgDef = Ident *__* (v.TypeTag+cnil)/t2('arg','name','type');
696 RetTypeItem= (Ident *__* v.TypeTag/function(n,t) t.alias=n return t end) + v.Type;
699 ---------------------------------------TYPE
701 TypeTag = (COLON *__* v.Type) + v.TypeSymbol;
703 Type = cpos(v.TableType);
705 TableType= cf(v.TypeCore *
706 (w(SOPEN) *
707 (v.Type+cnil) *
708 cerr(w(SCLOSE),"unclosed squre bracket"))^0,
710 function(a,b)
711 return {tag='tabletype',etype=a,ktype=b}
712 end);
715 TypeCore= v.TypeSymbol
716 + v.NamedType
717 + FUNCKW *__* cerr(v.FuncType, "function type syntax error")
718 + POpen*cerr(v.Type,"inner type missing")*PClose;
720 NamedType= cpos(v.TemplateType+Ident /t1('type','name'));
722 TypeSymbol= cpos(
723 (p'#'/'number'
724 + p'?'/'boolean'
725 + p'$'/'string'
726 + p'*'/'object')*__
727 /t1('type','name')
731 TemplateType=Ident*
732 (ct(LT*__*
733 cerr(v.Type*(COMMA*__*v.Type)^0,"type expected")*
734 cerr(GT*__,"'>' expected"))
736 /t2('ttype','name','arg')
739 TemplateVar=LT*__*
740 ct(cerr(Ident * (COMMA *__* Ident)^0,"type variable expected")) *
741 cerr(GT*__,"'>' expected")
744 TemplateVarItem=Ident *(EXTENDS * cerr(Ident,"type name expected") + cnil )/t2('tvar','name','super')
747 ----------------------Reflection-----------------------------
749 MetaData= AT*BOPEN*__*
750 (ct(v.MetaItem * __ *( COMMA *__ * cerr(v.MetaItem,"metadata item expected"))^0)+cnil) *__*
751 cerr(BCLOSE*__,"unclosed metadata body")/t1('meta','data')
752 +cnil
755 MetaItem= c(Name) *__* ASSIGN *__* cerr(v.Expr ,"metadata item value expected")/t2('mitem','k','v')
756 + c(Name) *__ /t1('mitem','k')
759 -- #--------------------Expression-------------------
760 ExprList=ct(v.Expr * ( COMMA *__* cerr(v.Expr,"expression expected") )^0);
762 Expr= cpos(v.Ternary);
764 Ternary= v.Logic *
765 (p'?' * __ * v.Ternary *
766 cerr( __ * STICK , "'|' expected") *
767 __ * v.Ternary / t2('ternary','vtrue','vfalse')
768 )^0/foldexpr;
770 Logic= v.Compare *
771 ( c(AND+OR) * - ASSIGN *
772 cerr(__ * v.Compare, "right operand expected for logic expr")/t2('binop','op','r')
773 )^0/foldexpr;
775 Compare= v.Concat *
776 ( c(EQ + NOTEQ + LESSEQ + GREATEQ + GREATER + LESS) *
777 cerr(__ * v.Concat, "right operand expected for comparison expr")/t2('binop','op','r')
778 )^0/foldexpr;
780 Concat =v.Sum *
781 ( c(DOTDOT) * -ASSIGN *
782 cerr(__ * v.Sum, "right operand expected for concat expr")/t2('binop','op','r')
783 )^0/foldexpr;
785 Sum =v.Product *
786 ( c(PLUS+MINUS+PERCENT) * -ASSIGN *
787 cerr(__ * v.Product, "right operand expected for arith expr")/t2('binop','op','r')
788 )^0/foldexpr;
790 Product=v.Unary *
791 ( c(STAR+SLASH+POW) * -ASSIGN *
792 cerr(__ * v.Unary, "right operand expected for arith expr")/t2('binop','op','r')
793 )^0/foldexpr;
795 Unary = c(MINUS) * cerr( __ * v.Unary, "operand expected for unary expr") / t2('unop','op','l')
796 + c(NOT_KW) * cerr( __ * v.Unary, "operand expected for unary expr")/ t2('unop','op','l')
797 + v.VarAcc;
799 VarAcc = v.Value *
801 w(SOPEN) * v.Expr * w(SCLOSE) /t1('index','id')--index
802 + DOT * -DOT *__* Ident /t1('member','id') --member
803 + AS * __ * v.Type / t1('cast','dst') --cast
804 + IS * __ * v.Type / t1('is','dst') --typecheck
805 + ct(String/t1('string','v')) / t1('call','args') --string call
806 + POpen * (v.ExprList+cnil) * PClose / t1('call','args')--call
807 )^0 / foldexpr
810 Value = POpen * v.Expr * PClose
811 + v.ValueCore;
813 ValueCore=cpos(
814 v.Const * __
815 + (p'\\'*cc(true)+cnil) * Ident * __ /t2('varacc','global','id')
816 + NIL *__ /t0'nil'
817 + SELF * __ /t0'self'
818 + SUPER * __ /t0'super'
819 + v.NewObj
820 + v.SeqBody
821 + v.TableBody
822 + v.Closure
823 + v.Spawn)
826 Const = Number/t1('number','v')
827 + String/t1('string','v')
828 + Boolean/t1('boolean','v')
831 Spawn = SPAWN * __ * cerr(v.Expr, "spawn expression expected" )/ t1('spawn','proto') ;
833 Closure = FUNCKW * __ *_NA * cerr(v.FuncType, "function type expected" ) * __ * v.FuncBlock/t2('closure','type','block');
835 SeqBody = w(BOPEN)*
836 (ct(v.Expr*(w(COMMA)*cerr(v.Expr,'expression expected'))^0)+cnil)
837 * w(BCLOSE) / t1('seq','items') ;
839 TableBody= w(BOPEN)*
840 ( v.TableItem*
841 (__* (COMMA+SEMI) *__* cerr(v.TableItem,"table item expected"))^0 * __ * (COMMA+SEMI)^-1 *__
842 )^-1 * cerr(w(BCLOSE),"unclosed table body") / tt('table','items') ;
844 TableItem = (Ident/t1('string','v') + (w(SOPEN)*v.Expr*w(SCLOSE)))
845 * ASSIGN * __* cerr(v.Expr,"table item value expected") / t2('item','k','v');
847 NewObj = NEW * __ * v.NamedType * __ *
848 (POpen* (v.ExprList+cnil)* PClose
849 + ct(v.TableBody + v.SeqBody)
850 + cnil) / t2('new','class','args')
855 function parse(source)
856 lineInfo={[1]=0}
857 local m= L.match(Module,source)
858 m.lineInfo=lineInfo
859 return m
862 function parseFile(file)
863 local f=io.open(file,'r')
864 assert(f,'file not found:'..file)
865 local src=f:read("*a")
866 f:close()
867 return parse(src)