• 🏆 Texturing Contest #33 is OPEN! Contestants must re-texture a SD unit model found in-game (Warcraft 3 Classic), recreating the unit into a peaceful NPC version. 🔗Click here to enter!
  • It's time for the first HD Modeling Contest of 2024. Join the theme discussion for Hive's HD Modeling Contest #6! Click here to post your idea!

New vJASS Interpreter/Parser/Lexer/Translator

Status
Not open for further replies.
Level 31
Joined
Jul 10, 2007
Messages
6,306
All right, so far I've finished the Lexer ^_^.

Could use feedback o-o.

Written with Antlr 4


So some of the features
-compatible with vJASS
-string interpolation
-code interpolation
-full code preprocessing interpretation
-binary number support
-any size ascii number support
-for, while, do while, for/in, loop, break, continue
-proper order of initialization
-generic blocks
-declare locals anywhere
-properly working prefix/posfix operators
-modulo
-assign append operators (+=, -=, *=, /=, %=)
-lambda (constant)
-internal, protected modifiers
-private scopes
-auto run code not inside of a function (put it in blocks to localize)
-vJASS interpreter for compile time code, some of it translated to Lua for manipulating map
-new lines no longer required, meaning that they can be used freely as white space!
-native declaration
-type declaration
-struct (extend type, array, or other struct)
-all the other normal vJASS stuff
-use of either # or //! for preprocessor directives
-nested functions
-nested structs
-enums
-textmacros may call other textmacros
-nested textmacros
-globals do not have to be in a global block
-full boolean expression support for static ifs
-modules may take arguments
-module_once vs module (you should be able to guess at what each one does)
-onInit no longer required, use blocks
-no zinc support (sry, hardly anyone uses it, but someone is more than free to write up a lexer/grammar for it)
-static extension (no polymorphism support) vs regular extension (polymorphic support)
-full operator overloading (add missing stuff, allow more stuff)
-function overloading (hi(1) vs hi(1,2))
-default arguments (function hi takes integer m, integer o = 6 returns nothing)
-allow full use of underscores
-public won't add _ for scopes/libraries, that has always been weird...
-structs won't generate code that isn't being utilized
-override allocation, deallocation, create, destroy, polymorphic behavior, extension behavior
-new link type (like delegates, but use "this" instead of what is stored in the delegate)
-import from relative directories
-github support (define github repositories to look up, any missing required libraries will be searched on github, libraries marked for autoupdating will check github for updates)
-function sorting
-variable sorting
-no more need for keyword to see a struct below you
-static ifs may use anything from globals to struct methods to interpolations
-static if is the same as #if is the same as //! if
-textmacro interpolation will only be $ or ${ }, not $$, sry :(
-textmacros no longer need to take strings, they can take any type
-text inside of a string will not automatically be replaced by a textmacro, you need to interpolate it twice, the textmacro is a #function and its params are locals
-auto clean return of local handles
-hook (takes args), hook_after (takes args + return), hook_override(takes args, returns, can have many) with smarter hooks that only use triggers when absolutely necessary
-triggers will be built as balanced trees when constant (hooks, polymorphism, etc)
-typedef
-multi array overload
-input multiple files (as many .j files as you want, including war3map.j, common.j, Blizzard.j, common.ai, random.j, w/e)
-debug is a variable
-templates (list<int>)

likely going to translate the vJASS preprocess stuff into Groovy + allow users to write preprocessor code in Groovy if they want, this way they can use Java code and a whole slew of things =)

some interesting things you can do with interpolation
#name = "hi"
string $name = "$$name" //string hi = "hi", lol...

"hello there $name[GetPlayerId(GetLocalPlayer())]! Your income is ${team.income + income[GetPlayerId(GetLocalPlayer())]}." //yes, this actually works, lol... look at giant pic for proof, it works o_O

and ofc.. this is the most whacked thing ever

"${"$name"}" //lol...

Input
Code:
-0b1011
'\\\\\\\\'
"hello there ${  "$name!"  }! /*testing" //test complete
"hello there $player[id]! /*testing"
"$$name!"
"$name"
/* this is at test /*another test o-o /*nesting!!*/ */ */
//"what are you up to? //testing" //test complete

//var = 15.5 + 0b110 + 0xff + 'a' + (('ffff')) + 14 + true + null





//hi there
//ho

/*wtf

/*woah*/

/* /* */ */

*/

Output
attachment.php


Grammar (hardly started)
Code:
parser grammar vJASSParser;

options { tokenVocab = vJASSLexer; }

/*
*   globals
*       variable declaration
*   type declaration
*   native declaration
*   function declaration
*       local declarations
*       statements
*   statement
*       if
*       loop
*       return
*       set
*       call
*   interface
*   struct
*   library
*       scope
*       struct
*       interface
*       globals
*       type
*       native
*       function
*   scope
*       struct
*       interface
*       globals
*       type
*       native
*       function
*/

start: literal*;

variableType
    : BOOLEAN_TYPE
    | INTEGER_TYPE
    | REAL_TYPE
    | STRING_TYPE
    | CODE_TYPE 
    | HANDLE_TYPE 
    | LAMBDA_TYPE 
    | IDENTIFIER
    ;

literal
    : (
          BOOLEAN
        | INTEGER
        | REAL 
        | NULL
        | IDENTIFIER
      )
    | stringLiteral
    ;

//globalBlock: GLOBALS variableDeclaration* ENDGLOBALS;

//variableDeclaration: variableType ARRAY? IDENTIFIER (ASSIGN expression)?;
expression: INTERPOLATE expression | INTERPOLATE LBRACE expression RBRACE | literal | expression LPAREN expression RPAREN | LPAREN expression RPAREN | expression LBRACK expression RBRACK;

stringLiteral: STRING_START (STRING_CHUNK | INTERPOLATE expression | INTERPOLATE LBRACE expression RBRACE)* STRING_END;

/*
expression
    : '(' expression ')'
    | 'this'
    | 'super'
    | 'exists'
    | 'thistype'
    | literal 
    | Identifier
    |   expression '.' expression
    |   expression '[' expression ']'
    |   expression '(' expressionList? ')'
    |   expression ('++' | '--')
    |   ('+'|'-'|'++'|'--') expression
    |   ('not') expression
    |   expression ('*'|'/'|'%') expression
    |   expression ('+'|'-') expression
    |   expression ('<=' | '>=' | '>' | '<') expression
    |   expression 'instanceof' type
    |   expression ('==' | '!=') expression
    |   expression 'and' expression
    |   expression 'or' expression
    |   expression '?' expression ':' expression
    |   'set' expression
        (   '='<assoc=right>
        |   '+='<assoc=right>
        |   '-='<assoc=right>
        |   '*='<assoc=right>
        |   '/='<assoc=right>
        |   '%='<assoc=right>
        )
        expression
    ;

literal
    :   Integer
    |   Real
    |   stringLiteral
    |   Ascii
    |   Boolean
    |   'null'
    ;
*/
//expressionList: expression (',' expression)*;

//functionCallExpression: 'call' functionExpression;
//functionExpression: Identifier '(' expressionList? ')';

//stringLiteral: StringStart (StringText | stringInterpolation)* StringEnd;
//stringInterpolation: StringInterpolationStart interpolationVariable=Identifier StringInterpolationEnd;

//<T> template
//#     -> print result
//#{}   -> print result
//ternary
//=
//+=, -=
//*=, /=, %=
//<<=, >>>=, >>=
//&=, ^=, |=
//,

Lexer
Code:
lexer grammar vJASSLexer;

tokens {
    /* filters                      */
    COMMENT, WHITESPACE
    ,

    /* atoms                        */
    STRING_START, STRING_CHUNK, STRING_END
    ,
    IDENTIFIER
    ,
    GROOVY
    ,
    
    /* primitives                   */
    BOOLEAN_TYPE, INTEGER_TYPE, REAL_TYPE, STRING_TYPE, CODE_TYPE, HANDLE_TYPE, LAMBDA_TYPE, NOTHING_TYPE,
    BOOLEAN, INTEGER, REAL, NULL
    ,

    /* keywords                     */
    ARRAY
    ,
    BLOCK, BREAK
    ,
    CONSTANT, CONTINUE
    ,
    DEBUG, DEBUG_MODE, DEFAULT, DELEGATE, DO
    ,
    ELSE, ELSEIF, ENDBLOCK, ENDDO, ENDENUM, ENDFOR, ENDFUNCTION, ENDGLOBALS,
    ENDIF, ENDLIBRARY, ENDLOOP, ENDMETHOD, ENDMODULE, ENDNOVJASS, ENDSCOPE, ENDSTRUCT,
    ENDTEXTMACRO, ENDWHILE, ENUM, EXISTS, EXTENDS
    ,
    FINAL, FOR, FUNCTION
    ,
    GLOBALS
    ,
    IF, IMPLEMENT, IMPLEMENTS, IMPORT, IN, INITIALIZER, INSTANCEOF, INTERFACE,
    INTERNAL
    ,
    LOCAL, LOOP, LIBRARY
    ,
    METHOD, MODULE
    ,
    NATIVE, NEEDS, NOVJASS
    ,
    OPERATOR
    ,
    PRIVATE, PROTECTED, PUBLIC
    ,
    READONLY, REQUIRES, RETURN, RETURNS, RUNTEXTMACRO
    ,
    SCOPE, SET, STATIC, STRUCT, SUPER
    ,
    TAKES, TEXTMACRO, THIS, THISTYPE
    ,
    USES
    ,
    TYPE
    ,
    WHILE
    ,
    
    /* separators                   */
    LPAREN, RPAREN
    ,
    LBRACE, RBRACE
    ,
    LBRACK, RBRACK
    ,
    COMMA, DOT
    ,
    
    /* operators                    */
    ASSIGN, ADD_ASSIGN, SUB_ASSIGN, MUL_ASSIGN, DIV_ASSIGN, MOD_ASSIGN,
    AND_ASSIGN, XOR_ASSIGN, OR_ASSIGN, LEFT_SHIFT_ASSIGN, RIGHT_SHIFT_ASSIGN,
    LOGICAL_RIGHT_SHIFT_ASSIGN
    ,
    GT, LT, LTE, GTE
    ,
    EQ, NEQ
    ,
    NOT, AND, OR, AND_BITWISE, OR_BITWISE, XOR_BITWISE
    ,
    QUESTION, COLON
    ,
    INC, DEC
    ,
    ADD, SUB, MUL, DIV, MOD
    ,
    INTERPOLATE
    ,
    
    /* misc                         */
    AT
    ,

    /* generic error                */
    ERROR
}

@members {
    public static final int CHANNEL_WHITESPACE = 1;
    public static final int CHANNEL_COMMENTS = 2;
    
    public java.util.Stack<Integer> modeStack = new java.util.Stack<Integer>();
    public boolean hasModeTerminal() { return !modeStack.empty(); }
    public void pushModeTerminal(int symbol) { modeStack.push(symbol); }
    public void popModeTerminal() { if (modeStack.empty()) return; modeStack.pop(); }
    public boolean checkModeTerminal(int symbol) { if (modeStack.empty()) return false; return modeStack.peek() == symbol; }
    
    public void parseBinary() {
        _text = getText();
        if (_text.charAt(0) == '-' || _text.charAt(0) == '+')
            _text = _text.substring(0, 1) + _text.substring(3, _text.length());
        else
            _text = _text.substring(2, _text.length());
        _text = Integer.toString(Integer.parseInt(_text, 2));
        _type = INTEGER;
    }
    
    public void parseOctal() {
        _text = getText();
        if (_text.charAt(0) == '-' || _text.charAt(0) == '+')
            _text = _text.substring(0, 1) + _text.substring(2, _text.length());
        else
            _text = _text.substring(1, _text.length());
        _text = Integer.toString(Integer.parseInt(_text, 8));
        _type = INTEGER;
    }
    
    public void parseDecimal() {
        _text = getText();
        _text = Integer.toString(Integer.parseInt(_text, 10));
        _type = INTEGER;
    }
    
    public void parseHex() {
        _text = getText();
        if (_text.charAt(0) == '-' || _text.charAt(0) == '+')
            _text = _text.substring(0, 1) + _text.substring(3, _text.length());
        else
            _text = _text.substring(2, _text.length());
        _text = Integer.toString(Integer.parseInt(_text, 16));
        _type = INTEGER;
    }
    
    public void parseAscii() {
        _text = getText();

        int m = 0;
        int start = 1;
        int end = _text.length() - 1;

        while (start < end) {
            if (_text.charAt(start) == '\\')
                ++start;

            m = m*256 + _text.charAt(start++);
        }
        _text = Integer.toString(m);
        _type = INTEGER;
    }
    
    public void filterGroovy() {
        _text = getText();
        _text = _text.substring(6, _text.length() - 9);
        _type = GROOVY;
    }
}

/*
*   Filters
*/
LINE_COMMENT_FILTER
    : '//' ('!' | ~[!\n] ~[\n]* '\n'? | '\n'?)
      -> type(COMMENT), channel(CHANNEL_COMMENTS);
DELIMITED_COMMENT_FILTER
    : '/*'
      -> pushMode(inDelimitedComment), more;
WHITESPACE_FILTER
    : [ \t\r\n\u000C]+
      -> type(WHITESPACE), channel(CHANNEL_WHITESPACE);

/*
*   Primitives
*/
BOOLEAN_PRIMITIVE
    : 'boolean'
      -> type(BOOLEAN_TYPE);
INTEGER_PRIMITIVE
    : 'integer'
      -> type(INTEGER_TYPE);
REAL_PRIMITIVE
    : 'real'
      -> type(REAL_TYPE);
STRING_PRIMITIVE
    : 'string'
      -> type(STRING_TYPE);
CODE_PRIMITIVE
    : 'code'
      -> type(CODE_TYPE);
HANDLE_PRIMITIVE
    : 'handle'
      -> type(HANDLE_TYPE);
LAMBDA_PRIMITIVE
    : 'lambda'
      -> type(LAMBDA_TYPE);
NOTHING_PRIMITIVE
    : 'nothing'
      -> type(NOTHING_TYPE);

/*
*   Keywords
*/
ARRAY_KEYWORD
    : 'array'
      -> type(ARRAY);
BLOCK_KEYWORD
    : 'block'
      -> type(BLOCK);
BREAK_KEYWORD
    : 'break'
      -> type(BREAK);
CONSTANT_KEYWORD
    : 'constant'
      -> type(CONSTANT);
CONTINUE_KEYWORD
    : 'continue'
      -> type(CONTINUE);
DEBUG_KEYWORD
    : 'debug'
      -> type(DEBUG);
DEBUG_MODE_KEYWORD
    : 'DEBUG_MODE'
      -> type(DEBUG_MODE);
DEFAULT_KEYWORD
    : 'default'
      -> type(DEFAULT);
DELEGATE_KEYWORD
    : 'delegate'
      -> type(DELEGATE);
DO_KEYWORD
    : 'do'
      -> type(DO);
ELSE_KEYWORD
    : 'else'
      -> type(ELSE);
ELSEIF_KEYWORD
    : 'elseif'
      -> type(ELSEIF);
ENDBLOCK_KEYWORD
    : 'endblock'
      -> type(ENDBLOCK);
ENDDO_KEYWORD
    : 'enddo'
      -> type(ENDDO);
ENDENUM_KEYWORD
    : 'endenum'
      -> type(ENDENUM);
ENDFOR_KEYWORD
    : 'endfor'
      -> type(ENDFOR);
ENDFUNCTION_KEYWORD
    : 'endfunction'
      -> type(ENDFUNCTION);
ENDGLOBALS_KEYWORD
    : 'endglobals'
      -> type(ENDGLOBALS);
ENDIF_KEYWORD
    : 'endif'
      -> type(ENDIF);
ENDLIBRARY_KEYWORD
    : 'endlibrary'
      -> type(ENDLIBRARY);
ENDLOOP_KEYWORD
    : 'endloop'
      -> type(ENDLOOP);
ENDMETHOD_KEYWORD
    : 'endmethod'
      -> type(ENDMETHOD);
ENDMODULE_KEYWORD
    : 'endmodule'
      -> type(ENDMODULE);
ENDNOVJASS_KEYWORD
    : 'endnovjass'
      -> type(ENDNOVJASS);
ENDSCOPE_KEYWORD
    : 'endscope'
      -> type(ENDSCOPE);
ENDSTRUCT_KEYWORD
    : 'endstruct'
      -> type(ENDSTRUCT);
ENDTEXTMACRO_KEYWORD
    : 'endtextmacro'
      -> type(ENDTEXTMACRO);
ENDWHILE_KEYWORD
    : 'endwhile'
      -> type(ENDWHILE);
ENUM_KEYWORD
    : 'enum'
      -> type(ENUM);
EXISTS_KEYWORD
    : 'exists'
      -> type(EXISTS);
