Artifact Content
Not logged in

Artifact 8d6e708eceba536ad77e6c5815ddf6b659506269


     1  /**
     2   * Authors: k.inaba
     3   * License: NYSL 0.9982 http://www.kmonos.net/nysl/
     4   *
     5   * Evaluator for Polemy programming language.
     6   */
     7  module polemy.eval;
     8  import polemy._common;
     9  import polemy.failure;
    10  import polemy.ast;
    11  import polemy.parse;
    12  import polemy.value;
    13  import polemy.layer;
    14  import polemy.value;
    15  import polemy.valueconv;
    16  import std.signals;
    17  
    18  /// Objects for maitaining global environment and evaluation of expression on it
    19  class Evaluator
    20  {
    21  public:
    22  	/// Initialize evaluator with empty context
    23  	this() { theContext = new Table; }
    24  
    25  	/// Evaluate the AST
    26  	Value evalAST(AST e)
    27  	{
    28  		AST[void*] mandeCache;
    29  		return macroAndEval(e, ValueLayer, theContext, OverwriteCtx, mandeCache)[0];
    30  	}
    31  
    32  	/// Evaluate the string
    33  	Value evalString(S,T...)(S str, T fn_ln_cn)
    34  	{
    35  		return evalAST(parseString(str,fn_ln_cn));
    36  	}
    37  
    38  	/// Evaluate the file
    39  	Value evalFile(S,T...)(S filename, T ln_cn)
    40  	{
    41  		return evalAST(parseFile(filename,ln_cn));
    42  	}
    43  
    44  	/// Get the global context
    45  	Table globalContext()
    46  	{
    47  		return theContext;
    48  	}
    49  
    50  private:
    51  	Table theContext;
    52  
    53  	enum : bool { CascadeCtx=false, OverwriteCtx=true };
    54  
    55  	Value eval( AST e, Layer lay, Table ctx, bool overwriteCtx=CascadeCtx )
    56  	{
    57  		// dynamic-overload-resolution-pattern: modify here
    58  		enum funName = "eval";
    59  		alias TypeTuple!(e,lay,ctx,overwriteCtx) params;
    60  
    61  		// dynamic-overload-resolution-pattern: dispatch
    62  		alias typeof(__traits(getOverloads, this, funName)) ovTypes;
    63  		alias staticMap!(firstParam, ovTypes)              fstTypes;
    64  		alias DerivedToFront!(fstTypes)             fstTypes_sorted;
    65  		foreach(i, T; fstTypes_sorted)
    66  			static if( is(T == typeof(params[0])) ) {} else if( auto _x = cast(T)params[0] )
    67  				return __traits(getOverloads, this, funName)[i](_x, params[1..$]);
    68  
    69  		// dynamic-overload-resolution-pattern: default behavior
    70  		assert(false, text("eval() for ",typeid(e)," [",e.pos,"] is not defined"));
    71  	}
    72  
    73  	Value eval( Str e, Layer lay, Table ctx, bool overwriteCtx=CascadeCtx )
    74  	{
    75  		if( isASTLayer(lay) )
    76  			return ast2table(e, (AST e){return eval(e,lay,ctx);});
    77  		if( isUserDefinedLayer(lay) )
    78  			return lift(new StrValue(e.data), lay, ctx, e.pos);
    79  		return new StrValue(e.data);
    80  	}
    81  
    82  	Value eval( Int e, Layer lay, Table ctx, bool overwriteCtx=CascadeCtx )
    83  	{
    84  		if( isASTLayer(lay) )
    85  			return ast2table(e, (AST e){return eval(e,lay,ctx);});
    86  		if( isUserDefinedLayer(lay) )
    87  			return lift(new IntValue(e.data), lay, ctx, e.pos);
    88  		return new IntValue(e.data);
    89  	}
    90  
    91  	Value eval( Var e, Layer lay, Table ctx, bool overwriteCtx=CascadeCtx )
    92  	{
    93  		if( isASTLayer(lay) )
    94  			if( isMacroLayer(lay) && ctx.has(e.name,MacroLayer) )
    95  				return ctx.get(e.name, MacroLayer, e.pos);
    96  			else
    97  				return ast2table(e, (AST e){return eval(e,lay,ctx);});
    98  		if( isUserDefinedLayer(lay) && !ctx.has(e.name, lay) )
    99  			return lift(ctx.get(e.name, ValueLayer, e.pos), lay, ctx, e.pos);
   100  		return ctx.get(e.name, lay, e.pos);
   101  	}
   102  
   103  	Value eval( App e, Layer lay, Table ctx, bool overwriteCtx=CascadeCtx )
   104  	{
   105  		Value f = eval( e.fun, lay, ctx );
   106  		if( isASTLayer(lay) ) {
   107  			auto ff = cast(FunValue)f;
   108  			if( ff !is null && isMacroLayer(lay) )
   109  				return invokeFunction(ff, e.args, lay, ctx, e.pos, getNameIfPossible(e.fun));
   110  			else
   111  				return ast2table(e, (AST e){return eval(e,lay,ctx);});
   112  		}
   113  		return invokeFunction(f, e.args, lay, ctx, e.pos, getNameIfPossible(e.fun));
   114  	}
   115  	
   116  	Value eval( Fun e, Layer lay, Table ctx, bool overwriteCtx=CascadeCtx )
   117  	{
   118  		if( isASTLayer(lay) )
   119  		{
   120  			// need this for correct scoping (outer scope macro variables must be hidden!)
   121  			Table newCtx = new Table(ctx, Table.Kind.NotPropagateSet);
   122  			foreach(p; e.params)
   123  				newCtx.set(p.name, NoopLayer, null);
   124  			return ast2table(e, (AST e){return eval(e,lay,newCtx);});
   125  		}
   126  		else
   127  			return createNewFunction(e, ctx);
   128  	}
   129  	
   130  	Value eval( Lay e, Layer lay, Table ctx, bool overwriteCtx=CascadeCtx )
   131  	{
   132  		if( isNoLayerChangeLayer(lay) )
   133  			return ast2table(e, (AST e){return eval(e,lay,ctx);});
   134  		else
   135  			return eval(e.expr, e.layer, ctx);
   136  	}
   137  	
   138  	Value eval( Let e, Layer lay, Table ctx, bool overwriteCtx=CascadeCtx )
   139  	{
   140  		Table newCtx = overwriteCtx ? ctx : new Table(ctx, Table.Kind.NotPropagateSet);
   141  		if( isASTLayer(lay) )
   142  			return ast2table(e, (AST ee){
   143  				// need this for correct scoping (outer scope macro variables must be hidden!)
   144  				if(e.name!="_" && ee is e.expr)
   145  					newCtx.set(e.name, NoopLayer, null);
   146  				return eval(ee,lay,newCtx);
   147  			});
   148  		else
   149  		{
   150  			Value ri = eval(e.init, lay, newCtx);
   151  			if(e.name!="_")
   152  				newCtx.set(e.name, e.layer.empty ? lay : e.layer, ri);
   153  			return eval(e.expr, lay, newCtx, OverwriteCtx);
   154  		}
   155  	}
   156  
   157  	Value eval( Die e, Layer lay, Table ctx, bool overwriteCtx=CascadeCtx )
   158  	{
   159  		if( isMacroLayer(lay) )
   160  			return ast2table(e, (AST e){return eval(e,lay,ctx);});
   161  		if( isUserDefinedLayer(lay) )
   162  			return new UndefinedValue;
   163  		throw genex!RuntimeException(e.pos, "undefined case");
   164  	}
   165  
   166  private:
   167  	// little little bit incremental macro defining version.
   168  	// enables @macro foo(x)=... in ... foo ..., only at the top level of the
   169  	// interpreter and functions. better than nothing :P
   170  	Tuple!(Value,AST) macroAndEval( AST e_, Layer lay, Table ctx, bool overwriteCtx
   171  		, ref AST[void*] mandeCache) // [TODO] avoid assuming non-moving GC
   172  	{
   173  		assert( !isASTLayer(lay) );
   174  
   175  		AST decodeAST(Value v, LexPosition pos)
   176  		{
   177  			// [TODO] more informative error message
   178  			return polemy2d!(AST)(v, pos);
   179  		}
   180  
   181  		if(auto e = cast(Let)e_)
   182  		{
   183  			void* key = cast(void*)e.init;
   184  			AST ai;
   185  			if(auto p = key in mandeCache)
   186  				ai = *p;
   187  			else {
   188  				ai = decodeAST(eval(e.init, RawMacroLayer, ctx), e.init.pos);
   189  				mandeCache[key] = ai;
   190  			}
   191  			Value vi = eval(ai, lay, ctx);
   192  			
   193  			if( !overwriteCtx )
   194  				ctx = new Table(ctx, Table.Kind.NotPropagateSet);
   195  			string theLayer = e.layer.empty ? lay : e.layer;
   196  			ctx.set(e.name, theLayer, vi);
   197  
   198  			auto ave = macroAndEval( e.expr, lay, ctx, OverwriteCtx, mandeCache );
   199  			AST  a = new Let(e.pos, e.name, e.layer, ai, ave[1]);
   200  			return tuple(ave[0], a);
   201  		}
   202  		else
   203  		{
   204  			void* key = cast(void*)e_;
   205  			AST a;
   206  			if(auto p = key in mandeCache)
   207  				a = *p;
   208  			else {
   209  				a = decodeAST(eval(e_, RawMacroLayer, ctx), e_.pos);
   210  				mandeCache[key] = a;
   211  			}
   212  			Value v = eval(a, lay, ctx, overwriteCtx);
   213  			return tuple(v, a);
   214  		}
   215  	}
   216  
   217  private:
   218  	string getNameIfPossible(AST e)
   219  	{
   220  		if(auto v = cast(Var)e)
   221  			return v.name;
   222  		return "";
   223  	}
   224  	
   225  	Value invokeFunction(Value _f, AST[] args, Layer lay, Table ctx, LexPosition pos, string callstackmsg)
   226  	{
   227  		if(auto f = cast(FunValue)_f)
   228  		{
   229  			Table newCtx = new Table(f.definitionContext(), Table.Kind.NotPropagateSet);
   230  			foreach(i,p; f.params())
   231  				if( p.layers.empty )
   232  					newCtx.set(p.name, isMacroLayer(lay)?MacroLayer:lay, eval(args[i], lay, ctx));
   233  				else
   234  					foreach(argLay; p.layers)
   235  						if( lay!=MacroLayer && isMacroLayer(argLay) ) // explicit @macro invokes (rawmacro)
   236  							newCtx.set(p.name, argLay, eval(args[i], RawMacroLayer, ctx));
   237  						else
   238  							newCtx.set(p.name, argLay, eval(args[i], argLay, ctx));
   239  			scope _ = new PushCallStack(pos, callstackmsg);
   240  			return f.invoke(isMacroLayer(lay)?MacroLayer:lay, newCtx, pos);
   241  		}
   242  		throw genex!RuntimeException(pos, text("tried to call non-function: ",_f));
   243  	}
   244  
   245  	Value lift(Value v, Layer lay, Table ctx, LexPosition pos)
   246  	{
   247  		assert( !isASTLayer(lay), "lift to the @macro layer should never happen" );
   248  
   249  		// functions are automatically lifterd
   250  		if( cast(FunValue) v )
   251  			return v;
   252  
   253  		if( !ctx.has(lay, LiftLayer) )
   254  			throw genex!RuntimeException(pos, "lift function for "~lay~" is not registered" );
   255  
   256  		// similar to invokeFunction, but with only one argument bound to ValueLayer
   257  		auto _f = ctx.get(lay, LiftLayer, pos);
   258  		if(auto f = cast(FunValue)_f)
   259  		{
   260  			Table newCtx = new Table(f.definitionContext(), Table.Kind.NotPropagateSet);
   261  			auto ps = f.params();
   262  			if( ps.length != 1 )
   263  				throw genex!RuntimeException(pos,
   264  					text("lift function for", lay, " must take exactly one argument of ", ValueLayer));
   265  			if( ps[0].layers.length==0 || ps[0].layers.length==1 && ps[0].layers[0]==ValueLayer )
   266  			{
   267  				newCtx.set(ps[0].name, ValueLayer, v);
   268  				scope _ = new PushCallStack(pos, lay);
   269  				return f.invoke(ValueLayer, newCtx, pos);
   270  			}
   271  			else
   272  				throw genex!RuntimeException(pos,
   273  					text("lift function for", lay, " must take exactly one argument of ", ValueLayer));
   274  		}
   275  		throw genex!RuntimeException(pos,
   276  			text("non-function ", _f, " is registered as the lift function for ", lay));
   277  	}
   278  
   279  	Value createNewFunction(Fun e, Table ctx)
   280  	{
   281  		class UserDefinedFunValue : FunValue
   282  		{
   283  			Fun   ast;
   284  			Table defCtx;
   285  			override const(Parameter[]) params() { return ast.params; }
   286  			override Table definitionContext()   { return defCtx; }
   287  
   288  			this(Fun ast, Table defCtx) { this.ast=ast; this.defCtx=defCtx; }
   289  			override string toString() const
   290  				{ return sprintf!"(function:%x:%x)"(cast(void*)ast, cast(void*)defCtx); }
   291  			override int opCmp(Object rhs) {
   292  				if(auto r = cast(UserDefinedFunValue)rhs) {
   293  					if(auto c = typeid(void*).compare(cast(void*)ast, cast(void*)r.ast))
   294  						return c;
   295  					if(auto c = typeid(void*).compare(cast(void*)defCtx, cast(void*)r.defCtx))
   296  						return c;
   297  					return 0;// [TODO] avoid using pointer value...
   298  				}
   299  				if(auto r = cast(Value)rhs) return typeid(this).opCmp(typeid(r));
   300  				throw genex!RuntimeException("comparison with value and something other");
   301  			}
   302  			override hash_t toHash() {
   303  				return (cast(hash_t)cast(void*)ast) + (cast(hash_t)cast(void*)defCtx);
   304  			}
   305  
   306  			AST macroCache;
   307  			AST[void*] mandeCache;
   308  			static class MemokeyType
   309  			{
   310  				void* a; Layer b; Tuple!(string,Layer,Value)[] c;
   311  				hash_t toHash() {
   312  					hash_t h = structuralHash(a) + structuralHash(b);
   313  					foreach(e; c)
   314  						h += structuralHash(e[0])+structuralHash(e[1])+structuralHash(e[2]);
   315  					return h;
   316  				}
   317  				mixin SimpleToString;
   318  				mixin SimpleConstructor;
   319  				mixin SimpleCompareWithoutToHash;
   320  			}
   321  			static Tuple!(Value,int)[MemokeyType] memo;
   322  
   323  			override Value invoke(Layer lay, Table ctx, LexPosition pos)
   324  			{
   325  				if( isASTLayer(lay) )
   326  					return eval(ast.funbody, lay, ctx);
   327  
   328  				auto nonMemoizedRun = (){
   329  					if( macroCache is null )
   330  					{
   331  						auto va = macroAndEval(e.funbody, lay, ctx, CascadeCtx, mandeCache);
   332  						macroCache = va[1];
   333  						return va[0];
   334  					}
   335  					else
   336  						return eval(macroCache, lay, ctx);
   337  				};
   338  
   339  				if( !isUserDefinedLayer(lay) )
   340  					return nonMemoizedRun();
   341  
   342  				MemokeyType memokey = new MemokeyType(cast(void*)ast, lay, ctx.direct_entries());
   343  
   344  				if(auto p = memokey in memo)
   345  				{
   346  					(*p)[1] ++;
   347  					return (*p)[0];
   348  				}
   349  				else
   350  					memo[memokey] = tuple(lift(new UndefinedValue, lay, ctx, pos), 0);
   351  
   352  				Value r = nonMemoizedRun();
   353  
   354  				int touched = memo[memokey][1];
   355  				memo[memokey] = tuple(r, 12345678);
   356  				//if(touched) {DBG("rerun :: ",r);r = nonMemoizedRun();} // twice!!
   357  				return r;
   358  			}
   359  		}
   360  		return new UserDefinedFunValue(e,ctx);
   361  	}
   362  
   363  public:
   364  	/// Add primitive function to the global context
   365  	void addPrimitive(R,T...)(string name, Layer defLay, R delegate (T) dg)
   366  	{
   367  		class NativeFunValue : FunValue
   368  		{
   369  			override const(Parameter[]) params() { return params_data; }
   370  			override Table definitionContext()   { return theContext; }
   371  
   372  			override string toString() { return sprintf!"(native:%x)"(dg.funcptr); }
   373  			override int opCmp(Object rhs) {
   374  				if(auto r = cast(NativeFunValue)rhs) return typeid(typeof(dg)).compare(&dg,&r.dg);
   375  				if(auto r = cast(Value)rhs)          return typeid(this).opCmp(typeid(r));
   376  				throw genex!RuntimeException("comparison with value and something other");
   377  			}
   378  			override hash_t toHash() const {
   379  				return typeid(dg).getHash(&dg);
   380  			}
   381  
   382  			R delegate(T) dg;
   383  			Parameter[] params_data;
   384  
   385  			this(R delegate(T) dg)
   386  			{
   387  				this.dg = dg;
   388  				foreach(i, Ti; T)
   389  					params_data ~= new Parameter(text(i), []);
   390  			}
   391  
   392  			override Value invoke(Layer lay, Table ctx, LexPosition pos)
   393  			{
   394  				if( lay != defLay )
   395  					throw genex!RuntimeException(pos,
   396  						text("only ", defLay, " layer can call native function: ", name));
   397  				T typed_args;
   398  				foreach(i, Ti; T) {
   399  					typed_args[i] = cast(Ti) ctx.get(text(i), ValueLayer, pos);
   400  					if( typed_args[i] is null )
   401  						throw genex!RuntimeException(pos,
   402  							sprintf!"type mismatch on the argument %d of native function: %s"(i+1,name));
   403  				}
   404  				try {
   405  					return dg(typed_args);
   406  				} catch( RuntimeException e ) {
   407  					throw e.pos is null ? new RuntimeException(pos, e.msg, e.file, e.line) : e;
   408  				}
   409  			}
   410  		}
   411  		theContext.set(name, defLay, new NativeFunValue(dg));
   412  	}
   413  }
   414  
   415  version(unittest) import polemy.runtime;
   416  unittest
   417  {
   418  	auto e = new Evaluator;
   419  	enrollRuntimeLibrary(e);
   420  	auto r = assert_nothrow( e.evalString(`var x = 21; x + x*x;`) );
   421  	assert_eq( r, new IntValue(BigInt(21+21*21)) );
   422  	assert_eq( e.globalContext.get("x",ValueLayer), new IntValue(BigInt(21)) );
   423  	assert_nothrow( e.globalContext.get("x",ValueLayer) );
   424  	assert_throw!RuntimeException( e.globalContext.get("y",ValueLayer) );
   425  }
   426  unittest
   427  {
   428  	auto e = new Evaluator;
   429  	enrollRuntimeLibrary(e);
   430  	auto r = assert_nothrow( e.evalString(`var x = 21; var x = x + x*x;`) );
   431  	assert_eq( r, new IntValue(BigInt(21+21*21)) );
   432  	assert_eq( e.globalContext.get("x",ValueLayer), new IntValue(21+21*21) );
   433  	assert_nothrow( e.globalContext.get("x",ValueLayer) );
   434  	assert_throw!RuntimeException( e.globalContext.get("y",ValueLayer) );
   435  }
   436  unittest
   437  {
   438  	auto e = new Evaluator;
   439  	enrollRuntimeLibrary(e);
   440  	assert_eq( e.evalString(`let x=1; let y=(let x=2); x`), new IntValue(1) ); 
   441  	assert_eq( e.evalString(`let x=1; let y=(let x=2;fun(){x}); y()`), new IntValue(2) ); 
   442  }
   443  
   444  unittest
   445  {
   446  	auto e = new Evaluator;
   447  	enrollRuntimeLibrary(e);
   448  	assert_eq( e.evalString(`@a x=1; @b x=2; @a(x)`), new IntValue(BigInt(1)) );
   449  	assert_eq( e.evalString(`@a x=1; @b x=2; @b(x)`), new IntValue(BigInt(2)) );
   450  	assert_eq( e.evalString(`let x=1; let _ = (@a x=2;2); x`), new IntValue(BigInt(1)) );
   451  	e = new Evaluator;
   452  	assert_throw!Throwable( e.evalString(`let x=1; let _ = (@a x=2;2); @a(x)`) );
   453  }
   454  
   455  unittest
   456  {
   457  	auto e = new Evaluator;
   458  	enrollRuntimeLibrary(e);
   459  	assert_eq( e.evalString(`
   460  		@@s(x){x};
   461  		@s "+" = fun(x, y) {@value(
   462  			@s(x) - @s(y)
   463  		)};
   464  		@s(1 + 2)
   465  	`), new IntValue(BigInt(-1)) );
   466  }
   467  
   468  unittest
   469  {
   470  	auto e = new Evaluator;
   471  	enrollRuntimeLibrary(e);
   472  	assert_eq( e.evalString(`
   473  @@3(x){x};
   474  def incr(x) { x+1 };
   475  @ 3 incr(x) {@value( if @ 3(x)+1< 3 then @3(x)+1 else 0 )};
   476  def fb(n @value @3) { @3(n) };
   477  fb(incr(incr(incr(0))))
   478  	`), new IntValue(BigInt(0)) );
   479  }
   480  
   481  unittest
   482  {
   483  	auto e = new Evaluator;
   484  	enrollRuntimeLibrary(e);
   485  	assert_nothrow( e.evalString(`
   486  @macro twice(x) { x; x };
   487  def main() { twice(1) };
   488  main()
   489  	`) );
   490  }
   491  unittest
   492  {
   493  	auto e = new Evaluator;
   494  	enrollRuntimeLibrary(e);
   495  	assert_throw!RuntimeException( e.evalString(`case 1`) );
   496  	assert_nothrow( e.evalString(`case 1 when 1: 2`) );
   497  
   498  	// this is a shorthand for
   499  	//   @macro x = fun(){} in @macro(x)
   500  	// so it is ok to fail, but it is really incovenient on REPL
   501  	assert_nothrow( e.evalString(`@macro x=fun(){}`) );
   502  }
   503  
   504  unittest
   505  {
   506  	auto e = new Evaluator;
   507  	enrollRuntimeLibrary(e);
   508  	assert_throw!RuntimeException( e.evalString(`...`) );
   509  	assert_eq( e.evalString(`@@foo(x){x}; @foo(...)`), new UndefinedValue );
   510  }