Artifact Content
Not logged in

Artifact 10da2d7378e56ec4422fb34c758e5190914d5ff8


     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  		return macroAndEval(e, ValueLayer, theContext, OverwriteCtx);
    29  	}
    30  
    31  	/// Evaluate the string
    32  	Value evalString(S,T...)(S str, T fn_ln_cn)
    33  	{
    34  		return evalAST(parseString(str,fn_ln_cn));
    35  	}
    36  
    37  	/// Evaluate the file
    38  	Value evalFile(S,T...)(S filename, T ln_cn)
    39  	{
    40  		return evalAST(parseFile(filename,ln_cn));
    41  	}
    42  
    43  	/// Get the global context
    44  	Table globalContext()
    45  	{
    46  		return theContext;
    47  	}
    48  
    49  private:
    50  	Table theContext;
    51  
    52  	enum : bool { CascadeCtx=false, OverwriteCtx=true };
    53  
    54  	LayerEval getLayerEvaluator(Layer lay)
    55  	{
    56  		if( lay == ValueLayer )
    57  			return new ValueLayerEval;
    58  		if( lay == RawMacroLayer )
    59  			return new RawMacroLayerEval;
    60  		if( lay == MacroLayer )
    61  			return new MacroLayerEval;
    62  		return new UserDefinedLayerEval(lay);
    63  	}
    64  
    65  	abstract class LayerEval
    66  	{
    67  		/// Concrete layers should implement these
    68  		Layer currentLayer();
    69  		Value eval_( Die e, Table ctx, bool ctxMod );///
    70  		Value eval_( Str e, Table ctx, bool ctxMod );///
    71  		Value eval_( Int e, Table ctx, bool ctxMod );///
    72  		Value eval_( Var e, Table ctx, bool ctxMod );///
    73  		Value eval_( Lay e, Table ctx, bool ctxMod );///
    74  		Value eval_( Let e, Table ctx, bool ctxMod );///
    75  		Value eval_( App e, Table ctx, bool ctxMod );///
    76  		Value eval_( Fun e, Table ctx, bool ctxMod );///
    77  
    78  		/// dynamic-overload-resolution
    79  		Value eval( AST e, Table ctx, bool ctxMod )
    80  		{
    81  			enum funName = "eval_";                 // modify here to customize
    82  			alias TypeTuple!(e,ctx,ctxMod) params;  // modify here to customize
    83  
    84  			alias typeof(__traits(getOverloads, this, funName)) ovTypes;
    85  			alias staticMap!(firstParam, ovTypes)              fstTypes;
    86  			alias DerivedToFront!(fstTypes)             fstTypes_sorted;
    87  			foreach(i, T; fstTypes_sorted)
    88  				static if( is(T == typeof(params[0])) ) {} else if( auto _x = cast(T)params[0] )
    89  					return __traits(getOverloads, this, funName)[i](_x, params[1..$]);
    90  
    91  			// modify here to customize the default behavior
    92  			assert(false, text("eval() for ",typeid(e)," [",e.pos,"] is not defined"));
    93  		}
    94  
    95  		/// 
    96  		Value invokeFunction(Value _f, AST[] args, Table ctx, LexPosition pos, string callstackmsg)
    97  		{
    98  			if(auto f = cast(FunValue)_f)
    99  			{
   100  				Table newCtx = new Table(f.definitionContext(), Table.Kind.NotPropagateSet);
   101  				foreach(i,p; f.params())
   102  					if( p.layers.empty ) {
   103  						Value v = this.eval(args[i], ctx, CascadeCtx);
   104  						if(v is null) v = ast2table(args[i]);
   105  						newCtx.set(p.name, currentLayer(), v);
   106  					}
   107  					else
   108  						foreach(argLay; p.layers) {
   109  							Layer ll = argLay;
   110  							if( isMacroLayer(argLay) && typeid(this)!=typeid(MacroLayerEval) )
   111  								ll = RawMacroLayer; // explicit @macro invokes (rawmacro)
   112  							Value v = getLayerEvaluator(ll).eval(args[i], ctx, CascadeCtx);
   113  							if(v is null) v = ast2table(args[i]);
   114  							newCtx.set(p.name, argLay, v);
   115  						}
   116  				scope _ = new PushCallStack(pos, callstackmsg);
   117  				return f.invoke(currentLayer(), newCtx, pos);
   118  			}
   119  			throw genex!RuntimeException(pos, text("tried to call non-function: ",_f));
   120  		}
   121  
   122  		///
   123  		Value lift(Value v, Table ctx, LexPosition pos)
   124  		{
   125  			Layer lay = currentLayer();
   126  
   127  			// functions are automatically lifterd
   128  			if( cast(FunValue) v )
   129  				return v;
   130  
   131  			if( !ctx.has(lay, LiftLayer) )
   132  				throw genex!RuntimeException(pos, "lift function for "~lay~" is not registered" );
   133  
   134  			// similar to invokeFunction, but with only one argument bound to ValueLayer
   135  			auto _f = ctx.get(lay, LiftLayer, pos);
   136  			if(auto f = cast(FunValue)_f)
   137  			{
   138  				Table newCtx = new Table(f.definitionContext(), Table.Kind.NotPropagateSet);
   139  				auto ps = f.params();
   140  				if( ps.length != 1 )
   141  					throw genex!RuntimeException(pos,
   142  						text("lift function for", lay, " must take exactly one argument of ", ValueLayer));
   143  				if( ps[0].layers.length==0 || ps[0].layers.length==1 && ps[0].layers[0]==ValueLayer )
   144  				{
   145  					newCtx.set(ps[0].name, ValueLayer, v);
   146  					scope _ = new PushCallStack(pos, lay);
   147  					return f.invoke(ValueLayer, newCtx, pos);
   148  				}
   149  				else
   150  					throw genex!RuntimeException(pos,
   151  						text("lift function for", lay, " must take exactly one argument of ", ValueLayer));
   152  			}
   153  			throw genex!RuntimeException(pos,
   154  				text("non-function ", _f, " is registered as the lift function for ", lay));
   155  		}
   156  	}
   157  
   158  	/// Evaluator for standard @value semantics
   159  	class ValueLayerEval : LayerEval
   160  	{
   161  		override Layer currentLayer()
   162  		{
   163  			return ValueLayer;
   164  		}
   165  		override Value eval_( Die e, Table ctx, bool ctxMod )
   166  		{
   167  			throw genex!RuntimeException(e.pos, "undefined case");
   168  		}
   169  		override Value eval_( Str e, Table ctx, bool ctxMod )
   170  		{
   171  			return new StrValue(e.data);
   172  		}
   173  		override Value eval_( Int e, Table ctx, bool ctxMod )
   174  		{
   175  			return new IntValue(e.data);
   176  		}
   177  		override Value eval_( Var e, Table ctx, bool ctxMod )
   178  		{
   179  			return ctx.get(e.name, currentLayer(), e.pos);
   180  		}
   181  		override Value eval_( Lay e, Table ctx, bool ctxMod )
   182  		{
   183  			auto le = getLayerEvaluator(e.layer);
   184  			auto v  = le.eval(e.expr,ctx,CascadeCtx);			
   185  			if( (v is null) && (cast(MacroLayerEval)le !is null) )
   186  				return ast2table(e.expr);
   187  			else
   188  				return v;
   189  		}
   190  		override Value eval_( Let e, Table ctx, bool ctxMod )
   191  		{
   192  			Table newCtx = ctxMod ? ctx : new Table(ctx, Table.Kind.NotPropagateSet);
   193  			Value ri = this.eval(e.init, newCtx, CascadeCtx);
   194  			if(e.name!="_")
   195  				newCtx.set(e.name, e.layer.empty ? currentLayer() : e.layer, ri);
   196  			return this.eval(e.expr, newCtx, OverwriteCtx);
   197  		}
   198  		override Value eval_( App e, Table ctx, bool ctxMod )
   199  		{
   200  			Value f = this.eval( e.fun, ctx, CascadeCtx );
   201  			return this.invokeFunction(f, e.args, ctx, e.pos, getNameIfPossible(e.fun));
   202  		}
   203  		override Value eval_( Fun e, Table ctx, bool ctxMod )
   204  		{
   205  			return createNewFunction(e, ctx);
   206  		}
   207  	}
   208  
   209  	/// Evaluator for user-defined layer
   210  	class UserDefinedLayerEval : ValueLayerEval
   211  	{
   212  		Layer layerID;
   213  		mixin SimpleConstructor;
   214  
   215  		override Layer currentLayer()
   216  		{
   217  			return layerID;
   218  		}
   219  		override Value eval_( Die e, Table ctx, bool ctxMod )
   220  		{
   221  			return new UndefinedValue;
   222  		}
   223  		override Value eval_( Str e, Table ctx, bool ctxMod )
   224  		{
   225  			return this.lift(new StrValue(e.data), ctx, e.pos);
   226  		}
   227  		override Value eval_( Int e, Table ctx, bool ctxMod )
   228  		{
   229  			return this.lift(new IntValue(e.data), ctx, e.pos);
   230  		}
   231  		override Value eval_( Var e, Table ctx, bool ctxMod )
   232  		{
   233  			if( ctx.has(e.name, currentLayer()) )
   234  				return ctx.get(e.name, currentLayer());
   235  			return this.lift(ctx.get(e.name, ValueLayer, e.pos), ctx, e.pos);
   236  		}
   237  	}
   238  
   239  	// Convention!!
   240  	//   returns null if never used macro-like feature
   241  	class MacroLayerEval : LayerEval
   242  	{
   243  		override Layer currentLayer()
   244  		{
   245  			return MacroLayer;
   246  		}
   247  		override Value eval_( Die e, Table ctx, bool ctxMod )
   248  		{
   249  			return null;
   250  		}
   251  		override Value eval_( Str e, Table ctx, bool ctxMod )
   252  		{
   253  			return null;
   254  		}
   255  		override Value eval_( Int e, Table ctx, bool ctxMod )
   256  		{
   257  			return null;
   258  		}
   259  		override Value eval_( Var e, Table ctx, bool ctxMod )
   260  		{
   261  			if( ctx.has(e.name, currentLayer()) )
   262  				return ctx.get(e.name, currentLayer(), e.pos);
   263  			else
   264  				return null;
   265  		}
   266  		override Value eval_( Lay e, Table ctx, bool ctxMod )
   267  		{
   268  			auto le = getLayerEvaluator(e.layer);
   269  			return le.eval(e.expr,ctx,CascadeCtx);
   270  		}
   271  		override Value eval_( Let e, Table ctx, bool ctxMod )
   272  		{
   273  			Table newCtx = ctxMod ? ctx : new Table(ctx, Table.Kind.NotPropagateSet);
   274  			Value ai = this.eval(e.init, newCtx, CascadeCtx);
   275  			newCtx.set(e.name, NoopLayer, null);
   276  			Value ae = this.eval(e.expr, newCtx, OverwriteCtx);
   277  			if( ai is null && ae is null )
   278  				return null;
   279  			if( ai is null ) ai = ast2table(e.init);
   280  			if( ae is null ) ae = ast2table(e.expr);
   281  			return ast2table(e, delegate Value (AST _){
   282  				if(_ is e.init) { return ai; }
   283  				if(_ is e.expr) { return ae; }
   284  				assert(false);
   285  			});
   286  		}
   287  		override Value eval_( App e, Table ctx, bool ctxMod )
   288  		{
   289  			Value f = this.eval( e.fun, ctx, CascadeCtx );
   290  			if(auto ff = cast(FunValue)f)
   291  				return this.invokeFunction(ff, e.args, ctx, e.pos, getNameIfPossible(e.fun));
   292  			else {
   293  				bool allNull = (f is null);
   294  				Value[] vas;
   295  				foreach(a; e.args) {
   296  					Value va = this.eval(a, ctx, CascadeCtx);
   297  					if(va !is null) allNull = false;
   298  					vas ~= va;
   299  				}
   300  				if( allNull )
   301  					return null;
   302  				return ast2table(e, delegate Value (AST _){
   303  					if(_ is e.fun) return (f is null ? ast2table(e.fun) : f);
   304  					foreach(i,a; e.args) if(_ is a) return (vas[i] is null ? ast2table(a) : vas[i]);
   305  					assert(false);
   306  				});
   307  			}
   308  		}
   309  		override Value eval_( Fun e, Table ctx, bool ctxMod )
   310  		{
   311  			Table newCtx = new Table(ctx, Table.Kind.NotPropagateSet);
   312  			foreach(p; e.params)
   313  				newCtx.set(p.name, NoopLayer, null);
   314  			Value af = this.eval(e.funbody, newCtx, CascadeCtx);
   315  			if( af is null )
   316  				return null;
   317  			return ast2table(e, (AST _){if(_ is e.funbody)return af; assert(false);});
   318  		}
   319  	}
   320  
   321  	class RawMacroLayerEval : MacroLayerEval
   322  	{
   323  		override Value eval_( Lay e, Table ctx, bool ctxMod )
   324  		{
   325  			Value ae = this.eval(e.expr, ctx, CascadeCtx);
   326  			return ae is null ? null
   327  			       : ast2table(e, delegate Value (AST _){if(_ is e.expr)return ae; assert(false);});
   328  		}
   329  	}
   330  
   331  private:
   332  	Value macroAndEval( AST e_, Layer lay, Table ctx, bool ctxMod )
   333  	{
   334  		assert( !isASTLayer(lay) );
   335  		if(auto e = cast(Let)e_)
   336  		{
   337  			Value vai = getLayerEvaluator(RawMacroLayer).eval(e.init, ctx, CascadeCtx);
   338  			AST ai = (vai is null ? e.init : polemy2d!(AST)(vai, e.pos));
   339  
   340  			if( !ctxMod )
   341  				ctx = new Table(ctx, Table.Kind.NotPropagateSet);
   342  
   343  			Value vi = getLayerEvaluator(lay).eval(ai, ctx, CascadeCtx);
   344  			string theLayer = e.layer.empty ? lay : e.layer;
   345  			ctx.set(e.name, theLayer, vi);
   346  
   347  			return macroAndEval( e.expr, lay, ctx, OverwriteCtx );
   348  		}
   349  		else
   350  		{
   351  			Value va = getLayerEvaluator(RawMacroLayer).eval(e_, ctx, ctxMod);
   352  			AST a = (va is null ? e_ : polemy2d!(AST)(va, e_.pos));
   353  			return getLayerEvaluator(lay).eval(a, ctx, ctxMod);
   354  		}
   355  	}
   356  
   357  private:
   358  	string getNameIfPossible(AST e)
   359  	{
   360  		if(auto v = cast(Var)e)
   361  			return v.name;
   362  		return "";
   363  	}
   364  
   365  	Value createNewFunction(Fun e, Table ctx)
   366  	{
   367  		class UserDefinedFunValue : FunValue
   368  		{
   369  			Fun   ast;
   370  			Table defCtx;
   371  			override const(Parameter[]) params() { return ast.params; }
   372  			override Table definitionContext()   { return defCtx; }
   373  
   374  			this(Fun ast, Table defCtx) { this.ast=ast; this.defCtx=defCtx; }
   375  			override string toString() const
   376  				{ return sprintf!"(function:%x:%x)"(cast(void*)ast, cast(void*)defCtx); }
   377  			override int opCmp(Object rhs) {
   378  				if(auto r = cast(UserDefinedFunValue)rhs) {
   379  					if(auto c = typeid(void*).compare(cast(void*)ast, cast(void*)r.ast))
   380  						return c;
   381  					if(auto c = typeid(void*).compare(cast(void*)defCtx, cast(void*)r.defCtx))
   382  						return c;
   383  					return 0;// [TODO] avoid using pointer value...
   384  				}
   385  				if(auto r = cast(Value)rhs) return typeid(this).opCmp(typeid(r));
   386  				throw genex!RuntimeException("comparison with value and something other");
   387  			}
   388  			override hash_t toHash() {
   389  				return (cast(hash_t)cast(void*)ast) + (cast(hash_t)cast(void*)defCtx);
   390  			}
   391  
   392  			AST macroCache;
   393  			AST[void*] mandeCache;
   394  			static class MemokeyType
   395  			{
   396  				void* a; Layer b; Tuple!(string,Layer,Value)[] c;
   397  				hash_t toHash() {
   398  					hash_t h = structuralHash(a) + structuralHash(b);
   399  					foreach(e; c)
   400  						h += structuralHash(e[0])+structuralHash(e[1])+structuralHash(e[2]);
   401  					return h;
   402  				}
   403  				mixin SimpleToString;
   404  				mixin SimpleConstructor;
   405  				mixin SimpleCompareWithoutToHash;
   406  			}
   407  			static Tuple!(Value,int)[MemokeyType] memo;
   408  
   409  			override Value invoke(Layer lay, Table ctx, LexPosition pos)
   410  			{
   411  				if( isASTLayer(lay) ) {
   412  					Value v = getLayerEvaluator(lay).eval(ast.funbody, ctx, CascadeCtx);
   413  					if( v is null ) v = ast2table(ast.funbody);
   414  					return v;
   415  				}
   416  				return macroAndEval(ast.funbody, lay, ctx, CascadeCtx);
   417  /*
   418  				auto nonMemoizedRun = (){
   419  					if( macroCache is null )
   420  					{
   421  						auto va = macroAndEval(e.funbody, lay, ctx, CascadeCtx, mandeCache);
   422  						macroCache = va[1];
   423  						return va[0];
   424  					}
   425  					else
   426  						return eval(macroCache, lay, ctx);
   427  				};
   428  
   429  				if( !isUserDefinedLayer(lay) )
   430  					return nonMemoizedRun();
   431  
   432  				MemokeyType memokey = new MemokeyType(cast(void*)ast, lay, ctx.direct_entries());
   433  
   434  				if(auto p = memokey in memo)
   435  				{
   436  					(*p)[1] ++;
   437  					return (*p)[0];
   438  				}
   439  				else
   440  					memo[memokey] = tuple(lift(new UndefinedValue, lay, ctx, pos), 0);
   441  
   442  				Value r = nonMemoizedRun();
   443  
   444  				int touched = memo[memokey][1];
   445  				memo[memokey] = tuple(r, 12345678);
   446  				//if(touched) {DBG("rerun :: ",r);r = nonMemoizedRun();} // twice!!
   447  				return r;
   448  */
   449  			}
   450  		}
   451  		return new UserDefinedFunValue(e,ctx);
   452  	}
   453  
   454  public:
   455  	/// Add primitive function to the global context
   456  	void addPrimitive(R,T...)(string name, Layer defLay, R delegate (T) dg)
   457  	{
   458  		class NativeFunValue : FunValue
   459  		{
   460  			override const(Parameter[]) params() { return params_data; }
   461  			override Table definitionContext()   { return theContext; }
   462  
   463  			override string toString() { return sprintf!"(native:%x)"(dg.funcptr); }
   464  			override int opCmp(Object rhs) {
   465  				if(auto r = cast(NativeFunValue)rhs) return typeid(typeof(dg)).compare(&dg,&r.dg);
   466  				if(auto r = cast(Value)rhs)          return typeid(this).opCmp(typeid(r));
   467  				throw genex!RuntimeException("comparison with value and something other");
   468  			}
   469  			override hash_t toHash() const {
   470  				return typeid(dg).getHash(&dg);
   471  			}
   472  
   473  			R delegate(T) dg;
   474  			Parameter[] params_data;
   475  
   476  			this(R delegate(T) dg)
   477  			{
   478  				this.dg = dg;
   479  				foreach(i, Ti; T)
   480  					params_data ~= new Parameter(text(i), []);
   481  			}
   482  
   483  			override Value invoke(Layer lay, Table ctx, LexPosition pos)
   484  			{
   485  				if( lay != defLay )
   486  					throw genex!RuntimeException(pos,
   487  						text("only ", defLay, " layer can call native function: ", name));
   488  				T typed_args;
   489  				foreach(i, Ti; T) {
   490  					typed_args[i] = cast(Ti) ctx.get(text(i), ValueLayer, pos);
   491  					if( typed_args[i] is null )
   492  						throw genex!RuntimeException(pos,
   493  							sprintf!"type mismatch on the argument %d of native function: %s"(i+1,name));
   494  				}
   495  				try {
   496  					return dg(typed_args);
   497  				} catch( RuntimeException e ) {
   498  					throw e.pos is null ? new RuntimeException(pos, e.msg, e.file, e.line) : e;
   499  				}
   500  			}
   501  		}
   502  		theContext.set(name, defLay, new NativeFunValue(dg));
   503  	}
   504  }
   505  
   506  version(unittest) import polemy.runtime;
   507  unittest
   508  {
   509  	auto e = new Evaluator;
   510  	enrollRuntimeLibrary(e);
   511  	auto r = assert_nothrow( e.evalString(`var x = 21; x + x*x;`) );
   512  	assert_eq( r, new IntValue(BigInt(21+21*21)) );
   513  	assert_eq( e.globalContext.get("x",ValueLayer), new IntValue(BigInt(21)) );
   514  	assert_nothrow( e.globalContext.get("x",ValueLayer) );
   515  	assert_throw!RuntimeException( e.globalContext.get("y",ValueLayer) );
   516  }
   517  unittest
   518  {
   519  	auto e = new Evaluator;
   520  	enrollRuntimeLibrary(e);
   521  	auto r = assert_nothrow( e.evalString(`var x = 21; var x = x + x*x;`) );
   522  	assert_eq( r, new IntValue(BigInt(21+21*21)) );
   523  	assert_eq( e.globalContext.get("x",ValueLayer), new IntValue(21+21*21) );
   524  	assert_nothrow( e.globalContext.get("x",ValueLayer) );
   525  	assert_throw!RuntimeException( e.globalContext.get("y",ValueLayer) );
   526  }
   527  unittest
   528  {
   529  	auto e = new Evaluator;
   530  	enrollRuntimeLibrary(e);
   531  	assert_eq( e.evalString(`let x=1; let y=(let x=2); x`), new IntValue(1) ); 
   532  	assert_eq( e.evalString(`let x=1; let y=(let x=2;fun(){x}); y()`), new IntValue(2) ); 
   533  }
   534  
   535  unittest
   536  {
   537  	auto e = new Evaluator;
   538  	enrollRuntimeLibrary(e);
   539  	assert_eq( e.evalString(`@a x=1; @b x=2; @a(x)`), new IntValue(BigInt(1)) );
   540  	assert_eq( e.evalString(`@a x=1; @b x=2; @b(x)`), new IntValue(BigInt(2)) );
   541  	assert_eq( e.evalString(`let x=1; let _ = (@a x=2;2); x`), new IntValue(BigInt(1)) );
   542  	e = new Evaluator;
   543  	assert_throw!Throwable( e.evalString(`let x=1; let _ = (@a x=2;2); @a(x)`) );
   544  }
   545  
   546  unittest
   547  {
   548  	auto e = new Evaluator;
   549  	enrollRuntimeLibrary(e);
   550  	assert_eq( e.evalString(`
   551  		@@s(x){x};
   552  		@s "+" = fun(x, y) {@value(
   553  			@s(x) - @s(y)
   554  		)};
   555  		@s(1 + 2)
   556  	`), new IntValue(BigInt(-1)) );
   557  }
   558  
   559  unittest
   560  {
   561  	auto e = new Evaluator;
   562  	enrollRuntimeLibrary(e);
   563  	assert_eq( e.evalString(`
   564  @@3(x){x};
   565  def incr(x) { x+1 };
   566  @ 3 incr(x) {@value( if @ 3(x)+1< 3 then @3(x)+1 else 0 )};
   567  def fb(n @value @3) { @3(n) };
   568  fb(incr(incr(incr(0))))
   569  	`), new IntValue(BigInt(0)) );
   570  }
   571  
   572  unittest
   573  {
   574  	auto e = new Evaluator;
   575  	enrollRuntimeLibrary(e);
   576  	assert_nothrow( e.evalString(`
   577  @macro twice(x) { x; x };
   578  def main() { twice(1) };
   579  main()
   580  	`) );
   581  }
   582  unittest
   583  {
   584  	auto e = new Evaluator;
   585  	enrollRuntimeLibrary(e);
   586  	assert_throw!RuntimeException( e.evalString(`case 1`) );
   587  	assert_nothrow( e.evalString(`case 1 when 1: 2`) );
   588  
   589  	// this is a shorthand for
   590  	//   @macro x = fun(){} in @macro(x)
   591  	// so it is ok to fail, but it is really incovenient on REPL
   592  	assert_nothrow( e.evalString(`@macro x=fun(){}`) );
   593  }
   594  
   595  unittest
   596  {
   597  	auto e = new Evaluator;
   598  	enrollRuntimeLibrary(e);
   599  	assert_throw!RuntimeException( e.evalString(`...`) );
   600  	assert_eq( e.evalString(`@@foo(x){x}; @foo(...)`), new UndefinedValue );
   601  }