EXTENDS_KEYWORD
    : 'extends'
      -> type(EXTENDS);
FINAL_KEYWORD
    : 'final'
      -> type(FINAL);
FOR_KEYWORD
    : 'for'
      -> type(FOR);
FUNCTION_KEYWORD
    : 'function'
      -> type(FUNCTION);
GLOBALS_KEYWORD
    : 'globals'
      -> type(GLOBALS);
IF_KEYWORD
    : 'if'
      -> type(IF);
IMPLEMENT_KEYWORD
    : 'implement'
      -> type(IMPLEMENT);
IMPLEMENTS_KEYWORD
    : 'implements'
      -> type(IMPLEMENTS);
IMPORT_KEYWORD
    : 'import'
      -> type(IMPORT);
IN_KEYWORD
    : 'in'
      -> type(IN);
INITIALIZER_KEYWORD
    : 'initializer'
      -> type(INITIALIZER);
INSTANCEOF_KEYWORD
    : 'instanceof'
      -> type(INSTANCEOF);
INTERFACE_KEYWORD
    : 'interface'
      -> type(INTERFACE);
INTERNAL_KEYWORD
    : 'internal'
      -> type(INTERNAL);
LOCAL_KEYWORD
    : 'local'
      -> type(LOCAL);
LOOP_KEYWORD
    : 'loop'
      -> type(LOOP);
LIBRARY_KEYWORD
    : 'library'
      -> type(LIBRARY);
METHOD_KEYWORD
    : 'method'
      -> type(METHOD);
MODULE_KEYWORD
    : 'module'
      -> type(MODULE);
NATIVE_KEYWORD
    : 'native'
      -> type(NATIVE);
NEEDS_KEYWORD
    : 'needs'
      -> type(NEEDS);
NOVJASS_KEYWORD
    : 'novjass'
      -> type(NOVJASS);
OPERATOR_KEYWORD
    : 'operator'
      -> type(OPERATOR);
PRIVATE_KEYWORD
    : 'private'
      -> type(PRIVATE);
PROTECTED_KEYWORD
    : 'protected'
      -> type(PROTECTED);
PUBLIC_KEYWORD
    : 'public'
      -> type(PUBLIC);
READONLY_KEYWORD
    : 'readonly'
      -> type(READONLY);
REQUIRES_KEYWORD
    : 'requires'
      -> type(REQUIRES);
RETURN_KEYWORD
    : 'return'
      -> type(RETURN);
RETURNS_KEYWORD
    : 'returns'
      -> type(RETURNS);
RUNTEXTMACRO_KEYWORD
    : 'runtextmacro'
      -> type(RUNTEXTMACRO);
SCOPE_KEYWORD
    : 'scope'
      -> type(SCOPE);
SET_KEYWORD
    : 'set'
      -> type(SET);
STATIC_KEYWORD
    : 'static'
      -> type(STATIC);
STRUCT_KEYWORD
    : 'struct'
      -> type(STRUCT);
SUPER_KEYWORD
    : 'super'
      -> type(SUPER);
TAKES_KEYWORD
    : 'takes'
      -> type(TAKES);
TEXTMACRO_KEYWORD
    : 'textmacro'
      -> type(TEXTMACRO);
THIS_KEYWORD
    : 'this'
      -> type(THIS);
THISTYPE_KEYWORD
    : 'thistype'
      -> type(THISTYPE);
USES_KEYWORD
    : 'uses'
      -> type(USES);
TYPE_KEYWORD
    : 'type'
      -> type(TYPE);
WHILE_KEYWORD
    : 'while'
      -> type(WHILE);

/*
*   Separators
*/
LPAREN_SEP
    : '('
      {_type = LPAREN; if (hasModeTerminal()) {pushModeTerminal(LPAREN);}};
RPAREN_SEP
    : ')'
      {_type = RPAREN; if (checkModeTerminal(LPAREN)) {popModeTerminal(); if (!hasModeTerminal()) { popMode(); }}};
LBRACE_SEP
    : '{'
      {_type = LBRACE; if (hasModeTerminal()) {pushModeTerminal(LBRACE);}};
RBRACE_SEP
    : '}'
      {_type = RBRACE; if (checkModeTerminal(LBRACE)) {popModeTerminal(); if (!hasModeTerminal()) { popMode(); }}};
LBRACK_SEP
    : '['
      {_type = LBRACK; if (hasModeTerminal()) {pushModeTerminal(LBRACK);}};
RBRACK_SEP
    : ']'
      {_type = RBRACK; if (checkModeTerminal(LBRACK)) {popModeTerminal(); if (!hasModeTerminal()) { popMode(); }}};
COMMA_SEP
    : ','
      -> type(COMMA);
DOT_SEP
    : '.'
      -> type(DOT);

/*
*   Operators
*/
ASSIGN_OP
    : '='
      -> type(ASSIGN);
ADD_ASSIGN_OP
    : '+='
      -> type(ADD_ASSIGN);
SUB_ASSIGN_OP
    : '-='
      -> type(SUB_ASSIGN);
MUL_ASSIGN_OP
    : '*='
      -> type(MUL_ASSIGN);
DIV_ASSIGN_OP
    : '/='
      -> type(DIV_ASSIGN);
MOD_ASSIGN_OP
    : '%='
      -> type(MOD_ASSIGN);
AND_ASSIGN_OP
    : '&='
      -> type(AND_ASSIGN);
XOR_ASSIGN_OP
    : '^='
      -> type(XOR_ASSIGN);
OR_ASSIGN_OP
    : '|='
      -> type(OR_ASSIGN);
LEFT_SHIFT_ASSIGN_OP
    : '<<='
      -> type(LEFT_SHIFT_ASSIGN);
RIGHT_SHIFT_ASSIGN_OP
    : '>>='
      -> type(RIGHT_SHIFT_ASSIGN);
LOGICAL_RIGHT_SHIFT_ASSIGN_OP
    : '>>>='
      -> type(LOGICAL_RIGHT_SHIFT_ASSIGN);
GT_OP
    : '>'
      {_type = GT;};
LT_OP
    : '<'
      {_type = LT;};
NOT_OP
    : 'not'
      -> type(NOT);
QUESTION_OP
    : '?'
      -> type(QUESTION);
COLON_OP
    : ':'
      -> type(COLON);
EQ_OP
    : '=='
      -> type(EQ);
LTE_OP
    : '<='
      -> type(LTE);
GTE_OP
    : '>='
      -> type(GTE);
NEQ_OP
    : '!='
      -> type(NEQ);
AND_OP
    : ('and' | '&&')
      {_type = AND; _text = "and";};
OR_OP
    : ('or' | '||')
      {_type = OR; _text = "or";};
XOR_BITWISE_OP
    : '^'
      -> type(XOR_BITWISE);
OR_BITWISE_OP
    : '|'
      -> type(OR_BITWISE);
AND_BITWISE_OP
    : '&'
      -> type(AND_BITWISE);
INC_OP
    : '++'
      -> type(INC);
DEC_OP
    : '--'
      -> type(DEC);
ADD_OP
    : '+'
      -> type(ADD);
SUB_OP
    : '-'
      -> type(SUB);
MUL_OP
    : '*'
      -> type(MUL);
DIV_OP
    : '/'
      -> type(DIV);
MOD_OP
    : '%'
      -> type(MOD);
INTERPOLATE_OP
    : '$'
      -> type(INTERPOLATE);

/*
*   Misc
*/
AT_MISC
    : '@'
      -> type(AT);

/*
*   Atoms
*/
GROOVY_ATOM
    : 'groovy' (GROOVY_STRING_ATOM | GROOVY_ASCII_ATOM | LINE_COMMENT_FILTER | GROOVY_DELIMITED_COMMENT_FILTER | .)*? 'endgroovy' 
      { filterGroovy(); }
    ;
    fragment GROOVY_STRING_ATOM
        : '"' (~["] | '\\"')* '"'
        ;
    fragment GROOVY_ASCII_ATOM
        : '\'' (~['] | '\\\'')* '\''
        ;
    fragment GROOVY_DELIMITED_COMMENT_FILTER
        : '/*' .*? '*/'
        ;

STRING_ATOM
    : '"'
      -> pushMode(inString), type(STRING_START);

NULL_ATOM
    : 'null'
      -> type(NULL);
BOOLEAN_ATOM
    : ('true' | 'false')
      -> type(BOOLEAN);
REAL_ATOM
    : (SIGN_SUB? (([1-9] [0-9]* | '0') '.' [0-9]*))
      -> type(REAL);
BIN_SUB
    : SIGN_SUB? ('0' ('b' | 'B') [0-1]+)
      { parseBinary(); };
OCT_SUB
    : SIGN_SUB? ('0' [0-7]+)
      { parseOctal(); };
DEC_SUB
    : SIGN_SUB? ([1-9] [0-9]* | '0')
      { parseDecimal(); };
HEX_SUB
    : SIGN_SUB? ('0' ('x' | 'X') [0-9a-fA-F]+)
      { parseHex(); };
ASCII_SUB
    : '\'' ASCII_SUB_DIG+ '\''
      { parseAscii(); };
    fragment ASCII_SUB_DIG
        : ~['\\] | ('\\' ['\\]);
    fragment SIGN_SUB
        : ('+'|'-');

IDENTIFIER_ATOM
    : [a-zA-Z_] [a-zA-Z0-9_]*
      -> type(IDENTIFIER);

mode inDelimitedComment;
DELIMITED_COMMENT_START
    : '/*'
      -> pushMode(inDelimitedComment), more;
DELIMITED_COMMENT_END
    : '*/'
      {popMode(); if (_mode == inDelimitedComment) { more(); } else { _type = COMMENT; _channel = CHANNEL_COMMENTS; } };
DELIMITED_COMMENT_ERROR
    : EOF
      -> type(ERROR); 
DELIMITED_COMMENT_TEXT
    : .
      -> more; 

mode inString;
STRING_ATOM_ERROR
    : EOF
      -> type(ERROR);
STRING_ATOM_TEXT
    : (~["\\$\Z] | ('\\' ["\\$]))+
      -> type(STRING_CHUNK);
STRING_ATOM_END
    : STRING_ATOM
      {popMode(); _type = STRING_END;};
STRING_ATOM_INTERPOLATION
    : INTERPOLATE_OP
      -> type(INTERPOLATE), pushMode(inPartialInterpolationString);

mode inPartialInterpolationString;
PARTIAL_INTERPOLATION_STRING_LBRACK_SEP
    : LBRACK_SEP
      {_type = LBRACK; pushMode(DEFAULT_MODE); pushModeTerminal(LBRACK);};
PARTIAL_INTERPOLATION_STRING_LPAREN_SEP
    : LPAREN_SEP
      {_type = LPAREN; pushMode(DEFAULT_MODE); pushModeTerminal(LPAREN);};
PARTIAL_INTERPOLATION_STRING_LBRACE_SEP
    : LBRACE_SEP
      {_type = LBRACE; pushMode(DEFAULT_MODE); pushModeTerminal(LBRACE);};
PARTIAL_INTERPOLATION_STRING_DOT_SEP
    : DOT_SEP
      -> type(DOT);

PARTIAL_INTERPOLATION_STRING_NULL_ATOM
    : NULL_ATOM
      -> type(NULL);
PARTIAL_INTERPOLATION_STRING_BOOLEAN_ATOM
    : BOOLEAN_ATOM
      -> type(BOOLEAN);
PARTIAL_INTERPOLATION_STRING_BIN_SUB
    : SIGN_SUB? ('0' ('b' | 'B') [0-1]+)
      { parseBinary(); };
PARTIAL_INTERPOLATION_STRING_OCT_SUB
    : SIGN_SUB? ('0' [0-7]+)
      { parseOctal(); };
PARTIAL_INTERPOLATION_STRING_DEC_SUB
    : SIGN_SUB? ([1-9] [0-9]* | '0')
      { parseDecimal(); };
PARTIAL_INTERPOLATION_STRING_HEX_SUB
    : SIGN_SUB? ('0' ('x' | 'X') [0-9a-fA-F]+)
      { parseHex(); };
PARTIAL_INTERPOLATION_STRING_ASCII_SUB
    : '\'' ASCII_SUB_DIG+ '\''
      { parseAscii(); };
PARTIAL_INTERPOLATION_STRING_REAL_ATOM
    : REAL_ATOM
      -> type(REAL);
PARTIAL_INTERPOLATION_STRING_IDENTIFIER_ATOM
    : IDENTIFIER_ATOM
      -> type(IDENTIFIER);

PARTIAL_INTERPOLATION_STRING_INTERPOLATE_OP
    : INTERPOLATE_OP
      -> type(INTERPOLATE);
PARTIAL_INTERPOLATION_STRING_STR
    : STRING_ATOM
      -> popMode, popMode, type(STRING_END);
PARTIAL_INTERPOLATION_STRING_ERROR
    : EOF
      -> type(ERROR);
PARTIAL_INTERPOLATION_STRING_POP
    : .
      -> popMode, type(STRING_CHUNK);
 

Attachments

  • antlr4_parse_tree.png
    antlr4_parse_tree.png
    23.4 KB · Views: 1,153
Last edited:
Level 31
Joined
Jul 10, 2007
Messages
6,306
For highlighting, you want to use tagging, which would just be the lexer.

For intellisense and underlining syntax errors, that's where you want to use the full shebang, but you only want to partially parse the stuff and keep a state + updating..

I'll give it the capability ;o

@coke, as you see, all I've finished thus far is the Lexer ;P



Everything is in Java ;)
 

peq

peq

Level 6
Joined
May 13, 2007
Messages
171
This sounds promising. Maybe I can use it to make vJass work better with Wurst ;)

If you want to, you can also use parts of Wurst for the translation. If you translate to the Wurst intermediate language you will get some features for free: translation to Jass, optimizations, null-setting of handles, basic translation of classes and dynamic dispatch, tuples, and an interpreter. If you are interested I can give you more details...

Some comments to the proposed features:

-compatible with vJASS

Some of the other features are not compatible with vJass, so it will only be like 95% compatible, right?

-new link type (like delegates, but use "this" instead of what is stored in the delegate)

This sounds interesting, but I do not quite understand how this will work. Could you give an example, please?

-github support (define github repositories to look up, any missing required libraries will be searched on github, libraries marked for autoupdating will check github for updates)

This is extremely cool. We were thinking about adding something similar to Wurst. One open question was, if the dependencies should have versions, or if it should always take the latest version. Without versions a library
could break if a dependency is updated and with versions there could be conflicts if there are dependencies to the
same library but with different versions. Do you have a solution for this?

#name = "hi"

What will be the scope of $name in this case? Will $name be visible only in the current function or in the whole map?
 

Cokemonkey11

Code Reviewer
Level 29
Joined
May 9, 2006
Messages
3,522
This is extremely cool. We were thinking about adding something similar to Wurst. One open question was, if the dependencies should have versions, or if it should always take the latest version. Without versions a library
could break if a dependency is updated and with versions there could be conflicts if there are dependencies to the
same library but with different versions. Do you have a solution for this?

Good API design is the correct solution, but if you want to be supportive of bad API design, you'll have to implement an error or selection logic (eg choose newest version in case of conflict)

See: Maven
 
Level 31
Joined
Jul 10, 2007
Messages
6,306
If you want to, you can also use parts of Wurst for the translation. If you translate to the Wurst intermediate language you will get some features for free: translation to Jass, optimizations, null-setting of handles, basic translation of classes and dynamic dispatch, tuples, and an interpreter. If you are interested I can give you more details...

Sadly, there are some features in this that aren't compatible with Wurst, like overriding every portion of the struct (allocate, dealloate, create, destroy, etc) and extending off of any type. For example, if you extend off of unit, a method will look like this

JASS:
function myMethod takes unit this returns nothing
endfunction

