-Subproject commit c13d5da0476a1409d2f501e7e014a58f55be9fd8
+Subproject commit 04b44ae194ffa5b2d20c963c92971f1acbab8ea0
where when case varloop
defer try perform handle retry
fun function typedef distinct funptr
- new spork fork'
+ new spork fork locale'
attributes='const var static private public protect variadic template samp ms second minute delay'
- types='auto int float bool dur void Object Shred Event'
+ types='auto int float bool dur time void Object Shred Event'
values='true false none this now me adc dac maybe'
builtins='__file__ __line__ __func__'
entities='class struct trait union enum'
color mauve "\<Ref\>"
comment "#!"
-color italic,red start="#\<(pragma|include|define|ifdef|ifndef|undef|endif|import)\>" end="$"
-
color brightred "\<(typeof|spork|fork)\>"
color lightred "\<(second|ms|day|samp|minute|hour)\>"
color brightcyan "\<(maybe)\>"
color cyan "\<(adc|blackhole)\>"
-color brightgreen "\<(try|handle|perform|retry|class|struct|trait|union|enum|fun|operator|funptr|typedef|distinct|new)\>"
+color brightgreen "\<(try|handle|perform|retry|class|struct|trait|union|enum|fun|locale|operator|funptr|typedef|distinct|new)\>"
+color italic,red start="#\<(pragma|include|define|ifdef|ifndef|undef|endif|import|locale)\>" end="$"
+color italic,red "#locale"
color italic,yellow "extends"
color italic,brightgreen "\<(final|abstract)\>"
color lightgreen "@[a-zA-Z]+[a-zA-Z0-9_]*|&[a-zA-Z]+[a-zA-Z0-9_]*"
--- /dev/null
+#ifndef __CURRY
+#define __CURRY
+ANN2(1,2,3) Type curry_type(const Env env, const Exp exp, const Exp func, const Exp args, const bool lambda);
+#endif
struct Gwion_ * gwion;
struct EmitterInfo_ *info;
struct Vector_ stack;
+ Func locale;
uint16_t this_offset; // reset
uint16_t vararg_offset; // reset
};
Nspc nspc;
m_str name;
Ast tree;
- Func locale;
uint16_t ref;
uint16_t weight;
bool error;
-Subproject commit 49a4be94f9c4042f854dc82c8c6e598ec9d4df29
+Subproject commit 524694345a2e9ed7b257bf6ff8a3d70940e5aa61
ANN static inline m_bool passes(struct Gwion_ *gwion, struct Compiler *c) {
const Env env = gwion->env;
const Context ctx = new_context(env->gwion->mp, c->ast, env->name);
-//ctx->locale = nspc_lookup_value1(gwion->env->global_nspc, insert_symbol(gwion->st, "@DefaultLocale"))->d.func_ref;
env_reset(env);
load_context(ctx, env);
const m_bool ret = _passes(gwion, c);
#include "specialid.h"
#include "vararg.h"
#include "looper.h"
+#include "shreduler_private.h"
#undef insert_symbol
#define insert_symbol(a) insert_symbol(emit->gwion->st, (a))
emit_localx(emit, emit->gwion->type[et_string]);
return GW_OK;
}
-#include "shreduler_private.h"
+
ANN static m_bool emit_ensure_func(const Emitter emit, const Func f) {
const struct ValueFrom_ *from = f->value_ref->from;
if(from->owner_class)
}
ANN static m_bool emit_prim_locale(const Emitter emit, const Symbol *id) {
- CHECK_BB(emit_ensure_func(emit, emit->env->context->locale));
+ if(emit->locale->def->d.code) {
+ const Stmt stmt = mp_vector_at((emit->locale->def->d.code->d.stmt_code.stmt_list), struct Stmt_, 0);
+ const Func f = stmt->d.stmt_exp.val->d.exp_call.func->type->info->func;
+ CHECK_OB(emit_ensure_func(emit, f));
+ }
+ CHECK_OB(emit_ensure_func(emit, emit->locale));
emit_push_code(emit, "locale"); // new code {
-
- // push args
const M_Object string = new_string(emit->gwion, s_name(*id));
regpushi(emit, (m_uint)string);
-
- regpushi(emit, (m_uint)emit->env->context->locale->code);
- emit_exp_call1(emit, emit->env->context->locale, true);
-
- regpop(emit, emit->env->context->locale->def->base->ret_type->size);
+ regpushi(emit, (m_uint)emit->locale->code);
+ emit_exp_call1(emit, emit->locale, true);
+ regpop(emit, emit->locale->def->base->ret_type->size);
const VM_Code code = finalyze(emit, EOC);
const VM_Shred shred = new_vm_shred(emit->gwion->mp, code);
vm_add_shred(emit->gwion->vm, shred);
shred->info->me->ref++;
vm_run(emit->gwion->vm);
emit->gwion->vm->bbq->is_running = true;
- if(tflag(emit->env->context->locale->def->base->ret_type, tflag_float)) {
- const Instr instr = emit_add_instr(emit, RegPushImm2);
- instr->f = *(m_float*)shred->reg;
- } else if(emit->env->context->locale->def->base->ret_type->size == SZ_INT)
- regpushi(emit, *(m_uint*)shred->reg);
- else {
- // here we would need to deallocate
- ERR_B(prim_pos(id), "not implemented atm");
- }
+ const Instr instr = emit_add_instr(emit, RegPushImm2);
+ instr->f = *(m_float*)shred->reg;
return GW_OK;
}
ANN static m_bool emit_stmt_pp(const Emitter emit,
const struct Stmt_PP_ *stmt) {
- if (stmt->pp_type == ae_pp_pragma) {
+ if (stmt->pp_type == ae_pp_include)
+ emit->env->name = stmt->data;
+ else if (stmt->pp_type == ae_pp_locale)
+ emit->locale = stmt->exp->d.exp_lambda.def->base->func;
+ else if (stmt->pp_type == ae_pp_pragma) {
if (!strncmp(stmt->data, "unroll", strlen("unroll")))
emit->info->unroll = strtol(stmt->data + 6, NULL, 10);
- } else if (stmt->pp_type == ae_pp_include)
- emit->env->name = stmt->data;
+ }
return GW_OK;
}
ANN m_bool emit_func_def(const Emitter emit, const Func_Def fdef) {
const uint16_t depth = emit->env->scope->depth;
emit->env->scope->depth = 0;
+ const Func locale = emit->locale;
const m_bool ret = _emit_func_def(emit, fdef);
+ emit->locale = locale;
emit->env->scope->depth = depth;
return ret;
}
return ret;
}
-ANN static m_bool emit_class_def(const Emitter emit, const Class_Def cdef) {
- if (tmpl_base(cdef->base.tmpl)) return GW_OK;
+ANN static m_bool _emit_class_def(const Emitter emit, const Class_Def cdef) {
const Type t = cdef->base.type;
- if (tflag(t, tflag_emit)) return GW_OK;
set_tflag(t, tflag_emit);
const Class_Def c = t->info->cdef;
if (c->base.ext && t->info->parent->info->cdef &&
return GW_OK;
}
+ANN static m_bool emit_class_def(const Emitter emit, const Class_Def cdef) {
+ if (tmpl_base(cdef->base.tmpl)) return GW_OK;
+ if (tflag(cdef->base.type, tflag_emit)) return GW_OK;
+ const Func locale = emit->locale;
+ const m_bool ret = _emit_class_def(emit, cdef);
+ emit->locale = locale;
+ return ret;
+}
+
ANN static inline void emit_free_code(const Emitter emit, Code *code) {
if (vector_size(&code->instr)) free_code_instr(&code->instr, emit->gwion);
free_code(emit->gwion->mp, code);
ANN m_bool emit_ast(const Env env, Ast *ast) {
const Emitter emit = env->gwion->emit;
+ const Func locale = emit->locale;
emit_clear(emit);
emit->code = new_code(emit, emit->env->name);
emit_push_scope(emit);
else
emit_free_stack(emit);
emit_clear(emit);
+ emit->locale = locale;
return ret;
}
gwion->vm->gwion = gwion->emit->gwion = gwion->env->gwion = gwion;
}
+
+ANN static Func gwion_locale(const Gwion gwion) {
+ const Nspc nspc = gwion->env->curr;
+ const Symbol sym = insert_symbol(gwion->st, "BasicLocale");
+ const Value v = nspc_lookup_value1(nspc, sym);
+ return v->d.func_ref;
+}
+
ANN static m_bool gwion_ok(const Gwion gwion, CliArg *arg) {
CHECK_BB(plug_ini(gwion, &arg->lib));
shreduler_set_loop(gwion->vm->shreduler, arg->loop);
plug_run(gwion, &arg->mod);
if (type_engine_init(gwion)) {
gwion->vm->cleaner_shred = gwion_cleaner(gwion);
+ gwion->emit->locale = gwion_locale(gwion);
(void)arg_compile(gwion, arg);
return GW_OK;
}
#include "gwi.h"
#include "traverse.h"
#include "parse.h"
+#include "curry.h"
ANN static Arg_List curry_arg_list(const Env env, const Arg_List base, const Exp e) {
Arg_List args = new_mp_vector(env->gwion->mp, sizeof(Arg), 0);
return args;
}
-ANN2(1) static Func_Base *curry_base(const Env env, const Func_Base *base, Exp earg, const loc_t loc) {
+ANN2(1, 2) static inline Func_Base *curry_base(const Env env, const Func_Base *base, Exp earg, const loc_t loc) {
Arg_List args = earg ? curry_arg_list(env, base->args, earg) : NULL;
Func_Base *fb = new_func_base(env->gwion->mp, cpy_type_decl(env->gwion->mp, base->td), lambda_name(env->gwion->st, loc.first), args, ae_flag_none, loc);
- fb->fbflag |= fbflag_lambda;
return fb;
}
return new_stmt_code(env->gwion->mp, slist, efun->pos);
}
-ANN static Type curry_type(const Env env, const Exp exp, const Exp efun, const Exp earg) {
- Func_Base *base = curry_base(env, efun->type->info->func->def->base, earg, exp->pos);
- Stmt code = curry_code(env, efun, earg);
+ANN2(1,2,3) Type curry_type(const Env env, const Exp exp, const Exp func, const Exp args, const bool lambda) {
+ Func_Base *const base = curry_base(env, func->type->info->func->def->base, args, exp->pos);
+ const Stmt code = curry_code(env, func, args);
+ if(lambda)base->fbflag |= fbflag_lambda; // rewritem
exp->d.exp_lambda.def = new_func_def(env->gwion->mp, base, code);
exp->exp_type = ae_exp_lambda;
return check_exp(env, exp);
const Exp earg = efun->next;
efun->next = NULL;
const Type ret = check_exp(env, efun)
- ? curry_type(env, exp_self(call), efun, earg)
+ ? curry_type(env, exp_self(call), efun, earg, true)
: env->gwion->type[et_error];
mp_free(env->gwion->mp, Exp, earg);
return ret;
CHECK_BB(add_op(gwi->gwion, &opi));
return GW_OK;
}
-
vector_release(&v);
}
+ANN static m_float basic_locale(m_str str) {
+ const char base = str[0];
+ str++;
+ if(base < 'A' || base > 'G') return -1;
+ m_int bnote = base - 'A';
+ if(*str == '#') { bnote++; str++; }
+ else if(*str == 'b') { bnote--; str++; }
+ char *remainder;
+ const long octave = strtol(str, &remainder, 10);
+ if(*remainder != '\0') return -1;
+ const int note = bnote + 12 * octave + 21;
+ return (pow(2, (note - 69) / 12.0) * 440.0);
+}
+
+static SFUN(BasicLocale) {
+ const M_Object arg = *(M_Object*)MEM(0);
+ const m_float ret = basic_locale(STRING(arg));
+ if(ret == -1.0)
+ handle(shred, "invalid value for locale");
+ *(m_float*)RETURN = ret;
+}
+
ANN static m_bool import_core_libs(const Gwi gwi) {
gwidoc(gwi, "one type to rule them all.");
const Type t_class = gwi_mk_type(gwi, "Class", SZ_INT, NULL);
GWI_BB(import_curry(gwi));
+gwi_func_ini(gwi, "float", "BasicLocale");
+gwi_func_arg(gwi, "string", "str");
+gwi_func_end(gwi, BasicLocale, ae_flag_none);
+
// seemed need at a point to ease liking
gwi_enum_ini(gwi, "@hidden_enum");
gwi_enum_add(gwi, "@hidden_enum", 0);
const Func_Def fdef = bin->lhs->d.exp_lambda.def;
unset_fbflag(fdef->base, fbflag_lambda);
CHECK_BN(traverse_func_def(env, fdef));
+ set_fbflag(fdef->base, fbflag_lambda);
const Type actual = fdef->base->func->value_ref->type;
set_fbflag(fdef->base, fbflag_lambda);
Var_Decl vd = mp_vector_at(bin->rhs->d.exp_decl.list, struct Var_Decl_, 0);
#include "match.h"
#include "specialid.h"
#include "tmp_resolve.h"
+#include "curry.h"
ANN static m_bool check_stmt_list(const Env env, Stmt_List list);
ANN m_bool check_class_def(const Env env, const Class_Def class_def);
ERR_O(prim_pos(data),
_("non-global variable '%s' used from global function/class."),
s_name(var))
+ } else if(env->func && fbflag(env->func->def->base, fbflag_locale)) {
+ if(!is_func(env->gwion, value->type) && value->from->owner && !from_global_nspc(env, value->from->owner))
+ ERR_O(prim_pos(data), _("invalid variable access from locale definition"));
}
return value;
}
}
ANN static Type check_prim_locale(const Env env, const Symbol *data NUSED) {
- return env->context->locale->def->base->ret_type;
+ return env->gwion->type[et_float];
}
#define describe_prim_xxx(name, type) \
}
if(e)
ERR_O(exp_self(exp)->pos, _("argument number does not match for lambda"))
-/*
- while (arg && e) {
- arg->type = e->type;
- if(is_class(env->gwion, arg->type))
- type_addref(arg->type);
- arg = arg->next;
- e = e->next;
- }
- if (arg || e)
- ERR_O(exp_self(exp)->pos, _("argument number does not match for lambda"))
-*/
l->def->base->values = env->curr->info->value;
const m_bool ret = traverse_func_def(env, l->def);
if (l->def->base->func) {
ANN static m_bool check_stmt_pp(const Env env, const Stmt_PP stmt) {
if (stmt->pp_type == ae_pp_include) env->name = stmt->data;
// check for memoization
- if (env->func && stmt->pp_type == ae_pp_pragma &&
+ else if (env->func && stmt->pp_type == ae_pp_pragma &&
!strncmp(stmt->data, "memoize", strlen("memoize")))
env->func->memoize = strtol(stmt->data + 7, NULL, 10);
+ else if(stmt->pp_type == ae_pp_locale) {
+ const loc_t loc = stmt_self(stmt)->pos;
+ const Exp id = new_prim_id(env->gwion->mp, stmt->xid, loc);
+ const Exp arg = new_prim_id(env->gwion->mp, insert_symbol("_"), loc);
+ arg->next = stmt->exp;
+ const Exp call = new_exp_call(env->gwion->mp, id, arg, loc);
+ stmt->exp = call;
+ CHECK_BB(traverse_exp(env, id));
+ CHECK_OB(curry_type(env, call, id, call->d.exp_call.args, false));
+ CHECK_OB(traverse_func_def(env, call->d.exp_lambda.def));
+ }
return GW_OK;
}
--- /dev/null
+#! [contains] 42
+
+fun void test(int i, int j) {
+ <<< "The answer: ${ i + j}" >>>;
+}
+
+curry(test, 40, _)(2);
+
+curry(test, _, 2) @=> const (void(int)) func0;
+
+curry(test, 40, _) @=> const auto func1;
+
+func0(40);
+
+func1(2);
--- /dev/null
+#! [contains] 440
+
+<<< `A4` >>>;
--- /dev/null
+#! [contains] 432
+locale Test(float base : 432) { return base; }
+
+#locale Test
+<<< `foo` >>>;
--- /dev/null
+#! [contains] 440
+locale Test(float base : 432) { return base; }
+
+#locale Test 440
+<<< `foo` >>>;