make volatile part of the system (SWI compatibility).
This commit is contained in:
1
C/init.c
1
C/init.c
@@ -354,6 +354,7 @@ static Opdef Ops[] = {
|
|||||||
{"dynamic", fx, 1150},
|
{"dynamic", fx, 1150},
|
||||||
{"thread_local", fx, 1150},
|
{"thread_local", fx, 1150},
|
||||||
{"initialization", fx, 1150},
|
{"initialization", fx, 1150},
|
||||||
|
{"volatile", fx, 1150},
|
||||||
{"mode", fx, 1150},
|
{"mode", fx, 1150},
|
||||||
{"public", fx, 1150},
|
{"public", fx, 1150},
|
||||||
{"multifile", fx, 1150},
|
{"multifile", fx, 1150},
|
||||||
|
@@ -203,21 +203,6 @@ predmerge(<, P, H1, H2, T1, T2, [H1|R]) :-
|
|||||||
% maybe a good idea to eventually support this in YAP.
|
% maybe a good idea to eventually support this in YAP.
|
||||||
% but for now just ignore it.
|
% but for now just ignore it.
|
||||||
%
|
%
|
||||||
:- meta_predicate prolog:volatile(:).
|
|
||||||
|
|
||||||
:- op(1150, fx, 'volatile').
|
|
||||||
|
|
||||||
prolog:volatile(P) :- var(P),
|
|
||||||
throw(error(instantiation_error,volatile(P))).
|
|
||||||
prolog:volatile(M:P) :-
|
|
||||||
do_volatile(P,M).
|
|
||||||
prolog:volatile((G1,G2)) :-
|
|
||||||
prolog:volatile(G1),
|
|
||||||
prolog:volatile(G2).
|
|
||||||
prolog:volatile(P) :-
|
|
||||||
prolog_load_context(module, M),
|
|
||||||
do_volatile(P,M).
|
|
||||||
|
|
||||||
prolog:load_foreign_library(P,Command) :-
|
prolog:load_foreign_library(P,Command) :-
|
||||||
absolute_file_name(P,[file_type(executable),solutions(first),file_errors(fail)],Lib),
|
absolute_file_name(P,[file_type(executable),solutions(first),file_errors(fail)],Lib),
|
||||||
load_foreign_files([Lib],[],Command).
|
load_foreign_files([Lib],[],Command).
|
||||||
@@ -225,8 +210,6 @@ prolog:load_foreign_library(P,Command) :-
|
|||||||
prolog:load_foreign_library(P) :-
|
prolog:load_foreign_library(P) :-
|
||||||
prolog:load_foreign_library(P,install).
|
prolog:load_foreign_library(P,install).
|
||||||
|
|
||||||
do_volatile(P,M) :- dynamic(M:P).
|
|
||||||
|
|
||||||
:- use_module(library(lists)).
|
:- use_module(library(lists)).
|
||||||
|
|
||||||
prolog:term_to_atom(Term,Atom) :-
|
prolog:term_to_atom(Term,Atom) :-
|
||||||
|
@@ -21,7 +21,22 @@
|
|||||||
thread_create(:),
|
thread_create(:),
|
||||||
thread_at_exit(:),
|
thread_at_exit(:),
|
||||||
thread_signal(+,:),
|
thread_signal(+,:),
|
||||||
with_mutex(+,:).
|
with_mutex(+,:),
|
||||||
|
volatile(:).
|
||||||
|
|
||||||
|
volatile(P) :- var(P),
|
||||||
|
throw(error(instantiation_error,volatile(P))).
|
||||||
|
volatile(M:P) :-
|
||||||
|
'$do_volatile'(P,M).
|
||||||
|
volatile((G1,G2)) :-
|
||||||
|
'$do_volatile'(G1),
|
||||||
|
'$do_volatile'(G2).
|
||||||
|
volatile(P) :-
|
||||||
|
'$current_module'(M),
|
||||||
|
'$do_volatile'(P,M).
|
||||||
|
|
||||||
|
'$do_volatile'(P,M) :- dynamic(M:P).
|
||||||
|
|
||||||
|
|
||||||
:- initialization('$init_thread0').
|
:- initialization('$init_thread0').
|
||||||
|
|
||||||
|
Reference in New Issue
Block a user