-Subproject commit f2438438e053f26be2f768a01d0ac5fc2f96a7e6
+Subproject commit c516e9b680287fc6b2849aff6a97a50394f99dc8
Value value_ref;
Func next;
m_str name;
- struct Map_ upvalues;
float inline_mult;
uint16_t weight;
uint16_t memoize;
return NULL;
}
+ANN Type ref_type(const Gwion gwion, const Type t, const loc_t loc);
+
typedef enum {
et_void,
et_int,
vflag_direct = 1 << 4,
vflag_builtin = 1 << 5,
vflag_member = 1 << 6,
- vflag_closed = 1 << 7,
- vflag_inner = 1 << 8, // value is in a scope
- vflag_release = 1 << 9,
- vflag_assigned = 1 << 10
+ vflag_inner = 1 << 7, // value is in a scope
+ vflag_release = 1 << 8,
+ vflag_assigned = 1 << 9
// vflag_used = 1 << 3
} __attribute__((packed));
if (v->from->filename) // TODO: check why is that from check
gwerr_secondary(_("defined here"), v->from->filename, v->from->loc);
}
+
+ANN static inline void valid_value(const Env env, const Symbol xid, const Value v) {
+ set_vflag(v, vflag_valid);
+ nspc_add_value(env->curr, xid, v);
+}
#endif
eSporkFunc,
eSporkMemberFptr,
eSporkExp,
+ eSporkCode,
+ eForkEnd,
eSporkEnd,
eBranchEqInt,
eBranchNeqInt,
#define SporkFunc (f_instr)eSporkFunc
#define SporkMemberFptr (f_instr)eSporkMemberFptr
#define SporkExp (f_instr)eSporkExp
+#define SporkCode (f_instr)eSporkCode
+#define ForkEnd (f_instr)eForkEnd
#define SporkEnd (f_instr)eSporkEnd
#define BranchEqInt (f_instr)eBranchEqInt
#define BranchNeqInt (f_instr)eBranchNeqInt
gw_out(" {-R}%-14"UINT_F"{0}", instr->m_val);
gw_out("\n");
break;
+ case eSporkCode:
+ gw_out("{Y}┃{0}{-}% 4lu{0}: SporkCode ", j);
+ gw_out(" {-R}%-14"UINT_F"{0}", instr->m_val);
+ gw_out("\n");
+ break;
+ case eForkEnd:
+ gw_out("{Y}┃{0}{-}% 4lu{0}: ForkEnd ", j);
+ gw_out("\n");
+ break;
case eSporkEnd:
gw_out("{Y}┃{0}{-}% 4lu{0}: SporkEnd ", j);
gw_out("\n");
!exp->d.prim.d.num;
}
+ANN static inline bool not_upvalue(const Env env, const Value v) {
+ return GET_FLAG(v, global) || vflag(v, vflag_fglobal) ||
+ (v->from->owner_class && isa(v->from->owner_class, env->class_def) > 0) ||
+ nspc_lookup_value1(env->curr, insert_symbol(v->name));
+}
#endif
#define __VM
typedef struct Closure_ {
- m_bit * data;
struct Map_ m;
m_uint sz;
+ m_bit data[];
} Closure;
ANN Closure *new_closure(MemPool mp, const m_uint sz);
ANN void free_closure(Closure *a, const Gwion gwion);
SporkFunc
SporkMemberFptr~u
SporkExp~u
+SporkCode~u
+ForkEnd
SporkEnd
BranchEqInt~pc
BranchNeqInt~pc
-Subproject commit 28cbcb9e3929cb723b444d1fe79ec50d2f733752
+Subproject commit 72d7ab32170d564d0312613311182f37d9f1c2f2
clean_exp(a, b->rhs);
}
+ANN static void clean_captures(Clean *a, Capture_List b) {
+ for(uint32_t i = 0; i < b->len; i++) {
+ const Capture *cap = mp_vector_at(b, Capture, i);
+ if(cap->v) value_remref(cap->v, a->gwion);
+ }
+}
+
ANN static void clean_exp_unary(Clean *a, Exp_Unary *b) {
switch (b->unary_type) {
case unary_exp:
clean_stmt(a, b->code);
break;
}
+ if(b->captures) clean_captures(a, b->captures);
}
ANN static void clean_exp_cast(Clean *a, Exp_Cast *b) {
ANN static void clean_func_def(Clean *a, Func_Def b) {
clean_func_base(a, b->base);
+ if(b->captures) clean_captures(a, b->captures);
++a->scope;
if (!b->builtin && b->d.code &&
!(b->base->func && safe_vflag(b->base->func->value_ref, vflag_builtin)))
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) {
+ if (prim->value && emit->env->func && emit->env->func->def->captures) {
+ const Capture_List caps = emit->env->func->def->captures;
+ for (uint32_t i = 0; i < caps->len; ++i) {
+ Capture *cap = mp_vector_at(caps, Capture, i);
+ if (!strcmp(prim->value->name, cap->v->name)) {
const Instr instr = emit_kind(emit, prim->value->type->size,
exp_getvar(exp_self(prim)), upvalue);
- instr->m_val = i ? VVAL(map, i) : 0;
+ instr->m_val = cap->offset;
return GW_OK;
}
}
}
ANN static m_bool emit_func_args(const Emitter emit, const Exp_Call *exp_call) {
- if (exp_call->args) {
- CHECK_BB(emit_exp(emit, exp_call->args));
-// emit_exp_addref_array(emit, exp_call->args, -exp_totalsize(exp_call->args));
- }
+ if (exp_call->args) CHECK_BB(emit_exp(emit, exp_call->args));
const Type t = actual_type(emit->gwion, exp_call->func->type);
if (is_func(emit->gwion, t) &&
fbflag(t->info->func->def->base, fbflag_variadic))
const Exp exp;
VM_Code vm_code;
const Type type;
+ const Capture_List captures;
const bool emit_var;
const bool is_spork;
};
ANN void spork_code(const Emitter emit, const struct Sporker *sp) {
const Instr args = emit_add_instr(emit, SporkExp);
args->m_val = emit->code->stack_depth;
- const Instr instr = emit_add_instr(emit, SporkEnd);
+ const Instr instr = emit_add_instr(emit, sp->is_spork ? SporkEnd : ForkEnd);
instr->m_val = sp->emit_var;
}
.exp = unary->unary_type == unary_exp ? unary->exp : NULL,
.code = unary->unary_type == unary_code ? unary->code : NULL,
.type = exp_self(unary)->type,
+ .captures = unary->captures,
.is_spork = (unary->op == insert_symbol("spork")),
.emit_var = exp_getvar(exp_self(unary))};
CHECK_OB((sporker.vm_code = spork_prepare(emit, &sporker)));
if(!sporker.is_spork)
emit_local_exp(emit, exp_self(unary));
spork_ini(emit, &sporker);
+ // add this if needed
+ uint32_t offset = 0;
+ if(emit->env->class_def && sporker.code) {
+ struct Exp_ exp = {
+ .d = { .prim = {
+ .d = { .var = insert_symbol("this") },
+ .prim_type = ae_prim_id
+ }},
+ .type = emit->env->class_def,
+ .exp_type = ae_exp_primary
+ };
+ emit_exp(emit, &exp);
+ offset += SZ_INT;
+ }
+ if(sporker.captures) {
+ Capture_List caps = sporker.captures;
+ for (uint32_t i = 0; i < caps->len; i++) {
+ Capture *cap = mp_vector_at(caps, Capture, i);
+ const Value v = nspc_lookup_value1(emit->env->curr, cap->xid);
+ struct Exp_ exp = {
+ .d = { .prim = {
+ .d = { .var = cap->xid },
+ .value = v,
+ .prim_type = ae_prim_id
+ }},
+ .type = v->type,
+ .exp_type = ae_exp_primary
+ };
+ if(cap->is_ref) exp_setvar(&exp, true);
+ offset += exp_size(&exp);
+ emit_exp(emit, &exp);
+ }
+ }
+ if(offset) {
+ regpop(emit, offset);
+ const Instr args = emit_add_instr(emit, SporkCode);
+ args->m_val = offset;
+ }
(unary->unary_type == unary_code ? spork_code : spork_func)(emit, &sporker);
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) {
- 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));
+ const Capture_List caps = func->def->captures;
+ for (uint32_t i = 0; i < caps->len; ++i) {
+ Capture *cap = mp_vector_at(caps, Capture, i);
+ const Value value = cap->v;
+ struct Exp_ exp = {
+ .d = { .prim = {
+ .d = { .var = cap->xid },
+ .value = value,
+ .prim_type = ae_prim_id
+ }},
+ .type = value->type,
+ .exp_type = ae_exp_primary,
+ .pos = cap->pos
+ };
+ if(cap->is_ref) exp_setvar(&exp, true);
+ CHECK_BB(emit_exp(emit, &exp));
+ if (isa(value->type, emit->gwion->type[et_compound]) > 0) {
+ emit_exp_addref1(emit, &exp, -value->type->size);
+ map_set(&func->code->closure->m, (vtype)value->type, cap->offset);
}
- 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;
+ const Capture *cap = mp_vector_at(func->def->captures, Capture, (func->def->captures->len - 1));
+ const m_uint sz = cap->offset + cap->v->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));
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)
+ if (lambda->def->captures)
CHECK_BB(emit_closure(emit, lambda->def->base->func));
if (vflag(lambda->def->base->func->value_ref, vflag_member) &&
!exp_getvar(exp_self(lambda)))
loop_idx->m_val = key_offset;
loop_idx->m_val2 = -1;
stmt->v->from->offset = val_offset;
+//value_addref(stmt->v);
+nspc_add_value(emit->env->curr, stmt->sym, stmt->v);
emit_debug(emit, stmt->v);
if (stmt->idx) {
stmt->idx->v->from->offset = key_offset;
- emit_debug(emit, stmt->v);
+nspc_add_value(emit->env->curr, stmt->idx->sym, stmt->idx->v);
+//value_addref(stmt->idx->v);
+ emit_debug(emit, stmt->idx->v);
}
struct Looper loop = {.exp = stmt->exp,
.stmt = stmt->body,
ANN static m_bool emit_stmt_each(const Emitter emit, const Stmt_Each stmt) {
const uint n = emit->info->unroll;
+ nspc_push_value(emit->gwion->mp, emit->env->curr);
CHECK_BB(emit_exp(emit, stmt->exp)); // add ref?
regpop(emit, SZ_INT);
m_uint end_pc = 0;
const m_bool ret = _emit_stmt_each(emit, stmt, &end_pc);
emit_pop_stack(emit, end_pc);
+nspc_pop_value(emit->gwion->mp, emit->env->curr);
emit->info->unroll = 0;
return ret;
}
emit->code->stack_depth += type->size;
arg->var_decl.value->from->offset = emit_localn(emit, type);
emit_debug(emit, arg->var_decl.value);
+ nspc_add_value(emit->env->curr, insert_symbol(arg->var_decl.value->name), arg->var_decl.value);
}
}
const Func f = fdef->base->func;
if (f->memoize && fflag(f, fflag_pure))
CHECK_BB(emit_memoize(emit, fdef));
+ nspc_push_value(emit->gwion->mp, emit->env->curr); // handle
CHECK_BB(emit_func_def_body(emit, fdef));
emit_func_def_return(emit);
+ nspc_pop_value(emit->gwion->mp, emit->env->curr); // handle
return GW_OK;
}
ANN void free_func(Func a, Gwion gwion) {
if (fflag(a, fflag_tmpl)) 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);
}
env_set_error(env);
return env->gwion->type[et_error];
}
- if (!strncmp(base->name, "Ref:[", 5)) {
+ if (tflag(base, tflag_ref)) {
gwerr_basic("Can't use ref types as array base", NULL, NULL, "/dev/null",
(loc_t) {}, 0);
env_set_error(env);
const Type et = exp->type;
DECL_OO(Type, base, = typedef_base(et));
DECL_OO(const Type, t, = array_base_simple(base));
- const m_uint depth = base->array_depth - 1;
- return depth ? array_type(env, t, depth) : t;
+ if(!tflag(base, tflag_ref)) {
+ const m_uint depth = base->array_depth - 1;
+ return depth ? array_type(env, t, depth) : t;
+ }
+ const Type inner = (Type)vector_front(&base->info->tuple->contains);
+ const Type refbase = array_base_simple(inner);
+ const m_uint depth = inner->array_depth - 1;
+ return depth ? array_type(env, refbase, depth) : refbase;
}
// rewrite me
const Exp exp = (const Exp) data;
DECL_ON(const Type, base, = foreach_type(env, exp));
CHECK_BN(ensure_traverse(env, base));
- const m_str basename = type2str(env->gwion, base, exp->pos);
- char c[15 + strlen(basename)];
- sprintf(c, "Ref:[%s]", basename);
- return str2type(env->gwion, c, exp->pos);
+ return ref_type(env->gwion, base, exp->pos);
}
static OP_EMIT(opem_array_each) {
ANN static inline Type deep_type(const Gwion gwion, const Type t) {
if(!tflag(t, tflag_struct))
return t;
- char c[128];
- sprintf(c, "Ref:[%s]", t->name);
- return str2type(gwion, c, t->info->value->from->loc);
+ return ref_type(gwion, t, t->info->value->from->loc);
}
ANN static void deep_emit_init(const Emitter emit, struct DeepEmit *d, const m_int offset) {
}
ANN static m_bool _check_lambda(const Env env, Exp_Lambda *l,
- const Func_Def def) {
+ const Func_Def fdef) {
// if(l->def->base->func) return GW_OK;
- Arg_List bases = def->base->args;
+ Arg_List bases = fdef->base->args;
Arg_List args = l->def->base->args;
// arity match
if ((bases ? bases->len : 0) != (args ? args->len : 0))
ERR_B(exp_self(l)->pos, _("argument number does not match for lambda"))
+ if(fdef->captures) {
+ // here move to arguments
+ uint32_t offset = 0;
+ for(uint32_t i = 0; i < fdef->captures->len; i++) {
+ Capture *cap = mp_vector_at(fdef->captures, Capture, i);
+ const Value v = nspc_lookup_value1(env->curr, cap->xid);
+ if(!v) ERR_B(cap->pos, _("unknown value in capture"));
+ offset += (!cap->is_ref ? SZ_INT : v->type->size);
+ cap->v = v;
+ cap->offset = offset;
+ }
+ }
const bool is_tmpl =
- safe_tflag(def->base->func->value_ref->from->owner_class, tflag_tmpl);
+ safe_tflag(fdef->base->func->value_ref->from->owner_class, tflag_tmpl);
if (is_tmpl)
template_push_types(
env,
- def->base->func->value_ref->from->owner_class->info->cdef->base.tmpl);
+ fdef->base->func->value_ref->from->owner_class->info->cdef->base.tmpl);
if(bases) {
for(uint32_t i = 0; i < bases->len; i++) {
Arg *base = mp_vector_at(bases, Arg, i);
Arg *arg = mp_vector_at(args, Arg, i);
arg->td = type2td(env->gwion, known_type(env, base->td), exp_self(l)->pos);
}
-
}
l->def->base->td =
- type2td(env->gwion, known_type(env, def->base->td), exp_self(l)->pos);
+ type2td(env->gwion, known_type(env, fdef->base->td), exp_self(l)->pos);
if (is_tmpl) nspc_pop_type(env->gwion->mp, env->curr);
- l->def->base->flag = def->base->flag;
+ l->def->base->flag = fdef->base->flag;
// if(GET_FLAG(def->base, global) && !l->owner &&
// def->base->func->value_ref->from->owner_class)
UNSET_FLAG(l->def->base, global);
l->def->base->values = env->curr->info->value;
const m_uint scope = env->scope->depth;
- if(GET_FLAG(def->base, global) && !l->owner &&
- def->base->func->value_ref->from->owner_class)
+ if(GET_FLAG(fdef->base, global) && !l->owner &&
+ fdef->base->func->value_ref->from->owner_class)
env_push(env, NULL, env->context->nspc);
env->scope->depth = 0;
const m_bool ret = traverse_func_def(env, l->def);
env->scope->depth = scope;
- if(GET_FLAG(def->base, global) && !l->owner &&
- def->base->func->value_ref->from->owner_class)
+ if(GET_FLAG(fdef->base, global) && !l->owner &&
+ fdef->base->func->value_ref->from->owner_class)
env_pop(env, scope);
if (l->def->base->func) {
instr->m_val2 = -SZ_INT;
return ret;
}
-
-ANN Type check_exp_unary_spork(const Env env, const Stmt code);
-
+/*
ANN static void fork_exp(const Env env, const Exp_Unary *unary) {
Stmt_List slist = new_mp_vector(env->gwion->mp, sizeof(struct Stmt_), 1);
mp_vector_set(slist, struct Stmt_, 0,
((Exp_Unary *)unary)->code = code;
((Exp_Unary *)unary)->unary_type = unary_code;
}
-
+*/
ANN static Type fork_type(const Env env, const Exp_Unary *unary) {
const Type t = unary->exp->type;
- fork_exp(env, unary);
+// fork_exp(env, unary);
if (t == env->gwion->type[et_void]) return env->gwion->type[et_fork];
char c[21 + strlen(t->name)];
sprintf(c, "TypedFork:[%s]", t->name);
return ret;
}
+ANN Type upvalue_type(const Env env, Capture *cap) {
+ const Value v = nspc_lookup_value1(env->curr, cap->xid);
+ if(!v)exit(3);
+ if(cap->is_ref && not_upvalue(env, v))
+ ERR_O(cap->pos, _("can't take ref of a scoped value"));
+ cap->v = v;
+ const Type base_type = !tflag(v->type, tflag_ref) ? v->type : (Type)vector_front(&v->type->info->tuple->contains);
+ return !cap->is_ref ? base_type : ref_type(env->gwion, base_type, cap->pos);
+}
+
static OP_CHECK(opck_spork) {
const Exp_Unary *unary = (Exp_Unary *)data;
if (unary->unary_type == unary_exp && unary->exp->exp_type == ae_exp_call) {
return is_spork ? env->gwion->type[et_shred] : fork_type(env, unary);
}
if (unary->unary_type == unary_code) {
+ if(unary->captures) {
+ uint32_t offset = !env->class_def ? 0 : SZ_INT;
+ for(uint32_t i = 0; i < unary->captures->len; i++) {
+ Capture *const cap = mp_vector_at(unary->captures, Capture, i);
+ DECL_OO(const Type, t, = upvalue_type(env, cap));
+ cap->v = new_value(env->gwion->mp, t, s_name(cap->xid));
+ cap->v->from->offset = offset;
+ offset += cap->v->type->size;
+ }
+ }
++env->scope->depth;
- nspc_push_value(env->gwion->mp, env->curr);
+ const Scope scope = env->curr->info->value;
+ env->curr->info->value = new_scope(env->gwion->mp);
+ if(unary->captures) {
+ for(uint32_t i = 0; i < unary->captures->len; i++) {
+ Capture *const cap = mp_vector_at(unary->captures, Capture, i);
+ valid_value(env, cap->xid, cap->v);
+ }
+ }
+ const Func f = env->func;
+ struct Value_ value = {};
+ if(env->class_def)
+ set_vflag(&value, vflag_member);
+ struct Func_Base_ fbase = { .xid=insert_symbol("in spork"), .values = scope};
+ struct Func_Def_ fdef = { .base = &fbase};
+ struct Func_ func = { .name = "in spork", .def = &fdef, .value_ref = &value};
+ env->func = &func;
const m_bool ret = check_stmt(env, unary->code);
- nspc_pop_value(env->gwion->mp, env->curr);
+ env->func = f;
+ free_scope(env->gwion->mp, env->curr->info->value);
+ env->curr->info->value = scope;
--env->scope->depth;
CHECK_BN(ret);
return env->gwion
ANN static Type member_type(const Gwion gwion, const Type base) {
const Type t = actual_type(gwion, base);
- if(strncmp(t->name, "Ref:[", 5))
- return t;
- return (Type)vector_front(&t->info->tuple->contains);
+ return !tflag(t, tflag_ref) ? t: (Type)vector_front(&t->info->tuple->contains);
}
OP_EMIT(opem_object_dot) {
#include "gwi.h"
#include "tmpl_info.h"
+ANN Type ref_type(const Gwion gwion, const Type t, const loc_t loc) {
+ char c[7 + strlen(t->name)];
+ sprintf(c, "Ref:[%s]", t->name);
+ return str2type(gwion, c, loc);
+}
+
static m_bool ref_access(const Env env, const Exp e) {
const m_str access = exp_access(e);
if (!access) return GW_OK;
const m_int start = *(m_uint *)REG(0);
const size_t strsz = strlen(str);
m_int end = *(m_uint *)REG(SZ_INT);
- if (end < 0) end = strsz + end;
+ if (end < 0) end = strsz + end - 1;
if (bounds(str, start) < 0 || bounds(str, end) < 0) {
handle(shred, "OutOfBoundsStringSlice");
return;
gwi_func_ini(gwi, "float", "atof");
GWI_BB(gwi_func_end(gwi, string_atof, ae_flag_none))
-/*
- gwi_func_ini(gwi, "int", "atoi");
- gwi_func_arg(gwi, "Ref:[int]", "idx");
- GWI_BB(gwi_func_end(gwi, string_atoi2, ae_flag_none))
-*/
+
GWI_BB(gwi_class_end(gwi))
GWI_BB(gwi_oper_ini(gwi, "string", "string", "bool"))
arg_release(&arg);
if (ini > 0) gwion_run(&gwion);
gwion_end(&gwion);
+ gwion.vm = NULL;
#ifndef BUILD_ON_WINDOWS
pthread_exit(NULL);
#endif
return GW_OK;
}
-ANN static inline void valid_value(const Env env, const Symbol xid, const Value v) {
- set_vflag(v, vflag_valid);
- nspc_add_value(env->curr, xid, v);
-}
-
ANN static m_bool check_decl(const Env env, const Exp_Decl *decl) {
Var_Decl_List list = decl->list;
for(uint32_t i = 0; i < list->len; i++) {
return v ? v->from->owner : env->curr;
}
-ANN static void check_upvalue(const Env env, const Exp_Primary *prim) {
+ANN static m_bool check_upvalue(const Env env, const Exp_Primary *prim) {
const Value v = prim->value;
- if (GET_FLAG(v, global) || vflag(v, vflag_fglobal) ||
- (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);
- }
+ if(not_upvalue(env, v))
+ return GW_OK;
+ gwerr_basic(_("value not in lambda scope"), NULL, NULL, env->name, exp_self(prim)->pos, 4242);
+ gwerr_warn("declared here", NULL, _("{-}try adding it to capture list{0}"), v->from->filename, v->from->loc);
+ env->context->error = true;
+ return GW_ERROR;
}
ANN static Type prim_owned(const Env env, const Symbol *data) {
prim_self(data)->value = env->gwion->type[et_op]->info->value;
return env->gwion->type[et_op];
}
- gwerr_basic(_("Invalid variable"), _("not legit at this point."), NULL,
+ const m_str hint = (!env->func || strcmp(env->func->name, "in spork")) ?
+ NULL : "vapturelist?";
+ gwerr_basic(_("Invalid variable"), _("not legit at this point."), hint,
env->name, prim_pos(data), 0);
did_you_mean_nspc(v ? value_owner(env, v) : env->curr, s_name(sym));
env_set_error(env);
if (!GET_FLAG(v, const) && v->from->owner)
unset_fflag(env->func, fflag_pure);
if (fbflag(env->func->def->base, fbflag_lambda))
- check_upvalue(env, prim_self(data));
+ CHECK_BO(check_upvalue(env, prim_self(data)));
}
// set_vflag(v->vflag, vflag_used);
return v->type;
func->def->base->ret_type : exp->func->d.exp_dot.base->type;
}
-ANN static Type check_lambda_call(const Env env, const Exp_Call *exp) {
- if (exp->args) CHECK_OO(check_exp(env, exp->args));
+ANN Type upvalue_type(const Env env, Capture *cap);
+
+ANN static m_bool lambda_args_ref(const Env env, Exp_Call *const call) {
+ Exp e = call->args;
+ CHECK_OB(check_exp(env, e));
+ do if(tflag(e->type, tflag_ref) && !safe_tflag(exp_self(e)->cast_to, tflag_ref))
+ exp_setvar(e, true);
+ while((e = e->next));
+ return GW_OK;
+}
+
+ANN2(1) static m_bool lambda_append_args(const Env env, Exp_Call *const call, const Exp add) {
+ if(!add) return GW_ERROR;
+ if (call->args) {
+ Exp e = call->args;
+ while(e->next) e = e->next;
+ e->next = add;
+ } else call->args = add;
+ return traverse_exp(env, add);
+}
+
+ANN static Exp check_lambda_captures(const Env env, const Func_Def fdef) {
+ if(!fdef->base->args)
+ fdef->base->args = new_mp_vector(env->gwion->mp, sizeof(Arg), 0);
+ Exp args = NULL, tmp;
+ for(uint32_t i = 0; i < fdef->captures->len; i++) {
+ Capture *const cap = mp_vector_at(fdef->captures, Capture, i);
+ const Type t = upvalue_type(env, cap);
+ if(!t) {
+ if(args) free_exp(env->gwion->mp, args);
+ return NULL;
+ }
+ Arg arg = {
+ .td = type2td(env->gwion, t, cap->pos),
+ .var_decl = { .xid = cap->xid }
+ };
+ mp_vector_add(env->gwion->mp, &fdef->base->args, Arg, arg);
+ const Exp exp = new_prim_id(env->gwion->mp, cap->xid, cap->pos);
+ if(args) tmp = tmp->next = exp;
+ else args = tmp = exp;
+ }
+ free_mp_vector(env->gwion->mp, sizeof(Capture), fdef->captures);
+ fdef->captures = NULL;
+ return args;
+}
+
+ANN static Type check_lambda_call(const Env env, Exp_Call *const exp) {
+ const Func_Def fdef = exp->func->d.exp_lambda.def;
+ const bool captures = !!fdef->captures;
+ if (exp->args) CHECK_BO(lambda_args_ref(env, exp));
+ const Exp _args = !captures ? NULL : check_lambda_captures(env, fdef);
+ if(captures) CHECK_BO(lambda_append_args(env, exp, _args));
Exp_Lambda *l = &exp->func->d.exp_lambda;
Arg_List args = l->def->base->args;
Exp e = exp->args;
const Exp ret_id =
new_prim_id(env->gwion->mp, insert_symbol("self"), when->pos);
ret_id->d.prim.value = new_value(env->gwion->mp, tdef->type, "self");
+ // valuefrom?
struct Stmt_ ret = {
.stmt_type = ae_stmt_return, .d = { .stmt_exp = { .val = ret_id }},
.pos = when->pos
DECL_OB(const Type, ret, = check_each_val(env, stmt->exp));
stmt->v = new_value(env->gwion->mp, ret, s_name(stmt->sym));
valid_value(env, stmt->sym, stmt->v);
+ valuefrom(env, stmt->v->from, stmt->vpos);
return check_conts(env, stmt_self(stmt), stmt->body);
}
const Exp_Primary *prim) {
const Symbol sym = prim->d.var;
const Value v = new_value(env->gwion->mp, base, s_name(sym));
+ // valuefrom?
valid_value(env, sym, v);
return v;
}
if(!is_typed_hole(env, e)) {
const Exp next = e->next;
e->next = NULL;
- check_exp(env, e);
+ const Type ret = check_exp(env, e);
e->next = next;
+ CHECK_OO(ret);
} else
CHECK_OO((e->type = known_type(env, e->d.exp_cast.td)));
if (!func_match_inner(env, e, arg->type, implicit, specific)) break;
}
ANN Type partial_type(const Env env, Exp_Call *const call) {
- const Func f = partial_match(env, call->func->type->info->func, call->args, call->func->pos);
+ const Func base = call->func->type->info->func;
+ if(!base) ERR_O(call->func->pos, _("can't do partial application on a literal lambda"));
+ const Func f = partial_match(env, base, call->args, call->func->pos);
if(!f) {
const Exp e = expand(env, call->func->type->info->func, call->args, call->func->pos);
if(e) {
}
ERR_O(call->func->pos, _("no match found for partial application"));
}
- Func_Base *const base = partial_base(env, f->def->base, call->args, call->func->pos);
+ Func_Base *const fbase = partial_base(env, f->def->base, call->args, call->func->pos);
const Stmt code = partial_code(env, call->func, call->args);
const Exp exp = exp_self(call);
- exp->d.exp_lambda.def = new_func_def(env->gwion->mp, base, code);
+ exp->d.exp_lambda.def = new_func_def(env->gwion->mp, fbase, code);
exp->exp_type = ae_exp_lambda;
CHECK_OO(traverse_func_def(env, exp->d.exp_lambda.def));
return exp->d.exp_lambda.def->base->func->value_ref->type;
CHECK_BO(scan0_defined(env, cdef->base.xid, cdef->pos));
const Type parent = cdef_parent(env, cdef);
if (parent == (Type)GW_ERROR) return NULL;
+ if(GET_FLAG(cdef, global) && !type_global(env, parent)) {
+ gwerr_basic(_("parent type is not global"), NULL, NULL, env->name, cdef->base.ext ? cdef->base.ext->pos : cdef->base.pos, 0);
+ const Value v = parent->info->value;
+ gwerr_warn("declared here", NULL, NULL, v->from->filename, v->from->loc);
+ env->context->error = true;
+ return NULL;
+ }
//if(parent) type_addref(parent);
if (cdef->traits) CHECK_BO(find_traits(env, cdef->traits, cdef->pos));
const Type t = scan0_type(env, s_name(cdef->base.xid), parent);
ANN static inline m_bool scan1_exp_unary(const restrict Env env,
Exp_Unary *const unary) {
- if (unary->unary_type == unary_code) {
- const loc_t pos = exp_self(unary)->pos;
- const Symbol sym = lambda_name(env->gwion->st, pos.first);
- Exp lambda = new_exp_lambda(env->gwion->mp, sym, NULL, unary->code, pos);
- mp_free(env->gwion->mp, Stmt, unary->code);
- unary->exp = new_exp_call(env->gwion->mp, lambda, NULL, pos);
- unary->unary_type = unary_exp;
- }
- return unary->unary_type == unary_exp ? scan1_exp(env, unary->exp) : GW_OK;
+ if(unary->unary_type == unary_exp)
+ return scan1_exp(env, unary->exp);
+ if (unary->unary_type == unary_code)
+ return scan1_stmt(env, unary->code);
+ return GW_OK;
}
#define scan1_exp_lambda dummy_func
vd->xid ? s_name(vd->xid) : (m_str) __func__);
if (vd->array)
v->type = arg->type = array_type(env, arg->type, vd->array->depth);
- if (arg->td) {
+ if (arg->td)
v->flag = arg->td->flag;
- // SET_FLAG(v, global); ???
- }
+ v->from->loc = arg->var_decl.pos;
+ v->from->filename = env->name;
return v;
}
#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);
+ Closure *a = mp_malloc2(mp, sizeof(Closure) + sz);
map_init(&a->m);
a->sz = sz;
return a;
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);
+ _mp_free(gwion->mp, sizeof(Closure) + a->sz, a);
}
VM * vm = shred->info->vm;
if (!vm->gwion->data->child.ptr) vector_init(&vm->gwion->data->child);
vector_add(&vm->gwion->data->child, (vtype)o);
- fork_launch(o);
return ME(o);
}
&®tomem, &®tomemother,
&&overflow,
&&funcusrend, &&funcusrend2, &&funcmemberend,
- &&sporkini, &&forkini, &&sporkfunc, &&sporkmemberfptr, &&sporkexp,
- &&sporkend, &&brancheqint, &&branchneint, &&brancheqfloat,
+ &&sporkini, &&forkini, &&sporkfunc, &&sporkmemberfptr, &&sporkexp, &&sporkcode,
+ &&forkend, &&sporkend, &&brancheqint, &&branchneint, &&brancheqfloat,
&&branchnefloat, &&unroll, &&arrayappend, &&autounrollinit, &&autoloop,
&&arraytop, &&arrayaccess, &&arrayget, &&arrayaddr, &&newobj, &&addref,
&&addrefaddr, &&structaddref, &&structaddrefaddr, &&objassign, &&assign,
regpushmemaddr:
*(m_bit **)reg = &*(m_bit *)(mem + IVAL);
reg += SZ_INT;
- DISPATCH()
+ DISPATCH();
regpushmemderef:
memcpy(reg, *(m_bit **)(mem + IVAL), VAL2);
reg += VAL2;
for (m_uint i = 0; i < VAL; i += SZ_INT)
*(m_uint *)(child->mem + i) = *(m_uint *)(mem + i);
DISPATCH()
+ sporkcode:
+ // LOOP_OPTIM
+ for (m_uint i = 0; i < VAL; i += SZ_INT)
+ *(m_uint *)(child->mem + i) = *(m_uint *)(reg + i);
+ DISPATCH()
+ forkend:
+ fork_launch(child->info->me);
sporkend:
assert(!VAL); // spork are not mutable
*(M_Object *)(reg - SZ_INT) = child->info->me;
&&_regtomem, &&_regtomemother,
&&_overflow,
&&_funcusrend, &&_funcusrend2, &&_funcmemberend,
- &&_sporkini, &&_forkini, &&_sporkfunc, &&_sporkmemberfptr, &&_sporkexp,
+ &&_sporkini, &&_forkini, &&_sporkfunc, &&_sporkmemberfptr, &&_sporkexp, &&_sporkcode, &&_forkend,
&&_sporkend, &&_brancheqint, &&_branchneint, &&_brancheqfloat,
&&_branchnefloat, &&_unroll, &&_arrayappend, &&_autounrollinit, &&_autoloop,
&&_arraytop, &&_arrayaccess, &&_arrayget, &&_arrayaddr, &&_newobj, &&_addref,
PREPARE(sporkfunc);
PREPARE(sporkmemberfptr);
PREPARE(sporkexp);
+ PREPARE(sporkcode);
+ PREPARE(forkend);
PREPARE(sporkend);
PREPARE(brancheqint);
PREPARE(branchneint);
--- /dev/null
+#! [contains] 42
+40 => var int a;
+{
+\ : a : { <<< a + 2 >>>; }();
+}
--- /dev/null
+#! [contains] can't take ref of a scoped value
+foreach(a : [1,2])
+ spork : &a :{ <<< "${a}" >>>; samp => now; <<< "${a}" >>>; };
--- /dev/null
+#! [contains] 42 1
+foreach(a : [ 1, 2])
+ spork : a : { <<< "42 ${a}" >>>; };
+samp => now;
#! [contains] non-global type in a global class
-class State{}
+class C {}
+class global State{}
class global States extends State[16] {
- var State current;
+ var C current;
}
--- /dev/null
+#! [contains] can't do partial application on a literal lambda
+<<< \a { }(_) >>>;