Because Wurst doesn't let you be nitpicky about every feature if you want, I can't translate to Wurst ;(.

There is no need for struct extends array anymore. If you want to extend something without polymorphic features, you can do

struct Hi extends static OtherStruct

Some of the other features are not compatible with vJass, so it will only be like 95% compatible, right?

nah, straight vJASS'll work in this thing ;). You'll be able to run any regular vJASS code.

Without versions a library
could break if a dependency is updated and with versions there could be conflicts if there are dependencies to the
same library but with different versions. Do you have a solution for this?

The most common way is to just have those libraries break. That's how most things do it :\. Go complain to the authors if they break backwards compatibility ;o.

What will be the scope of $name in this case? Will $name be visible only in the current function or in the whole map?

If #name was just declared out in the global space (no block or anything), it will be visible everywhere.

The preprocessor stuff is all translated into Groovy. From here, Groovy evaluates the stuff. static ifs, textmacros, all of it will be Groovy ^_^. Ofc, you'll also be able to write in Groovy if you want to too.


This sounds interesting, but I do not quite understand how this will work. Could you give an example, please?

A link is a way to do multi-struct extension while using the "this" from the current struct as the instance.

JASS:
struct A
    integer a
endstruct
struct B
    integer b
endstruct
struct Rawr extends static A //poor way to do this, need to come up with syntax for struct A declaration to make it static-only extension
                                          //from here, no need to have extends static A, can just do extends A
    link B

    //it would inherit from both A and B. It can override anything from A/B
    //super would use A, but it could specifically access either A or B via
    //A. and B. too.

    integer a
    integer b

    method ho takes nothing returns nothing
        set A.a = 5 //this, allocated from A
        set super.a = 5 //this, allocated from A
        set B.b = 6 //this

        //a link is different from a delegate in that a delegate is set to a value
        //a link is always "this"
        //the same could be achieved with a delegate array
        //a link also does no variable lookup (except for this) (otherStruct[this])
        //a delegate does a variable lookup (otherStruct[myDelegate[this]])
    endmethod

    //this struct's allocate method returns A.allocate()
endstruct
 

peq

peq

Level 6
Joined
May 13, 2007
Messages
171
Sadly, there are some features in this that aren't compatible with Wurst, like overriding every portion of the struct (allocate, dealloate, create, destroy, etc) and extending off of any type. For example, if you extend off of unit, a method will look like this

I understand that it is not possible to translate to Wurst, but my suggestion was to translate to an intermediate language which we use in the translation process of wurst. The translation process of Wurst is roughly like this:
  1. lex
  2. parse
  3. name resolution and typechecking
  4. translate to intermediate language AST
  5. Several transformation steps on the intermediate language (eliminate classes, eliminate tuples, flatten, null-setting, inlining, optimizing, ...)
  6. Translate to Jass AST
  7. Print Jass

My suggestion was that you could reuse code from the last three steps. The intermediate language is quite close to Jass but a bit more flexible to make the translation process easier.
 

Cokemonkey11

Code Reviewer
Level 29
Joined
May 9, 2006
Messages
3,522
can you please search through the map script for occurrences of struct instaniations (Struct.create()), and remove generated struct code for structs which are purely static?

EG: Someone uses struct in an API to make a nice syntax, but the struct is never instanciated = don't generate worthless code (and don't require the ugly extends array)
 
Level 31
Joined
Jul 10, 2007
Messages
6,306
Here is what I'm looking atm for going over the AST, which sucks (these are the passes)

Pass 1: vJASS preprocess -> Groovy, Groovy
Execute Groovy (add code at positions etc)
Pass 2: Symbols, function usages, package order (library initializers), scoping
Pass 3: Symbol validation, expression simplification, inlining, optimize phase 1, essentially everything else
Pass 4: Optimize phase 2 (remove unused code)

So... it would take 3 passes over the AST with the current design. I don't know of any way to lower this number.

With requirements, it can be seen if a function or a variable is used by anything at all. If nothing references a function or a variable, it won't be outputted ;). Something is only referenced if its symbol is used. This means that things that are inlined are not referenced.
 
Level 31
Joined
Jul 10, 2007
Messages
6,306
Updated lexer


- Removed # (use $)

- Added groovy endgroovy block (can't have identifiers named endgroovy in the groovy code, sry. You can have endgroovy in string, comment, etc tho)

- Fixed //!. The //! was being treated as a comment. It now works correctly. The Lexer just filters out the //!, so it's like a pointless thing to write, lol. It's purely for backwards compatibility.
 

peq

peq

Level 6
Joined
May 13, 2007
Messages
171
With requirements, it can be seen if a function or a variable is used by anything at all. If nothing references a function or a variable, it won't be outputted ;). Something is only referenced if its symbol is used. This means that things that are inlined are not referenced.

So you will also drop full support for ExecuteFunc?


So... it would take 3 passes over the AST with the current design. I don't know of any way to lower this number.

You need the preprocess phase and the groovy phase, because you designed the language like that. In my opinion it is easier to live without preprocessing. You can still generate code using groovy, if you want to. Just generate the code into separate files and only generate the code, when the input changes.

This is the usual approach taken with Java. For example tools like antlr will generate Java in a separate file and you only have to generate the code when the grammar file changes.

Once you are past the preprocessing and have the AST in memory it is not really important how many passes you have. As everything is in memory the compilation speed will not so much depend on the number of phases but more on how complex your rules and transformations are.

Having many passes over the AST is actually a good thing, because it keeps your code clean. However not everything can be separated into phases. For example name analysis and type checking usually have to be done together as one depends on the other.

Btw: is the source code already available for what you got so far?
 
Level 31
Joined
Jul 10, 2007
Messages
6,306
I can't really follow all the programming jargon, but this would allow using Java to write the map script...?

no

Btw: is the source code already available for what you got so far?

lexer is. Not much has been done with the parser tbh >.<. I can put what I have up so far though ;).

Once the parser grammar is done, then I can work on the passes for the AST.

I'm probably going to add closures (lexer supports them) as well as the end keyword. Also, the return type is going to be dynamically retrieved ;), so the returns etc stuff will no longer be needed, I'm just going to filter that stuff out.

If you return two different types in a function, they will be moved up into a type that can contain both of them, like an agent, a handle, or a real. If there is no such type, then it'll throw an error.

Here are some examples

function hi takes nothing
endfunction

function hi takes nothing
end

function hi takes nothing {
}

function hi() {
}

also, the function bit isn't even necessary

hi() {
}

or

hi takes nothing {
}

hi takes nothing
end


so why am I allowing all of the above? Backwards compatibility and the JASS style. JASS style would lead to ugly lambda expressions, so I want { } to be there. Really, this is all it really needs -> hi() { }, but oh well. I haven't done much on the parser yet, so nothing is set in stone. If people are against having whatever code you wanna code, I can change it to something definite, but I definitely want closures and I want smart return types ^)^.
 
Level 17
Joined
Apr 27, 2008
Messages
2,455
Well, ofc the position of letters is not random, it depends which language will be used, in french it's optimized.
Ofc even if i still really hate {} because of my Azerty keyboard, that was nothing more than trolling.
Ruby style is a good option but that's 100 % up to Nestharus.
 
Level 23
Joined
Apr 16, 2012
Messages
4,041
well, I never saw french keyboard, Im just used to qertz(yes, z :D) because thats the standard in here, but its interesting to hear that kind of layout

and even tho I will most likely never use the lexer, its nice to have multiple different ways of typing

While, it is a bit more chaotic, but it offers "yours" most beloved way of typing
 
Level 19
Joined
Aug 8, 2007
Messages
2,765
Two things that I couldn't find answers for...

1) Are you going to use the default wc3 text editor or are you going to use another text editor like Eclipse

2) (not really a question but a suggestion) You should do native waits.. e.g.

JASS:
a takes nothing
    local real elapsedTime = GetElapsedTime()
    wait 5
    call BJDebugMsg(R2S(GetElapsedTime() - elapsedTime)) 
 end

Not the most elegant solution but it would be a hellofalot nicer for people who aren't experienced with stuff like CTL

Other than that, great project highly looking forward to it (except the part where warcraft 3 is only a couple years older than the PS2 yet we're still trying to mod with it)
 
Level 17
Joined
Apr 27, 2008
Messages
2,455
A such behavior (wait) needs to "convert" locals in globals (in an hashtable or global arrays) and handle timers as well + more stuff
Its funny that i planned to make it in ruby just for fun, but if Nestharus plan to do it i suppose i should do something else.
But i doubt he will ever do it, since there is absoluletly no way that such stuff will be more efficient as manually handle it yourself, we all know how Nestharus is with "efficiency".
 
Last edited:
Level 31
Joined
Jul 10, 2007
Messages
6,306
A such behavior (wait) needs to "convert" locals in globals (in an hashtable or global arrays) and handle timers as well + more stuff
Its funny that i planned to make it in ruby just for fun, but if Nestharus plan to do it i suppose i should do something else.
But i doubt he will ever do it, since there is absoluletly no way that such stuff will be more efficient as manually handle it yourself, we all know how Nestharus is with "efficiency".

You could always help me out with the Java thing

btw, if I were big on efficiency, I wouldn't be using Antlr : P

Also, I'm likely going to support all ways (JASS, Ruby/Lua/etc, C), so everyone can be happy to write closures however they like

hi() { }
hi() end
hi takes nothing endfunction

lol

the function keyword isn't necessary :eek:
 
Level 23
Joined
Apr 16, 2012
Messages
4,041
Once you are past the preprocessing and have the AST in memory it is not really important how many passes you have. As everything is in memory the compilation speed will not so much depend on the number of phases but more on how complex your rules and transformations are.

Having many passes over the AST is actually a good thing, because it keeps your code clean. However not everything can be separated into phases. For example name analysis and type checking usually have to be done together as one depends on the other.

http://youtu.be/4YsVtwOyWmo?t=48m06s watch till the end
 
Level 31
Joined
Jul 10, 2007
Messages
6,306
Are you going to use the default wc3 text editor or are you going to use another text editor like Eclipse
All I'm doing is the translator thing. You'll be able to use it in any tool you want. I will have a Groovy API (remember that the vJASS preprocess stuff translates into Groovy) for accessing the Lua exes (manipulating the map content). The API will generate Lua code and pack it all together in chunks and then pass these chunks into the various exes that they are targeted at.

So anyways, these can run inside of an IDE, text editor/cmd, or w/e you want really ;). Someone can also run it through NewGen if they wanted to.

It will take a wc3 map (for working with w/e) and a set of files. This means that you do not have to have files inside of a wc3 map.

The other thing I'm going to do is write all of the natives and BJ functions right into the interpreter. Of course, it will be able to read and interpret a native declaration too ;). I'm doing this to increase the speed a bit ; P. JassHelper reads common.j, which adds quite a bit of extra overhead : \.

As for native waits... I think that's best done as a system, perhaps through preprocessing.

JASS:
a takes nothing
    real elapsedTime = GetElapsedTime()
    $wait(5)
    BJDebugMsg(R2S(GetElapsedTime() - elapsedTime))
end

//the $wait would be a preprocess function that takes 5, which would end the above function and create a new one
//it would also start a timer

//here is an example, but GetElapsedTime would break : |
//could use the trick by Troll-Brain to fix the timer ^)^
a takes nothing
    real elapsedTime = GetElapsedTime()
    a_sub_r = elapsedTime
    call TimerStart(CreateTimer(), 5, false, function a_sub)
end
real a_sub_r
a_sub takes nothing
    local real elapsedTime = a_sub_r
    call DestroyTimer(GetExpiredTimer())
    BJDebugMsg(R2S(GetElapsedTime() - elapsedTime))
end

The one thing I'm unsure of atm is the syntax (besides //!) for preprocessor code. The $ is used to access preprocessor symbols from non-preprocessor code. In a string, it's used to access symbols in the script from the string.

I was going to use static, but I realized that it would be problematic in structs ;O. I could use # I suppose.

JASS:
#{
}

#block
end

#if
end

static if //translated to #if, translated to Groovy
end

#a() {
}

#real x = 5 //can be applied to blocks or statements

ofc the following wouldn't be legal

real r = #time

why? #time wouldn't be returned back into the script, it'd just be evaluated. $ evaluates and prints to the script.

This would be legal though..

real r = #{time = 5} $time

lol...

The next question is how to explicitly print back into the script. For example, you have a preprocessor block, but you want to write non-preprocessor script, like variables. I was thinking of something like ->, but I really have no idea what should be done ;). I don't want to do a print("") because the coloring gets lost.
 
Level 17
Joined
Apr 27, 2008
Messages
2,455
My plan was to use an hashtable and GetHandleId and create/destroy timer.
Hashtables are cool because you can flush all data of the first key in O(1), and it's easy to "convert" local arrays as well.
But it's not as simple as you think, you have to handle code blocks (wait inside if/then, loop).
Don't forget that you can have several waits within the same function.
Also functions which returns something are really a pain in the ass, if it is even possible to handle them correctly (i have not really thought about it), but i suppose it would be good enough if you allow a wait only inside a function which returns nothing.
And finally what a about a function with a wait inside which is called by an other function.

Code:
F2()
   BJDebugMsg("F2")
   Wait(0)
   BJDebugMsg("F2 end")
end

F1()
   BJDebugMsg("F1")
   F2()
   BJDebugMsg("F1 end")
end

The easiest way is to go when jass is generated and checked (and then, before this step consider Wait just as en empty BJ function which takes a real and returns nothing)
Yay, it will need one more pass, but at least the code will be clear and modular.
 
Last edited:

peq

peq

Level 6
Joined
May 13, 2007
Messages
171
The video stops in the mid of a sentence for me. The full video is on Channel9.

And I am not sure what you want to tell me with this. The clang-guy is talking about doing lexing, preprocessing, and parsing in one step without backtracking. That makes sense, but I was talking about the phases after parsing where you already have the AST. Here clang also has many passes afaik. LLVM is modularized into many passes and I think clang uses many of them.

Also the answer is specific to C++, because unlike most other languages, parsing depends on name-resolution in C++. That is why he says, that the header files in C++ are important.

As for native waits...

I think it is quite complicated to do this. But if you want to do it, you might want to look at how async and await in C# are translated. If I remember it correctly they basically create a final state machine around the functions body and generate jumps to the correct parts of the code. Now since Jass does not have goto, you will probably have to do more difficult transformations.

Closures and custom functions are a bit more ugly, but in my opinion they are good enough and more flexible.
 
Level 31
Joined
Jul 10, 2007
Messages
6,306
Here's a question

Because the Groovy code can generate JASS, should I generate 2 ASTs (one after the other)?

AST 1: only get preprocess code (groovy, etc)
AST 2: only get script (no preprocess code left)

The reason is because the script gets additions from preprocessing code :\

With this, there would have to be two lexer grammars and two parser grammars :eek:.

edit
example

JASS:
#integer i = 0
#while (i++ < 5) {
    integer var$i = $i
#}

//outputs
//integer var1 = 1
//integer var2 = 2
//integer var3 = 3
//integer var4 = 4
//integer var5 = 5
With block style

JASS:
foo() {
    #{ //#, when applied to a block, turns the entire block to preprocessor.
        //The first bit of code I had isn't legal, it was just to show what I meant ;P
        integer i = 0
        while (i++ < 5) {
            -> integer var$i = $i //no idea what the syntax should be for going back to script
            //could also use ->{ } for entire blocks ;)
        }
     }
}

//outputs
function foo takes nothing returns nothing
    local integer var1 = 1
    local integer var2 = 2
    local integer var3 = 3
    local integer var4 = 4
    local integer var5 = 5
endfunction
Could also be (suggested by muzzel)

JASS:
foo() {
    #{ 
        integer i = 0
        while (i++ < 5) {
            \#integer var$i = $i
        }
     }
}
So I guess this will be up for a vote

->
\#

or does anyone else have better ideas? The $ is out of the question ;P, that'd make absolutely 0 sense, lol.

edit
function keyword is required, realized that foo() { } could be interpreted as either a function call/block or a function declaration. Function keyword is only way to show dif between the two.

For lambda expressions.. lambda function() { }

Both lambda and function are necessary as you may have a function called lambda ; P.

edit
ok, so brackets are then defined as something that creates an anonymous scope. A block creates a 1 line scope (can accept a single statement). { } is a valid statement, and the { } thing can hold N statements.

Therefore, the following are valid

JASS:
function foo() return 5 //inside of the scope of foo
function foo() { return 5 } //the return 5 is in the anonymous scope of { }, which is inside of the scope of foo

# is the preprocessor operator. It accepts exactly 1 statement. Once again, the { } can be used for that statement ;), which would make all of the code inside of it preprocessor code.

The \# is a special thing for preprocessor code that goes back out to regular script. It accepts exactly one statement.

You can do some whacked things, like nesting (following is valid) # \# # \# # int i = 5

#{ } goes into the global scope for preprocessor. If you want it to be local, you need to do #{{ }}

Any line may be a statement or a block. Statements between blocks are put into the same function

JASS:
integer i = 5
print("$i")
function foo() { }
integer i = 5 //start of another anonymous function that is automatically run, would still throw a syntax error though as i is global

you may of course put a scope in for a statement
{
}

variables declared inside of this scope would now be local to that scope and would only be able to be accessed via the scope's name or within that scope (which in this case is anonymous)

JASS:
{
    integer i = 5 //still throws a syntax error since there are two globals named i within this scope
    print("$i")
    function foo() { } //this would only be seen within the scope
    integer i = 5
}

what about a named scope?

JASS:
name {
}

anything declared within it would be accessed via name.

the . is the access operator. It accesses things within a scope. A struct generates code within a scope named after the struct's name.

JASS:
struct hi {
}

//creates code local to the scope named hi

