This is the source text of the frontend of a translator that translates D language source to D. This is not a terribly useful exercise, although it does do a certain amount of pretty-printing, and could do more. The aim was
- to have a substantial test case for the language machine
- to have the basis for porting the language machine to other languages if necessary
- to experiment with very close integration of lmn with the D language
These rules have to be combined with a backend to do anythin useful - the D-to-D backend is what actually regenerates D language source text from the fairly complete analysis done by the frontend. So this could stand as a frontend to other backends, a process which would almost certainly produces places where more has to be done, or where things have to be done differently.
The D-to-D translator has been tested
- by translating Digital Mars DMDscript system
- by translating the sources of the language machine itself
In each case the resulting source was compiled and tested, though not in the case of DMDscript to any great extent. For the language machine, the resulting sources were used to build a new instance of the language machine, and that was used to repeat the process so as to obtain an identical result.
// ******************************* d language analyser front end ********************************* // ********* (c) Copyright Peri Hankey 2005. Distribution licensed under GNU GPLv2 ***********
.d() // top level - rules applied when looking for end of file - unit compile ! <- eof - ;
.d(B) - stat :X <- unit X code ; "module" modulename :N ";" <- unit module :N eoc code ;
- name:M repeat "." pathname:M <- modulename :M ;
- name:N <- pathname :{ path :M :N };
- modulename:N repeat "," modulename:N <- modulenames :{ each N };
- decldef:A <- stat :{ unit:A };
- exec:A <- stat :{ unit:A };
symbol :S ":" labelled:X <- stat :{ label:{sy:S} X } ;
- <- labelled :{} ;
";" <- labelled :eoc ;
";" <- decldef :{ } ;
"import" modulenames:N ";" <- decldef :{ import :N eoc } ;
"public" prag:D <- decldef :{ prot :public :D };
"protected" prag:D <- decldef :{ prot :protected :D };
"private" prag:D <- decldef :{ prot :private :D };
"pragma" "(" name:N { repeat "," arg:P } ")" prag:X <- decldef :{ xpragma :N :{ each P } :X } ;
":" <- prag :prag;
";" <- prag :eoc;
- stat:X <- prag :{ X };
"{" { repeat stat:X } "}" <- prag :{ st:{each X } };
- <- debugArg :{ };
"(" expr:N ")" <- debugArg :{ debugarg :N };
- <- alt :{ };
"else" maybe :S <- alt :{ alt :S };
- stat:X <- maybe :X;
"{" { repeat stat:X } "}" <- maybe :{ st :{each X } };
"debug" debugArg:D maybe:S alt:A <- decldef :{ xdebug :D :S :A };
"version" "(" expr:V ")" maybe:S alt:A <- decldef :{ xversion :V :S :A };
"mixin" name:T mixargs:A optName:M ";" <- decldef :{ xmixin :T :A :M };
- <- mixargs :{ };
"!" "(" formals:P ")" <- mixargs :{ mixargs:P };
"typedef" decl:A <- decldef :{ typedef :A } ;
"alias" decl:A <- decldef :{ alias :A } ;
- decl:A <- decldef :A ;
"struct" structname :N types :T structbody :B <- decldef :{ struct :N :T :B } ;
"union" structname :N types :T structbody :B <- decldef :{ union :N :T :B } ;
- <- structname :anonymous; - name:N <- structname :N;
"enum" enumbody :B <- decldef :{ enum0 :B } ;
"enum" enumname :N enumtype :T enumbody :B <- decldef :{ enum1 :N :T :B } ;
- name :N <- enumname :N ; - basictype :T ":" enumbody :B <- enumname :anonymous enumtype:T enumbody:B ;
":" basictype :T <- enumtype :T; - <- enumtype :"int";
"{" { repeat enummember:D option "," } "}" <- enumbody :{ enumbody :{ each D } } ;
";" <- enumbody :enumdecl;
- name:N initenum:E <- enummember :{ N E };
- <- initenum :{ N };
"class" name :N types :T superclasses :H classbody :B <- decldef :{ classdef :N :T :H :B } ;
"interface" name :N types :T superfaces :H interfacebody :B <- decldef :{ interfacedef :N :T :H :B } ;
"template" name:N "(" tparams:T ")" body:B <- decldef :{ template :N :T :B } ;
- repeat tparam:T option "," <- tparams :{ each T };
"alias" typename:T specialise:S <- tparam :{ tparamA :T :S };
- typename:T specialise:S <- tparam :{ tparamT :T :S };
- basictype:T declarator :D :E :N initassign:I <- tparam :{ tparamV :T :D :N :I };
- <- specialise :{ };
":" basictype:T declarator2 :D <- specialise :{ specialise :T :D };
- <- types :{ };
"(" formals :T ")" <- types :{ types :T };
- <- superclasses :{ };
":" superclass:S repeat "," superface:S <- superclasses :{ supers :{ each S }};
- <- superfaces :{ };
":" superface:S repeat "," superface:S <- superfaces :{ supers :{ each S }};
- name:N repeat typepath:N <- superclass :{ superclass :{ each N }};
- name:N repeat typepath:N <- superface :{ superface :{ each N }};
";" <- structbody :{ } ;
"{" { repeat decldef:D } "}" <- structbody :{ each D } ;
"{" { repeat decldef:D } "}" <- classbody :{ each D } ;
"{" { repeat decldef:D } "}" <- interfacebody :{ each D } ;
"this" "(" params:P ")" body:B <- decldef :{ ctor :P :B } ;
"~" "this" "(" params:P ")" body:B <- decldef :{ dtor :P :B } ;
- <- linkage :{ };
"(" name:N ")" <- linkage :{ linkage :N };
"extern" linkage :L prag :D <- decldef :{ extern :L :D };
"static" "assert" "(" expr:E ")" ";" <- decldef :{ staticassert :E };
"static" "this" "(" params:P ")" body:B <- decldef :{ staticCtor :P :B };
"static" "~" "this" "(" params:P ")" body:B <- decldef :{ staticDtor :P :B };
"new" "(" params:P ")" body:B <- decldef :{ classallocator :P :B } ;
"delete" "(" params:P ")" body:B <- decldef :{ classdeallocator :P :B };
"invariant" body:B <- decldef :{ classinvariant :B };
"unittest" body:B <- decldef :{ utest :B } ;
"abstract" <- storageclass :abstract; "auto" <- storageclass :auto; "const" <- storageclass :const; "deprecated" <- storageclass :deprecated; "final" <- storageclass :final; "override" <- storageclass :override; "static" <- storageclass :static; "synchronized" <- storageclass :synchronized;
"." pathname:P <- typepath :{ N P };
"!" "(" formals:S ")" <- typepath :{ N { templateInstance :{} :S }};
- name:N repeat typepath:N <- typename :N;
"." typename:N <- basictype :{ typename :{ "." N} };
- typename:N <- basictype :{ typename :N };
- primitivetype:T <- basictype :{ ty:T };
"typeof" "(" expr:E ")" <- basictype :{ typeof :E };
"bit" <- primitivetype :"bit" ; "byte" <- primitivetype :"byte" ; "ubyte" <- primitivetype :"ubyte" ; "short" <- primitivetype :"short" ; "ushort" <- primitivetype :"ushort" ; "int" <- primitivetype :"int" ; "uint" <- primitivetype :"uint" ; "long" <- primitivetype :"long" ; "ulong" <- primitivetype :"ulong" ; "char" <- primitivetype :"char" ; "wchar" <- primitivetype :"wchar" ; "dchar" <- primitivetype :"dchar" ; "float" <- primitivetype :"float" ; "double" <- primitivetype :"double" ; "real" <- primitivetype :"real" ; "ifloat" <- primitivetype :"ifloat" ; "idouble" <- primitivetype :"idouble" ; "ireal" <- primitivetype :"ireal" ; "cfloat" <- primitivetype :"cfloat" ; "cdouble" <- primitivetype :"cdouble" ; "creal" <- primitivetype :"creal" ; "void" <- primitivetype :"void" ;
"{" { repeat decldef:D } "}" <- decl :{ st:{ each D } };
- storageclass:S decl:D <- decl :{ storageclass :S :D } ;
- basictype:T declarator :A :B :N declaration :D <- decl :D ;
"*" <- basictype2 :{ star } ;
"[" "]" <- basictype2 :{ row } ;
"[" expr:E "]" <- basictype2 :{ dim :E } ;
"[" type:T "]" <- basictype2 :{ aaa :T } ;
"delegate" "(" formals:P ")" <- basictype2 :{ xdelegate :P } ;
"function" "(" formals:P ")" <- basictype2 :{ xfunction :P } ;
"[" "]" <- declsuffix :{ row } :{};
"[" expr:E "]" <- declsuffix :{ dim :E } :{};
"[" type:T "]" <- declsuffix :{ aaa :T } :{};
"(" params:P ")" <- declsuffix :{} :{ fun :P };
- <- declsuffixes :{} :W;
- declsuffix :V :W declsuffixes :X :Y <- declsuffixes :{ V } :{ Y };
- basictype:T declarator2:B <- type :{ T B };
- <- declarator2 :{ } ;
- basictype2 :B declarator2 :D <- declarator2 :{ B D } ;
"(" declarator2 :D ")" declsuffixes :X :Y <- declarator2 :{ tb :D X Y } ;
- basictype2 :B declarator :D :E :N <- declarator :{ B D } :E :N ;
- name :N declsuffixes :X :Y <- declarator :{ X } :Y :N ;
"(" declarator :D :E :N ")" declsuffixes :X :Y <- declarator :{ tb :{ D E N } } :Y :{} ;
- repeat param :S option "," <- params :{ each S } ;
- repeat formal:S option "," <- formals :{ each S } ;
- name:N <- optName :N;
- <- optName :{};
- basictype:T declarator2 :D optName :N <- formal :{ formal0 :T :D :N };
"in" basictype:T declarator2 :D optName :N <- formal :{ formal1 :"in" :T :D :N };
"out" basictype:T declarator2 :D optName :N <- formal :{ formal1 :"out" :T :D :N };
"inout" basictype:T declarator2 :D optName :N <- formal :{ formal1 :"inout" :T :D :N };
"..." <- param :{ varargs };
- basictype:T declarator :D :E :N initparam:I <- param :{ param0 :T :D :N :I };
"in" basictype:T declarator :D :E :N initparam:I <- param :{ param1 :"in" :T :D :N :I } ;
"out" basictype:T declarator :D :E :N initparam:I <- param :{ param1 :"out" :T :D :N :I } ;
"inout" basictype:T declarator :D :E :N initparam:I <- param :{ param1 :"inout" :T :D :N :I } ;
- initdecl :X { repeat "," name :N initial :X } ";" <- declaration :{ each X eoc };
";" <- declaration :{ declare :T :A :B :N eoc };
"{" { repeat stat:X } "}" <- declaration :{ define :T :A :B :N :{ each X }};
"in" body :I ocontract :R bcontract :X <- declaration :{ cdefine :T :A :B :N :{ contracts :"in" :{}:I :R :X }};
"out" outresult :V body :R icontract :I bcontract :X <- declaration :{ cdefine :T :A :B :N :{ contracts :"out" :V :R :I :X }};
"body"outresult :V body :R <- declaration :{ cdefine :T :A :B :N :{ contracts :"body":{}:{}:{}:X }};
.d(10R)
"=" expr:E <- initassign :{ E };
- <- initdecl :{ declare :T :A :B :N };
- initassign :E <- initdecl :{ initdecl :T :A :B :N :E };
- <- initial :{ decl :N };
- initassign:E <- initial :{ init :N :E };
- <- initparam :{ dParam };
- initassign:E <- initparam :{ iParam :E };
- <- initenum :{ dEnum };
- initassign:E <- initenum :{ iEnum :E };
.d(B)
"if" "(" expr:E ")" cond:A alts:B <- exec :{ xif :E :A :B };
"do" repeated:B "while" "(" expr:E ")" <- exec :{ xdo :E :B };
"while" "(" expr:E ")" repeated:B <- exec :{ xwhile :E :B };
"for" "(" init :I test:E next:N ")" repeated:B <- exec :{ xfor :I :E :N :B };
"foreach" "(" eachtypes:I ";" expr:E ")" repeated:B <- exec :{ xforeach :I :E :B };
"switch" "(" expr:E ")" body:B <- exec :{ xswitch :E :B } ;
"case" expr:E {repeat "," expr:E} ":" repeat stat:S <- exec :{ xcase :{ each E } :{ each S } } ;
"default" ":" repeat stat:S <- exec :{ xdefault :{ each S }};
"continue" ";" <- exec :{ xcont0 eoc } ;
"continue" name:N ";" <- exec :{ xcont1 :N eoc } ;
"break" ";" <- exec :{ xbreak0 eoc } ;
"break" name:N ";" <- exec :{ xbreak1 :N eoc } ;
"return" ";" <- exec :{ xreturnZ eoc } ;
"return" expr:E ";" <- exec :{ xreturnE :E eoc} ;
"goto" name:N ";" <- exec :{ xgoName :N eoc } ;
"goto" "default" ";" <- exec :{ xgodefault eoc } ;
"goto" "case" ";" <- exec :{ xgocase0 eoc } ;
"goto" "case" expr:E ";" <- exec :{ xgocase1 :E eoc } ;
"with" "(" expr:X ")" body:B <- exec :{ xwithB :X :B } ;
"with" "(" name:X ")" body:B <- exec :{ xwithN :X :B } ;
"with" "(" templateinstance:X ")" body:B <- exec :{ xwithT :X :B } ;
"synchronized" stat:S <- exec :{ xsync0 :S } ;
"synchronized" "(" expr:E ")" stat:S <- exec :{ xsync1 :E :S } ;
"try" exec:B catches:C lastcatch:L finalcatch:F <- exec :{ xtry :B :C :L :F } ;
- <- finalcatch :{ };
"finally" exec:F <- finalcatch :{ finally :B };
"catch" "(" param:P ")" exec:B <- catcher :{ catch1 :P :B };
- <- lastcatch :{} ;
"catch" exec:B <- lastcatch :{ catch0 :B } ;
- repeat catcher:C <- catches:{ each C };
"throw" expr:E ";" <- exec:{ xthrow :E eoc } ;
"volatile" stat:S <- exec:{ xvolatile :S } ;
"asm" "{" { repeat asm:A ";" } "}" <- exec:{ asmblock :{ each A } } ;
- <- asm :{ };
- asmitem:A { repeat asmitem :A } <- asm :{ asmstat :{ each A eoc } };
"," <- asmitem :comma ;
"[" { repeat asmitem :A } "]" <- asmitem :{ "[" each A "]" };
"(" { repeat asmitem :A } ")" <- asmitem :{ "(" each A ")" };
symbol:X <- asmitem :{ asmitem :{ sy :X }} ;
number:X <- asmitem :{ asmitem :{ nm :X }} ;
squote:X repeat squote:X <- asmitem :{ asmitem :{ sq :{ each X }}} ;
dquote:X repeat dquote:X <- asmitem :{ asmitem :{ dq :{ each X }}} ;
- <- icontract:{ };
"in" body:B <- icontract:{ contract :"in" :{} :B };
- <- ocontract:{ };
"out" outresult:R body:B <- ocontract:{ contract :"out" :R :B };
"body" body:B <- bcontract:{ contract :"body" :{} :B };
"in" body:I ocontract:A bcontract:B <- exec :{ contracts :"in" :{} :I :A :B };
"out" outresult:R body:B icontract:A bcontract:B <- exec :{ contracts :"out" :R :B :A :B };
"body" body:B <- exec :{ contract :"body" :{} :B };
- <- outresult:{ };
"(" name:N ")" <- outresult:{ outresult:N };
.d()
- stat:B <- cond :B;
"else" stat:B <- alts :{ xelse :B };
"else" "if" "(" expr:E ")" cond:B alts:C <- alts :{ xelsif :E :B :C };
- <- alts :{ xelsez };
- stat:B <- repeated: B ;
";" <- repeated:{ };
"{" { repeat stat:X } "}" <- body :{ each X };
"{" { repeat stat:X } "}" <- exec :{ st :{ each X }};
- lvalue expr:A ";" <- exec :{ A eoc };
"(" lvalue <- lvalue "(" ;
"*" <- lvalue "*" ;
"--" <- lvalue "--" ;
"++" <- lvalue "++" ;
"cast" <- lvalue "cast" ;
"this" <- lvalue "this" ;
"super" <- lvalue "super" ;
"new" <- lvalue "new" ;
"delete" <- lvalue "delete" ;
"assert" <- lvalue "assert" ;
"version" <- lvalue symbol :"version" ;
symbol <- lvalue symbol ;
- expr:X ";" <- init:{ X } ;
- basictype:T declarator :A :B :N initdecl:X { repeat "," name:N initial:X } ";" <- init:{ each X } ;
";" <- init:{ } ;
- eachtype :D repeat "," eachtype :D <- eachtypes:{ each D };
- basictype:T declarator :A :B :N <- eachtype :{ eachtyp0 :T :A :B :N };
"in" basictype:T declarator :A :B :N <- eachtype :{ eachtyp1 :"in" :T :A :B :N };
"out" basictype:T declarator :A :B :N <- eachtype :{ eachtyp1 :"out" :T :A :B :N };
"inout" basictype:T declarator :A :B :N <- eachtype :{ eachtyp1 :"inout" :T :A :B :N };
- expr:X ";" <- test :X ;
";" <- test :{} ;
- expr:X <- next :X ;
- <- next :{} ;
symbol:X <- name :{ sy :X } ;
name :X <- opnd :X;
symbol:X <- opnd :{ sy :X } ;
number:X <- opnd :{ nm :X } ;
squote:X repeat squote:X <- opnd :{ sq :{ each X }} ;
dquote:X repeat dquote:X <- opnd :{ dq :{ each X }} ;
"this" <- opnd :{ "this" };
"super" <- opnd :{ "super" };
"null" <- opnd :{ "null" };
"true" <- opnd :{ truth :"true" };
"false" <- opnd :{ truth :"false" };
- basictype:T "." name:N <- opnd :{ typeattribute :T :N };
"typeid" "(" type:T ")" <- opnd :{ typeid :T };
- opnd :A op <- expr - ;
.d(B)
- expr:B <- nest:{ B };
"(" expr:B ")" <- opnd:{ br:B };
"!" "(" formals:S ")" <- op opnd:{ templateInstance :A :S };
- <- op expr:A ;
"(" args:B ")" <- op opnd:{ fn :A :B };
"[" indx:C "]" <- op opnd:{ C };
"." name:B <- op opnd:{ dot :A :B };
"cast" "(" type :T ")" expr:B <- opnd:{ cast :T :B } ;
"(" type :T ")" "." name:X <- opnd:{ typeattribute :{ br :T } :X } ;
"assert" "(" expr:B ")" <- opnd:{ assert :B } ;
"function" body:B <- opnd:{ xfunction :"void" :{} :B };
"function" "(" params:P ")" body:B <- opnd:{ xfunction :"void" :P :B };
"function" type:T "(" params:P ")" body:B <- opnd:{ xfunction :T :P :B };
"delegate" body:B <- opnd:{ xdelegate :"void" :{} :B };
"delegate" "(" params:P ")" body:B <- opnd:{ xdelegate :"void" :P :B };
"delegate" type:T "(" params:P ")" body:B <- opnd:{ xdelegate :T :P :B };
"{" list:B "}" <- opnd:{ structinit :B };
"[" list:B "]" <- opnd:{ arrayinit :B };
- repeat cell:E option "," <- list:{ each E };
- expr:E cellvalue :X <- cell:X ;
- <- cellvalue :{ cellV :E };
":" expr:E <- cellvalue :{ cellN :N :E };
.d(8R)
"," expr:B <- op opnd:{ "," :A :B };
.d(10R)
- <- indx:{ idx0 :A };
- expr:B ind1:C <- indx:{ C };
- <- ind1:{ idx :A :B };
".." expr:C <- ind1:{ sli :A :B :C };
- expr:A <- arg :{ arg :A };
- <- args:{ };
- arg:E repeat "," arg:E <- args:{ each E };
"=" expr:B <- op opnd:{ fa :"=" :A :B };
"+=" expr:B <- op opnd:{ fa :"+=" :A :B };
"-=" expr:B <- op opnd:{ fa :"-=" :A :B };
"*=" expr:B <- op opnd:{ fa :"*=" :A :B };
"/=" expr:B <- op opnd:{ fa :"/=" :A :B };
"%=" expr:B <- op opnd:{ fa :"%=" :A :B };
"&=" expr:B <- op opnd:{ fa :"&=" :A :B };
"|=" expr:B <- op opnd:{ fa :"|=" :A :B };
"^=" expr:B <- op opnd:{ fa :"^=" :A :B };
"~=" expr:B <- op opnd:{ fa :"~=" :A :B };
"<<=" expr:B <- op opnd:{ fa :"<<=" :A :B };
">>=" expr:B <- op opnd:{ fa :">>=" :A :B };
">>>="expr:B <- op opnd:{ fa :">>>=":A :B };
.d(12R)
"?" nest:B ":" expr:C <- op opnd:{ "?" :A :B :C };
.d(12L)
"||" expr:B <- op opnd:{ fl :"||" :A :B };
.d(14L)
"&&" expr:B <- op opnd:{ fl :"&&" :A :B };
.d(16R)
"|" expr:B <- op opnd:{ fb :"|" :A :B };
.d(18L)
"&" expr:B <- op opnd:{ fb :"&" :A :B };
.d(20R)
"^" expr:B <- op opnd:{ fb :"^" :A :B };
.d(22R)
"&" expr:B <- op opnd:{ fb :"&" :A :B };
.d(24L)
"is" expr:B <- op opnd:{ fq :"is" :A :B };
"!is" expr:B <- op opnd:{ fq :"!is" :A :B };
"===" expr:B <- op opnd:{ fq :"is" :A :B };
"!==" expr:B <- op opnd:{ fq :"!is" :A :B };
"==" expr:B <- op opnd:{ fe :"==" :A :B };
"!=" expr:B <- op opnd:{ fe :"!=" :A :B };
.d(26L)
"<" expr:B <- op opnd:{ fc :"<" :A :B };
">" expr:B <- op opnd:{ fc :">" :A :B };
"<=" expr:B <- op opnd:{ fc :"<=" :A :B };
">=" expr:B <- op opnd:{ fc :">=" :A :B };
"!<>=" expr:B <- op opnd:{ fc :"!<>=" :A :B };
"!<>" expr:B <- op opnd:{ fc :"!<>" :A :B };
"<>" expr:B <- op opnd:{ fc :"<>" :A :B };
"<>=" expr:B <- op opnd:{ fc :"<>=" :A :B };
"!>" expr:B <- op opnd:{ fc :"!>" :A :B };
"!>=" expr:B <- op opnd:{ fc :"!>=" :A :B };
"!<" expr:B <- op opnd:{ fc :"!<" :A :B };
"!<=" expr:B <- op opnd:{ fc :"!<=" :A :B };
"in" expr:B <- op opnd:{ fc :"in" :A :B };
"<<" expr:B <- op opnd:{ fs :"<<" :A :B };
">>" expr:B <- op opnd:{ fs :">>" :A :B };
">>>" expr:B <- op opnd:{ fs :">>>" :A :B };
.d(28L)
"+" expr:B <- op opnd:{ fx :"+" :A :B };
"-" expr:B <- op opnd:{ fx :"-" :A :B };
"~" expr:B <- op opnd:{ fs :"~" :A :B };
.d(30L)
"*" expr:B <- op opnd:{ fx :"*" :A :B };
"/" expr:B <- op opnd:{ fx :"/" :A :B };
"%" expr:B <- op opnd:{ fx :"%" :A :B };
.d(32L)
"++" <- op opnd:{ post :inc :A };
"--" <- op opnd:{ post :dec :A };
.d(32R)
"++" expr:B <- opnd :{ pre :inc :B };
"--" expr:B <- opnd :{ pre :dec :B };
"&" expr:B <- opnd :{ ur :ref :B };
"*" expr:B <- opnd :{ ur :deref :B };
"-" expr:B <- opnd :{ ux :neg :B };
"+" expr:B <- opnd :{ ux :pos :B };
"!" expr:B <- opnd :{ ub :not :B };
"~" expr:B <- opnd :{ ub :inv :B };
"delete" expr:B <- opnd :{ aa :del :B };
"new" newexpr:B <- opnd :{ B };
.d(B)
- basictype :T stars:S newargs:A <- newexpr :{ nu :T :S :A };
- <- newargs :{ };
"[" newv:B "]" repeat "[" newv:B "]" <- newargs :{ each B };
"(" args:B ")" <- newargs :{ args :B };
- <- newv :{ newvec0 };
- expr:B <- newv :{ newvec1 :B };
- repeat star:S <- stars :{ each S };
"*" <- star :{ star };
// "new" basictype stars "[" assignexpression "]" declarator <- newexpression ;
// "new" basictype stars "(" argumentlist ")" <- newexpression ;
// "new" basictype stars <- newexpression ;
// "new" "(" argumentlist ")" basictype stars "[" assignexpression "]" declarator <- newexpression ;
// "new" "(" argumentlist ")" basictype stars "(" argumentlist ")" <- newexpression ;
// "new" "(" argumentlist ")" basictype stars <- newexpression ;
// - <- stars ; // "*" <- stars ; // "*" stars <- stars ;
.d(1010R) // comments, errors etc // rest of line for a single line comment - anything <- line - ; '\n' <- line ; eof <- line eof ;
// multi line comments - can be nested '/+' acomment '+/' <- acomment - ; '/+' acomment '+/' <- bcomment - ;
'/+' acomment '+/' <- acomment - ; '/*' bcomment '*/' <- bcomment - ;
- anything <- acomment - ; '+/' <- acomment '+/' ; eof <- acomment '+/' eof ;
'*/' <- bcomment '*/' ; - anything <- bcomment - ; eof <- bcomment '*/' eof ;
// error handling - catch any unrecognised material at top level or in rules
- { flagError :F error message } <- eof - ;
- { repeat skip t } <- error F 'ERROR\n' message ;
- err <- message - ;
- anything <- skip t; '\n' <- skip f; eof <- skip f;
.d(1000L) // some lexical rules [ \r\n\t] <- - ;
'//' line <- - ; // remainder of line is comment '/+' acomment '+/' <- - ; // delimited comments with nesting '/*' bcomment '*/' <- - ; // delimited comments with nesting
'/' <- - "/" ;
'/=' <- - "/=" ;
'.' <- - "." ;
'..' <- - ".." ;
'...' <- - "..." ;
'&' <- - "&" ;
'&=' <- - "&=" ;
'&&' <- - "&&" ;
'|' <- - "|" ;
'|=' <- - "|=" ;
'||' <- - "||" ;
'-' <- - "-" ;
'-=' <- - "-=" ;
'--' <- - "--" ;
'+' <- - "+" ;
'+=' <- - "+=" ;
'++' <- - "++" ;
'<' <- - "<" ;
'<=' <- - "<=" ;
'<<' <- - "<<" ;
'<<=' <- - "<<=" ;
'<>' <- - "<>" ;
'<>=' <- - "<>=" ;
'>' <- - ">" ;
'>=' <- - ">=" ;
'>>=' <- - ">>=" ;
'>>>=' <- - ">>>=";
'>>' <- - ">>" ;
'>>>' <- - ">>>" ;
'!' <- - "!" ;
'!=' <- - "!=" ;
'!is' <- - "!is" ;
'!==' <- - "!==" ;
'!<>' <- - "!<>" ;
'!<>=' <- - "!<>=";
'!<' <- - "!<" ;
'!<=' <- - "!<=" ;
'!>' <- - "!>" ;
'!>=' <- - "!>=" ;
'(' <- - "(" ;
')' <- - ")" ;
'[' <- - "[" ;
']' <- - "]" ;
'{' <- - "{" ;
'}' <- - "}" ;
'?' <- - "?" ;
',' <- - "," ;
';' <- - ";" ;
':' <- - ":" ;
'$' <- - "$" ;
'=' <- - "=" ;
'==' <- - "==" ;
'===' <- - "===" ;
'*' <- - "*" ;
'*=' <- - "*=" ;
'%' <- - "%" ;
'%=' <- - "%=" ;
'^' <- - "^" ;
'^=' <- - "^=" ;
'~' <- - "~" ;
'~=' <- - "~=" ;
// symbols: eg A::Sym combines each A to yield a unique symbol - identifier <- - ; - word :W s t <- - W ;
'\'' { repeat e1 [^\'] % } '\'' toStr:Str <- - squote :{ Str } ;
'\"' { repeat e2 [^\"] % } '\"' toStr:Str <- - dquote :{ Str } ;
'.' % decimal % dexp % rtype % type:T <- - number % ;
'0' % znumber % type:T <- - number % ;
[1-9] % { repeat [0-9] % } dpoint % type:T <- - number % ;
.d(1010R) // analysis within atoms
[0-9] % { repeat [0-9] % } <- decimal % ;
- { repeat [0-9] % } dpoint % <- znumber % ;
- { repeat [0-7] % } octal t itype % <- znumber % ;
'b' % [01] % { repeat [01] % } itype % <- znumber % ;
[xX] % [0-9a-fA-F] % { repeat [0-9a-fA-F] % } xpoint % <- znumber % ;
- <- octal t ; [.8-9] <- octal f ;
- itype % <- dpoint % ;
[eE] % expsign % decimal % rtype % <- dpoint % ;
'.' % [0-9] % { repeat [0-9] % } dexp % rtype % <- dpoint % ;
- itype % <- xpoint % ;
[pP] % expsign % decimal % rtype % <- xpoint % ;
'.' % [0-9a-fA-F] % { repeat [0-9a-fA-F] % } xexp % rtype % <- xpoint % ;
- <- dexp :{} ;
[eE] % expsign % decimal % <- dexp % ;
- <- xexp :{} ;
[pP] % expsign % decimal % <- xexp % ;
- <- expsign :{} ;
[-+] % <- expsign % ;
- <- rtype :{} type :"double" ;
'i' <- rtype :"i" type :"idouble" ;
'I' <- rtype :"i" type :"idouble" ;
'l' <- rtype :"l" type :"real" ;
'L' <- rtype :"l" type :"real" ;
'li' <- rtype :"li" type :"ireal" ;
'Li' <- rtype :"li" type :"ireal" ;
'lI' <- rtype :"li" type :"ireal" ;
'LI' <- rtype :"li" type :"ireal" ;
'f' <- rtype :"f" type :"float" ;
'F' <- rtype :"f" type :"float" ;
'fi' <- rtype :"fi" type :"ifloat" ;
'Fi' <- rtype :"fi" type :"ifloat" ;
'fI' <- rtype :"fi" type :"ifloat" ;
'FI' <- rtype :"fi" type :"ifloat" ;
- <- itype :{} type :"int" ;
'l' <- itype :"l" type :"long" ;
'L' <- itype :"l" type :"long" ;
'u' <- itype :"u" type :"ulong";
'U' <- itype :"u" type :"ulong";
'lu' <- itype :"lu" type :"ulong";
'Lu' <- itype :"lu" type :"ulong";
'lU' <- itype :"lu" type :"ulong";
'LU' <- itype :"lu" type :"ulong";
'ul' <- itype :"lu" type :"ulong";
'uL' <- itype :"lu" type :"ulong";
'Ul' <- itype :"lu" type :"ulong";
'UL' <- itype :"lu" type :"ulong";
[a-z_A-Z] % { { repeat [a-zA-Z_0-9] % } toSym:X } <- identifier symbol :X ;
- <- s t ; - [a-zA-Z_0-9] <- s f ;
- <- e1 ; - <- e2 ;
'\"' <- e1 [^\']: "\"" ; '\\a' <- e1 [^\']: "\\a" ; '\\b' <- e1 [^\']: "\\b" ; '\\f' <- e1 [^\']: "\\f" ; '\\n' <- e1 [^\']: "\\n" ; '\\r' <- e1 [^\']: "\\r" ; '\\t' <- e1 [^\']: "\\t" ; '\\v' <- e1 [^\']: "\\v" ; '\\f' <- e1 [^\']: "\\f" ; '\\\\' <- e1 [^\']: "\\\\"; '\\\'' <- e1 [^\']: "\\\'"; '\\\"' <- e1 [^\']: "\\\"";
'\\a' <- e2 [^\"]: "\\a" ; '\\b' <- e2 [^\"]: "\\b" ; '\\f' <- e2 [^\"]: "\\f" ; '\\n' <- e2 [^\"]: "\\n" ; '\\r' <- e2 [^\"]: "\\r" ; '\\t' <- e2 [^\"]: "\\t" ; '\\v' <- e2 [^\"]: "\\v" ; '\\f' <- e2 [^\"]: "\\f" ; '\\\\' <- e2 [^\"]: "\\\\"; '\\\'' <- e2 [^\"]: "\\\'"; '\\\"' <- e2 [^\"]: "\\\"";
'abstract' <- word :"abstract" ; 'alias' <- word :"alias" ; 'align' <- word :"align" ; 'asm' <- word :"asm" ; 'assert' <- word :"assert" ; 'auto' <- word :"auto" ; 'bit' <- word :"bit" ; 'body' <- word :"body" ; 'break' <- word :"break" ; 'byte' <- word :"byte" ; 'case' <- word :"case" ; 'cast' <- word :"cast" ; 'catch' <- word :"catch" ; 'cdouble' <- word :"cdouble" ; 'cent' <- word :"cent" ; 'cfloat' <- word :"cfloat" ; 'char' <- word :"char" ; 'class' <- word :"class" ; 'const' <- word :"const" ; 'continue' <- word :"continue" ; 'creal' <- word :"creal" ; 'dchar' <- word :"dchar" ; 'debug' <- word :"debug" ; 'default' <- word :"default" ; 'delegate' <- word :"delegate" ; 'delete' <- word :"delete" ; 'deprecated' <- word :"deprecated" ; 'do' <- word :"do" ; 'double' <- word :"double" ; 'else' <- word :"else" ; 'enum' <- word :"enum" ; 'export' <- word :"export" ; 'extern' <- word :"extern" ; 'false' <- word :"false" ; 'final' <- word :"final" ; 'finally' <- word :"finally" ; 'float' <- word :"float" ; 'for' <- word :"for" ; 'foreach' <- word :"foreach" ; 'function' <- word :"function" ; 'goto' <- word :"goto" ; 'idouble' <- word :"idouble" ; 'if' <- word :"if" ; 'ifloat' <- word :"ifloat" ; 'import' <- word :"import" ; 'in' <- word :"in" ; 'inout' <- word :"inout" ; 'int' <- word :"int" ; 'interface' <- word :"interface" ; 'invariant' <- word :"invariant" ; 'ireal' <- word :"ireal" ; 'is' <- word :"is" ; 'long' <- word :"long" ; 'mixin' <- word :"mixin" ; 'module' <- word :"module" ; 'new' <- word :"new" ; 'null' <- word :"null"; 'out' <- word :"out" ; 'override' <- word :"override" ; 'package' <- word :"package" ; 'pragma' <- word :"pragma" ; 'private' <- word :"private" ; 'protected' <- word :"protected" ; 'public' <- word :"public" ; 'real' <- word :"real" ; 'return' <- word :"return" ; 'short' <- word :"short" ; 'static' <- word :"static" ; 'struct' <- word :"struct" ; 'super' <- word :"super" ; 'switch' <- word :"switch" ; 'synchronized' <- word :"synchronized" ; 'template' <- word :"template" ; 'this' <- word :"this" ; 'throw' <- word :"throw" ; 'true' <- word :"true" ; 'try' <- word :"try" ; 'typedef' <- word :"typedef" ; 'typeid' <- word :"typeid" ; 'typeof' <- word :"typeof" ; 'ubyte' <- word :"ubyte" ; 'ucent' <- word :"ucent" ; 'uint' <- word :"uint" ; 'ulong' <- word :"ulong" ; 'union' <- word :"union" ; 'unittest' <- word :"unittest" ; 'ushort' <- word :"ushort" ; 'version' <- word :"version" ; 'void' <- word :"void" ; 'volatile' <- word :"volatile" ; 'wchar' <- word :"wchar" ; 'while' <- word :"while" ; 'with' <- word :"with" ;






