Artifact Content
Not logged in

Artifact f4751e4eb7df513a09ba62a901f535331bcd5963


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