the only thing that matters for ordering are things that are initialized. The rest is intelligently ordered by symbol requirements.

The traditional vJASS way has been libraries. You could do intelligent ordering again, but it won't really work out well. Suppose a function creates a trigger, and a function inside of that trigger uses a symbol. Another trigger is created on the same event that initializes that symbol. When the first trigger fires, the symbol is not yet initialized :|.

init1
TrigA -> FunctionA -> Read Symbol

init2
TrigB -> FunctionB -> Init Symbol

where TrigA and TrigB run on the same event and init1 runs first.

I could do something like requiring scopes ;). Libraries would just be translated into scopes. This would only be used for ordering initializers, nothing else.
 
Last edited:
Level 17
Joined
Apr 27, 2008
Messages
2,455
So you plan to implement the wait stuff or not ?
If not, i will do it just like i said, and in ruby, but anyway once the code is done you can do copy/paste it in any language.
And well that's just a project i don't have the time right now for it.
 
Level 31
Joined
Jul 10, 2007
Messages
6,306
hm...

vJASS designed a lot of things wrong : |.

For one, variables declared in some scopes are only local to those scopes when there is an access modifier. In others, they are local to the scope w/ or w/o the access modifier (library/scope vs struct).

For two, he uses _ instead of . -.-

I guess this will have partial compatibility with vJASS >.<.

I'll probably add a using or something so that you won't have to type the scope name ;). structs are scopes too :|, so I'll have to do some pondering to do the design right =). I guess we could have dif types of scopes : o.

For scopes, variables are public by default. You would access the var or w/e with scopename.fieldname. For { } scopes, you would just access it w/o the scope name.

Now the next question is auto run code in a script like this

JASS:
//not in anything
string m = "hi"
print(m)

or this
JASS:
{
    string m = "hi"
    print(m)
}

would string m be global or local? It depends on whether or not things outside of the block or inside of a function trying to use it.

The rule is that if m is used in any block other than the block it is declared in, it will be made global. Blocks are only merged if they are in the same scope. If they are not, they are their own functions. This is because of op limit. In the above 2 situations, m would be local. However, if m was used in another scope (be it a function, a nested { }, or an external { }) it would be global.

If you had Trigger 1 and Trigger 2 with the following code
JASS:
print(m)
JASS:
string m = "foo"
print(m)

It would turn into this
JASS:
function i takes nothing returns nothing
    local string m = "foo"
    call DisplayTimedTextToPlayer(GetLocalPlayer(),0,0,60,m)
    call DisplayTimedTextToPlayer(GetLocalPlayer(),0,0,60,m)
endfunction

Now given that m is never changed, it would actually turn into

JASS:
function i takes nothing returns nothing
    call DisplayTimedTextToPlayer(GetLocalPlayer(),0,0,60,"foo")
    call DisplayTimedTextToPlayer(GetLocalPlayer(),0,0,60,"foo")
endfunction

These are merged into one function because they are in the same scope (the global scope).

If you instead had this
JASS:
{
    print(m)
}
JASS:
{
    string m = "foo" //public by default
    print(m)
}

It would then be this

JASS:
globals
     string m = "foo"
endglobals

function i takes nothing returns nothing
    call DisplayTimedTextToPlayer(GetLocalPlayer(),0,0,60,m)
endfunction

function b takes nothing returns nothing
    call DisplayTimedTextToPlayer(GetLocalPlayer(),0,0,60,m)
endfunction

Or rather this

JASS:
function i takes nothing returns nothing
    call DisplayTimedTextToPlayer(GetLocalPlayer(),0,0,60,"foo")
endfunction

function b takes nothing returns nothing
    call DisplayTimedTextToPlayer(GetLocalPlayer(),0,0,60,"foo")
endfunction
 
Last edited:
Level 31
Joined
Jul 10, 2007
Messages
6,306
Ok, howdy all again. Sry, I have another update. I'm taking an entirely different approach with this now. I've decided that vJASS sucks, so I'm starting over from the JASS level. This will not be compatible with vJASS at all : |. Blame Vexorian.

symbols
A symbol, regardless of type, can't be reused except in the case of shadowing.

JASS:
foo {
    integer foo //works
}

function foo() { } //doesn't work

foo.foo = 5 //perfect

scope
A scope is a local space that can run code and so forth. Symbols within a scope are always public without an access modifier. If the scope is anonymous, they are accessed w/o a scope name (as if they are in the global scope). If the scope is not anonymous, they are accessed via the scope name.

JASS:
scope
endscope

scope
end

scope { }

{ }

scope hi
end

hi {
    ho {
        {
             integer m //hi.ho.m
        }
    }
}

type
JASS works off of types, not structs. As a result, the syntax will be type, not struct.

To simply declare a new type, you use the regular JASS syntax
type m extends integer

To declare/expand a type, you use the vtype keyword instead. This must be done as using the type keyword will result in an ambiguous grammar.

JASS:
vtype m extends integer { }

vtype m extends integer
endvtype

vtype m extends integer
end

vtype unit extends widget integer i

The vtype stands for virtual type. vtype expects 1 statement, whether that statement be a scope or a single statement. Two vtypes of the same name must be identical in their extension. If they both extend two different things, an error will be thrown. If an extends is not used, then the vtype will extend integer by default.

vtype is an expansion of scope in that it allows some new features, such as instantiation.

If two vtypes are the same, they are merged. In the same way, if two scopes are the same, they are also merged.

JASS:
vtype test {
    integer m
}

vtype test {
    integer o
}

//test.m
//test.o

vtype unit extends widget {
    function getLife() { return GetWidgetLife(this) }
}

//local unit u = CreateUnit(...)
//call print(u.getLife())

When a vtype is declared, it may be polymorphic.

JASS:
poly vtype m { }

In this case, when anything extends m, polymorphism will be supported.

You may apply the poly keyword to functions too. What this will do is make a function polymorphic for a vtype if that vtype isn't polymorphic.

No primitive types are polymorphic. A vtype extending off of anything may be polymorphic or non-polymorphic itself.

A vtype may also be static. However, the static keyword is for nested vtypes in which you don't want the nested vtype to be linked to the enclosing vtype.

JASS:
vtype o {
    vtype b { //is in the scope of an instance of o
                  //o om = new o()
                  //o.b omb = new om.b()
    }

    static vtype m { //is in the scope of o
    }
}

types may also have fields, functions, and properties

JASS:
vtype bleh {
    //fields
    integer m = 2
    static integer m2 = 3

    //function
    function foo() { }

    //static function, just in the scope of bleh
    static function foo2() { }

    //property
    property i { //getter
        return m
    }
    property i = integer v { //setter
       m = v
    }
    static property p {
        return "foo"
    }
    static operator bleh b1 + bleh b2 { }
    //property syntax follows expression syntax

    operator += bleh b { }
    operator [integer i] { }
    operator [integer i, integer b][integer o] { }
    //bleh b
    //b[1,6][3]

    //etc, all of the syntax for operators should be fairly obvious
}

//bleh b = new bleh()
//print(b.i)
//b.i = 4
//print(bleh.p)

The allocator, deallocator, constructor, and destructor may be overwritten. When overwriting constructor/destructor, no allocator or deallocator will be created unless they are used.

JASS:
vtype rawr {
    static function allocate() { } //may use allocate
    function deallocate() { } //may use deallocate

    static function create() { } //may use .create or new
    function destroy() { } //may use .destroy or delete
}

//the above code overwrites allocate, deallocate, create, and destroy
//they are overwritten so long as the symbols are used
//params do not matter for allocate or create

You may also declare things outside of a vtype.

JASS:
integer m._i = 4
property m.i { return 5 }
property m.i = integer v { set _i = v }
function m.o() { }
static function m.o(unit u) { } //function overloading

variables
You do not have to declare variables, you can use them on the fly. They will automatically be created and their type will be inferred.

JASS:
i = 5 //declares an integer i and initializes it to 5
i = 5.1 //integer is now changed to real
i = CreateUnit(...) //error

Symbols will be recycled for different scopes within functions to minimize variable declarations.

JASS:
function foo() {

{
    private unit m //creates symbol m and assigns it to id firstId

    set m = null
} //releases id firstId
{
    private unit o //creates symbol o and assigns it to an id
                        //firstId can be used since it is for type unit, so
                        //it uses that

    set o = null
}

}

The resulting code
JASS:
function foo takes nothing returns nothing
    local unit a
    set a = null //m
    set a = null //o
endfunction

typecast
uses (type)var

(type) expects an atom. The atom may be ( ) ;)

this just makes me life easier with the parser grammar

JASS:
vtype integer {
    property (string) {
        return I2S(this)
    }
    function toString() { return (string)this }
} //(string)5 -> "5"
   //5.toString() -> "5"

order of initialization
This is pretty important.

A scope may require another scope. This is not for code ordering. This is only for ordering of initialization. If a scope isn't required by anything, its initializers are just put wherever. Initialization order can't be intelligently determined :(.

JASS:
ohg {
}

fms requires ogh {
}

keeping a function even if it's "not" used
Sometimes functions may be used by ExecuteFunc.

To keep a symbol so that it's never removed, just write keep

keep function foo() { }

lol...

debug
debug keyword can be put in a line for debug mode only. This works for both preprocessor code and regular code.

DEBUG_MODE will be defined as a preprocessor variable.

preprocessor perks
The preprocessor will be able to access any and all symbols for a given scope. Preprocessor will be able to work within the scope that it's currently in.

Symbols will have such functions as .exists and will be defined as variables. You will be able to check if a method or a variable exists. You will also be able to check its supertype (variable vs function vs etc) and its type (integer, function return type, etc).

If you want to create a preprocessor function for a module, or a preprocessor library for writing modules.

JASS:
#{
    //add stuff to vtype code :o
    poly vtype vtype {
        dictionary moduleTable //could also add non-preprocessor code
    }
    poly vtype module {
        static function create(string name) {
            if (external.vtype.moduleTable[name]) return

            external.vtype.moduleTable[name] = true

            //external = caller scope location
            //internal = current scope location

            //vtype = next highest vtype scope
            //moduleTable = the moduleTable added by above vtype
            //name = name of module
        }
    }
}

access modifiers
script
-internal (accessible by current file/trigger)
-protected (accessible by current vtype and extending vtypes)
-private (accessible by current scope)
-public (accessible anywhere)

access modifiers may also be applied to extensions

vtype o extends private integer //all of the standard integer operations can only be used within o
//this is the default extension method

vtype o extends integer //public
vtype o extends private integer //children

no internal for extensions

inline

inline function foo() { return 5 } //inlined no matter what

operators
++ (suffix/prefix), -- (suffix/prefix), *, +, -, /, +=, -=, *=, /=, =, [], ., #, $, new, delete, (type), and, or, not

There are additional preprocess operators. These operators may also be overloaded in regular script vtype.

>>, <<, >>>, &, |, ^, >>=, <<=, >>>=, &=, |=, ^=, ~

JASS:
vtype integer {
    static operator integer i << integer i2 { return i*R2I(Pow(2, i2) + .5) }
}

preprocessor natives
preprocessor will have natives for working with the script and the map objects (units, items, etc)

preprocessor vtypes are just like script vtypes

preprocess has one vtype for each structure, so you can *add* code generation or whatever you like. Removing/overriding would break behavior.

type
vtype
scope
function
loop
while
do while
for
operator
atom
variable
property

other changes
No libraries
No structs (use vtype instead)
No strange : syntax (nothing, that was just weird)
No //! (use # instead)
No external blocks (use preprocessor natives)
No textmacros (use preprocessor functions instead)
No modules (use preprocessor functions instead)

Oh, and as a result of the lexer, you can do some whacked things

JASS:
function foo takes nothing returns item
    return 5 //works, because the returns item is 100% ignored, lol...
endfunction


Well, hopefully everyone is ok with the syntax and the changes :). I'm sorry that I couldn't make it work with vJASS, vJASS is just too messed up. methods vs functions? whacked typecast that is identical to a function? Introducing structs to JASS rather than working off of types? extends array? c'mon, lol...

anyways, I'm going to organize everything and plan out this entire language again, then update the lexer with the correct changes and move on to the parser. I have been giving this a lot of thought ^)^.
 
Level 31
Joined
Jul 10, 2007
Messages
6,306
This, unlike vJASS and Wurst, builds off of the JASS style. Wurst is the biggest offender for that. While it builds off of the JASS style, it also offers the flexibility to let you code the way you want to code and have complete optional control over the output of your code ;).

vJASS did some weird mix of Java, JASS, and wtf, lol.

Now, what I could do are vjass code blocks as vJASS is different enough form JASS to merit its own language. Things like structs are an abomination ; |.

Would vJASS code blocks be a nice compromise? Inside of them, you could only have vJASS :eek:, minus the external blocks ofc.

JASS:
vjass
endvjass

vjass
end

vjass { }

Also, the ExecuteFunc thing can't really be searched for reliably because of things like string concatenation, variables, and player input.

edit
I'll do vjass blocks. Problem solved ^)^. I could do zinc blocks too, but I don't think anyone uses zinc. Heck, I'll even do the external blocks ;O.

For the external blocks, I'll merge everything into a single file, so be sure to put your code in do blocks and make the stuff local, otherwise you could have some nasty collisions ;).

You could say that it's my own thing that should go into special blocks and vJASS deserves to run alongside regular JASS, but my own thing runs closer to JASS than vJASS does : \. vtypes follow the jass paradigm more closely than structs ever will >.<.
 

Cokemonkey11

Code Reviewer
Level 29
Joined
May 9, 2006
Messages
3,522
This, unlike vJASS and Wurst, builds off of the JASS style. Wurst is the biggest offender for that. While it builds off of the JASS style, it also offers the flexibility to let you code the way you want to code and have complete optional control over the output of your code ;).

vJASS did some weird mix of Java, JASS, and wtf, lol.

Now, what I could do are vjass code blocks as vJASS is different enough form JASS to merit its own language. Things like structs are an abomination ; |.

Would vJASS code blocks be a nice compromise? Inside of them, you could only have vJASS :eek:, minus the external blocks ofc.

JASS:
vjass
endvjass

vjass
end

vjass { }

Also, the ExecuteFunc thing can't really be searched for reliably because of things like string concatenation, variables, and player input.

edit
I'll do vjass blocks. Problem solved ^)^. I could do zinc blocks too, but I don't think anyone uses zinc. Heck, I'll even do the external blocks ;O.

vJass blocks would be decent.

Also, the ExecuteFunc thing can't really be searched for reliably because of things like string concatenation, variables, and player input.

Totally not an excuse. Just concatenate the string inside each ExecuteFunc call and flag the corresponding function. If you can't search a string fast enough you're doing it wrong.
 
Level 31
Joined
Jul 10, 2007
Messages
6,306
The vJASS won't remove any functions, k? vJASS will behave in the way you'd expect it to behave, except that I'll do the nice code ordering, better allocators, and other nice background things that won't mess with your code. You'll get all of the advanced stuff in JASSX :).

vJASS will be able to use JASSX and JASSX vJASS ^)^. It'll all be put into the same structures and stuff, so all of the code will boil down to the same thing. I'm not going to keep it in an AST because the Antlr AST would be painful to work with. To perform transformations on the AST = rebuilding the entire thing. Not fun.

edit
well, reworking the primary JASS language thing to completely follow the JASS paradigm.

So JASSX will be the nice { } and so on. vJASS will be vJASS. JASS will be JASS with some extended features. All of the syntax in JASS will follow the JASS style.

For example, rather than vtype (I'm removing that altogether), it'll be something like this

JASS:
type ds extends private integer //creates type ds and scope ds

//all scopes of the same name in the same scope will be merged
scope ds
end

//actually, this is still bad as scope is missing the signature
//maybe scope will accept a signature instead ;)
//this would allow you to use scopes to merge function code from different places together too

There will be no *optional* keywords. Rather than being optional, each keyword will do something. The only keyword I can't figure out is set : |. That keyword just seems totally useless to me and it breaks thing like i++.
 
Last edited:

peq

peq

Level 6
Joined
May 13, 2007
Messages
171
So what exactly is the difference between structs/classes and vtypes? One difference I saw was the possibility to split a single vtype into several code blocks. Is there more?

What is the meaning of vtype unit extends widget integer i?
 
Level 31
Joined
Jul 10, 2007
Messages
6,306
Oh woops, the widget integer was a typo. It shoulda been vtype unit extends widget ;).

Well, as I said in the last post, I removed vtypes. Vtypes were essentially just structs. However, JASS relies on types, not classes/structs, so I decided to follow that instead.

The new layout gets rid of vtypes and just uses types.

Here are my notes for the updates

I'll write more later (still missing stuff) and further organize it. It's coming along nicely. My only problem is how to do i++ syntax cuz of the damn useless set keyword. The call keyword is useless too >.<.

