]> Nishi Git Mirror - gwion.git/commitdiff
:art: Introduce closures 221/head
authorfennecdjay <fennecdjay@gwion.tk>
Tue, 10 Nov 2020 16:44:21 +0000 (17:44 +0100)
committerfennecdjay <fennecdjay@gwion.tk>
Tue, 10 Nov 2020 16:44:21 +0000 (17:44 +0100)
21 files changed:
ast
include/emit.h
include/env/context.h
include/env/func.h
include/env/value.h
include/import/checker.h
include/instr.h
include/object.h
include/opcode.h
include/vm.h
opcode.txt
src/emit/emit.c
src/env/func.c
src/lib/instr.c
src/lib/lib_func.c
src/parse/check.c
src/parse/operator.c
src/parse/scan2.c
src/vm/closure.c [new file with mode: 0644]
src/vm/vm.c
src/vm/vm_code.c

diff --git a/ast b/ast
index f75d51f0b87497057ccf739063a1a6b58fe3da2f..edf503c3ffa210ad6f2ac72d57b92315f35f1335 160000 (submodule)
--- a/ast
+++ b/ast
@@ -1 +1 @@
-Subproject commit f75d51f0b87497057ccf739063a1a6b58fe3da2f
+Subproject commit edf503c3ffa210ad6f2ac72d57b92315f35f1335
index 049133a7d2d9026ad9240df74259c78f75e163de..9a8009ab64f927f03613122b7d3e49df3bc381a5 100644 (file)
@@ -7,12 +7,11 @@ typedef struct Frame_ {
 } Frame;
 
 typedef struct Code_ {
-  m_str  name;
+  Frame* frame;
   size_t stack_depth;
   struct Vector_ instr;
   struct Vector_ stack_cont, stack_break, stack_return;
-  Frame* frame;
-  ae_flag flag;
+  m_str  name;
 } Code;
 
 struct EmitterInfo_ {
index 53a1280010f95541acf01e5121ef27f1d32b1341..34b7b2e333006a0364f7d57a74b1ca71292dcee9 100644 (file)
@@ -6,9 +6,9 @@ struct Context_ {
   Ast         tree;
   Nspc        nspc;
   struct Map_ lbls;
-  uint16_t ref;
   m_bool error;
   m_bool global;
+  uint16_t ref;
 };
 
 ANN void free_context(const Context, struct Gwion_*const);
index e28a706ef74db777cf549bdd574c16f511e8d97d..b0b6203cb5a69315f0d7609403b32c27e234643b 100644 (file)
@@ -16,6 +16,7 @@ struct Func_ {
   Value value_ref;
   Func next;
   size_t vt_index;
+  struct Map_ upvalues;
   uint16_t ref;
   ae_flag flag;
   enum fflag fflag;
index c3b334337fc9b2dff74277511c5301aa2dc6e688..912eed82c11a20c26b25f02a0344d1df99a0fa0f 100644 (file)
@@ -17,7 +17,8 @@ enum vflag {
   vflag_valid    = 1 << 6,
   vflag_direct    = 1 << 7,
   vflag_builtin    = 1 << 8,
-  vflag_member   = 1 << 9
+  vflag_member   = 1 << 9,
+  vflag_closed   = 1 << 10
 //  vflag_used = 1 << 3
 } __attribute__((packed));
 
index 5ef1d61aab9e830b4cb1356b38f75c96cc5a6872..3221164c98a316a28a61eddbca00156314cb0b6c 100644 (file)
@@ -30,9 +30,9 @@ typedef struct ImportCK { // name_checker ?
     Type_Decl *td; // typedef
     ID_List curr;// enum
   };
-  ae_flag flag; // ????
   uint variadic;
   enum importck_type type;
+  ae_flag flag; // ????
 } ImportCK;
 
 typedef struct OperCK { // name_checker ?
index 5e260639d9a5f9e32243304e43ef8529e90f586e..d709f7e4cea632ad8d2366d0656f4168a25a231d 100644 (file)
@@ -61,7 +61,6 @@ struct dottmpl_ {
   Func_Def base, def;
   Type owner_class;
   Nspc owner;
-  size_t vt_index;
   Type_List tl;
   void* xfun;// (type is f_xfun)
 };
index 8b7d688a4121fa043bce720de84ab47d241161b3..e16f77934d4311ada76117c7f8480fb066510d2c 100644 (file)
@@ -40,5 +40,11 @@ typedef void (f_release)(const VM_Shred shred, const Type t NUSED, const m_bit*
 #define RELEASE_FUNC(a) void (a)(const VM_Shred shred, const Type t NUSED, const m_bit* ptr)
 static inline RELEASE_FUNC(object_release) { release(*(M_Object*)ptr, shred); }
 RELEASE_FUNC(struct_release);
+static inline void compound_release(const VM_Shred shred, const Type t, const m_bit* ptr) {
+  if(!tflag(t, tflag_struct))
+    object_release(shred, t, ptr);
+  else
+    struct_release(shred, t, ptr);
+}
 
 #endif
index a7ed4a7418746dd33ef8c0ec8c80099fd4bb6649..4385852b6b2d45a02fd1bc4feef3dc714fa1604a 100644 (file)
@@ -17,6 +17,7 @@ enum {
   eRegPushBase3,
   eRegPushBase4,
   eReg2Reg,
+  eReg2RegOther,
   eReg2RegAddr,
   eReg2RegDeref,
   eStructMember,
@@ -165,6 +166,10 @@ enum {
   eDotStatic,
   eDotStatic2,
   eDotStatic3,
+  eUpvalueInt,
+  eUpvalueFloat,
+  eUpvalueOther,
+  eUpvalueAddr,
   eDotFunc,
   eDotStaticFunc,
   eGcIni,
@@ -195,6 +200,7 @@ enum {
 #define  RegPushBase3        (f_instr)eRegPushBase3
 #define  RegPushBase4        (f_instr)eRegPushBase4
 #define  Reg2Reg             (f_instr)eReg2Reg
+#define  Reg2RegOther        (f_instr)eReg2RegOther
 #define  Reg2RegAddr         (f_instr)eReg2RegAddr
 #define  Reg2RegDeref        (f_instr)eReg2RegDeref
 #define  StructMember        (f_instr)eStructMember
@@ -343,6 +349,10 @@ enum {
 #define  DotStatic           (f_instr)eDotStatic
 #define  DotStatic2          (f_instr)eDotStatic2
 #define  DotStatic3          (f_instr)eDotStatic3
+#define  UpvalueInt          (f_instr)eUpvalueInt
+#define  UpvalueFloat        (f_instr)eUpvalueFloat
+#define  UpvalueOther        (f_instr)eUpvalueOther
+#define  UpvalueAddr         (f_instr)eUpvalueAddr
 #define  DotFunc             (f_instr)eDotFunc
 #define  DotStaticFunc       (f_instr)eDotStaticFunc
 #define  GcIni               (f_instr)eGcIni
index 6dd7c9293e80717f951f12b689d8cd8b18810787..fe802a9ea83d606e0737b7369983524e26ccbc61 100644 (file)
@@ -1,6 +1,14 @@
 #ifndef __VM
 #define __VM
 
+typedef struct Closure_ {
+  m_bit *data;
+  struct Map_ m;
+  m_uint sz;
+} Closure;
+ANN Closure* new_closure(MemPool mp, const m_uint sz);
+ANN void free_closure(Closure *a, const Gwion gwion);
+
 typedef struct VM_Code_* VM_Code;
 struct VM_Code_ {
   m_bit *bytecode;
@@ -10,6 +18,7 @@ struct VM_Code_ {
   };
   size_t stack_depth;
   void* memoize;
+  Closure *closure;
   m_str name;
   uint16_t ref;
   ae_flag flag;
index 2ae78cc84e4cf64fcf5253c28245baeb36972a4a..18d94e12315c1c8ece230d4dc4481573022a8198 100644 (file)
@@ -14,6 +14,7 @@ RegPushBase2
 RegPushBase3
 RegPushBase4
 Reg2Reg
+Reg2RegOther
 Reg2RegAddr
 Reg2RegDeref
 StructMember
@@ -162,6 +163,10 @@ DotMember4
 DotStatic
 DotStatic2
 DotStatic3
+UpvalueInt
+UpvalueFloat
+UpvalueOther
+UpvalueAddr
 DotFunc
 DotStaticFunc
 GcIni
index 4fc29dd775ee15d3332fbdfce29ecde9abcd58ef..526f237ceb1c89107d3a177d8051dcf036bd2d58 100644 (file)
@@ -470,7 +470,19 @@ ANN static inline Instr specialid_instr(const Emitter emit,
   return spid->exec ? emit_add_instr(emit, spid->exec) : spid->em(emit, prim);
 }
 
+static const f_instr upvalue[] = { UpvalueInt, UpvalueFloat, UpvalueOther, UpvalueAddr };
 ANN static m_bool emit_prim_id(const Emitter emit, const Symbol *data) {
+  const Exp_Primary *prim = prim_self(data);
+  if(prim->value && emit->env->func && emit->env->func->upvalues.ptr) {
+    const Map map = &emit->env->func->upvalues;
+    for(m_uint i = 0; i < map_size(map); ++i) {
+      if(prim->value == (Value)((Exp_Primary*)VKEY(map, i))->value) {
+        const Instr instr = emit_kind(emit, prim->value->type->size, exp_getvar(exp_self(prim)), upvalue);
+        instr->m_val = i ? VVAL(map, i) : 0;
+        return GW_OK;
+      }
+    }
+  }
   struct SpecialId_ * spid = specialid_get(emit->gwion, *data);
   if(spid)
     return specialid_instr(emit, spid, prim_self(data)) ? GW_OK : GW_ERROR;
@@ -710,7 +722,7 @@ if(isa(type, emit->gwion->type[et_union]) < 0)
       push->m_val = -(missing_depth) * SZ_INT;
     }
     assign->m_val = emit_var;
-    (void)emit_addref(emit, emit_var);
+//    (void)emit_addref(emit, emit_var);
   } else if(struct_ctor(v) /* && !GET_FLAG(decl->td, ref) */)
     emit_struct_decl_finish(emit, v->type, emit_addr);
   return GW_OK;
@@ -930,7 +942,6 @@ static inline m_bool push_func_code(const Emitter emit, const Func f) {
     c[sz] = '\0';
     struct dottmpl_ *dt = mp_calloc(emit->gwion->mp, dottmpl);
     dt->name = s_name(insert_symbol(c));
-    dt->vt_index = f->def->base->tmpl->base;
     dt->tl = cpy_type_list(emit->gwion->mp, f->def->base->tmpl->call);
     dt->base = f->def;
     instr->opcode = eOP_MAX;
@@ -969,7 +980,6 @@ ANN static void tmpl_prelude(const Emitter emit, const Func f) {
   c[sz] = '\0';
   dt->tl = cpy_type_list(emit->gwion->mp, f->def->base->tmpl->call);
   dt->name = s_name(insert_symbol(c));
-  dt->vt_index = f->def->base->tmpl->base;
   dt->base = f->def;
   dt->owner = f->value_ref->from->owner;
   dt->owner_class = f->value_ref->from->owner_class;
@@ -1301,31 +1311,6 @@ ANN static m_bool emit_exp_if(const Emitter emit, const Exp_If* exp_if) {
   return ret;
 }
 
-ANN static m_bool emit_lambda(const Emitter emit, const Exp_Lambda * lambda) {
-  CHECK_BB(emit_func_def(emit, lambda->def))
-  if(vflag(lambda->def->base->func->value_ref, vflag_member) && !exp_getvar(exp_self(lambda)))
-    emit_add_instr(emit, RegPushMem);
-  regpushi(emit, (m_uint)lambda->def->base->func->code);
-  return GW_OK;
-}
-
-ANN static m_bool emit_exp_lambda(const Emitter emit, const Exp_Lambda * lambda) {
-  if(!lambda->def->base->func) {
-    regpushi(emit, SZ_INT);
-    return GW_OK;
-  }
-  struct EnvSet es = { .env=emit->env, .data=emit, .func=(_exp_func)emit_cdef,
-    .scope=emit->env->scope->depth, .flag=tflag_emit };
-  CHECK_BB(envset_push(&es, lambda->owner, lambda->def->base->func->value_ref->from->owner))
-  const m_bool ret = emit_lambda(emit, lambda);
-  if(es.run)
-    envset_pop(&es, lambda->owner);
-  return ret;
-}
-
-DECL_EXP_FUNC(emit, m_bool, Emitter)
-
-
 ANN static void struct_addref(const Emitter emit, const Type type,
     const m_int size, const m_bool offset, const m_bool emit_var) {
   if(!type->info->tuple)
@@ -1341,6 +1326,7 @@ ANN static void struct_addref(const Emitter emit, const Type type,
   }
 }
 
+
 ANN static inline m_uint exp_size(const Exp e) {
   if(exp_getvar(e))
     return SZ_INT;
@@ -1364,6 +1350,73 @@ ANN2(1) static void emit_exp_addref(const Emitter emit, /* const */Exp exp, m_in
   } while((exp = exp->next));
 }
 
+
+ANN static inline m_bool emit_prim_novar(const Emitter emit, const Exp_Primary *prim) {
+  const Exp e = exp_self(prim);
+  const uint var = exp_getvar(e);
+  exp_setvar(e, 0);
+  CHECK_BB(emit_symbol(emit, prim))
+  exp_setvar(e, var);
+  return GW_OK;
+}
+
+ANN static m_bool emit_upvalues(const Emitter emit, const Func func) {
+  const Map map = &func->upvalues;
+  for(m_uint i = 0; i < map_size(map); ++i) {
+    const Exp_Primary *prim = (Exp_Primary*)VKEY(map, i);
+    const Value v = prim->value;
+    CHECK_BB(emit_prim_novar(emit, prim));
+    if(isa(prim->value->type, emit->gwion->type[et_compound]) > 0) {
+       emit_exp_addref1(emit, exp_self(prim), -v->type->size);
+       if(vflag(v, vflag_fglobal) && !vflag(v, vflag_closed))
+         emit_exp_addref1(emit, exp_self(prim), -v->type->size);
+       map_set(&func->code->closure->m, (vtype)v->type, VVAL(map, i));
+    }
+    set_vflag(v, vflag_closed);
+  }
+  return GW_OK;
+}
+
+ANN static m_bool emit_closure(const Emitter emit, const Func func) {
+  const Map map = &func->upvalues;
+  const m_uint sz = VVAL(map, VLEN(map) - 1) + ((Exp_Primary*)VKEY(map, VLEN(map) - 1))->value->type->size;
+  func->code->closure = new_closure(emit->gwion->mp, sz);
+  regpushi(emit, (m_uint)func->code->closure->data);
+  CHECK_BB(emit_upvalues(emit, func))
+  regpop(emit, sz);
+  const Instr cpy = emit_add_instr(emit, Reg2RegOther);
+  cpy->m_val2 = sz;
+  regpop(emit, SZ_INT);
+  return GW_OK;
+}
+
+ANN static m_bool emit_lambda(const Emitter emit, const Exp_Lambda * lambda) {
+  CHECK_BB(emit_func_def(emit, lambda->def))
+  if(lambda->def->base->func->upvalues.ptr)
+    CHECK_BB(emit_closure(emit, lambda->def->base->func))
+  if(vflag(lambda->def->base->func->value_ref, vflag_member) && !exp_getvar(exp_self(lambda)))
+    emit_add_instr(emit, RegPushMem);
+  regpushi(emit, (m_uint)lambda->def->base->func->code);
+  return GW_OK;
+}
+
+ANN static m_bool emit_exp_lambda(const Emitter emit, const Exp_Lambda * lambda) {
+  if(!lambda->def->base->func) {
+    regpushi(emit, SZ_INT);
+    return GW_OK;
+  }
+  struct EnvSet es = { .env=emit->env, .data=emit, .func=(_exp_func)emit_cdef,
+    .scope=emit->env->scope->depth, .flag=tflag_emit };
+  CHECK_BB(envset_push(&es, lambda->owner, lambda->def->base->func->value_ref->from->owner))
+  const m_bool ret = emit_lambda(emit, lambda);
+  if(es.run)
+    envset_pop(&es, lambda->owner);
+  return ret;
+}
+
+DECL_EXP_FUNC(emit, m_bool, Emitter)
+
+
 ANN2(1) /*static */m_bool emit_exp(const Emitter emit, /* const */Exp e) {
   Exp exp = e;
   do {
index 6417d2a3b53d563cb6accb41eca085016a7ddde1..c6289ccd037774d87cf2f198f85233aa24cfbd16 100644 (file)
@@ -10,6 +10,8 @@ ANN void free_func(Func a, Gwion gwion) {
     func_def_cleaner(gwion, a->def);
   if(a->code)
     vmcode_remref(a->code, gwion);
+  if(a->upvalues.ptr)
+    map_release(&a->upvalues);
   mp_free(gwion->mp, Func, a);
 }
 
index da19212806ef68c0758493cee419871ba13e6ad5..775c3f3f8d890cc55c73a9e7e3655cffa48597cd 100644 (file)
@@ -33,7 +33,7 @@ INSTR(PopArrayClass) {
 ANN static Func_Def from_base(const Env env, struct dottmpl_ *const dt, const Nspc nspc) {
   const Func_Def fdef = dt->def ?: dt->base;
   const Symbol sym = func_symbol(env, nspc->name, s_name(fdef->base->xid),
-    "template", dt->vt_index);
+    "template", dt->base->base->tmpl->base);
   DECL_OO(const Value, v, = nspc_lookup_value0(nspc, sym) ?: nspc_lookup_value0(nspc, fdef->base->xid))
   if(isa(v->type, env->gwion->type[et_class]) > 0)
     return NULL;
@@ -45,7 +45,7 @@ ANN static Func_Def from_base(const Env env, struct dottmpl_ *const dt, const Ns
   if(vflag(v, vflag_builtin))
     v->d.func_ref->def->d.dl_func_ptr = dt->xfun;
   def->base->tmpl->call = cpy_type_list(env->gwion->mp, dt->tl);
-  def->base->tmpl->base = dt->vt_index;
+  def->base->tmpl->base = dt->base->base->tmpl->base;
   dt->def = def;
   dt->owner = v->from->owner;
   dt->owner_class = v->from->owner_class;
index 9d6cdf2bcff9454fef823f3ed90a665905c57761..40e060577f20aa39d577a9de0d5e9143e8805b82 100644 (file)
@@ -152,29 +152,24 @@ ANN static m_bool _check_lambda(const Env env, Exp_Lambda *l, const Func_Def def
     ERR_B(exp_self(l)->pos, _("argument number does not match for lambda"))
   l->def->base->flag = def->base->flag;
   l->def->base->td = cpy_type_decl(env->gwion->mp, def->base->td);
-  map_set(&env->curr->info->func->map, (m_uint)l->def->base, env->scope->depth);
-  const m_bool ret = check_traverse_fdef(env, l->def);
-  map_remove(&env->curr->info->func->map, (m_uint)l->def->base);
-  CHECK_BB(ret)
+  l->def->base->values = env->curr->info->value;
+  const m_bool ret = traverse_func_def(env, l->def);
+  if(l->def->base->func) {
+    free_scope(env->gwion->mp, env->curr->info->value);
+    env->curr->info->value = l->def->base->values;
+  }
   arg = l->def->base->args;
   while(arg) {
     arg->td = NULL;
     arg = arg->next;
   }
-  return GW_OK;
+  return ret;
 }
 
 ANN m_bool check_lambda(const Env env, const Type t, Exp_Lambda *l) {
   const Func_Def fdef = t->info->func->def;
-  struct EnvSet es = { .env=env, .data=env, .func=(_exp_func)check_cdef,
-    .scope=env->scope->depth, .flag=tflag_check };
   l->owner = t->info->owner_class;
-  CHECK_BB(envset_push(&es, l->owner, t->info->owner))
-  const m_bool ret = _check_lambda(env, l, fdef);
-  if(es.run)
-    envset_pop(&es, l->owner);
-  if(ret < 0)
-    return GW_ERROR;
+  CHECK_BB(_check_lambda(env, l, fdef))
   exp_self(l)->info->type = l->def->base->func->value_ref->type;
   return GW_OK;
 }
index 3c82b6b459646b88f1179f366638c4c40cea3100..07ffe7488a3664971b19f25b836aa218f98ca856 100644 (file)
@@ -247,9 +247,18 @@ ANN m_bool not_from_owner_class(const Env env, const Type t,
   return GW_OK;
 }
 
+ANN static inline Value get_value(const Env env, const Symbol sym) {
+  const Value value = nspc_lookup_value1(env->curr, sym);
+  if(value)
+    return value;
+  if(env->func && env->func->def->base->values)
+    return  (Value)scope_lookup1(env->func->def->base->values, (vtype)sym);
+  return NULL;
+}
+
 ANN static Value check_non_res_value(const Env env, const Symbol *data) {
   const Symbol var = *data;
-  const Value value = nspc_lookup_value1(env->curr, var);
+  const Value value = get_value(env, var);
   if(env->class_def) {
     if(value && value->from->owner_class)
       CHECK_BO(not_from_owner_class(env, env->class_def, value, prim_pos(data)))
@@ -280,22 +289,20 @@ static inline Nspc value_owner(const Value v) {
   return v ? v->from->owner : NULL;
 }
 
-ANN static m_bool lambda_valid(const Env env, const Exp_Primary* exp) {
-  const Value val = exp->value;
-  const Symbol sym = insert_symbol(val->name);
-  const Vector vec = (Vector)&env->curr->info->value->ptr;
-  const m_uint scope = map_get(&env->curr->info->func->map, (m_uint)env->func->def->base);
-  if(GET_FLAG(val, global))
-    return GW_OK;
-  if(val->from->owner_class && isa(val->from->owner_class, env->class_def) > 0)
-    return GW_OK;
-  const m_uint sz = vector_size(vec);
-  for(m_uint i = scope; i < sz; ++i) {
-    const Map map = (Map)vector_at(vec, i);
-    if(map_get(map, (m_uint)sym))
-      return GW_OK;
+ANN static void check_upvalue(const Env env, const Exp_Primary *prim) {
+  const Value v = prim->value;
+  if(GET_FLAG(v, global) || (v->from->owner_class && isa(v->from->owner_class, env->class_def) > 0) ||
+      nspc_lookup_value1(env->curr, insert_symbol(v->name)))
+    return;
+  const Map map = &env->func->upvalues;
+  if(!map->ptr) {
+    map_init(map);
+    map_set(&env->func->upvalues, (vtype)prim, 0);
+  } else {
+    if(map_get(map, (vtype)v))return;
+    const m_uint offset = VVAL(map, VLEN(map) -1) + ((Exp_Primary*)VKEY(map, VLEN(map) - 1))->value->type->size;
+    map_set(&env->func->upvalues, (vtype)prim, offset);
   }
-  ERR_B(exp_self(exp)->pos, _("variable '%s' is not in lambda scope"), val->name)
 }
 
 ANN static Type prim_id_non_res(const Env env, const Symbol *data) {
@@ -311,11 +318,11 @@ ANN static Type prim_id_non_res(const Env env, const Symbol *data) {
   prim_self(data)->value = v;
   if(env->func) {
     if(isa(env->func->value_ref->type, env->gwion->type[et_lambda]) > 0)
-      CHECK_BO(lambda_valid(env, prim_self(data)))
+      check_upvalue(env, prim_self(data));
     if(env->func && !GET_FLAG(v, const) && v->from->owner)
       unset_fflag(env->func, fflag_pure);
   }
-  //v->vflag |= used;
+  //set_vflag(v->vflag, vflag_used);
   if(GET_FLAG(v, const))
     exp_setmeta(prim_exp(data), 1);
   if(v->from->owner_class) {
@@ -655,11 +662,18 @@ ANN static Type check_lambda_call(const Env env, const Exp_Call *exp) {
   }
   if(arg || e)
     ERR_O(exp_self(exp)->pos, _("argument number does not match for lambda"))
-  CHECK_BO(check_traverse_fdef(env, l->def))
-  if(env->class_def)
-    set_vflag(l->def->base->func->value_ref, vflag_member);
+  l->def->base->values = env->curr->info->value;
+  const m_bool ret = traverse_func_def(env, l->def);
+  if(l->def->base->func) {
+    free_scope(env->gwion->mp, env->curr->info->value);
+    env->curr->info->value = l->def->base->values;
+    if(env->class_def)
+      set_vflag(l->def->base->func->value_ref, vflag_member);
+  }
   ((Exp_Call*)exp)->m_func = l->def->base->func;
-  return l->def->base->ret_type ?: (l->def->base->ret_type = env->gwion->type[et_void]);
+  if(!l->def->base->ret_type)
+    l->def->base->ret_type = env->gwion->type[et_void];
+  return ret > 0 ? l->def->base->ret_type : NULL;
 }
 
 ANN Type check_exp_call1(const Env env, const Exp_Call *exp) {
index f781edacd36ded3c384ec500edd81e281965cb8c..85739fb4a06b77d7b3b0cc32df8934fc6ca59b1c 100644 (file)
@@ -273,6 +273,7 @@ ANN Type op_check(const Env env, struct Op_Import* opi) {
       } while(l && (l = op_parent(env, l)));
     }
   } while((nspc = nspc->parent));
+//  if(env->func && env->func->nspc)
   if(opi->op == insert_symbol(env->gwion->st, "$") && opi->rhs == opi->lhs)
     return opi->rhs;
   if(opi->op != insert_symbol(env->gwion->st, "@implicit"))
index 102b7c4eba622c345bc58a07e8ecd5b463eb02a9..3d85bcd6151d5c6050ed9391f76492c524320059 100644 (file)
@@ -322,15 +322,15 @@ ANN static m_bool scan2_func_def_overload(const Env env, const Func_Def f, const
 
 ANN static Func scan_new_func(const Env env, const Func_Def f, const m_str name) {
   const Func func = new_func(env->gwion->mp, name, f);
-  if(env->class_def) {
-    if(tflag(env->class_def, tflag_tmpl))
-      set_fflag(func, fflag_ftmpl);
-  }
+  if(env->class_def && tflag(env->class_def, tflag_tmpl))
+    set_fflag(func, fflag_ftmpl);
+  if(fbflag(f->base, fbflag_lambda))
+    env->curr->info->value = new_scope(env->gwion->mp);
   return func;
 }
 
 ANN static Type func_type(const Env env, const Func func) {
-  const Type base = env->gwion->type[func->def->base->td ? et_function : et_lambda];
+  const Type base = env->gwion->type[!fbflag(func->def->base, fbflag_lambda) ? et_function : et_lambda];
   const Type t = type_copy(env->gwion->mp, base);
   t->xid = ++env->scope->type_xid;
   t->info->parent = base;
diff --git a/src/vm/closure.c b/src/vm/closure.c
new file mode 100644 (file)
index 0000000..b31b587
--- /dev/null
@@ -0,0 +1,27 @@
+#include "gwion_util.h"
+#include "gwion_ast.h"
+#include "gwion_env.h"
+#include "vm.h"
+#include "instr.h"
+#include "object.h"
+#include "array.h"
+#include "memoize.h"
+#include "gwion.h"
+#include "operator.h"
+#include "import.h"
+
+ANN Closure* new_closure(MemPool mp, const m_uint sz) {
+  Closure *a = mp_malloc(mp, Closure);
+  a->data = mp_malloc2(mp, sz);
+  map_init(&a->m);
+  a->sz = sz;
+  return a;
+}
+
+ANN void free_closure(Closure *a, const Gwion gwion) {
+  const Map m = &a->m;
+  for(m_uint i = 0; i < map_size(m); ++i)
+    compound_release(gwion->vm->cleaner_shred, (Type)VKEY(m, i), a->data + VVAL(m, i));
+  map_release(m);
+  _mp_free(gwion->mp, a->sz, a->data);
+}
index 4d3432322746db3236e9eef9cf6f7cf20445b99c..86a302939d0313e4104e6c1dcb96acfd373a34ea 100644 (file)
@@ -284,7 +284,7 @@ ANN void vm_run(const VM* vm) { // lgtm [cpp/use-of-goto]
     &&regpushmem, &&regpushmemfloat, &&regpushmemother, &&regpushmemaddr, &&regpushmemderef,
     &&pushnow,
     &&baseint, &&basefloat, &&baseother, &&baseaddr,
-    &&regtoreg, &&regtoregaddr, &&regtoregderef,
+    &&regtoreg, &&regtoregother, &&regtoregaddr, &&regtoregderef,
     &&structmember, &&structmemberfloat, &&structmemberother, &&structmemberaddr,
     &&memsetimm,
     &&regpushme, &&regpushmaybe,
@@ -324,6 +324,7 @@ ANN void vm_run(const VM* vm) { // lgtm [cpp/use-of-goto]
     &&newobj, &&addref, &&addrefaddr, &&objassign, &&assign, &&remref,
     &&except, &&allocmemberaddr, &&dotmember, &&dotfloat, &&dotother, &&dotaddr,
     &&staticint, &&staticfloat, &&staticother,
+    &&upvalueint, &&upvaluefloat, &&upvalueother, &&upvalueaddr,
     &&dotfunc, &&dotstaticfunc,
     &&gcini, &&gcadd, &&gcend,
     &&gacktype, &&gackend, &&gack, &&noop, &&eoc, &&other, &&regpushimm
@@ -415,6 +416,9 @@ baseaddr:
 regtoreg:
   *(m_uint*)(reg + (m_int)VAL) = *(m_uint*)(reg + (m_int)VAL2);
   DISPATCH()
+regtoregother:
+  memcpy(*(m_bit**)(reg - SZ_INT), reg + (m_int)VAL, VAL2);
+  DISPATCH()
 regtoregaddr:
   *(m_uint**)(reg + (m_int)VAL) = &*(m_uint*)(reg + (m_int)VAL2);
   DISPATCH()
@@ -834,6 +838,22 @@ staticother:
   memcpy(reg, (m_bit*)VAL, VAL2);
   reg += VAL2;
   DISPATCH()
+upvalueint:
+  *(m_uint*)reg = *(m_uint*)(code->closure->data + VAL);
+  reg += SZ_INT;
+  DISPATCH()
+upvaluefloat:
+  *(m_float*)reg = *(m_float*)(code->closure->data + VAL);
+  reg += SZ_FLOAT;
+  DISPATCH()
+upvalueother:
+  memcpy(reg, code->closure->data + VAL, VAL2);
+  reg += VAL2;
+  DISPATCH()
+upvalueaddr:
+  *(m_uint**)reg = (m_uint*)(code->closure->data + VAL);
+  reg += SZ_INT;
+  DISPATCH()
 dotfunc:
 PRAGMA_PUSH()
   *(VM_Code*)(reg) = ((Func)vector_at((*(M_Object*)(reg-SZ_INT))->vtable, VAL))->code;
index 3851a5b05c6dc10cba497c77552e6e72b792b08a..033a64e813586dc8a2bf4587e1da9efe4e9ce6cf 100644 (file)
@@ -33,6 +33,8 @@ ANN void free_vm_code(VM_Code a, Gwion gwion) {
     _mp_free(gwion->mp, vector_size(a->instr) * SZ_INT, a->bytecode);
     _free_code_instr(a->instr, gwion);
   }
+  if(a->closure)
+    free_closure(a->closure, gwion);
   free_mstr(gwion->mp, a->name);
   mp_free(gwion->mp , VM_Code, a);
 }