From 4c82dc467d342aba38700c578c62690c02782cb7 Mon Sep 17 00:00:00 2001 From: Kyryl R Date: Fri, 25 Oct 2024 18:18:49 +0300 Subject: [PATCH 01/10] First successful grammar opt --- .gitmodules | 6 + base_test.go | 9 +- circomlib | 2 +- data/Example1.circom | 9 + ed25519-circom | 1 + grammar/CircomLexer.g4 | 17 +- grammar/CircomParser.g4 | 422 +++++++++++++++++++++++++++++----------- maci | 1 + passport-zk-circuits | 2 +- 9 files changed, 351 insertions(+), 118 deletions(-) create mode 160000 ed25519-circom create mode 160000 maci diff --git a/.gitmodules b/.gitmodules index 77bc779..21acddb 100644 --- a/.gitmodules +++ b/.gitmodules @@ -7,3 +7,9 @@ [submodule "passport-zk-circuits"] path = passport-zk-circuits url = git@github.com:rarimo/passport-zk-circuits.git +[submodule "ed25519-circom"] + path = ed25519-circom + url = git@github.com:Electron-Labs/ed25519-circom.git +[submodule "maci"] + path = maci + url = git@github.com:privacy-scaling-explorations/maci.git diff --git a/base_test.go b/base_test.go index dab1b8a..ee500ab 100644 --- a/base_test.go +++ b/base_test.go @@ -9,7 +9,14 @@ import ( // TestParseAllCircuits recursively parses all circuit files in the directory func TestParseAllCircuits(t *testing.T) { - baseDirs := []string{"iden3-circuits/circuits", "circomlib/circuits", "data", "passport-zk-circuits/circuits"} + baseDirs := []string{ + "iden3-circuits/circuits", + "circomlib/circuits", + "data", + "passport-zk-circuits/circuits", + "ed25519-circom/circuits", + "maci/packages/circuits/circom", + } for _, baseDir := range baseDirs { err := filepath.Walk(baseDir, func(path string, info os.FileInfo, err error) error { diff --git a/circomlib b/circomlib index cff5ab6..0a045ae 160000 --- a/circomlib +++ b/circomlib @@ -1 +1 @@ -Subproject commit cff5ab6288b55ef23602221694a6a38a0239dcc0 +Subproject commit 0a045aec50d51396fcd86a568981a5a0afb99e95 diff --git a/data/Example1.circom b/data/Example1.circom index e96880d..55f6665 100644 --- a/data/Example1.circom +++ b/data/Example1.circom @@ -20,7 +20,16 @@ function nbits(a) { template A(a, b, c) {} +function TestFunc() { + return [[1, 2, 3]]; +} + template nbits(a) { + var i = 0; + for (kek.out[0] <-- 9; kek.out[0] < 10; i++) {} + for (9 --> kek.out[1]; kek.out[0] < 10; i++) {} + for (var some[1] = [0]; kek.out[0] < 10; i++) {} + var o_u_t; var o$o; var x[3] = [2,8,4]; diff --git a/ed25519-circom b/ed25519-circom new file mode 160000 index 0000000..99490fc --- /dev/null +++ b/ed25519-circom @@ -0,0 +1 @@ +Subproject commit 99490fc0b4ad14206a6f772baa73b0c64cf38146 diff --git a/grammar/CircomLexer.g4 b/grammar/CircomLexer.g4 index 72e5d64..4d3139e 100644 --- a/grammar/CircomLexer.g4 +++ b/grammar/CircomLexer.g4 @@ -1,7 +1,7 @@ lexer grammar CircomLexer; /*////////////////////////////////////////////////////////////// - COMMON STRUCTURES + COMMON STRUCTURES AND TERMINALS //////////////////////////////////////////////////////////////*/ VERSION: NUMBER '.' NUMBER '.' NUMBER ; @@ -22,6 +22,7 @@ INCLUDE: 'include' ; CUSTOM: 'custom' ; PARALLEL: 'parallel' ; +BUS: 'bus' ; TEMPLATE: 'template' ; FUNCTION: 'function' ; @@ -75,8 +76,12 @@ TERNARY_CONDITION: '?' ; TERNARY_ALTERNATIVE: ':' ; EQ_CONSTRAINT: '===' ; -LEFT_CONSTRAINT: '<--' | '<==' ; -RIGHT_CONSTRAINT: '-->' | '==>' ; + +LEFT_CONSTRAINT: '<==' ; +LEFT_ASSIGNMENT: '<--' ; + +RIGHT_CONSTRAINT: '==>' ; +RIGHT_ASSIGNMENT: '-->' ; // Unary operators SELF_OP: '++' | '--' ; @@ -118,9 +123,9 @@ OR: '||' ; ASSIGNMENT: '=' ; ASSIGNMENT_WITH_OP: '+=' | '-=' | '*=' | '**=' | '/=' | '\\=' | '%=' | '<<=' | '>>=' | '&=' | '^=' | '|=' ; -ID : ID_SYMBOL* LETTER (LETTER|DIGIT|ID_SYMBOL)*; +ID : ID_SYMBOL* LETTER (LETTER|ID_SYMBOL|DIGIT)* ; // r"[$_]*[a-zA-Z][a-zA-Z$_0-9]*" fragment -LETTER : [a-zA-Z\u0080-\u00FF] ; +LETTER : [a-zA-Z] ; fragment ID_SYMBOL : [_$] ; @@ -128,7 +133,7 @@ NUMBER: DIGIT+ | HEX; fragment DIGIT: [0-9] ; -HEX : '0' 'x' HEXDIGIT+ ; +HEX : '0' 'x' HEXDIGIT+ ; // 0x[0-9A-Fa-f]* fragment HEXDIGIT : ('0'..'9'|'a'..'f'|'A'..'F') ; diff --git a/grammar/CircomParser.g4 b/grammar/CircomParser.g4 index 16de660..a5561f8 100644 --- a/grammar/CircomParser.g4 +++ b/grammar/CircomParser.g4 @@ -3,171 +3,375 @@ parser grammar CircomParser; options { tokenVocab=CircomLexer; } circuit - : pragmaDeclaration* includeDeclaration* blockDeclaration* componentMainDeclaration? + : pragmaDefinition* includeDefinition* blockDefiniton* componentMainDeclaration? EOF ; -pragmaDeclaration - : 'pragma' 'circom' VERSION ';' - | 'pragma' 'custom_templates' ';' +/*////////////////////////////////////////////////////////////// + HEADERS +//////////////////////////////////////////////////////////////*/ + +signalHeader + : 'signal' SIGNAL_TYPE? tagDefinition? + | SIGNAL_TYPE 'signal' tagDefinition? + ; + +busHeader + : ID wireType=SIGNAL_TYPE? tagDefinition? + | ID '(' parameters=listable? ')' wireType=SIGNAL_TYPE? tagDefinition? + | wireType=SIGNAL_TYPE ID tagDefinition? + | wireType=SIGNAL_TYPE ID '(' parameters=listable? ')' tagDefinition? + ; + +/*////////////////////////////////////////////////////////////// + DEFINITONS +//////////////////////////////////////////////////////////////*/ + +pragmaDefinition + : 'pragma' 'circom' VERSION ';' #PragmaVersion + | 'pragma' 'circom' ';' #PragmaInvalidVersion + | 'pragma' 'custom_templates' ';' #PragmaCustomTemplates + ; + +includeDefinition + : 'include' path=STRING ';' + ; + +blockDefiniton + : functionDefinition + | templateDefinition + | busDefinition + ; + +functionDefinition + : 'function' name=ID '(' argNames=simpleIdentifierList? ')' parseBlock + ; + +templateDefinition + : 'template' customGate='custom'? 'parallel'? name=ID '(' argNames=simpleIdentifierList? ')' parseBlock ; -includeDeclaration - : 'include' STRING ';' +busDefinition + : 'bus' name=ID '(' argNames=simpleIdentifierList? ')' parseBlock ; -blockDeclaration - : functionDeclaration - | templateDeclaration +publicInputsDefinition + : '{' 'public' '[' publicInputs=simpleIdentifierList ']' '}' ; -functionDeclaration - : 'function' ID '(' args? ')' functionBlock +tagDefinition + : '{' values=simpleIdentifierList '}' ; -functionBlock - : '{' functionStmt* '}' +/*////////////////////////////////////////////////////////////// + DECLARATIONS +//////////////////////////////////////////////////////////////*/ + +varDeclaration + : 'var' '(' identifierList ')' tupleInitiation? + | 'var' (varIdentifierAssignment ',')* varIdentifierAssignment ; -functionStmt - : functionBlock #FuncBlock - | ID arrayDimension* SELF_OP ';' #FuncSelfOp - | varDeclaration ';' #FuncVarDeclaration - | identifier (ASSIGNMENT | ASSIGNMENT_WITH_OP) expression ';' #FuncAssignmentExpression - | '(' argsWithUnderscore ')' ASSIGNMENT ('(' expressionList ')' | expression) ';' #FuncVariadicAssignment - | 'if' parExpression functionStmt ('else' functionStmt)? #IfFuncStmt - | 'while' parExpression functionStmt #WhileFuncStmt - | 'for' '(' forControl ')' functionStmt #ForFuncStmt - | 'return' expression ';' #ReturnFuncStmt - | 'assert' parExpression ';' #AssertFuncStmt - | logStmt ';' #LogFuncStmt +signalDeclaration + : signalHeader '(' identifierList ')' tupleInitiation? + | signalHeader (signalIdentifierAssignment ',')* signalIdentifierAssignment ; -templateDeclaration - : 'template' 'custom'? 'parallel'? ID '(' args? ')' templateBlock +componentDeclaration + : 'component' '(' identifierList ')' tupleInitiation? + | 'component' (varIdentifierAssignment ',')* varIdentifierAssignment ; -templateBlock - : '{' templateStmt* '}' +busDeclaration + : busHeader (signalIdentifierAssignment ',')* signalIdentifierAssignment ; componentMainDeclaration - : 'component' 'main' publicInputsList? '=' ID '(' expressionList? ')' ';' + : 'component' 'main' publicInputsDefinition? '=' ID '(' argValues=listable? ')' ';' ; -publicInputsList - : '{' 'public' '[' args ']' '}' + +parseDeclaration + : varDeclaration + | signalDeclaration + | componentDeclaration + | busDeclaration ; -templateStmt - : templateBlock - | ID arrayDimension* SELF_OP ';' - | varDeclaration ';' - | signalDeclaration ';' - | componentDeclaration ';' - | blockInstantiation ';' - | identifier ASSIGNMENT expression ';' - | expression EQ_CONSTRAINT expression ';' - | element (LEFT_CONSTRAINT | ASSIGNMENT_WITH_OP) expression ';' - | '(' element (',' element)* ')' LEFT_CONSTRAINT '(' expression (',' expression)* ')' ';' - | expression RIGHT_CONSTRAINT element ';' - | expression RIGHT_CONSTRAINT '(' element (',' element)* ')' ';' - | '_' (ASSIGNMENT | LEFT_CONSTRAINT) (expression | blockInstantiation) ';' - | (expression | blockInstantiation) RIGHT_CONSTRAINT '_' ';' - | '(' argsWithUnderscore ')' (ASSIGNMENT | LEFT_CONSTRAINT) ('(' expressionList ')' | blockInstantiation | expression) ';' - | blockInstantiation RIGHT_CONSTRAINT '(' argsWithUnderscore ')' ';' - | 'if' parExpression templateStmt ('else' templateStmt)? - | 'while' parExpression templateStmt - | 'for' '(' forControl ')' templateStmt - | 'assert' parExpression ';' - | logStmt ';' +/*////////////////////////////////////////////////////////////// + BODIES +//////////////////////////////////////////////////////////////*/ + +//templateBody +// : '{' templateStmt* '}' +// ; +// +//busBody +// : '{' '}' +// ; +// +//functionBody +// : '{' functionStmt* '}' +// ; + +/*////////////////////////////////////////////////////////////// + STATEMENTS +//////////////////////////////////////////////////////////////*/ + +parseSubstitution + : expression ops=(ASSIGNMENT | LEFT_ASSIGNMENT | LEFT_CONSTRAINT) rhe=expression + | lhe=expression '-->' variable=expression + | lhe=expression '==>' variable=expression + | identifierStatment ASSIGNMENT_WITH_OP rhe=expression + | identifierStatment SELF_OP + | SELF_OP identifierStatment ; -element: (identifier ('.' identifier)?) ; +parseBlock: '{' stmts=parseStatment3* '}'; -forControl: forInit ';' expression ';' forUpdate ; +parseStatement: parseStatement0; -forInit: 'var'? identifier (ASSIGNMENT rhsValue)? ; +parseStatement0 + : parseStmt0NB + | parseStatement1 + ; -forUpdate: ID (SELF_OP | ((ASSIGNMENT | ASSIGNMENT_WITH_OP) expression)) | SELF_OP ID ; +parseStmt0NB + : 'if' '(' cond=expression ')' parseStmt0NB + | 'if' '(' cond=expression ')' parseStatement1 + | 'if' '(' cond=expression ')' parseStatement1 'else' elseCase=parseStmt0NB + ; -parExpression: '(' expression ')' ; +parseStatement1 + : 'if' '(' cond=expression ')' ifCase=parseStatement1 'else' elseCase=parseStatement1 + | parseStatement2 + ; -expression - : primary #PrimaryExpression - | blockInstantiation #BlockInstantiationExpression - | expression '.' ID ('[' expression ']')? #DotExpression - | op=('~' | '!' | '-') expression #UnaryExpression - | expression op=('**' | '*' | '/' | '\\' | '%') expression #BinaryExpression - | expression op=('+' | '-') expression #BinaryExpression - | expression op=('<<' | '>>') expression #BinaryExpression - | expression op=('&' | '^' | '|') expression #BinaryExpression - | expression op=('==' | '!=' | '>' | '<' | '>=' | '<=' | '&&' | '||') expression #BinaryExpression - | expression '?' expression ':' expression #TernaryExpression - ; +parseStatement2 + : 'for' '(' init=parseDeclaration ';' cond=expression ';' step=parseSubstitution ')' body=parseStatement2 + | 'for' '(' parseSubstitution ';' cond=expression ';' step=parseSubstitution ')' body=parseStatement2 + | 'while' '(' cond=expression ')' stmt=parseStatement2 + | 'return' value=expression ';' + | subs=parseSubstitution ';' + | lhe=expression '===' rhe=expression ';' + | parseStatementLog + | 'assert' '(' arg=expression ')' ';' + | lhe=expression ';' + | parseBlock + ; -primary - : '(' expression ')' - | '[' expressionList ']' - | NUMBER - | identifier - | args - | numSequence +parseStatementLog + : 'log' '(' args=logListable? ')' ';' ; -logStmt - : 'log' '(' ((STRING | expression) (',' (STRING | expression))*)? ')' +parseStatment3 + : parseDeclaration ';' + | parseStatement ; -componentDefinition: 'component' ID ; -componentDeclaration - : componentDefinition arrayDimension* (ASSIGNMENT blockInstantiation)? +//functionStmt +// : functionBody #FuncBlockDeclaration +// | identifier SELF_OP ';' #FuncIncDecOperation +// | varDeclaration ';' #FuncVarDeclaration +// | identifierStatment (ASSIGNMENT | ASSIGNMENT_WITH_OP) expression ';' #FuncAssignmentExpression +// | '(' argsWithUnderscore ')' ASSIGNMENT ('(' expressionList ')' | expression) ';' #FuncVariadicAssignment +// | 'if' parExpression functionStmt ('else' functionStmt)? #IfFuncStmt +// | 'while' parExpression functionStmt #WhileFuncStmt +// | 'for' '(' forControl ')' functionStmt #ForFuncStmt +// | 'return' expression ';' #ReturnFuncStmt +// | 'assert' parExpression ';' #AssertFuncStmt +// | logStmt ';' #LogFuncStmt +// ; +// +//templateStmt +// : templateBody +// | identifierStatment SELF_OP ';' +// | varDeclaration ';' +// | signalDeclaration ';' +// | componentDeclaration ';' +// | blockInstantiation ';' +// | identifierStatment ASSIGNMENT expression ';' +// | expression EQ_CONSTRAINT expression ';' +// | identifierStatment (LEFT_CONSTRAINT | ASSIGNMENT_WITH_OP) expression ';' +// | '(' identifierStatment (',' identifierStatment)* ')' LEFT_CONSTRAINT '(' expression (',' expression)* ')' ';' +// | expression RIGHT_CONSTRAINT identifierStatment ';' +// | expression RIGHT_CONSTRAINT '(' identifierStatment (',' identifierStatment)* ')' ';' +// | '_' (ASSIGNMENT | LEFT_CONSTRAINT) (expression | blockInstantiation) ';' +// | (expression | blockInstantiation) RIGHT_CONSTRAINT '_' ';' +// | '(' argsWithUnderscore ')' (ASSIGNMENT | LEFT_CONSTRAINT) ('(' expressionList ')' | blockInstantiation | expression) ';' +// | blockInstantiation RIGHT_CONSTRAINT '(' argsWithUnderscore ')' ';' +// | 'if' parExpression templateStmt ('else' templateStmt)? +// | 'while' parExpression templateStmt +// | 'for' '(' forControl ')' templateStmt +// | 'assert' parExpression ';' +// | logStmt ';' +// ; +// +//forControl: forInit ';' expression ';' forUpdate ; +// +//forInit +// : 'var'? ID (ASSIGNMENT rhsValue)? +// ; +// +//forUpdate: ID (SELF_OP | ((ASSIGNMENT | ASSIGNMENT_WITH_OP) expression)) | SELF_OP ID ; +// +//parExpression: '(' expression ')' ; +// +//expression +// : primary #ExpressionPrimary +// | blockInstantiation #ExpressionBlockInstantiation +// | op=('~' | '!' | '-') expression #ExpressionUnary +// | expression op=('**' | '*' | '/' | '\\' | '%') expression #ExpressionBinary +// | expression op=('+' | '-') expression #ExpressionBinary +// | expression op=('<<' | '>>') expression #ExpressionBinary +// | expression op=('&' | '^' | '|') expression #ExpressionBinary +// | expression op=('==' | '!=' | '>' | '<' | '>=' | '<=' | '&&' | '||') expression #ExpressionBinary +// | expression '?' expression ':' expression #ExpressionTernary +// ; +// +//primary +// : '(' expression ')' +// | '[' expressionList ']' +// | NUMBER +// | identifierStatment +// | simpleIdentifierList +// | numSequence +// ; +// +//logStmt +// : 'log' '(' ((STRING | expression) (',' (STRING | expression))*)? ')' +// ; +// +//rhsValue +// : '(' expressionList ')' +// | expression +// | blockInstantiation +// ; +// +//componentCall +// : '(' expressionList? ')' +// | '(' ID LEFT_CONSTRAINT expression (',' ID LEFT_CONSTRAINT expression)* ')' +// | '(' expression RIGHT_CONSTRAINT ID (',' expression RIGHT_CONSTRAINT ID)* ')' +// ; +// +//blockInstantiation: 'parallel'? ID '(' expressionList? ')' componentCall? ; +// + + +tupleInitiation + : '<==' rhs=expression + | '<--' rhs=expression + | '=' rhs=expression ; -signalDefinition: 'signal' SIGNAL_TYPE? tagList? identifier; +/*////////////////////////////////////////////////////////////// + EXPRESSIONS +//////////////////////////////////////////////////////////////*/ -tagList: '{' args '}' ; +listable + : (expression ',')* expression + ; -signalDeclaration - : signalDefinition (LEFT_CONSTRAINT rhsValue)? - | signalDefinition (',' identifier)* +listableWithInputNames + : (name=ID ops=(ASSIGNMENT | LEFT_ASSIGNMENT | LEFT_CONSTRAINT) expression ',')* name=ID ops=(ASSIGNMENT | LEFT_ASSIGNMENT | LEFT_CONSTRAINT) expression ; -varDefinition - : 'var' identifier - | 'var' '(' identifier (',' identifier)* ')' +listableAnon + : listableWithInputNames + | listable ; -varDeclaration - : varDefinition (ASSIGNMENT rhsValue)? - | varDefinition (',' identifier)* +parseLogArgument + : expression + | STRING ; -rhsValue - : '(' expressionList ')' - | expression - | blockInstantiation +logListable + : (parseLogArgument ',')* parseLogArgument ; -componentCall - : '(' expressionList? ')' - | '(' ID LEFT_CONSTRAINT expression (',' ID LEFT_CONSTRAINT expression)* ')' - | '(' expression RIGHT_CONSTRAINT ID (',' expression RIGHT_CONSTRAINT ID)* ')' +expression + : primary + | op=(NOT | BNOT | SUB) expression + | expression POW expression + | expression op=(MUL | DIV | QUO | MOD) expression + | expression op=(ADD | SUB) expression + | expression op=(SHL | SHR) expression + | expression BAND expression + | expression BXOR expression + | expression BOR expression + | expression op=(EQ | NEQ | LT | GT | LE | GE) expression + | expression AND expression + | expression OR expression + | cond=expression '?' if_true=expression ':' if_false=expression + | 'parallel' expression ; -blockInstantiation: 'parallel'? ID '(' expressionList? ')' componentCall? ; +// function call, array inline, anonymous component call +// Literal, parentheses +primary + : identifierStatment + | '_' + | NUMBER + | ID '(' listable? ')' '(' listableAnon? ')' + | ID '(' listable? ')' + | '[' listable ']' + | '(' listable ')' + ; + +/*////////////////////////////////////////////////////////////// + IDENTIFIER +//////////////////////////////////////////////////////////////*/ + +regularIdentifierAssignment + : identifier '=' rhs=expression + ; -expressionList: expression (',' expression)* ; +constraintIdentifierAssignment + : identifier '<==' rhs=expression + ; + +simpleIdentifierAssignment + : identifier '<--' rhs=expression + ; + +varIdentifierAssignment + : identifier + | regularIdentifierAssignment + ; + +signalIdentifierAssignment + : identifier + | simpleIdentifierAssignment + | constraintIdentifierAssignment + ; + +identifierStatment + : ID idetifierAccess* + ; identifier - : ID arrayDimension* ('.' ID)? arrayDimension* + : ID arrayDimension* + ; + +identifierList + : (identifier ',')* identifier ; -arrayDimension: '[' expression ']' ; +simpleIdentifierList + : (ID ',')* ID + ; -args: ID (',' ID)* ; +idetifierAccess + : arrayDimension + | identifierReferance + ; -argsWithUnderscore: ('_' | ID) (',' ('_' | ID) )* ; +arrayDimension + : '[' expression ']' + ; -numSequence: NUMBER (',' NUMBER)* ; \ No newline at end of file +identifierReferance + : '.' ID + ; \ No newline at end of file diff --git a/maci b/maci new file mode 160000 index 0000000..05e621b --- /dev/null +++ b/maci @@ -0,0 +1 @@ +Subproject commit 05e621b010cb7113859577f16c7d2d27435a09f4 diff --git a/passport-zk-circuits b/passport-zk-circuits index 15c7217..5449f41 160000 --- a/passport-zk-circuits +++ b/passport-zk-circuits @@ -1 +1 @@ -Subproject commit 15c721785b56e69e394475fa7382b8b625e05a0f +Subproject commit 5449f41c4ec5989b883f50230f48087928bcda29 From cb46f6ff8ebb04ad4d738d069293ac54a755e735 Mon Sep 17 00:00:00 2001 From: Kyryl R Date: Fri, 25 Oct 2024 22:59:21 +0300 Subject: [PATCH 02/10] Completed refactoring --- grammar/CircomParser.g4 | 333 +++++++++++----------------------------- 1 file changed, 93 insertions(+), 240 deletions(-) diff --git a/grammar/CircomParser.g4 b/grammar/CircomParser.g4 index a5561f8..d6e484b 100644 --- a/grammar/CircomParser.g4 +++ b/grammar/CircomParser.g4 @@ -18,9 +18,9 @@ signalHeader busHeader : ID wireType=SIGNAL_TYPE? tagDefinition? - | ID '(' parameters=listable? ')' wireType=SIGNAL_TYPE? tagDefinition? + | ID '(' parameters=expressionList? ')' wireType=SIGNAL_TYPE? tagDefinition? | wireType=SIGNAL_TYPE ID tagDefinition? - | wireType=SIGNAL_TYPE ID '(' parameters=listable? ')' tagDefinition? + | wireType=SIGNAL_TYPE ID '(' parameters=expressionList? ')' tagDefinition? ; /*////////////////////////////////////////////////////////////// @@ -44,15 +44,15 @@ blockDefiniton ; functionDefinition - : 'function' name=ID '(' argNames=simpleIdentifierList? ')' parseBlock + : 'function' name=ID '(' argNames=simpleIdentifierList? ')' body ; templateDefinition - : 'template' customGate='custom'? 'parallel'? name=ID '(' argNames=simpleIdentifierList? ')' parseBlock + : 'template' customGate='custom'? 'parallel'? name=ID '(' argNames=simpleIdentifierList? ')' body ; busDefinition - : 'bus' name=ID '(' argNames=simpleIdentifierList? ')' parseBlock + : 'bus' name=ID '(' argNames=simpleIdentifierList? ')' body ; publicInputsDefinition @@ -63,315 +63,168 @@ tagDefinition : '{' values=simpleIdentifierList '}' ; +logDefinition: 'log' '(' logArgs=expressionOrStringList? ')' ; + +assertDefinition: 'assert' '(' assertArgs=expression ')' ; + /*////////////////////////////////////////////////////////////// DECLARATIONS //////////////////////////////////////////////////////////////*/ +declarations + : varDeclaration + | signalDeclaration + | componentDeclaration + | busDeclaration + ; + varDeclaration - : 'var' '(' identifierList ')' tupleInitiation? - | 'var' (varIdentifierAssignment ',')* varIdentifierAssignment + : 'var' '(' identifierList ')' assignmentExpression? + | 'var' varIdentifierList ; signalDeclaration - : signalHeader '(' identifierList ')' tupleInitiation? - | signalHeader (signalIdentifierAssignment ',')* signalIdentifierAssignment + : signalHeader '(' identifierList ')' assignmentExpression? + | signalHeader signalIdentifierList ; componentDeclaration - : 'component' '(' identifierList ')' tupleInitiation? - | 'component' (varIdentifierAssignment ',')* varIdentifierAssignment + : 'component' '(' identifierList ')' assignmentExpression? + | 'component' varIdentifierList ; busDeclaration - : busHeader (signalIdentifierAssignment ',')* signalIdentifierAssignment + : busHeader signalIdentifierList ; componentMainDeclaration - : 'component' 'main' publicInputsDefinition? '=' ID '(' argValues=listable? ')' ';' - ; - - -parseDeclaration - : varDeclaration - | signalDeclaration - | componentDeclaration - | busDeclaration + : 'component' 'main' publicInputsDefinition? '=' ID '(' argValues=expressionList? ')' ';' ; -/*////////////////////////////////////////////////////////////// - BODIES -//////////////////////////////////////////////////////////////*/ - -//templateBody -// : '{' templateStmt* '}' -// ; -// -//busBody -// : '{' '}' -// ; -// -//functionBody -// : '{' functionStmt* '}' -// ; - /*////////////////////////////////////////////////////////////// STATEMENTS //////////////////////////////////////////////////////////////*/ -parseSubstitution - : expression ops=(ASSIGNMENT | LEFT_ASSIGNMENT | LEFT_CONSTRAINT) rhe=expression - | lhe=expression '-->' variable=expression - | lhe=expression '==>' variable=expression - | identifierStatment ASSIGNMENT_WITH_OP rhe=expression - | identifierStatment SELF_OP - | SELF_OP identifierStatment - ; - -parseBlock: '{' stmts=parseStatment3* '}'; - -parseStatement: parseStatement0; - -parseStatement0 - : parseStmt0NB - | parseStatement1 - ; +body: '{' stmts=statments* '}'; -parseStmt0NB - : 'if' '(' cond=expression ')' parseStmt0NB - | 'if' '(' cond=expression ')' parseStatement1 - | 'if' '(' cond=expression ')' parseStatement1 'else' elseCase=parseStmt0NB +statments + : declarations ';' + | ifStatments + | regularStatmetns + | logDefinition ';' + | assertDefinition ';' ; -parseStatement1 - : 'if' '(' cond=expression ')' ifCase=parseStatement1 'else' elseCase=parseStatement1 - | parseStatement2 +ifStatments + : 'if' '(' cond=expression ')' ifStatments + | 'if' '(' cond=expression ')' regularStatmetns + | 'if' '(' cond=expression ')' regularStatmetns 'else' ifStatments + | 'if' '(' cond=expression ')' regularStatmetns 'else' regularStatmetns ; -parseStatement2 - : 'for' '(' init=parseDeclaration ';' cond=expression ';' step=parseSubstitution ')' body=parseStatement2 - | 'for' '(' parseSubstitution ';' cond=expression ';' step=parseSubstitution ')' body=parseStatement2 - | 'while' '(' cond=expression ')' stmt=parseStatement2 +regularStatmetns + : body + | expression ';' + | substitutions ';' + | lhs=expression '===' rhs=expression ';' + | 'for' '(' declarations ';' cond=expression ';' step=substitutions ')' forBody=regularStatmetns + | 'for' '(' substitutions ';' cond=expression ';' step=substitutions ')' forBody=regularStatmetns + | 'while' '(' cond=expression ')' stmt=regularStatmetns | 'return' value=expression ';' - | subs=parseSubstitution ';' - | lhe=expression '===' rhe=expression ';' - | parseStatementLog - | 'assert' '(' arg=expression ')' ';' - | lhe=expression ';' - | parseBlock - ; - -parseStatementLog - : 'log' '(' args=logListable? ')' ';' - ; - -parseStatment3 - : parseDeclaration ';' - | parseStatement ; - -//functionStmt -// : functionBody #FuncBlockDeclaration -// | identifier SELF_OP ';' #FuncIncDecOperation -// | varDeclaration ';' #FuncVarDeclaration -// | identifierStatment (ASSIGNMENT | ASSIGNMENT_WITH_OP) expression ';' #FuncAssignmentExpression -// | '(' argsWithUnderscore ')' ASSIGNMENT ('(' expressionList ')' | expression) ';' #FuncVariadicAssignment -// | 'if' parExpression functionStmt ('else' functionStmt)? #IfFuncStmt -// | 'while' parExpression functionStmt #WhileFuncStmt -// | 'for' '(' forControl ')' functionStmt #ForFuncStmt -// | 'return' expression ';' #ReturnFuncStmt -// | 'assert' parExpression ';' #AssertFuncStmt -// | logStmt ';' #LogFuncStmt -// ; -// -//templateStmt -// : templateBody -// | identifierStatment SELF_OP ';' -// | varDeclaration ';' -// | signalDeclaration ';' -// | componentDeclaration ';' -// | blockInstantiation ';' -// | identifierStatment ASSIGNMENT expression ';' -// | expression EQ_CONSTRAINT expression ';' -// | identifierStatment (LEFT_CONSTRAINT | ASSIGNMENT_WITH_OP) expression ';' -// | '(' identifierStatment (',' identifierStatment)* ')' LEFT_CONSTRAINT '(' expression (',' expression)* ')' ';' -// | expression RIGHT_CONSTRAINT identifierStatment ';' -// | expression RIGHT_CONSTRAINT '(' identifierStatment (',' identifierStatment)* ')' ';' -// | '_' (ASSIGNMENT | LEFT_CONSTRAINT) (expression | blockInstantiation) ';' -// | (expression | blockInstantiation) RIGHT_CONSTRAINT '_' ';' -// | '(' argsWithUnderscore ')' (ASSIGNMENT | LEFT_CONSTRAINT) ('(' expressionList ')' | blockInstantiation | expression) ';' -// | blockInstantiation RIGHT_CONSTRAINT '(' argsWithUnderscore ')' ';' -// | 'if' parExpression templateStmt ('else' templateStmt)? -// | 'while' parExpression templateStmt -// | 'for' '(' forControl ')' templateStmt -// | 'assert' parExpression ';' -// | logStmt ';' -// ; -// -//forControl: forInit ';' expression ';' forUpdate ; -// -//forInit -// : 'var'? ID (ASSIGNMENT rhsValue)? -// ; -// -//forUpdate: ID (SELF_OP | ((ASSIGNMENT | ASSIGNMENT_WITH_OP) expression)) | SELF_OP ID ; -// -//parExpression: '(' expression ')' ; -// -//expression -// : primary #ExpressionPrimary -// | blockInstantiation #ExpressionBlockInstantiation -// | op=('~' | '!' | '-') expression #ExpressionUnary -// | expression op=('**' | '*' | '/' | '\\' | '%') expression #ExpressionBinary -// | expression op=('+' | '-') expression #ExpressionBinary -// | expression op=('<<' | '>>') expression #ExpressionBinary -// | expression op=('&' | '^' | '|') expression #ExpressionBinary -// | expression op=('==' | '!=' | '>' | '<' | '>=' | '<=' | '&&' | '||') expression #ExpressionBinary -// | expression '?' expression ':' expression #ExpressionTernary -// ; -// -//primary -// : '(' expression ')' -// | '[' expressionList ']' -// | NUMBER -// | identifierStatment -// | simpleIdentifierList -// | numSequence -// ; -// -//logStmt -// : 'log' '(' ((STRING | expression) (',' (STRING | expression))*)? ')' -// ; -// -//rhsValue -// : '(' expressionList ')' -// | expression -// | blockInstantiation -// ; -// -//componentCall -// : '(' expressionList? ')' -// | '(' ID LEFT_CONSTRAINT expression (',' ID LEFT_CONSTRAINT expression)* ')' -// | '(' expression RIGHT_CONSTRAINT ID (',' expression RIGHT_CONSTRAINT ID)* ')' -// ; -// -//blockInstantiation: 'parallel'? ID '(' expressionList? ')' componentCall? ; -// - - -tupleInitiation - : '<==' rhs=expression - | '<--' rhs=expression - | '=' rhs=expression +substitutions + : lhs=expression op=(ASSIGNMENT | LEFT_ASSIGNMENT | LEFT_CONSTRAINT) rhs=expression + | lhs=expression op='-->' variable=expression + | lhs=expression op='==>' variable=expression + | identifierStatment op=ASSIGNMENT_WITH_OP rhs=expression + | identifierStatment SELF_OP + | SELF_OP identifierStatment ; /*////////////////////////////////////////////////////////////// EXPRESSIONS //////////////////////////////////////////////////////////////*/ -listable - : (expression ',')* expression - ; +expressionList: (expression ',')* expression ; -listableWithInputNames +expressionListWithNames : (name=ID ops=(ASSIGNMENT | LEFT_ASSIGNMENT | LEFT_CONSTRAINT) expression ',')* name=ID ops=(ASSIGNMENT | LEFT_ASSIGNMENT | LEFT_CONSTRAINT) expression ; -listableAnon - : listableWithInputNames - | listable - ; - -parseLogArgument - : expression - | STRING - ; - -logListable - : (parseLogArgument ',')* parseLogArgument - ; - expression - : primary + : primaryExpression | op=(NOT | BNOT | SUB) expression - | expression POW expression + | expression op=POW expression | expression op=(MUL | DIV | QUO | MOD) expression | expression op=(ADD | SUB) expression | expression op=(SHL | SHR) expression - | expression BAND expression - | expression BXOR expression - | expression BOR expression + | expression op=BAND expression + | expression op=BXOR expression + | expression op=BOR expression | expression op=(EQ | NEQ | LT | GT | LE | GE) expression - | expression AND expression - | expression OR expression - | cond=expression '?' if_true=expression ':' if_false=expression + | expression op=AND expression + | expression op=OR expression + | cond=expression '?' ifTrue=expression ':' ifFalse=expression | 'parallel' expression ; -// function call, array inline, anonymous component call -// Literal, parentheses -primary +// Literal, parentheses, function call, array inline, anonymous component call +primaryExpression : identifierStatment | '_' | NUMBER - | ID '(' listable? ')' '(' listableAnon? ')' - | ID '(' listable? ')' - | '[' listable ']' - | '(' listable ')' + | '(' expressionList ')' + | '[' expressionList ']' + | ID '(' expressionList? ')' + | ID '(' expressionList? ')' '(' (expressionList | expressionListWithNames)? ')' + ; + +assignmentExpression + : '<==' rhs=expression + | '<--' rhs=expression + | '=' rhs=expression ; /*////////////////////////////////////////////////////////////// IDENTIFIER //////////////////////////////////////////////////////////////*/ -regularIdentifierAssignment - : identifier '=' rhs=expression - ; - -constraintIdentifierAssignment - : identifier '<==' rhs=expression - ; +varIdentifier: identifier ('=' rhs=expression)? ; -simpleIdentifierAssignment - : identifier '<--' rhs=expression - ; +varIdentifierList: (varIdentifier ',')* varIdentifier ; -varIdentifierAssignment +signalIdentifier : identifier - | regularIdentifierAssignment + | identifier '<--' rhs=expression + | identifier '<==' rhs=expression ; -signalIdentifierAssignment - : identifier - | simpleIdentifierAssignment - | constraintIdentifierAssignment - ; +signalIdentifierList: (signalIdentifier ',')* signalIdentifier ; -identifierStatment - : ID idetifierAccess* - ; +identifierStatment: ID idetifierAccess* ; -identifier - : ID arrayDimension* - ; +identifier: ID arrayDimension* ; -identifierList - : (identifier ',')* identifier - ; +identifierList: (identifier ',')* identifier ; -simpleIdentifierList - : (ID ',')* ID - ; +simpleIdentifierList: (ID ',')* ID ; idetifierAccess : arrayDimension | identifierReferance ; -arrayDimension - : '[' expression ']' - ; +arrayDimension: '[' expression ']' ; identifierReferance : '.' ID - ; \ No newline at end of file + ; + +/*////////////////////////////////////////////////////////////// + PRIMITIVES +//////////////////////////////////////////////////////////////*/ + +expressionOrString: expression | STRING ; + +expressionOrStringList: (expressionOrString ',')* expressionOrString ; From 4322ae9cce3df0290f3eb4a6640fd8de8bf023c3 Mon Sep 17 00:00:00 2001 From: Kyryl R Date: Fri, 25 Oct 2024 23:03:34 +0300 Subject: [PATCH 03/10] Minor fixes --- grammar/CircomParser.g4 | 33 ++++++++++----------------------- 1 file changed, 10 insertions(+), 23 deletions(-) diff --git a/grammar/CircomParser.g4 b/grammar/CircomParser.g4 index d6e484b..3601649 100644 --- a/grammar/CircomParser.g4 +++ b/grammar/CircomParser.g4 @@ -33,9 +33,7 @@ pragmaDefinition | 'pragma' 'custom_templates' ';' #PragmaCustomTemplates ; -includeDefinition - : 'include' path=STRING ';' - ; +includeDefinition: 'include' path=STRING ';' ; blockDefiniton : functionDefinition @@ -43,25 +41,17 @@ blockDefiniton | busDefinition ; -functionDefinition - : 'function' name=ID '(' argNames=simpleIdentifierList? ')' body - ; +functionDefinition: 'function' name=ID '(' argNames=simpleIdentifierList? ')' body ; templateDefinition : 'template' customGate='custom'? 'parallel'? name=ID '(' argNames=simpleIdentifierList? ')' body ; -busDefinition - : 'bus' name=ID '(' argNames=simpleIdentifierList? ')' body - ; +busDefinition: 'bus' name=ID '(' argNames=simpleIdentifierList? ')' body ; -publicInputsDefinition - : '{' 'public' '[' publicInputs=simpleIdentifierList ']' '}' - ; +publicInputsDefinition: '{' 'public' '[' publicInputs=simpleIdentifierList ']' '}' ; -tagDefinition - : '{' values=simpleIdentifierList '}' - ; +tagDefinition: '{' values=simpleIdentifierList '}' ; logDefinition: 'log' '(' logArgs=expressionOrStringList? ')' ; @@ -93,9 +83,7 @@ componentDeclaration | 'component' varIdentifierList ; -busDeclaration - : busHeader signalIdentifierList - ; +busDeclaration: busHeader signalIdentifierList ; componentMainDeclaration : 'component' 'main' publicInputsDefinition? '=' ID '(' argValues=expressionList? ')' ';' @@ -105,7 +93,7 @@ componentMainDeclaration STATEMENTS //////////////////////////////////////////////////////////////*/ -body: '{' stmts=statments* '}'; +body: '{' statments* '}'; statments : declarations ';' @@ -149,7 +137,8 @@ substitutions expressionList: (expression ',')* expression ; expressionListWithNames - : (name=ID ops=(ASSIGNMENT | LEFT_ASSIGNMENT | LEFT_CONSTRAINT) expression ',')* name=ID ops=(ASSIGNMENT | LEFT_ASSIGNMENT | LEFT_CONSTRAINT) expression + : (name=ID ops=(ASSIGNMENT | LEFT_ASSIGNMENT | LEFT_CONSTRAINT) expression ',')* + name=ID ops=(ASSIGNMENT | LEFT_ASSIGNMENT | LEFT_CONSTRAINT) expression ; expression @@ -217,9 +206,7 @@ idetifierAccess arrayDimension: '[' expression ']' ; -identifierReferance - : '.' ID - ; +identifierReferance: '.' ID ; /*////////////////////////////////////////////////////////////// PRIMITIVES From e8627d04c0ae4446deaa3cbde8d093110ffc5fbc Mon Sep 17 00:00:00 2001 From: Kyryl R Date: Fri, 25 Oct 2024 23:38:38 +0300 Subject: [PATCH 04/10] Added annotations for visitor --- grammar/CircomParser.g4 | 60 ++++++++++++++++++++++------------------- 1 file changed, 32 insertions(+), 28 deletions(-) diff --git a/grammar/CircomParser.g4 b/grammar/CircomParser.g4 index 3601649..0321439 100644 --- a/grammar/CircomParser.g4 +++ b/grammar/CircomParser.g4 @@ -104,30 +104,34 @@ statments ; ifStatments - : 'if' '(' cond=expression ')' ifStatments - | 'if' '(' cond=expression ')' regularStatmetns - | 'if' '(' cond=expression ')' regularStatmetns 'else' ifStatments - | 'if' '(' cond=expression ')' regularStatmetns 'else' regularStatmetns + : 'if' '(' cond=expression ')' ifStatments #IfWithFollowUpIf + | 'if' '(' cond=expression ')' regularStatmetns #IfRegular + | 'if' '(' cond=expression ')' regularStatmetns 'else' ifStatments #IfRegularElseWithFollowUpIf + | 'if' '(' cond=expression ')' regularStatmetns 'else' regularStatmetns #IfRegularElseRegular ; regularStatmetns - : body - | expression ';' - | substitutions ';' - | lhs=expression '===' rhs=expression ';' - | 'for' '(' declarations ';' cond=expression ';' step=substitutions ')' forBody=regularStatmetns - | 'for' '(' substitutions ';' cond=expression ';' step=substitutions ')' forBody=regularStatmetns - | 'while' '(' cond=expression ')' stmt=regularStatmetns - | 'return' value=expression ';' + : body #RStatmentBody + | expression ';' #RStatmentExpression + | substitutions ';' #RStatmentSucstitutions + | cycleStatments #RStatmentCycles + | lhs=expression '===' rhs=expression ';' #RStatmentEqConstraint + | 'return' value=expression ';' #RStatmentReturn + ; + +cycleStatments + : 'for' '(' declarations ';' cond=expression ';' step=substitutions ')' forBody=regularStatmetns #CycleForWithDeclaration + | 'for' '(' substitutions ';' cond=expression ';' step=substitutions ')' forBody=regularStatmetns #CycleForWithoutDeclaration + | 'while' '(' cond=expression ')' stmt=regularStatmetns #CycleWhile ; substitutions - : lhs=expression op=(ASSIGNMENT | LEFT_ASSIGNMENT | LEFT_CONSTRAINT) rhs=expression - | lhs=expression op='-->' variable=expression - | lhs=expression op='==>' variable=expression - | identifierStatment op=ASSIGNMENT_WITH_OP rhs=expression - | identifierStatment SELF_OP - | SELF_OP identifierStatment + : lhs=expression op=(ASSIGNMENT | LEFT_ASSIGNMENT | LEFT_CONSTRAINT) rhs=expression #SubsLeftAssignmet + | lhs=expression op='-->' variable=expression #SubsRightSimpleAssignmet + | lhs=expression op='==>' variable=expression #SubsRightConstrAssignmet + | identifierStatment op=ASSIGNMENT_WITH_OP rhs=expression #SubsAssignmetWithOperation + | identifierStatment SELF_OP #SubsIcnDecOperation + | SELF_OP identifierStatment #SubsInvalidOperation ; /*////////////////////////////////////////////////////////////// @@ -160,19 +164,19 @@ expression // Literal, parentheses, function call, array inline, anonymous component call primaryExpression - : identifierStatment - | '_' - | NUMBER - | '(' expressionList ')' - | '[' expressionList ']' - | ID '(' expressionList? ')' - | ID '(' expressionList? ')' '(' (expressionList | expressionListWithNames)? ')' + : identifierStatment #PIdentifierStatment + | '_' #PUnderscore + | NUMBER #PNumber + | '(' expressionList ')' #PParentheses + | '[' expressionList ']' #PArray + | ID '(' expressionList? ')' #PCall + | ID '(' expressionList? ')' '(' (expressionList | expressionListWithNames)? ')' #PAnonymousCall ; assignmentExpression - : '<==' rhs=expression - | '<--' rhs=expression - | '=' rhs=expression + : '<==' rhs=expression #AssignExprConstraint + | '<--' rhs=expression #AssignExprSimple + | '=' rhs=expression #AssignExprRegular ; /*////////////////////////////////////////////////////////////// From 0d91961695be09ad1fc5281b0d548ac96ece7f1f Mon Sep 17 00:00:00 2001 From: Kyryl R Date: Fri, 25 Oct 2024 23:41:03 +0300 Subject: [PATCH 05/10] Updated submodules --- maci | 2 +- passport-zk-circuits | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/maci b/maci index 05e621b..bcae53f 160000 --- a/maci +++ b/maci @@ -1 +1 @@ -Subproject commit 05e621b010cb7113859577f16c7d2d27435a09f4 +Subproject commit bcae53f877d57715b38b03ec1d110c8bb0ed6110 diff --git a/passport-zk-circuits b/passport-zk-circuits index 5449f41..6ad43aa 160000 --- a/passport-zk-circuits +++ b/passport-zk-circuits @@ -1 +1 @@ -Subproject commit 5449f41c4ec5989b883f50230f48087928bcda29 +Subproject commit 6ad43aa339c8593d7d830270280ae9de2cb79ad0 From 6604e36e6a24487ab72381e0ab55c4ac229e8057 Mon Sep 17 00:00:00 2001 From: Kyryl R Date: Sun, 27 Oct 2024 16:36:17 +0200 Subject: [PATCH 06/10] Fixed typos --- grammar/CircomParser.g4 | 32 ++++++++++++++++---------------- 1 file changed, 16 insertions(+), 16 deletions(-) diff --git a/grammar/CircomParser.g4 b/grammar/CircomParser.g4 index 0321439..5e47eb8 100644 --- a/grammar/CircomParser.g4 +++ b/grammar/CircomParser.g4 @@ -33,7 +33,7 @@ pragmaDefinition | 'pragma' 'custom_templates' ';' #PragmaCustomTemplates ; -includeDefinition: 'include' path=STRING ';' ; +includeDefinition: 'include' STRING ';' ; blockDefiniton : functionDefinition @@ -41,13 +41,13 @@ blockDefiniton | busDefinition ; -functionDefinition: 'function' name=ID '(' argNames=simpleIdentifierList? ')' body ; +functionDefinition: 'function' ID '(' argNames=simpleIdentifierList? ')' body ; templateDefinition - : 'template' customGate='custom'? 'parallel'? name=ID '(' argNames=simpleIdentifierList? ')' body + : 'template' 'custom'? 'parallel'? ID '(' argNames=simpleIdentifierList? ')' body ; -busDefinition: 'bus' name=ID '(' argNames=simpleIdentifierList? ')' body ; +busDefinition: 'bus' ID '(' argNames=simpleIdentifierList? ')' body ; publicInputsDefinition: '{' 'public' '[' publicInputs=simpleIdentifierList ']' '}' ; @@ -93,24 +93,24 @@ componentMainDeclaration STATEMENTS //////////////////////////////////////////////////////////////*/ -body: '{' statments* '}'; +body: '{' statements* '}'; -statments +statements : declarations ';' | ifStatments - | regularStatmetns + | regularStatements | logDefinition ';' | assertDefinition ';' ; ifStatments : 'if' '(' cond=expression ')' ifStatments #IfWithFollowUpIf - | 'if' '(' cond=expression ')' regularStatmetns #IfRegular - | 'if' '(' cond=expression ')' regularStatmetns 'else' ifStatments #IfRegularElseWithFollowUpIf - | 'if' '(' cond=expression ')' regularStatmetns 'else' regularStatmetns #IfRegularElseRegular + | 'if' '(' cond=expression ')' regularStatements #IfRegular + | 'if' '(' cond=expression ')' regularStatements 'else' ifStatments #IfRegularElseWithFollowUpIf + | 'if' '(' cond=expression ')' regularStatements 'else' regularStatements #IfRegularElseRegular ; -regularStatmetns +regularStatements : body #RStatmentBody | expression ';' #RStatmentExpression | substitutions ';' #RStatmentSucstitutions @@ -120,9 +120,9 @@ regularStatmetns ; cycleStatments - : 'for' '(' declarations ';' cond=expression ';' step=substitutions ')' forBody=regularStatmetns #CycleForWithDeclaration - | 'for' '(' substitutions ';' cond=expression ';' step=substitutions ')' forBody=regularStatmetns #CycleForWithoutDeclaration - | 'while' '(' cond=expression ')' stmt=regularStatmetns #CycleWhile + : 'for' '(' declarations ';' cond=expression ';' step=substitutions ')' forBody=regularStatements #CycleForWithDeclaration + | 'for' '(' substitutions ';' cond=expression ';' step=substitutions ')' forBody=regularStatements #CycleForWithoutDeclaration + | 'while' '(' cond=expression ')' stmt=regularStatements #CycleWhile ; substitutions @@ -141,8 +141,8 @@ substitutions expressionList: (expression ',')* expression ; expressionListWithNames - : (name=ID ops=(ASSIGNMENT | LEFT_ASSIGNMENT | LEFT_CONSTRAINT) expression ',')* - name=ID ops=(ASSIGNMENT | LEFT_ASSIGNMENT | LEFT_CONSTRAINT) expression + : (ID ops=(ASSIGNMENT | LEFT_ASSIGNMENT | LEFT_CONSTRAINT) expression ',')* + ID ops=(ASSIGNMENT | LEFT_ASSIGNMENT | LEFT_CONSTRAINT) expression ; expression From e9071e1fbd910be073cf43837f85038268b4ef52 Mon Sep 17 00:00:00 2001 From: Kyryl R Date: Sun, 27 Oct 2024 16:42:26 +0200 Subject: [PATCH 07/10] Added test cases for bus structure --- data/Example3.circom | 74 ++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 74 insertions(+) create mode 100644 data/Example3.circom diff --git a/data/Example3.circom b/data/Example3.circom new file mode 100644 index 0000000..509389b --- /dev/null +++ b/data/Example3.circom @@ -0,0 +1,74 @@ +bus B1(){ + signal x; +} + +bus B2() { + signal x; +} + +template B1toB2(){ + input B1() b1; + output B2() b2; + b2 <== b1; +} + +bus Film() { + signal title[50]; + signal director[50]; + signal year; +} + +bus Date() { + signal day; + signal month; + signal year; +} + +bus Person() { + signal name[50]; + Film() films[10]; + Date() birthday; +} + +bus Line(dim){ + PointN(dim) start; + PointN(dim) end; +} + +bus Figure(num_sides, dim){ + Line(dim) side[num_sides]; +} + +bus Triangle2D(){ + Figure(3,2) {well_defined} triangle; +} + +bus Square3D(){ + Figure(4,3) {well_defined} square; +} + +template well_defined_figure(num_sides, dimension){ + input Figure(num_sides,dimension) t; + output Figure(num_sides,dimension) {well_defined} correct_t; + var all_equals = 0; + var isequal = 0; + for(var i = 0; i < num_sides; i=i+1){ + for(var j = 0; j < dimension; j=j+1){ + isequal = IsEqual()([t.side[i].end.x[j],t.side[(i+1)%num_sides].start.x[j]]); + all_equals += isequal; + } + } + all_equals === num_sides; + correct_t <== t; +} + +template Edwards2Montgomery () { + input Point() { edwards_point } in ; + output Point() { montgomery_point } out ; + + out.x <-- (1 + in.y ) / (1 - in.y ) ; + out.y <-- out.x / in.x ; + + out.x * (1 - in.y ) === (1 + in.y ) ; + out.y * in.x === out.x ; +} \ No newline at end of file From 2812f29eb6cadc7301be654265dd80fc997e1e44 Mon Sep 17 00:00:00 2001 From: Kyryl R Date: Sun, 27 Oct 2024 16:45:20 +0200 Subject: [PATCH 08/10] Fixed typo --- grammar/CircomParser.g4 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/grammar/CircomParser.g4 b/grammar/CircomParser.g4 index 5e47eb8..8d0e30a 100644 --- a/grammar/CircomParser.g4 +++ b/grammar/CircomParser.g4 @@ -131,7 +131,7 @@ substitutions | lhs=expression op='==>' variable=expression #SubsRightConstrAssignmet | identifierStatment op=ASSIGNMENT_WITH_OP rhs=expression #SubsAssignmetWithOperation | identifierStatment SELF_OP #SubsIcnDecOperation - | SELF_OP identifierStatment #SubsInvalidOperation + | SELF_OP identifierStatment #SubsInvalidIcnDecOperation ; /*////////////////////////////////////////////////////////////// From bd2c7342515df7c4b8668f8ee0fd54d5bb030350 Mon Sep 17 00:00:00 2001 From: Kyryl R Date: Wed, 30 Oct 2024 21:09:13 +0200 Subject: [PATCH 09/10] Fixed typos --- grammar/CircomParser.g4 | 32 ++++++++++++++++---------------- 1 file changed, 16 insertions(+), 16 deletions(-) diff --git a/grammar/CircomParser.g4 b/grammar/CircomParser.g4 index 8d0e30a..9de13f4 100644 --- a/grammar/CircomParser.g4 +++ b/grammar/CircomParser.g4 @@ -97,29 +97,29 @@ body: '{' statements* '}'; statements : declarations ';' - | ifStatments + | ifStatements | regularStatements | logDefinition ';' | assertDefinition ';' ; -ifStatments - : 'if' '(' cond=expression ')' ifStatments #IfWithFollowUpIf +ifStatements + : 'if' '(' cond=expression ')' ifStatements #IfWithFollowUpIf | 'if' '(' cond=expression ')' regularStatements #IfRegular - | 'if' '(' cond=expression ')' regularStatements 'else' ifStatments #IfRegularElseWithFollowUpIf + | 'if' '(' cond=expression ')' regularStatements 'else' ifStatements #IfRegularElseWithFollowUpIf | 'if' '(' cond=expression ')' regularStatements 'else' regularStatements #IfRegularElseRegular ; regularStatements - : body #RStatmentBody - | expression ';' #RStatmentExpression - | substitutions ';' #RStatmentSucstitutions - | cycleStatments #RStatmentCycles - | lhs=expression '===' rhs=expression ';' #RStatmentEqConstraint - | 'return' value=expression ';' #RStatmentReturn + : body #RStatementBody + | expression ';' #RStatementExpression + | substitutions ';' #RStatementSucstitutions + | cycleStatements #RStatementCycles + | lhs=expression '===' rhs=expression ';' #RStatementEqConstraint + | 'return' value=expression ';' #RStatementReturn ; -cycleStatments +cycleStatements : 'for' '(' declarations ';' cond=expression ';' step=substitutions ')' forBody=regularStatements #CycleForWithDeclaration | 'for' '(' substitutions ';' cond=expression ';' step=substitutions ')' forBody=regularStatements #CycleForWithoutDeclaration | 'while' '(' cond=expression ')' stmt=regularStatements #CycleWhile @@ -129,9 +129,9 @@ substitutions : lhs=expression op=(ASSIGNMENT | LEFT_ASSIGNMENT | LEFT_CONSTRAINT) rhs=expression #SubsLeftAssignmet | lhs=expression op='-->' variable=expression #SubsRightSimpleAssignmet | lhs=expression op='==>' variable=expression #SubsRightConstrAssignmet - | identifierStatment op=ASSIGNMENT_WITH_OP rhs=expression #SubsAssignmetWithOperation - | identifierStatment SELF_OP #SubsIcnDecOperation - | SELF_OP identifierStatment #SubsInvalidIcnDecOperation + | identifierStatement op=ASSIGNMENT_WITH_OP rhs=expression #SubsAssignmetWithOperation + | identifierStatement SELF_OP #SubsIcnDecOperation + | SELF_OP identifierStatement #SubsInvalidIcnDecOperation ; /*////////////////////////////////////////////////////////////// @@ -164,7 +164,7 @@ expression // Literal, parentheses, function call, array inline, anonymous component call primaryExpression - : identifierStatment #PIdentifierStatment + : identifierStatement #PIdentifierStatement | '_' #PUnderscore | NUMBER #PNumber | '(' expressionList ')' #PParentheses @@ -195,7 +195,7 @@ signalIdentifier signalIdentifierList: (signalIdentifier ',')* signalIdentifier ; -identifierStatment: ID idetifierAccess* ; +identifierStatement: ID idetifierAccess* ; identifier: ID arrayDimension* ; From f7fddc81c76ee5166036a65acee71606d8cfcdf9 Mon Sep 17 00:00:00 2001 From: Kyryl R Date: Thu, 31 Oct 2024 14:32:30 +0200 Subject: [PATCH 10/10] Fixed typos --- grammar/CircomParser.g4 | 14 +++++++------- 1 file changed, 7 insertions(+), 7 deletions(-) diff --git a/grammar/CircomParser.g4 b/grammar/CircomParser.g4 index 9de13f4..77aa0e5 100644 --- a/grammar/CircomParser.g4 +++ b/grammar/CircomParser.g4 @@ -104,8 +104,8 @@ statements ; ifStatements - : 'if' '(' cond=expression ')' ifStatements #IfWithFollowUpIf - | 'if' '(' cond=expression ')' regularStatements #IfRegular + : 'if' '(' cond=expression ')' ifStatements #IfWithFollowUpIf + | 'if' '(' cond=expression ')' regularStatements #IfRegular | 'if' '(' cond=expression ')' regularStatements 'else' ifStatements #IfRegularElseWithFollowUpIf | 'if' '(' cond=expression ')' regularStatements 'else' regularStatements #IfRegularElseRegular ; @@ -126,10 +126,10 @@ cycleStatements ; substitutions - : lhs=expression op=(ASSIGNMENT | LEFT_ASSIGNMENT | LEFT_CONSTRAINT) rhs=expression #SubsLeftAssignmet - | lhs=expression op='-->' variable=expression #SubsRightSimpleAssignmet - | lhs=expression op='==>' variable=expression #SubsRightConstrAssignmet - | identifierStatement op=ASSIGNMENT_WITH_OP rhs=expression #SubsAssignmetWithOperation + : lhs=expression op=(ASSIGNMENT | LEFT_ASSIGNMENT | LEFT_CONSTRAINT) rhs=expression #SubsLeftAssignment + | lhs=expression op='-->' variable=expression #SubsRightSimpleAssignment + | lhs=expression op='==>' variable=expression #SubsRightConstrAssignment + | identifierStatement op=ASSIGNMENT_WITH_OP rhs=expression #SubsAssignmentWithOperation | identifierStatement SELF_OP #SubsIcnDecOperation | SELF_OP identifierStatement #SubsInvalidIcnDecOperation ; @@ -164,7 +164,7 @@ expression // Literal, parentheses, function call, array inline, anonymous component call primaryExpression - : identifierStatement #PIdentifierStatement + : identifierStatement #PIdentifierStatement | '_' #PUnderscore | NUMBER #PNumber | '(' expressionList ')' #PParentheses