I've settled on 3 different versions (JASSX and vJASS will require blocks as they don't follow the JASS paradigm)

JASS: follows JASS paradigm
JASSX: less wordy, uses a lot more symbols
vJASS: it's vJASS

Hopefully the amount of thought that I've put into this redesign is evident ;).

I hope that others like the direction that the JASS version is going as much as I do ^_^

Also, rather than virtual functions, I should make them poly functions or something. virtual shouldn't have two different meanings :\, that's poor design. It's like the * operator in c++ has 3 different meanings -.-.

I also forgot <, <=, >, >=, ==, and !=. I'll add them in later, too tired.

I will say that block design like JASS, Lua, etc is flawed. I worked around the flaws as best I could ;). I'll still need to find an alternative to ${ } for string interpolation. The { } does not follow the JASS paradigm : |.

JASS:
global integer i	//explicitly global variable

globals
	integer i	//explicitly global variable
endglobals

local integer i		//explicitly local variable

locals
	integer i	//explicitly local variable
endlocals

integer i		//dynamic, either local or global

//a local variable is defined as a variable that only appears in one function

//a scope is a symbol space
scope //anonymous scope
endscope

//named scope
scope label
endscope

//scopes may link with a single signature

//a virtual scope is a scope that doesn't actually exist
//it is linked to another scope

virtual scope label link native label takes arguments
virutal scope label link function label takes arguments
virutal scope label link type label
virutal scope label link property label
virutal scope label link property label=
virutal scope label link operator expression //scope operator integer + integer
virutal scope label link scope label //may not link to virtual scope

//they may still be required by other scopes
//a virtual scope shares the same space as all other virtual scopes linked to the signature

//the . is the lookup operator. It will look up something within a scope

//two scopes with the same label are merged into the same space

scope hi
end

scope hi
end

//if two virtual scopes of the same name link to two different things, a syntax error will occur

virtual scope hi link function Foo takes nothing
end

virtual scope hi link function Boo takes nothing //syntax error
end

//only one virtual scope needs a link
virtual scope hi link integer //linked to integer
	private integer m
end

virtual scope hi //linked to integer
end

virtual scope boo link integer //linked to integer
	private integer m //syntax error
end


//two scopes of the same name must be the same

virtual scope hi link type integer
end

virtual scope hi //success 
end

scope hi //syntax error
end

virtual scope hi link type integer //success
end

virtual scope hi link type unit //syntax error
end

//the virtual scopes themselves have no code
scope test
	function Foo takes nothing
	end
end

virtual scope b link scope test
	function Gr takes nothing
	end
end

call test.Foo() //success
call test.Gr() //success
call b.Gr() //syntax error

//scopes may use, require, import, and create extensions of other scopes depending on the scope
//there are 5 types of scopes
//
//	function
//	type
//	property
//	operator
//	scope
//
//of these types, the following have a set lifetime
//
//	function
//	property
//	operator
//
//the following have an infinite lifetime
//
//	type
//	scope
//
//when a function, type, property, or operator are declared, they declare a scope using the label for code
//all blocks have scopes
//types are special in that they do not declare a block by themselves

//an explicit function signature
function hi takes nothing returns nothing
end

//a function without a "returns" has a dynamic return type that is automatically determined
//by what it returns inside of the code

function Hi takes nothing //this won't return anything
end

function Hi takes nothing //this will return an integer
	return 5
end

//a type is a new variable type following standard JASS syntax
type newtype

//access modifiers can be applied to extensions
//
//	public
//		can be seen from anywhere
//
//	protected
//		can be seen by children
//
//	private
//		can be seen only within the direct scope
//
//	internal
//		can be seen within the file or trigger

//this is generally what types will be like
type newtype extends private integer


//when working with types, the primitive or native type they work with depends on
//what they extend

type newtype extends private unit

//newType in this case would work with units
//types, like variable types, should be all lower case

//in order to write code for a type, merge into the scope

type newtype extends private unit

virtual scope test link type newtype
end

//only one scope may be linked to a given type

//code within a type may be static or non-static
//static code will be linked to the scope
//non-static code will be linked to an instance of the type

virtual scope test link type newtype
	fucntion GetLife takes nothing
		return GetWidgetLife(this)
	end

	static function Enumerate takes real x, real y, real range
		group g = CreateGroup()

		call GroupEnumUnitsInRange(g, x, y, range)

		return g
	end
end

newtype test = new newtype()
call Print(test.GetLife())
group g = newtype.Enumerate(5, 5, 60)

//functions may also be written specifically for a scope or virtual scope

scopename function FunctionName takes arguments
end

//for example, using newtype from before

static test function Enumerate takes integer unitTypeId returns group
	group g = CreateGroup()

	call GroupEnumUnitsOfType(g, unitTypeId)

	return g
end

group g = newtype.Enumerate('hfoo')

//non-static
test function test takes nothing
end

//the scope signature goes before the block

//scopes may be nested

scope test
	scope test
		integer i
	end
end

//recall that the . operator is the lookup operator

call Print(test.test.i)

//what about types?

type test extends private integer
virtual scope test link type test
	static type test extends private unit
	virtual scope test link type test
		function getName takes nothing return GetUnitName(this) end
	end
end

test.test myVar = new test.test() //the test symbols used refer to types, not virtual scopes

//a scope may require another scope  or virtual with the require operator

scope oh
end

scope meh
	require oh
end

//the require operator is only used for code initialization
//scopes explicitly defined within a scope will require everything
//that the scope requires

//consider the following

function Foo takes nothing
end

scope
	require meh //this could be placed in scope oh
	//everything within this scope will require the meh scope

	virtual scope oh link function Foo takes nothing
		return 5
	end
end

virtual scope meh link function Foo takes nothing
	call Print("hello")
end

//calling Foo would first display hello and then return 5

//the use operator is used to use all symbols of a scope
//the lookup operator (.) will not be required

scope test
	integer i
end

scope oh
	use test

	set i = 5 //correct
	set test.i = 5 //correct
end

scope m
	set i = 5 //syntax error
end

scope oh
	set i = 5 //still correct, this merged with the other scope
end

//the import operator is used to import the symbols of a type scope
//to another type scope
//if type A imports type B, the instances of A will be used for the symbols from B
//import does not use a scope, it uses a type****

type a extends private integer
type b extends private integer

virtual scope o link type a
	integer i

	function foo takes nothing
		return i*5
	end
end

virtual scope o2 link type b
	import type a

	local b br = new b()
	set br.i = 5 //correct
	call print(b.foo()) //prints 25
end

//symbols from the import statement can be overwritten
//using the previous example

virtual scope o3 link type b
	import type a

	private function foo takes nothing
		return i*3
	end

	local b br2 = new b()
	set br2.i = 5
	call print(br2.foo()) //prints 15, o2 would also print 15
end

local b br = new b()
set b.i = 5
call print(b.foo()) //syntax error, foo is private
//foo would be private unless a scope linked to b had a public foo

//an extension type variable is used to point to an instance of another type
//it's similar to import except that it uses the value inside of the extension

type a extends private integer
type b extends private integer

virtual scope a link a
	integer i
end

virtual scope b link b
	a extension ext
end

b test = new b()
set b.ext = new a()

set b.i = 5 //b.ext.i

//a look at putting a function into some arbitrary scope that does
//not exist

test.test2.test3 function meh takes nothing
	return 5
end

call Print(test.test2.test3.meh()) //prints 5

//properties are special functions that act like variables
//there are two forms

property label
	//code
end

property label = vartype label
	//code
end

//for example

type b extends private integer

virtual scope b link b
	private integer _i

	property i //getter, must return something
		return _i
	end

	property i = integer value //setter, can't return something
		set _i = value
	end

	//properties, like anything else in a type, may also be static
end

b test = new b()
set test.i = 5
call Print(test.i)

static b property g
	return 5
end

call Print(b.g) //prints 5

//operators are things like +, -, etc
//operators are the reason why the following syntax isn't used
//
//	//where a is a scope
//	function a.Foo takes nothing
//	end


virtual scope a link integer
	private integer v

	//all operators
	static operator integer i + integer i2
		return i + i2
	end
	static operator integer i - integer i2
		return i - i2
	end
	static operator integer i / integer i2
		return i/i2
	end
	static operator integer i * integer i2
		return i*i2
	end
	static operator integer i & integer i2
		return //?
	end
	static operator integer i | integer i2
		return //?
	end
	static operator integer i ^ integer i2
		return //?
	end
	static operator ~ integer i
		return //?
	end
	static operator integer i << integer i2
		return //?
	end
	static operator integer i >> integer i2
		return //?
	end
	static operator integer i >>> integer i2
		return //?
	end

	static operator integer i < integer i2
		return (super)i < (super)i2
	end
	static operator integer i <= integer i2
		return (super)i < (super)i2
	end
	static operator integer i > integer i2
		return (super)i > (super)i2
	end
	static operator integer i >= integer i2
		return (super)i >= (super)i2
	end
	static operator integer i == integer i2
		return (super)i == (super)i2
	end
	static operator integer i != integer i2
		return (super)i != (super)i2
	end

	operator += integer i
		set v = v + i
	end
	operator -= integer i
		set v = v - i
	end
	operator *= integer i
		set v = v*i
	end
	operator /= integer i
		set v = v/i
	end
	operator &= integer i
		//code
	end
	operator |= integer i
		//code
	end
	opreator ^= integer i
		//code
	end
	operator >>= integer i
		set v = v/R2I(Pow(2, i) + .5)
	end
	operator <<= integer i
		set v = v*R2I(Pow(2, i) + .5)
	end
	operator >>>= integer i
		//code
	end

	//operator (integer)
	//operator (real)
	//any type
	//if the operator does not exist, no typecast is performed other than a change of scope
	operator (string)
		return "foo"
	end

	operator this++
		set v = v + 1
		return v - 1
	end
	operator ++this
		set v = v + 1
		return v
	end
	operator this--
		set v = v - 1
		return v + 1
	end
	operator --this
		set v = v - 1
		return v
	end

	//any form of array
	//can be static as well
	//
	//	operator [integer i]
	//	operator [integer i, integer i2]
	//	operator [integer i][integer i2]
	//	operator [integer i, integer i2][integer i3]
	//	operator [integer i] = integer v
	//	operator [integer i, integer i2, integer i3][integer i4][integer i5] = integer v
	//

	static operator integer i and integer i2
		if (i == 0 or i2 == 0) then
			return 0
		end

		return 1
	end
	static operator integer i or integer i2
		if (i != 0 or i2 != 0) then return 1 end return 0
	end
	static operator not integer i
		if (i == 0) then
			return 1
		end

		return 0
	end

	//can take whatever and be overloaded like a regular function
	//if this is non-static, it is automatically allocated
	//if it is static, it isn't
	operator new takes nothing
		return this
	end

	static operator new takes nothing
		local integer this = allocate()

		return this
	end

	//if any form of new is created, the default empty new is lost
	
	//if this is non-static, it is automatically deallocated
	//if this is static, it isn't
	//can't be overloaded
	operator delete takes nothing
	end

	//alternative
	//static operator delete takes integer this
	//	call deallocate()
	//end
end

//functions that can be overrided from type
//if either of these are overwritten, allocators and deallocators are lost

static function allocate takes nothing
function deallocate takes nothing

//inline
inline function Foo takes nothing //inline is forced
	return 5
end

keep function Foo takes nothing //function is kept no matter what
end

//symbols are kept from strings so long as they can be derived from that string statically
//this means only set-once variables that originate from literals
call ExecuteFunc("${function Foo}")
call ExecuteFunc((string)function Foo)
call ExecuteFunc("Foo")

//runs preprocess code
preprocess
end

//debug only code
debug
end

//used inside of preprocess code to go back to script
script
end

//automatically determine signature of constant code
//anonymous function support
constant code c = 	function takes nothing
				return 5
			end

var i = c()

//use triggers for non-set once code
set c = function takes nothing
	end

call c() //trigger

//when no signature is provided, expects takes nothing returns nothing

function hi takes integer i, integer i2 returns integer
	return i + i2
end

hi code c = 	function takes integer m, integer m2 returns integer
			return m*m2
		end

c = function hi

call c(5, 6) //11

//virtual keyword may be applied to functions, operators, and properties within a type scope
//anything virtual will run off of triggers
virtual function Foo takes nothing returns nothing
end

type a extends private integer
virtual scope a link type a
	virtual function Foo takes nothing returns nothing
		return "a"
	end
end

type b extends a //public
virtual scope b link type b
	virtual function Foo takes nothing returns nothing
		return "b"
	end
end

a test1 = new a()
a test2 = new b()

call Print(test1.Foo()) //"a"
call Print(test2.Foo()) //"b"

//example of how scoping works

type a extends private integer

virtual scope o link type a
end

scope
	//access modifier on a one-liner refers to this scope
	//Foo is accessed from the target scope though
	private o function Foo takes nothing
	end
end

//The $ operator is used to interpolate things one level up
//string -> script -> preprocessor

string name = "hi"
call Print("$name") //prints hi

preprocess string name = "myVar" end
$name = "$$name" //myVar = "myVar"

loops
	loop
	for loop
	while loop
	do while loop

loop keywords
	exitwhen expression
	break
	continue

//example of some dynamic code with preprocess
preprocess
	type module

	virtual scope module link type module
		private static dictionary<signature> flag = new dictionary<signature>()

		protected virtual function createScript takes nothing returns nothing
		end

		static operator new takes signature sig
			if (flag[sig]) then return (module)0

			call createScript()

			return (module)1
		end
	end
end

preprocess
	type mymodule extends module

	virtual scope mymodule link type mymodule
		protected virtual function createScript takes nothing returns nothing
			integer i = 0

			while (i < 10)
				script
					public static string str$i = "str$i"
				end
			end
		end
	end
end

type test extends private integer
virtual scope test link type test
	preprocess new mymodule(type test) end

	//the above creates 10 string variables, str0 through str9

	//attempting to run it a second time will do nothing
	preprocess new mymodule(type test) end
end

//templates are created with < > and can be applied types, functions, operators, and properties
//< > can accept signatures or labels
//
//the signature type is any signature
//
//template arguments are defined in both the preprocessor and the script and are constant

type<type T> test extends private integer //type T may also be made more explicit with extends
					  //for example, type T extends list, meaning that T must be
					  //a type of list, including list itself
					  //variable signatures are also accepted, like integer array VAR

virtual scope test link type test<type T> //signature includes the template
	T value
end

test<type integer> t = new test<type integer>()
set t.value = 5


//The abstract keyword when applied to a type means that the type can't be used except for by other types.
//The sealed keyword when applied to a type means that the type can't be extended.
//The constant keyword when applied to a type means that all members of that type must be static and constant (like enums)
//when constant is applied to something, it can't change and it can only use constant code

//the super keyword is used in types to access the parent type

type a extends private integer
type b extends private a

virtual scope a link type a
	function foo takes nothing
		return "a"
	end
end

virtual scope b link type b
	function foo takes nothing
		return super.foo() //"a"
	end
end

//signature is a primitive type that holds signatures
//
//signatures include
//
//	function
//	scope
//	type
//	property
//	operator
//
//signatures can be used in various places
//the label of a signature can be used as a value (signaturetype label)
//the raw signature can also be used
//the signature type can be worked with like any other type
//
//the signature type includes the following functions and operators
//
//	(string)
//	scope //gets signature of enclosing scope
//	.exists //does the signature exist?
//
//the top level scope is called global

//expressions are simplified automatically
//
//not a or not b
//	not (a and b)
//
//3 + 4*5
//	23
//
//3 + a*4*3 + 4*foo()
//	3 + 4*(a*3 + foo())
//
//2*a + 3*a
//	5*a
//
//when an expression is simplified to a single atom that is not a function
//and the variable using that expression only ever uses that expression, the expressoin
//is inlined and the variable is removed unless that variable is specifically used for events etc
//
//function's are the same way
//
//an inlined function that is not simple enough to normally do inlining will create local variables
//to hold function calls

//code is reordered based on usage

function foo takes nothing
	call oh() //will work, oh is placed in front of foo
end

function oh takes nothing
end

//cyclical requirements will throw a syntax error

function foo takes nothing
	call oh()
end

function oh takes nothing
	call foo()
end


//closures

function rake takes nothing
	integer k = 5

	function far takes nothing
		set k = 6
	end

	call far()
	call Print(k) //prints 6

	call TimerStart(CreateTimer(), 1, false,
			function takes nothing
				call DestroyTimer(GetExpiredTimer())
				call Print(k) //prints 9
			end)

	set k = 9								
end

//set takes an expression (it really should be evaluate..)
//
//set i++
//set i--

//integer forms
//
//    	ascii: 'aaaaaaaaaaaaa'
//    	hex: 0x5
//	octal: 01
//	binary: 0b1

