1
1
mirror of https://github.com/kanaka/mal.git synced 2024-10-05 18:08:55 +03:00
mal/impls/prolog/env.pl
Nicolas Boulenguez 0ee1a51777 New SWI-prolog implementation
with, in stepA_mal.mal, a new way to pass all test and break
self-hosting nevertheless.
2021-04-19 09:53:22 -05:00

32 lines
947 B
Prolog

% -*- mode: prolog; -*- select prolog mode in the emacs text editor
:- format_predicate('V', env_format(_Arg,_Env)).
env(mal_env(Assoc, t)) :- empty_assoc(Assoc).
env(Outer, mal_env(Assoc, Outer)) :- empty_assoc(Assoc).
env_get(mal_env(Assoc, _), Key, Value) :- get_assoc(Key, Assoc, Value).
env_get(mal_env(_, Outer), Key, Value) :- env_get(Outer, Key, Value).
env_set(Env, Key, Value) :-
Env = mal_env(Old, _),
put_assoc(Key, Old, Value, New),
setarg(1, Env, New).
env_format(_Arg, mal_env(Assoc, _Outer)) :-
assoc_to_list(Assoc, Pairs),
maplist(env_format_pair, Pairs).
env_format_pair(K - V) :- format(" ~a:~F", [K, V]).
% Does *not* check that the keys are symbols. This is done once when
% the fn* structure is created.
env_bind(_Env, [], []).
env_bind(Env, ['&', K], Vs) :- !,
list(Vs, List),
env_set(Env, K, List).
env_bind(Env, [K | Ks], [V | Vs]) :-
env_set(Env, K, V),
env_bind(Env, Ks, Vs).