//variables that are not explicitly local or global will be local or global depending on use

integer i = 4 //local
set i = 5

integer m = 4 //local
function boo takes nothing
	set m = 6
end

integer o = 3 //removed
function oh takes nothing
	integer o = 4
end

integer p = 9 //global
set p = 12
function oh takes nothing
	set p = 3
end

//however, global and local variables don't really hold a place anymore

function rake takes nothing
	integer k = 5 //local variable

	//this is technically public, but it only exists for the lifetime of rake, so
	//it can't really be called outside of this instance of rake
	function far takes nothing
		//as no variables are copied, this just passes in the original closure
		//if there were new variables, it would create a new closure and give it old
		//closure + variables
		function far2 takes nothing
			call Print(k)
		end

		if (++k < 10) then
			call far()
		end
	end

	integer i = 4

	//a closure is created for this instance of rake
	//all locals used in far are copied to this closure
	//the closer is passed into far
	//far then uses the closure to work with the variables
	call far()

	//closure c = new closure(k)
	//call far(c)
	//	if (++c.k < 10) then call far(c) end
	//set k = c.k

	//i is not copied because far does not use it

	call Print(k) //prints 10

	//closures running on a timer or trigger or anything else are copied for those handles
	//via a hashtable
	call TimerStart(CreateTimer(), 1, false,
			function takes nothing
				call DestroyTimer(GetExpiredTimer())
				call Print(k) //prints 9

				call far() //passes in closure that this function has
				//if there were multiple timers, triggers, and so on from this function, they'd
				//all share the same closure
			end)

	set k = 9								
end

//type nesting is the same way, except that rather than closures, types are passed in
//this is because the type itself can serve as a closure
//as such, a non-static type nested inside of a type must be created a special way

type outside extends private integer
virtual scope outside link type outisde
	type inside extends private integer
end

outside test = new outside()
outside.inside test2 = new test.inside()


//preprocessor includes object type, which works with objects
//object types include units, items, doodads, etc

unit footman = unit['hfoo'] //access footman object

unit test = new unit('hfoo') //create a new object based on footman and return id
set test.life = 5000 //or w/e, properties are based off of object properties

//functions may take references
function hi takes reference integr i
	set i = 5
end

integer i = 4
call hi(i) //i is now 5
 
Last edited:
Level 31
Joined
Jul 10, 2007
Messages
6,306
All of the code in that JASS block is JASS ;).

After I finish laying out the syntax and API, I'll be doing some usability tests. I'll then work out JASSX, do some more usability tests with them together, and then I'll finally start on redoing the lexer, parser, and the java ;O.

I'm doing syntax publicly so that people can voice their opinions if I screw something up ^)^.

edit
references anyone?

JASS:
function Foo takes reference integer i
    set i = 5
end

integer m = 4
call Foo(m) //m is now 5 o-o
 

Cokemonkey11

Code Reviewer
Level 29
Joined
May 9, 2006
Messages
3,522
All of the code in that JASS block is JASS ;).

After I finish laying out the syntax and API, I'll be doing some usability tests. I'll then work out JASSX, do some more usability tests with them together, and then I'll finally start on redoing the lexer, parser, and the java ;O.

I'm doing syntax publicly so that people can voice their opinions if I screw something up ^)^.

Okay, so JASSX is the set of directives (code which creates JASS, kind of like text macros) that you mentioned?
 
Level 31
Joined
Jul 10, 2007
Messages
6,306
no, JASSX is more symbolic.


This is an example of JASSX. I winged the virtual scope syntax, so I don't know if we wanna keep that or not. JASSX code is still not set in stone as I haven't really started on it majorly yet. I'm aiming for lots of symbols and very few words. It should be a language that you can develop *very* quickly in.

Yes, I'm editing this every few seconds because I'm still working on the JASSX syntax ;o. I remember why I wanted ; to end every line now ^)^.

JASS:
jassx

type a : private b { } //scope can be written with the type
type b; //or without

foo() return 5;
int foo(int i) { return 5; } //explicit return type

{ } //anonymous scope
a { } //named scope

@b : type b { } //virtual scope with link

foo(); //function call
var c = 4;
c = 5; //variable set

#var i = 4; //preprocessor line
#{ } //preprocessor block
\#{ } //script block

end
 
Last edited:
Level 31
Joined
Jul 10, 2007
Messages
6,306
lmao

I'm designing all of this seriously ;)

edit
next draft : |

I did a usability test working on DDS and found some serious, serious flaws >.<. Not having modules killed me. It made the code harder to write and harder to use -.-. The new draft still has no modules because I hate exceptions and special structures. Instead, I added more tools for scopes that allows you to be the master of the universe! ;D

I removed a few things, like virtual scopes, but in place, I made scopes simpler.

Gotta love usability tests, they can make you redo some of your design.

As you'll see, I also improved the organization.

First block has all of the stuff I've rewritten. Second block has stuff I haven't gotten to rewriting yet.

I guess enums are useful as they have the auto-counter. I should add them.

So some changes

-scope mechanics
-operator syntax (left side of operator was always this, so.. I made operators non-static)
-type workings more defined (example output code included, it's beautiful)
-operator new
-operator delete
-abstract types (didn't exist, then was virtual, now is abstract)
-templates
-ternary
-override
-reference
-friend
-in/out
-for each
-for
-while

Eventually I'm going to start nailing on the preprocess code to get it well defined. I want to have a nice signature type and an API for getting signatures from scopes.

JASS:
/*
*	Comment
*
*	Comments may be either single line or delimited
*/

	//a single line comment
	
	/*
		a multi-line comment
	*/
	
/*
*	multi-line comments may be nested
*/

	/* /* hi */ */
	
/*
*	Statement
*
*	Every single line statement must end with either a new line or EOF.
*
*	A single line statement may be continued to another line with \.
*
*	Delimited statements include
*
*		1.	( )
*		2.	" "
*		3.	' '
*		4.	{ }
*/
	
/*
*	Scope
*
*	There are five different types of named scopes
*
*		1.	function scope
*		2. 	property scope
*		3.	operator scope
*		4.	type scope
*		5.	scope
*
*	Of these five types, they are split into the following name spaces
*
*		1.	function scope			A
*		2. 	property scope			B
*		3.	operator scope			C
*		4.	type scope				D
*		5.	scope					D
*
*	The reason why type scopes and scopes share the same space is because
*	they both utilize the lookup operator (.)
*
*/

	set hi.v = 5

/*
*	When a scope is used, the code inside of it is simply placed into the space of
*	that scope. There is no scope declaration, there is only scope setting. This
*	means that if two scopes are the same, the code inside of them share the same space.
*	However, there can still be differences between the two scopes (more later).
*/

/*
*	The scope may be anonymous or named
*/

	scope label
	end
	
	scope
	end
	
/*
*	Any scope of any type may be nested into any other scope of any type
*/

	scope
		scope rawr
			scope foo
			end
		end
	end

/*
*	Function Scope
*
*	A function scope is a scope with a limited lifetime. There are two special scopes
*	under the function scope.
*
*		1.	property scope
*		2.	operator scope
*
*	However, the three scopes do not share the same name space.
*
*	A function scope is accessed in the following manner
*
*/

	function label takes arguments returns type
	end

/*
*	An example of a function
*/

	function Hello takes nothing returns nothing
	end
	
/*
*	Functions may have either an explicit or implicit return type
*/

	function Hello takes nothing
	end
			
/*
*	The scope signature does not include the return type
*
*	If the same scope is accessed in two incompatible ways, the
*	scope can't be created. As such, a syntax error will occur.
*/

	function Hello takes nothing returns string
		return "hi"
	end
		
	function Hello takes nothing returns integer
		return 5
	end
		
/*
*	Note that an explicit return type will only accept that return type.
*
*	Implicit return types may work with explicit return types so long
*	as the implicit return types are compatible with the explicit return types.
*/

	//both of these return agents, so the scope is still valid
	function Boo takes nothing returns agent
		return CreateUnit(Player(0), 'hfoo', 0, 0, 270)
	end
		
	function Boo takes nothing
		return CreateItem('afac', 0, 0)
	end
			
/*
*	The function scope is used with the call keyword.
*
*	The parameters are passed in between the ( ).
*/

	call Boo()
			
/*
*	Please keep in mind JASS syntax for arguments.
*/

/*
*	Implicit return types return the compatible type among
*	types that the function returns.
*/

	function ReturnsWidget takes integer o
		if (o == 5) then
			return CreateUnit(Player(0), 'hfoo', 0, 0, 270)
		end
		
		return CreateItem('afac', 0, 0)
	end

/*
*	Unreachable statements are removed from functions
*/

	function ReturnsItem takes nothing
		if (false) then
			return CreateUnit(Player(0), 'hfoo', 0, 0, 270)
		end
		
		return CreateItem('afac', 0, 0)
	end
		
/*
*	Property Scope
*
*	The property scope is a function scope that acts like a variable
*
*	It has two forms
*/

	//getter, must return something
	property label
	end
	
	//setter
	property label = integer o
	end
		
/*
*	Example of properties
*/

	internal private integer m = 0
	
	property i
		return m
	end
	
	property i = integer o
		set m = o
	end
	
	set i = 4 //accessed just like a variable
	integer t = i
		
/*
*	The operator scope is a function that uses operator syntax
*
*	Keep in mind that any type can be used in the operators.
*	integer isn't being used for any particular reason.
*/

	//all operators
	//
	//static or non-static
	//
	//must return something
	operator + integer i
		return (thistype)((integer)this + i)
	end
	operator - integer i
		return (thistype)((integer)this - i)
	end
	operator / integer i
		return (thistype)((integer)this / i)
	end
	operator * integer i
		return (thistype)((integer)this * i)
	end
	operator & integer i
		return //?
	end
	operator | integer i
		return //?
	end
	operator ^ integer i
		return //?
	end
	operator ~
		return //?
	end
	operator << integer i
		return //?
	end
	operator >> integer i
		return //?
	end
	operator >>> integer i
		return //?
	end
	
	//static or non-static
	//
	//must return something
	operator < integer i
		return (integer)this < i
	end
	operator <= integer i
		return (integer)this <= i
	end
	operator > integer i
		return (integer)this > i
	end
	operator >= integer i
		return (integer)this >= i
	end
	operator == integer i
		return (integer)this == i
	end
	operator != integer i
		return (integer)this != i
	end
	
	//all operators
	//
	//static or non-static
	//
	//must return something
	reference operator = thistype i
		set this = i
		return this
	end
	reference operator += integer i
		set this = (thistype)((integer)this + i)
		return this
	end
	reference operator -= integer i
		set this = (thistype)((integer)this - i)
		return this
	end
	reference operator *= integer i
		set this = (thistype)((integer)this * i)
		return this
	end
	reference operator /= integer i
		set this = (thistype)((integer)this / i)
		return this
	end
	reference operator &= integer i
		//code
	end
	reference operator |= integer i
		//code
	end
	reference operator ^= integer i
		//code
	end
	reference operator >>= integer i
		return (thistype)((integer)this/R2I(Pow(2, i) + .5))
	end
	reference operator thistype reference this <<= integer i
		return (thistype)((integer)this*R2I(Pow(2, i) + .5))
	end
	reference operator >>>= integer i
		//code
	end

	//static or non-static
	//
	//typecast must be of a valid type
	//
	//	operator (integer)
	//	operator (real)
	//
	//a typecast operator is required for any type that isn't either
	//imported or extended
	//
	//any type may typecast to any other type that it extends without an operator
	//only non-virtual types may typecast to types that extend it
	//
	//must return the type
	//
	operator (string)
		return "foo"
	end

	//static or non-static
	//
	//must return something
	reference operator this++
		set this = (thistype)((integer)this + i)
		return (thistype)((integer)this - 1)
	end
	reference operator ++this
		set this = (thistype)((integer)this + i)
		return this
	end
	reference operator this--
		set this = (thistype)((integer)this - i)
		return (thistype)((integer)this + 1)
	end
	reference operator --this
		set this = (thistype)((integer)this - i)
		return this
	end

	//static or non-static
	//
	//any valid expression
	//
	//similar to properties
	//
	//	operator [integer i]
	//	operator [integer i, integer i2]
	//	operator [integer i][integer i2]
	//	operator [integer i, integer i2][integer i3]
	//	operator [integer i] = integer v
	//	operator [integer i, integer i2, integer i3][integer i4][integer i5] = integer v

	//static or non-static
	//
	//must return something
	operator and integer i
		if ((integer)this == 0 or (integer)i == 0) then
			return false
		end

		return true
	end
	operator or integer i
		if ((integer)this != 0 or (integer)i != 0) then
			return true
		end

		return false
	end
	operator not
		if ((integer)this == 0) then
			return false
		end

		return true
	end
	
	//static or non-static
	//
	//must return something
	operator ?
		if ((integer)this == 0) then
			return false
		end
		
		return true
	end
	
	//

	//can take whatever and be overloaded like a regular function
	//if this doesn't use override, it's automatically allocated and so on
	//if it does, it isn't
	operator new takes nothing
		
	end
	
	override operator new takes integer i
		set this = allocate()

		return this
	end

	//if any form of new is created, the default empty new is lost
	
	operator delete
	end

	//alternative
	//override operator delete
	//	call deallocate()
	//end

/*
*	Type Scope
*
*	The type scope creates a new variable type.
*
*	The primitive/native type it extends from dictates what variable type
*	it will work with.
*/

	type test extends integer
	//integer this
	
	type test2 extends unit
	//unit this
	
	type test3 extends widget
	//widget this
		
/*
*	It may have statements (either one or many)
*/

	type test2 extends integer scope
	end
	
	type test2 extends integer integer oh	//one-liner with member oh
		
/*
*	The label of a type may not share the same name as the label of a scope
*
*	This is because both of them use the same lookup operator
*/
		
	scope integer	//error
	end
	
/*
*	Access Modifier
*
*	public
*		can be seen from anywhere
*
*	protected
*		can be seen by extending types
*
*	private
*		can be seen only within the direct scope
*
*	internal
*		can be seen within the file or trigger
*		may be applied to other access modifiers
*
*	friend
*		can be seen only within scope (all scopes merging with it too)
*/

	public integer i
	protected integer i
	private integer i
	internal integer i
	
	internal public integer i
	internal protected integer i
	internal private integer i
	
	type a extends private integer 		//integer access stops at a
										//can be interpreted as integer.
										
	type a extends protected integer 	//integer access for children of a
										//can only be interpreted as integer by children
	
	type b extends private a 			//can see integer, but child can't
										//can't be interpreted as a
	
	type a extends internal integer 	//integer access only to other code in same file/trigger.
										//can only be interpreted as integer by other code in same file/trigger.
										
	type a extends integer				//anything can see integer from a
										//anything can interpret a as integer
										
	scope
		private scope
			integer i
		end
		set i = 5 //good
	end
	set i = 4 //bad
	
	friend integer i
	
	scope a
	end
	
	scope d
	end
	
	scope e
	end
	
	scope b
		//can only be seen by members of a if those
		//members decide to merge with b
		//nothing else can see it
		friend a integer i
		
		//can be seen by a,d,e when merged
		friend a,d,e integer i
		
		//can be seen by a,d,e
		public friend a,d,e integer i
		
		//friends are useful for things like with what modules used to do
		//you may only want the variable to be seen by a certain module
		//JASS has no modules, but it has constructs that can be used
		//to similar effect
	end
	
/*
*	Variable
*
*	A variable may be either implicit, global, or local.
*
*	A global variable is a variable that exists outside of a function scope.
*	A local variable is a variable that exists inside of a function scope.
*	An implicit variable exists either globally or locally depending on where it is used.
*/

	global integer i		//explicitly global variable
	local integer i			//explicitly local variable
	integer i				//may be global or local
	
	//explicit globals block
	globals
		integer i
	end
	
	//explicit locals block
	locals
		integer i
	end
	
/*
*	An example of implicit variables
*/

	integer i //i is local to Foo
	
	function Foo takes nothing
		set i = 4
	end
	
	integer m //m is local to the anonymous function in this scope
	
	set m = 5
	
	integer o //o is global
	
	set o = 3
	
	function Foo takes nothing
		set o = 4
	end
	
	local integer p
	
	function Foo takes nothing
		set p = 4 //syntax error
	end
	
	local integer z
	global integer z //no syntax error
	
	local integer L
	integer L //global, no syntax error
	
	function Foo takes nothing
		set L = 5
	end
	function Foo takes integer i
		set L = 5
	end
	
/*
*	Variable types may also be implicit
*/

	var i
	
	set i = 4 //integer
	
	var o
	
	set o = CreateUnit(...)
	set o = CreateItem(...) //widget
	
/*
*	Intelligent Simplification
*
*	Code is reordered based on use
*	If there is cyclical use, a syntax error will occur
*/

	//no errors
	function Oh takes nothing
		call Foo()
	end
	
	function Foo takes nothing
	end
	
	//cyclical error
	function Boo takes nothing
		call Grow()
	end
	
	function Grow takes nothing
		call Boo()
	end
	
/*
*	Symbols that are not used anywhere are not included in code output.
*
*	ExecuteFunc and TriggerRegisterVariableEvent symbol use is checked.
*
*	Symbol use within strings handles string concatenation and variable use.
*	Variables that do not resolve to a known finite set of values will cause all symbols
*	that match the expression to be kept.
*
*	If only a variable from an unknown source is used, then all symbols will be kept
*/

	//kept
	function cheese34958493 takes nothing
	end
	
	//not kept
	function cheese31914 takes nothing
	end
	
	//kept
	function cheeseqa9a923 takes nothing
	end

	function oh takes nothing
		local string str = GetEventPlayerChatString()
		
		call ExecuteFunc("cheese" + str + "3")
	end
	
/*
*	Both boolean and mathematical expressions are simplified
*/

	not a or not b -> not (a and b)
	3*a + 4*a -> 7*a
	392 + 5 -> 397
	3 + 3*a + 3*b -> 3*(1 + a + b)
	
/*
*	Lookup Operator (.)
*
*	Accesses members of a scope
*/

	scope a
		scope b
			integer o
		end
	end
	
	set a.b.o = 4
	
	type m extends integer static integer c
	
	set m.c = 5
	
	scope a.b
		integer a
	end
	
	set a.b.a = 5
	
	type m extends integer scope
		static type o extends integer static integer c
	end
	
	set m.o.c = 11
	
/*
*	Scope Import, Export, Require
*
*	Require is used to make one scope require another scope's code
*	before being placed. This is used only for autorun code.
*/

	scope
		require b
		
		call Print("ran anonymous scope")
	end
	
	scope b
		call Print("ran b")
	end
	
	//
	//outputs
	//
	//	ran b
	//	ran anonymous scope
	//
	
/*
*	Import is used to import the symbols of a scope.
*
*	Import may either be static or non-static. Static will not
*	import virtual symbols. Virtual symbols can't be imported into a
*	non-type scope.
*
*	Import may also be global. Global will start at the global scope.
*/

	scope a
		integer p
	end
	
	scope b
		import a
		
		set p = 4
	end
	
	type o scope
		static integer m
	end
	
	type z scope
		static import o //doesn't have to be static
		
		set m = 5
	end
	
	scope h
		scope a
			integer q
		end
		
		global static import a
		
		set p = 4 //imported a from global scope, not local
	end
	
/*
*	Export is used to export the symbols from the scope to another scope
*
*	Export may be global and or static
*
*	Exported symbols may not be seen within the local scope.
*/

	scope c
		integer o
	end
	
	scope d
		global static export c
			integer q 	//this q can see the scope it's in, but not the
						//scope it's being exported to
						//set o = 5 would not work
						//set c.o = 5 would work
		end
		
		//this scope can't see q
		//set q = 4 would not work
		//set c.q = 4 would work
	end
	
	scope c
		require d //just to let people know that we now want d
				  //this isn't necessary, but it's a good practice
				  
		set q = 5 //success
	end
	
/*
*	Symbols from a scope may only be imported into a scope once
*	The imported symbols are not copied!
*	The imported symbols can be shadowed
*/

	integer c = 4
	integer c = 4 //syntax error, multiple definitions
	
	scope a
		integer c
		integer d
	end
	
	scope b
		integer c
		integer e
		
		global static import a
		
		set c = 5 //b.c
		set d = 5 //a.d
	end
	
/*
*	Static
*
*		A static member is a member that is linked to a type scope, the an
*		instance of a type scope.
*
*		A static symbol is a symbol that is not virtual.
*/

	type d extends private integer scope
		integer m //not static
		static integer o //static
	end
	
	set d.o = 4 //linked to scope
	set ((d)1).m = 4 //linked to instance of scope
	
	//instances of a scope are also linked to the scope
	set ((d)1).o = 4
	
	//nothing in a type scope is static without the static keyword
	
	type d extends private integer scope
		static type a extends private integer
		type a2 extends private integer //this is not static!
	end
	
	//example
	d test = new d()
	
	d.a test2 = new d.a() //linked to scope
	d.a2 test3 = new test.a2() //linked to instance of scope
	
	//if test were to be deleted, test3 would also be deleted
	
	//this is primarily used for closures (more on this later)
	
/*
*	Type Instance
*
*		A type is instantiated with the new operator.
*
*		The new operator calls the allocate function, which
*		returns an instance of the type.
*
*		If the new operator is overloaded, the default empty new operator
*		is removed.
*
*		If either the allocate or deallocate functions or overloaded, the
*		default of the other will be removed.
*/
	
	type test extends private integer scope
		override operator new takes integer i
			set this = allocate()
			
			return this
		end
		
		override operator delete
			call deallocate()
		end

		private static integer instanceCount = 0
		private static integer array recycler
		private static function allocate takes nothing
			local integer instance = recycler[0]
			
			if (instance == 0) then
				set instance = instanceCount + 1
				set instanceCount = instance
			else
				set recycler[0] = recycler[instance]
			end
			
			return instance
		end
	
		private function deallocate takes nothing
			set recycler[(integer)this] = recycler[0]
			set recycler[0] = recycler[(integer)this]
		end
	end
	
	test t = new test() //error, the default new operator was removed
	
/*
*	If new doesn't override, it will automatically call allocate
*
*	If delete doesn't override, it will automatically call deallocate
*	When delete doesn't override, the flow looks like this
*
*		call HiddenDeleteFunction(this)
*		call Delete(this)
*
*	The HiddenDeleteFunction will first call delete, then it will
*	deallocate.
*
*	The new operator works the same way in that it will allocate, call
*	the new function, then return the allocated instance
*/

	function Delete takes integer this returns nothing
		//user code
	endfunction
	
	function Deallocate takes integer this returns nothing
		//user code or default code
	endfunction

	//what is actually called when delete doesn't override
	function HiddenDeleteFunction takes integer this returns nothing
		call Delete(this)
		call Deallocate(this)
	endfunction
	
	function New takes integer this returns nothing
		//user code
	endfunction
	
	function Allocate takes nothing returns integer
		//user code or default code
	endfunction
	
	//what is actually called
	function HiddenNewFunction takes nothing returns integer
		local integer this = Allocate()
		//initialize fields
		call New(this)
		return this
	endfunction
	
/*
*	If delete isn't overloaded, Deallocate is called directly.
*
*	The new operator is *never* called directly. If it's not overloaded, then
*	it's just not called. If allocate isn't overloaded, then initialize fields
*	goes into allocate. If nothing is overloaded, allocate is called directly.
*
*	Unless override is used on new, the matching signature from the parent is called.
*	Unless allocate is overloaded, the allocate relies on parent's allocator.
*
*	The override keyword is used to stop the child type from calling the parent.
*	All functions in a type go through a dummy function that calls the parent before
*	going to the actual user function if a parent signature exists and it does something.
*/
	
	type a extends private integer scope
		integer o = 3
		
		function Foo takes nothing
			set o = 4
			set o = 6
		end
		
		operator new takes nothing
			set o = 9
			set o = 10
		end
		
		operator delete
			set o = 9
			set o = 10
		end
	end
	
	type b extends a scope
		integer c = 5
		
		function Foo takes nothing
			set o = 7
			set o = 8
		end
		
		operator new takes nothing
			set o = 9
			set o = 10
		end
		
		operator delete
			set o = 9
			set o = 10
		end
	end
	
	//translates to (actual code isn't readable)
	globals
		integer array a_o
		integer array b_c
	endglobals
	
	function A_Foo takes integer this returns nothing
		set a_o[this] = 4
		set a_o[this] = 6
	endfunction
	
	function A_New takes integer this returns nothing
		set a_o[this] = 9
		set a_o[this] = 10
	endfunction
	
	function A_Delete takes integer this returns nothing
		set a_o[this] = 9
		set a_o[this] = 10
	endfunction
	
	//allocate globals, other allocate code
	function A_Allocate takes nothing returns integer
		//code
	endfunction
	function A_Deallocate takes nothing returns integer
		//code
	endfunction
	
	function A_Hidden_New takes nothing returns integer
		local integer this = A_Allocate()
		set a_o[this] = 3
		call A_New(this)
		return this
	endfunction
	
	function A_Hidden_Delete takes integer this returns nothing
		call A_Delete(this)
		call A_Deallocate(this)
	endfunction
	
	function B_Foo takes integer this returns nothing
		set a_o[this] = 7
		set a_o[this] = 8
	endfunction
	
	function B_New takes integer this returns nothing
		set a_o[this] = 9
		set a_o[this] = 10
	endfunction
	
	function B_Delete takes integer this returns nothing
		set a_o[this] = 9
		set a_o[this] = 10
	endfunction
	
	function B_Hidden_New takes nothing returns integer
		local integer this = A_Hidden_New()
		set b_c[this] = 5
		call B_New(this)
		return this
	endfunction
	
	function B_Hidden_Delete takes integer this returns nothing
		call A_Delete(this) //no way around this chain
		call B_Delete(this)
		call A_Deallocate(this)
	endfunction
	
/*
*	Types can be used as variable types
*/

	type o extends integer
	
	o test
	
/*
*	They can be created and destroyed
*/

	set test = new o()
	delete test
	
/*
*	Non-static members can be accessed
*/

	type o extends integer integer m
	
	set test = new o()
	set test.m = 5
	
	type o extends integer operator + o c
		return (integer)this + (integer)c
	end
	
	o test2 = new o()
	o test3 = test + test2 //dangerous
	
/*
*	Out vs In
*
*	Out switches to the scope relating to the current scope
*	In switches back to the current scope
*/

	out scope
	end
	
	in scope
	end
	
	in integer i
	out integer i
	
/*
*	Example
*/

scope a
	function Foo takes nothing
		private integer i
	end
end

scope a
	function Foo takes nothing
		scope c
			call Print("hello")
		end
	end
end

scope d
	private integer n
	
	global static export a
		out scope //only way to combine with Foo inside of d
			function Foo takes nothing
				//in refers to d
				//out refers to caller of Foo
				//in.out refers to Foo
				
				//can't see i, can't see n
				in scope
					//can see n now, but only because
					//n is part of the origin scope
					set n = 5
				end
				
				//this is dangerous
				out
					set f = 6 //any calling scope better see an f
					call RunMe() //wtf?
				end
				
				call Print("what?")
				
				require c
			end
		end
	end
end

scope z
	integer f
	
	function RunMe takes nothing
		call Print("ran")
	end

	call a.Foo()
end

scope
	integer f
	
	function RunMe takes nothing
		call Print("ran again")
	end

	call a.Foo()
end

/*
*		Output
*
*			"ran"
*			"ran again"
*			"hello"
*			"what"
*
*		Results
*
*			z.f = 6
*			anon.f = 6 //the anonymous scope
*/

/*
*	Keep in mind that for merging scopes, the only fields that may not be
*	visible are private an internal.
*
*	Private will never be visible.
*
*	Internal will only be visible if the merging scope is in the same file or trigger.
*/

//this example is about as whacked as it gets
function foo takes nothing
	out set o = 5
end
function t takes nothing
	integer o
	
	call foo()
	
	call Print(o) //prints 5
end

/*
*	One of the strangest examples ever
*	A way to return multiple variables
*/

function ReturnThis takes nothing
	out static export //no name needed
		integer i = out n
	end
end

scope
	function Woah takes nothing
		integer n = 4
		
		while (n++ < 10) do
			ReturnThis()
			Print(i)			//5
								//6
								//7
								//8
								//9
								//10
		end
	end
end

/*
*	Set
*
*	Set is used to explicitly require the = operator
*
*/

	set i = 5

/*
*	It can only ever be used with the = operator
*
*	Without set
*/

	i = 5
	i++
	++i
	i /= 5
	
/*
*	Call
*
*	Call is just an explicit function call. It may also be
*	implicit. As call does not really require anything, it
*	becomes an optional keyword.
*/

	call Foo()
	Foo()
	
/*
*	This fixes the special exceptions found in JASS
*/

	set i = Foo() //exception
	
	//should be
	
	set i = call Foo() //correct
	
	//by allowing call to be implicit, it fixes this exception
	
/*
*	Loops
*
*		for (integer i = 5, i < 4, ++4) do
*		end
*
*		while (i++ < 5) do
*		end
*
*		loop
*			while i++ < 5
*			exitwhen i++ >= 5
*		end
*
*		//overload the in operator
*		//overload the iterator operator
*		for (unit u in group) do
*		end
*/

JASS:
//inline
inline function Foo takes nothing //inline is forced
	return 5
end

//symbols are kept from strings so long as they can be derived from that string statically
//this means only set-once variables that originate from literals
call ExecuteFunc("${function Foo}")
call ExecuteFunc((string)function Foo)

//runs preprocess code
preprocess
end

//debug only code
debug
end

//used inside of preprocess code to go back to script
script
end

//automatically determine signature of constant code
//anonymous function support
constant code c = 	function takes nothing
				return 5
			end

var i = c()

//use triggers for non-set once code
set c = function takes nothing
	end

call c() //trigger

//when no signature is provided, expects takes nothing returns nothing

function hi takes integer i, integer i2 returns integer
	return i + i2
end

hi code c = 	function takes integer m, integer m2 returns integer
			return m*m2
		end

c = function hi

call c(5, 6) //11

//virtual keyword may be applied to functions, operators, and properties within a type scope
//anything virtual will run off of triggers
virtual function Foo takes nothing returns nothing
end

type a extends private integer
virtual scope a link type a
	virtual function Foo takes nothing returns nothing
		return "a"
	end
end

type b extends a //public
virtual scope b link type b
	virtual function Foo takes nothing returns nothing
		return "b"
	end
end

a test1 = new a()
a test2 = new b()

call Print(test1.Foo()) //"a"
call Print(test2.Foo()) //"b"

//example of how scoping works

type a extends private integer

virtual scope o link type a
end

scope
	//access modifier on a one-liner refers to this scope
	//Foo is accessed from the target scope though
	private o function Foo takes nothing
	end
end

//The $ operator is used to interpolate things one level up
//string -> script -> preprocessor

string name = "hi"
call Print("$name") //prints hi

preprocess string name = "myVar" end
$name = "$$name" //myVar = "myVar"

loops
	loop
	for loop
	while loop
	do while loop

loop keywords
	exitwhen expression
	break
	continue

//example of some dynamic code with preprocess
preprocess
	type module

	virtual scope module link type module
		private static dictionary<signature> flag = new dictionary<signature>()

		protected virtual function createScript takes nothing returns nothing
		end

		static operator new takes signature sig
			if (flag[sig]) then return (module)0

			call createScript()

			return (module)1
		end
	end
end

preprocess
	type mymodule extends module

	virtual scope mymodule link type mymodule
		protected virtual function createScript takes nothing returns nothing
			integer i = 0

			while (i < 10)
				script
					public static string str$i = "str$i"
				end
			end
		end
	end
end

type test extends private integer
virtual scope test link type test
	preprocess new mymodule(type test) end

	//the above creates 10 string variables, str0 through str9

	//attempting to run it a second time will do nothing
	preprocess new mymodule(type test) end
end

//templates are created with < > and can be applied types, functions, operators, and properties
//< > can accept signatures or labels
//
//the signature type is any signature
//
//template arguments are defined in both the preprocessor and the script and are constant

type<type T> test extends private integer //type T may also be made more explicit with extends
					  //for example, type T extends list, meaning that T must be
					  //a type of list, including list itself
					  //variable signatures are also accepted, like integer array VAR

virtual scope test link type test<type T> //signature includes the template
	T value
end

test<type integer> t = new test<type integer>()
set t.value = 5


//The abstract keyword when applied to a type means that the type can't be used except for by other types.
//The sealed keyword when applied to a type means that the type can't be extended.
//The constant keyword when applied to a type means that all members of that type must be static and constant (like enums)
//when constant is applied to something, it can't change and it can only use constant code

//the super keyword is used in types to access the parent type

type a extends private integer
type b extends private a

virtual scope a link type a
	function foo takes nothing
		return "a"
	end
end

virtual scope b link type b
	function foo takes nothing
		return super.foo() //"a"
	end
end

//signature is a primitive type that holds signatures
//
//signatures include
//
//	function
//	scope
//	type
//	property
//	operator
//
//signatures can be used in various places
//the label of a signature can be used as a value (signaturetype label)
//the raw signature can also be used
//the signature type can be worked with like any other type
//
//the signature type includes the following functions and operators
//
//	(string)
//	scope //gets signature of enclosing scope
//	.exists //does the signature exist?
//
//the top level scope is called global
//
//an inlined function that is not simple enough to normally do inlining will create local variables
//to hold function calls

//closures

function rake takes nothing
	integer k = 5

	function far takes nothing
		set k = 6
	end

	call far()
	call Print(k) //prints 6

	call TimerStart(CreateTimer(), 1, false,
			function takes nothing
				call DestroyTimer(GetExpiredTimer())
				call Print(k) //prints 9
			end)

	set k = 9								
end

//set takes an expression (it really should be evaluate..)
//
//set i++
//set i--

//integer forms
//
//    	ascii: 'aaaaaaaaaaaaa'
//    	hex: 0x5
//	octal: 01
//	binary: 0b1

//however, global and local variables don't really hold a place anymore

function rake takes nothing
	integer k = 5 //local variable

	//this is technically public, but it only exists for the lifetime of rake, so
	//it can't really be called outside of this instance of rake
	function far takes nothing
		//as no variables are copied, this just passes in the original closure
		//if there were new variables, it would create a new closure and give it old
		//closure + variables
		function far2 takes nothing
			call Print(k)
		end

		if (++k < 10) then
			call far()
		end
	end

	integer i = 4

	//a closure is created for this instance of rake
	//all locals used in far are copied to this closure
	//the closer is passed into far
	//far then uses the closure to work with the variables
	call far()

	//closure c = new closure(k)
	//call far(c)
	//	if (++c.k < 10) then call far(c) end
	//set k = c.k

	//i is not copied because far does not use it

	call Print(k) //prints 10

	//closures running on a timer or trigger or anything else are copied for those handles
	//via a hashtable
	call TimerStart(CreateTimer(), 1, false,
			function takes nothing
				call DestroyTimer(GetExpiredTimer())
				call Print(k) //prints 9

				call far() //passes in closure that this function has
				//if there were multiple timers, triggers, and so on from this function, they'd
				//all share the same closure
			end)

	set k = 9								
end

//type nesting is the same way, except that rather than closures, types are passed in
//this is because the type itself can serve as a closure
//as such, a non-static type nested inside of a type must be created a special way

type outside extends private integer
virtual scope outside link type outisde
	type inside extends private integer
end

outside test = new outside()
outside.inside test2 = new test.inside()


//preprocessor includes object type, which works with objects
//object types include units, items, doodads, etc

unit footman = unit['hfoo'] //access footman object

unit test = new unit('hfoo') //create a new object based on footman and return id
set test.life = 5000 //or w/e, properties are based off of object properties

//functions may take references
function hi takes reference integr i
	set i = 5
end

integer i = 4
call hi(i) //i is now 5

//	a virtual type is a type that can't be instantiated
//
//	type a extends private integer scope
//		virtual function oh takes nothing
//			call Print("a")
//		end
//	end
//
//	type b extends private integer scope
//		import a
//
//		virtual function oh takes nothing
//			call Print("b")
//		end
//	end
//
//	a test = new a()
//	a test2 = new b()
//
//	call test.oh() //prints "a"
//	call test2.oh() //error, not allocated
//
//	polymorpshim for function oh will still work under type b
//
//	type c extends private b scope
//		virtual function oh takes nothing
//			call Print("c")
//		end
//	end
//
//	b test3 = new c()
//	call test3.oh() //prints "c"
//
//	to use polymorphism, use extends or extensions
//
//	import will only import public symbols
//	extends and extensions will import public and protected symbols
//
//	.exists
//	.type
//	.signature
//	.super
//
//	a type may extend off of one non-virtual type
//	a type may extend off of many virtual types
//	a type may typecast to any type it extends from/to, including virtual types
//	a virtual type can't be typecasted to anything
//	types and virtual types can typecast to anything that they have an operator for
//	once a signature is virtual, it stays virtual
//	a signature may go from non-virtual to virtual
//	by default, methods will call super.method
//	in order to not call super.method, you may use the override keyword
//
 
Last edited:
Level 31
Joined
Jul 10, 2007
Messages
6,306
Ok, decided I'd give some updates since I haven't posted in awhile. Yes, I've been working :eek:, or studying anyways.


So, update #1

Here are the phases for the compiler >.>. Yes, it's a compiler.

Code:
Phases
	Preprocess
		For Each Language
			Lexical Analysis
			Parse Tree Generation
			AST Tree Generation
		AST Tree Merge
		Build Symbol Table
		Evaluate Inferenced Types
		Typecheck
		Groovy generation
		Groovy evaluation (script generation)
	Script
		For Each Language
			Lexical Analysis
			Parse Tree Generation
			AST Tree Generation
		AST Tree Merge
		Debug On
			Translate Debug Statements
		Debug Off
			Drop Debug Statements
		Build Symbol Table
		Evaluate Inferenced Types
		Typecheck
		If (Compile JASS)
			evaluate inline, etc
			AST -> JASS AST 
			Debug Off
				Semantic Analysis
				Codeflow Analysis
				JASS AST -> SSA AST Generation
				
				Until No Optimizations Left
					Local Optimization
					Global Optimization
					Intraprocedural Optimization
					Loop Optimization (etc)
					
				SSA AST -> JASS AST
				
			If (Compile Map)
				JASS AST -> JASS
			Else If (Compile dll)
				JASS AST -> bytecode
	Else If (Compile c#)
		evaluate export, etc
		AST -> c#

I studied up on compilers to get some 1337 skillz for optimization and stuffs =).

update #2

I will be using Antlr 4, which produces a Parse Tree, and JastAdd, which produces an AST. Thank you peq for linking me to JastAdd ^_^.

update #3

I have finalized the grammars for the languages. They are awesome and have no flaws. I'm able to code any vJASS library in very little time with amazing APIs and stuff =).


The languages are split into the following

JASS

vanilla JASS with a few extensions

now, while there is a lot, I only added things that stuck 100% with JASS, meaning that I gave very little extra power. The idea was not to introduce any new symbols but at the same time make it easier to script in JASS.

1. execute code form anywhere, doesn't have to be in a function
2. freely declare globals anywhere (globals block isn't needed)
3. local keyword is sorta like private now. It's required for variables in functions.
4. new container, which is like a scope. Containers may require other containers. Can be named or anonymous.
5. code reordering based on use
6. variable shadowing
7. compilation to either bytecode, JASS, or c#
8. supah optimization (outside of debug mode)
9. debug keyword
10. xjass block - extended jass
11. sjass block - symbolic jass
12. vjass block - very jass (from vexorian)
13. cjass
14. wurst?
15. zinc?

---I really want to make this modular, but I don't see how as the blocks can get buggy depending on the syntax if the syntax is unknown. I'd have to make the block do like

//where number of ticks is part of start/end symbol
script language ``````````
endscript ``````````

---I'm really going to have to implement each specific language to keep the language blocks from breaking

16. fast keyword - precedence for small symbol name
17. nested comments /* /* */ */
18. \ for terminal continuation
19. binary, octal, hexadecimal, ascii (any size), and decimal integer representation
20. allow new lines inside of delimited things: " ", [ ], ( )
21. correctly interpret new lines and tabs inside of " " and translate them to the correct string
xJASS

This is extended JASS, which goes all out and changes some of the syntax. It follows a slightly different paradigm.

JASS:
//the grammar I'd been working on up to this point has been xJASS
type hi extends unit scope
end

abstract type o extends private integer

function oh takes nothing scope
end

block
end

scope
end

//you should know most of the things from this language at this point
//$, etc
sJASS

Same as xJASS, but symbolic. More like C. Some of the grammar is also switched around to be more like C.

//where ? is like an evaluation for calculating type
?func() { return 5 }

?s = 5 +
6 +
7*8

//ternary also works
vJASS

You know this one ; P

A few new features, like nested textmacro calls, local textmacros
cJASS

This moves away from types and to classes/interfaces

Uses ; instead of \n

It's pretty much bastardized c++

Wurst

Wurst is of course about faster rapid prototyping. It sacrifices some power to make the coding go by as quickly as possible.

We'll see if I can work with peq and so on to get this all working with Wurst. If we can get all of the languages working together -> vJASS, cJASS, JASS, and Wurst, as well as my two new ones, xJASS and sJASS, imma go woo ^_^.

I don't know if Wurst is currently running on C or Java or what (it's probably, hopefully Java). Anyways, if it's Java, it wouldn't be too much effort to combine with everything else. As long as everything goes to a common AST, it can all work together :). One of the nasty things is that the grammars have to be combined :( - I love Antlr4, sry -, lol.

Here is the rewritten grammar for just JASS lexer atm. Not including the nested Java and tokens as there is a lot. Just showing how simple the grammar is now :). Used some proz designz.
Code:
/* whitespace */
WHITESPACE_STRNF: 	{tokens.whitespace.newline.enabled != 0}? [ \t\r\n\u000C]+		{tokens.whitespace.token();};
WHITESPACE_STRF: 	[ \t\r\u000C]+													{tokens.whitespace.token();};

/* comments */
COMMENT: 			'//' ~[\n]* 		{tokens.comment.token();};
DELIMITED_COMMENT: 	'/*' 				{tokens.comment.delimited.start();};

/* terminals */
TERMINAL:			'\n'				{tokens.terminal.token();};
TERMINAL_CONTINUE: 	'\\' 				{tokens.terminal._continue.start();};

/* literals */
LITERAL_NULL: 									'null' 								{tokens.literal._null();};
LITERAL_BOOLEAN: 								('true' | 'false') 					{tokens.literal._boolean();};
LITERAL_BINARY: 		('0' ('b' | 'B') 		[0-1]+) 							{tokens.literal.integer.binary();};
LITERAL_OCTAL: 			('0' 					[0-7]+)								{tokens.literal.integer.octal();};
LITERAL_DECIMAL: 		(						[1-9] [0-9]* | '0')					{tokens.literal.integer.decimal();};
LITERAL_HEXADECIMAL: 	('0' ('x' | 'X') 		[0-9a-fA-F]+)						{tokens.literal.integer.hexadecimal();};
LITERAL_ASCII_SUB: 		'\'' 					(~['\\] | ('\\' ['\\]))+ '\''		{tokens.literal.integer.ascii();};
LITERAL_REAL:			 						(([1-9] [0-9]* | '0') '.' [0-9]*) 	{tokens.literal.real();};
LITERAL_STRING: 		'"' 														{tokens.literal.string.start();};

/* keywords */
KEYWORD_ARRAY: 			'array' 		{tokens.keyword.array();};
KEYWORD_CONSTANT: 		'constant' 		{tokens.keyword.constant();};
KEYWORD_NATIVE: 		'native' 		{tokens.keyword._native();};
KEYWORD_FUNCTION: 		'function' 		{tokens.keyword.function();};
KEYWORD_ENDFUNCTION: 	'endfunction' 	{tokens.keyword.endfunction();};
KEYWORD_TAKES: 			'takes' 		{tokens.keyword.takes();};
KEYWORD_RETURNS: 		'returns' 		{tokens.keyword.returns();};
KEYWORD_LOCAL: 			'local' 		{tokens.keyword.local();};
KEYWORD_SET: 			'set' 			{tokens.keyword.set();};
KEYWORD_IF: 			'if' 			{tokens.keyword._if();};
KEYWORD_ENDIF: 			'endif' 		{tokens.keyword.endif();};
KEYWORD_ELSEIF: 		'elseif' 		{tokens.keyword.elseif();};
KEYWORD_ELSE: 			'else' 			{tokens.keyword._else();};
KEYWORD_THEN: 			'then' 			{tokens.keyword.then();};
KEYWORD_LOOP: 			'loop' 			{tokens.keyword.loop();};
KEYWORD_ENDLOOP: 		'endloop' 		{tokens.keyword.endloop();};
KEYWORD_EXITWHEN: 		'exitwhen' 		{tokens.keyword.exitwhen();};
KEYWORD_RETURN: 		'return' 		{tokens.keyword._return();};
KEYWORD_GLOBALS: 		'globals' 		{tokens.keyword.globals();};
KEYWORD_ENDGLOBALS: 	'endglobals' 	{tokens.keyword.endglobals();};
KEYWORD_TYPE: 			'type' 			{tokens.keyword.type();};
KEYWORD_EXTENDS: 		'extends' 		{tokens.keyword._extends();};
KEYWORD_CONTAINER: 		'container'	 	{tokens.keyword.container();};
KEYWORD_ENDCONTAINER: 	'endcontainer' 	{tokens.keyword.endcontainer();};
KEYWORD_DEBUG: 			'debug' 		{tokens.keyword.debug();};
KEYWORD_FAST: 			'fast' 			{tokens.keyword.fast();};
KEYWORD_INLINE:			'inline'		{tokens.keyword.inline();};

/* operators */
OPERATOR_ASSIGN: 		'=' 			{tokens.operator.assign();};
OPERATOR_GT: 			'>' 			{tokens.operator.gt();};
OPERATOR_LT: 			'<' 			{tokens.operator.lt();};
OPERATOR_LTE: 			'<=' 			{tokens.operator.lte();};
OPERATOR_GTE:			'>=' 			{tokens.operator.gte();};
OPERATOR_EQ: 			'==' 			{tokens.operator.eq();};
OPERATOR_NEQ: 			'!=' 			{tokens.operator.neq();};
OPERATOR_NOT: 			'not' 			{tokens.operator.not();};
OPERATOR_AND: 			'and' 			{tokens.operator.and();};
OPERATOR_OR: 			'or' 			{tokens.operator.or();};
OPERATOR_ADD: 			'+' 			{tokens.operator.add();};
OPERATOR_SUB: 			'-' 			{tokens.operator.sub();};
OPERATOR_MUL: 			'*' 			{tokens.operator.mul();};
OPERATOR_DIV: 			'/' 			{tokens.operator.div();};

LPAREN:					'('				{tokens.parens.start();};
RPAREN:					')'				{tokens.parens.end();};

LBRACK:					'['				{tokens.brack.start();};
RBRACK:					']'				{tokens.brack.end();};

IDENTIFIER:	[a-zA-Z_] [a-zA-Z0-9_]* 	{tokens.identifier();};

/* modes */
mode mode_comment_delimited;
	MODE_comment_delimited_START: 	'/*'	{tokens.comment.delimited.start();};
	MODE_comment_delimited_END: 	'*/'	{tokens.comment.delimited.end(true);};
	
	MODE_comment_delimited_ERROR: 	EOF		{tokens.comment.delimited.error();};
	MODE_comment_delimited_TEXT: 	.		{more();};
		
mode mode_string;
	MODE_string_END:		'"'				{tokens.literal.string.end();};

	MODE_string_NEW_LINE: 	'\n' 			{tokens.literal.string.newline();};
	MODE_string_TAB: 		'\t' 			{tokens.literal.string.tab();};
	MODE_string_ESCAPE:		'\\' 	 		{tokens.literal.string.escape.start();};
	
	MODE_string_ERROR: 		EOF 			{tokens.literal.string.error();};
	MODE_string_TEXT: 		. 				{tokens.literal.string._char();};
	
	mode mode_string_escape;
		MODE_string_escape_ESCAPE: 		'\\'	{tokens.literal.string.escape.end();};
		MODE_string_escape_NEW_LINE: 	'n'		{tokens.literal.string.escape.end();};
		MODE_string_escape_CARRIAGE: 	'r'		{tokens.literal.string.escape.end();};
		MODE_string_escape_QUOTE: 		'"'		{tokens.literal.string.escape.end();};
		MODE_string_escape_TAB: 		't'		{tokens.literal.string.escape.tab();};
		
		MODE_string_escape_ERROR: 		. 		{tokens.literal.string.escape.error();};
		
mode mode_terminal_continue;
	MODE_terminal_continue_END: 				('\n' | EOF)		{tokens.terminal._continue.end();};
	MODE_terminal_continue_COMMENT: 			'//' ~[\n]* '\n'? 	{tokens.comment.token(); tokens.terminal._continue.end();};
	
	MODE_terminal_continue_DELIMITED_COMMENT: 	'/*' 				{tokens.comment.delimited.start();};
	MODE_terminal_continue_WHITESPACE: 			[ \t\r\u000C]+		{tokens.whitespace.token();};

Btw, cool fact. I'll implement this ;)
Code:
//hello\
int
int
//int\b
int

edit
and implemented :eek:

it outputs 1 and 6 (no new lines)
the rest = comments
JASS:
1\//wtf?\
there we go!
6

This has exact same output (no new lines). This is because the /* */ comments the new line out : P. The \ is looking for a new line to consume.
JASS:
1\/*
*/
6

And one final example with again, the same output
JASS:
1\/*
*///\
huh?
6

eh one more
JASS:
1\//there is war!
6

All I had to do was modify the regex for single line comments :D
Code:
'//' (~[\n] | '\\' '\r'? '\n')*
 
Last edited:
Status
Not open for further replies.
Top