1/* Part of SWI-Prolog 2 3 Author: Jan Wielemaker 4 E-mail: J.Wielemaker@vu.nl 5 WWW: http://www.swi-prolog.org 6 Copyright (c) 2013-2022, VU University Amsterdam 7 CWI, Amsterdam 8 SWI-Prolog Solutions b.v 9 All rights reserved. 10 11 Redistribution and use in source and binary forms, with or without 12 modification, are permitted provided that the following conditions 13 are met: 14 15 1. Redistributions of source code must retain the above copyright 16 notice, this list of conditions and the following disclaimer. 17 18 2. Redistributions in binary form must reproduce the above copyright 19 notice, this list of conditions and the following disclaimer in 20 the documentation and/or other materials provided with the 21 distribution. 22 23 THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS 24 "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT 25 LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS 26 FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE 27 COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, 28 INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, 29 BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; 30 LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER 31 CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT 32 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN 33 ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE 34 POSSIBILITY OF SUCH DAMAGE. 35*/ 36 37:- module(sandbox, 38 [ safe_goal/1, % :Goal 39 safe_call/1 % :Goal 40 ]). 41:- use_module(library(apply_macros),[expand_phrase/2]). 42:- use_module(library(apply),[maplist/2]). 43:- use_module(library(assoc),[empty_assoc/1,get_assoc/3,put_assoc/4]). 44:- use_module(library(debug),[debug/3,debugging/1]). 45:- use_module(library(error), 46 [ must_be/2, 47 instantiation_error/1, 48 type_error/2, 49 permission_error/3 50 ]). 51:- use_module(library(lists),[append/3]). 52:- use_module(library(prolog_format),[format_types/2]). 53 54:- multifile 55 safe_primitive/1, % Goal 56 safe_meta_predicate/1, % Name/Arity 57 safe_meta/2, % Goal, Calls 58 safe_meta/3, % Goal, Context, Calls 59 safe_global_variable/1, % Name 60 safe_directive/1, % Module:Goal 61 safe_prolog_flag/2. % +Name, +Value 62 63% :- debug(sandbox).
79:- meta_predicate
80 safe_goal( ),
81 safe_call( ).
93safe_call(Goal0) :-
94 expand_goal(Goal0, Goal),
95 safe_goal(Goal),
96 call(Goal).
120safe_goal(M:Goal) :- 121 empty_assoc(Safe0), 122 catch(safe(Goal, M, [], Safe0, _), E, true), 123 !, 124 nb_delete(sandbox_last_error), 125 ( var(E) 126 -> true 127 ; throw(E) 128 ). 129safe_goal(_) :- 130 nb_current(sandbox_last_error, E), 131 !, 132 nb_delete(sandbox_last_error), 133 throw(E). 134safe_goal(G) :- 135 debug(sandbox(fail), 'safe_goal/1 failed for ~p', [G]), 136 throw(error(instantiation_error, sandbox(G, []))).
143safe(V, _, Parents, _, _) :- 144 var(V), 145 !, 146 Error = error(instantiation_error, sandbox(V, Parents)), 147 nb_setval(sandbox_last_error, Error), 148 throw(Error). 149safe(M:G, _, Parents, Safe0, Safe) :- 150 !, 151 must_be(atom, M), 152 must_be(callable, G), 153 known_module(M:G, Parents), 154 ( predicate_property(M:G, imported_from(M2)) 155 -> true 156 ; M2 = M 157 ), 158 ( ( safe_primitive(M2:G) 159 ; safe_primitive(G), 160 predicate_property(G, iso) 161 ) 162 -> Safe = Safe0 163 ; ( predicate_property(M:G, exported) 164 ; predicate_property(M:G, public) 165 ; predicate_property(M:G, multifile) 166 ; predicate_property(M:G, iso) 167 ; memberchk(M:_, Parents) 168 ) 169 -> safe(G, M, Parents, Safe0, Safe) 170 ; throw(error(permission_error(call, sandboxed, M:G), 171 sandbox(M:G, Parents))) 172 ). 173safe(G, _, Parents, _, _) :- 174 debugging(sandbox(show)), 175 length(Parents, Level), 176 debug(sandbox(show), '[~D] SAFE ~q?', [Level, G]), 177 fail. 178safe(G, _, Parents, Safe, Safe) :- 179 catch(safe_primitive(G), 180 error(instantiation_error, _), 181 rethrow_instantition_error([G|Parents])), 182 predicate_property(G, iso), 183 !. 184safe(G, M, Parents, Safe, Safe) :- 185 known_module(M:G, Parents), 186 ( predicate_property(M:G, imported_from(M2)) 187 -> true 188 ; M2 = M 189 ), 190 ( catch(safe_primitive(M2:G), 191 error(instantiation_error, _), 192 rethrow_instantition_error([M2:G|Parents])) 193 ; predicate_property(M2:G, number_of_rules(0)) 194 ), 195 !. 196safe(G, M, Parents, Safe0, Safe) :- 197 predicate_property(G, iso), 198 safe_meta_call(G, M, Called), 199 !, 200 add_iso_parent(G, Parents, Parents1), 201 safe_list(Called, M, Parents1, Safe0, Safe). 202safe(G, M, Parents, Safe0, Safe) :- 203 ( predicate_property(M:G, imported_from(M2)) 204 -> true 205 ; M2 = M 206 ), 207 safe_meta_call(M2:G, M, Called), 208 !, 209 safe_list(Called, M, Parents, Safe0, Safe). 210safe(G, M, Parents, Safe0, Safe) :- 211 goal_id(M:G, Id, Gen), 212 ( get_assoc(Id, Safe0, _) 213 -> Safe = Safe0 214 ; put_assoc(Id, Safe0, true, Safe1), 215 ( Gen == M:G 216 -> safe_clauses(Gen, M, [Id|Parents], Safe1, Safe) 217 ; catch(safe_clauses(Gen, M, [Id|Parents], Safe1, Safe), 218 error(instantiation_error, Ctx), 219 unsafe(Parents, Ctx)) 220 ) 221 ), 222 !. 223safe(G, M, Parents, _, _) :- 224 debug(sandbox(fail), 225 'safe/1 failed for ~p (parents:~p)', [M:G, Parents]), 226 fail. 227 228unsafe(Parents, Var) :- 229 var(Var), 230 !, 231 nb_setval(sandbox_last_error, 232 error(instantiation_error, sandbox(_, Parents))), 233 fail. 234unsafe(_Parents, Ctx) :- 235 Ctx = sandbox(_,_), 236 nb_setval(sandbox_last_error, 237 error(instantiation_error, Ctx)), 238 fail. 239 240rethrow_instantition_error(Parents) :- 241 throw(error(instantiation_error, sandbox(_, Parents))). 242 243safe_clauses(G, M, Parents, Safe0, Safe) :- 244 predicate_property(M:G, interpreted), 245 def_module(M:G, MD:QG), 246 \+ compiled(MD:QG), 247 !, 248 findall(Ref-Body, clause(MD:, Body, Ref), Bodies), 249 safe_bodies(Bodies, MD, Parents, Safe0, Safe). 250safe_clauses(G, M, [_|Parents], _, _) :- 251 predicate_property(M:G, visible), 252 !, 253 throw(error(permission_error(call, sandboxed, G), 254 sandbox(M:G, Parents))). 255safe_clauses(_, _, [G|Parents], _, _) :- 256 throw(error(existence_error(procedure, G), 257 sandbox(G, Parents))). 258 259compiled(system:(@(_,_))). 260 261known_module(M:_, _) :- 262 current_module(M), 263 !. 264known_module(M:G, Parents) :- 265 throw(error(permission_error(call, sandboxed, M:G), 266 sandbox(M:G, Parents))). 267 268add_iso_parent(G, Parents, Parents) :- 269 is_control(G), 270 !. 271add_iso_parent(G, Parents, [G|Parents]). 272 273is_control((_,_)). 274is_control((_;_)). 275is_control((_->_)). 276is_control((_*->_)). 277is_control(\+(_)).
286safe_bodies([], _, _, Safe, Safe). 287safe_bodies([Ref-H|T], M, Parents, Safe0, Safe) :- 288 ( H = M2:H2, nonvar(M2), 289 clause_property(Ref, module(M2)) 290 -> copy_term(H2, H3), 291 CM = M2 292 ; copy_term(H, H3), 293 CM = M 294 ), 295 safe(H3, CM, Parents, Safe0, Safe1), 296 safe_bodies(T, M, Parents, Safe1, Safe). 297 298def_module(M:G, MD:QG) :- 299 predicate_property(M:G, imported_from(MD)), 300 !, 301 meta_qualify(MD:G, M, QG). 302def_module(M:G, M:QG) :- 303 meta_qualify(M:G, M, QG).
311safe_list([], _, _, Safe, Safe). 312safe_list([H|T], M, Parents, Safe0, Safe) :- 313 ( H = M2:H2, 314 M == M2 % in our context 315 -> copy_term(H2, H3) 316 ; copy_term(H, H3) % cross-module call 317 ), 318 safe(H3, M, Parents, Safe0, Safe1), 319 safe_list(T, M, Parents, Safe1, Safe).
325meta_qualify(MD:G, M, QG) :- 326 predicate_property(MD:G, meta_predicate(Head)), 327 !, 328 G =.. [Name|Args], 329 Head =.. [_|Q], 330 qualify_args(Q, M, Args, QArgs), 331 QG =.. [Name|QArgs]. 332meta_qualify(_:G, _, G). 333 334qualify_args([], _, [], []). 335qualify_args([H|T], M, [A|AT], [Q|QT]) :- 336 qualify_arg(H, M, A, Q), 337 qualify_args(T, M, AT, QT). 338 339qualify_arg(S, M, A, Q) :- 340 q_arg(S), 341 !, 342 qualify(A, M, Q). 343qualify_arg(_, _, A, A). 344 345q_arg(I) :- integer(I), !. 346q_arg(:). 347q_arg(^). 348q_arg(//). 349 350qualify(A, M, MZ:Q) :- 351 strip_module(M:A, MZ, Q).
363goal_id(M:Goal, M:Id, Gen) :- 364 !, 365 goal_id(Goal, Id, Gen). 366goal_id(Var, _, _) :- 367 var(Var), 368 !, 369 instantiation_error(Var). 370goal_id(Atom, Atom, Atom) :- 371 atom(Atom), 372 !. 373goal_id(Term, _, _) :- 374 \+ compound(Term), 375 !, 376 type_error(callable, Term). 377goal_id(Term, Skolem, Gen) :- % most general form 378 compound_name_arity(Term, Name, Arity), 379 compound_name_arity(Skolem, Name, Arity), 380 compound_name_arity(Gen, Name, Arity), 381 copy_goal_args(1, Term, Skolem, Gen), 382 ( Gen =@= Term 383 -> ! % No more specific one; we can commit 384 ; true 385 ), 386 numbervars(Skolem, 0, _). 387goal_id(Term, Skolem, Term) :- % most specific form 388 debug(sandbox(specify), 'Retrying with ~p', [Term]), 389 copy_term(Term, Skolem), 390 numbervars(Skolem, 0, _).
397copy_goal_args(I, Term, Skolem, Gen) :- 398 arg(I, Term, TA), 399 !, 400 arg(I, Skolem, SA), 401 arg(I, Gen, GA), 402 copy_goal_arg(TA, SA, GA), 403 I2 is I + 1, 404 copy_goal_args(I2, Term, Skolem, Gen). 405copy_goal_args(_, _, _, _). 406 407copy_goal_arg(Arg, SArg, Arg) :- 408 copy_goal_arg(Arg), 409 !, 410 copy_term(Arg, SArg). 411copy_goal_arg(_, _, _). 412 413copy_goal_arg(Var) :- var(Var), !, fail. 414copy_goal_arg(_:_).
426term_expansion(safe_primitive(Goal), Term) :- 427 ( verify_safe_declaration(Goal) 428 -> Term = safe_primitive(Goal) 429 ; Term = [] 430 ). 431term_expansion((safe_primitive(Goal) :- Body), Term) :- 432 ( verify_safe_declaration(Goal) 433 -> Term = (safe_primitive(Goal) :- Body) 434 ; Term = [] 435 ). 436 437systemterm_expansion(sandbox:safe_primitive(Goal), Term) :- 438 \+ current_prolog_flag(xref, true), 439 ( verify_safe_declaration(Goal) 440 -> Term = sandbox:safe_primitive(Goal) 441 ; Term = [] 442 ). 443systemterm_expansion((sandbox:safe_primitive(Goal) :- Body), Term) :- 444 \+ current_prolog_flag(xref, true), 445 ( verify_safe_declaration(Goal) 446 -> Term = (sandbox:safe_primitive(Goal) :- Body) 447 ; Term = [] 448 ). 449 450verify_safe_declaration(Var) :- 451 var(Var), 452 !, 453 instantiation_error(Var). 454verify_safe_declaration(Module:Goal) :- 455 !, 456 must_be(atom, Module), 457 must_be(callable, Goal), 458 ( ok_meta(Module:Goal) 459 -> true 460 ; ( predicate_property(Module:Goal, visible) 461 -> true 462 ; predicate_property(Module:Goal, foreign) 463 ), 464 \+ predicate_property(Module:Goal, imported_from(_)), 465 \+ predicate_property(Module:Goal, meta_predicate(_)) 466 -> true 467 ; permission_error(declare, safe_goal, Module:Goal) 468 ). 469verify_safe_declaration(Goal) :- 470 must_be(callable, Goal), 471 ( predicate_property(system:Goal, iso), 472 \+ predicate_property(system:Goal, meta_predicate()) 473 -> true 474 ; permission_error(declare, safe_goal, Goal) 475 ). 476 477ok_meta(system:assert(_)). 478ok_meta(system:load_files(_,_)). 479ok_meta(system:use_module(_,_)). 480ok_meta(system:use_module(_)). 481ok_meta('$syspreds':predicate_property(_,_)). 482 483verify_predefined_safe_declarations :- 484 forall(clause(safe_primitive(Goal), _Body, Ref), 485 ( E = error(F,_), 486 catch(verify_safe_declaration(Goal), E, true), 487 ( nonvar(F) 488 -> clause_property(Ref, file(File)), 489 clause_property(Ref, line_count(Line)), 490 print_message(error, bad_safe_declaration(Goal, File, Line)) 491 ; true 492 ) 493 )). 494 495:- initialization(verify_predefined_safe_declarations, now).
509% First, all ISO system predicates that are considered safe 510 511safe_primitive(true). 512safe_primitive(fail). 513safe_primitive(system:false). 514safe_primitive(repeat). 515safe_primitive(!). 516 % types 517safe_primitive(var(_)). 518safe_primitive(nonvar(_)). 519safe_primitive(system:attvar(_)). 520safe_primitive(integer(_)). 521safe_primitive(float(_)). 522:- if(current_predicate(rational/1)). 523safe_primitive(system:rational(_)). 524safe_primitive(system:rational(_,_,_)). 525:- endif. 526safe_primitive(number(_)). 527safe_primitive(atom(_)). 528safe_primitive(system:blob(_,_)). 529safe_primitive(system:string(_)). 530safe_primitive(atomic(_)). 531safe_primitive(compound(_)). 532safe_primitive(callable(_)). 533safe_primitive(ground(_)). 534safe_primitive(system:nonground(_,_)). 535safe_primitive(system:cyclic_term(_)). 536safe_primitive(acyclic_term(_)). 537safe_primitive(system:is_stream(_)). 538safe_primitive(system:'$is_char'(_)). 539safe_primitive(system:'$is_char_code'(_)). 540safe_primitive(system:'$is_char_list'(_,_)). 541safe_primitive(system:'$is_code_list'(_,_)). 542 % ordering 543safe_primitive(@>(_,_)). 544safe_primitive(@>=(_,_)). 545safe_primitive(==(_,_)). 546safe_primitive(@<(_,_)). 547safe_primitive(@=<(_,_)). 548safe_primitive(compare(_,_,_)). 549safe_primitive(sort(_,_)). 550safe_primitive(keysort(_,_)). 551safe_primitive(system: =@=(_,_)). 552safe_primitive(system:'$btree_find_node'(_,_,_,_,_)). 553 554 % unification and equivalence 555safe_primitive(=(_,_)). 556safe_primitive(\=(_,_)). 557safe_primitive(system:'?='(_,_)). 558safe_primitive(system:unifiable(_,_,_)). 559safe_primitive(unify_with_occurs_check(_,_)). 560safe_primitive(\==(_,_)). 561 % arithmetic 562safe_primitive(is(_,_)). 563safe_primitive(>(_,_)). 564safe_primitive(>=(_,_)). 565safe_primitive(=:=(_,_)). 566safe_primitive(=\=(_,_)). 567safe_primitive(=<(_,_)). 568safe_primitive(<(_,_)). 569:- if(current_prolog_flag(bounded, false)). 570safe_primitive(system:nth_integer_root_and_remainder(_,_,_,_)). 571:- endif. 572 573 % term-handling 574safe_primitive(arg(_,_,_)). 575safe_primitive(system:setarg(_,_,_)). 576safe_primitive(system:nb_setarg(_,_,_)). 577safe_primitive(system:nb_linkarg(_,_,_)). 578safe_primitive(functor(_,_,_)). 579safe_primitive(system:functor(_,_,_,_)). 580safe_primitive(_ =.. _). 581safe_primitive(system:compound_name_arity(_,_,_)). 582safe_primitive(system:compound_name_arguments(_,_,_)). 583safe_primitive(system:'$filled_array'(_,_,_,_)). 584safe_primitive(copy_term(_,_)). 585safe_primitive(system:copy_term(_,_,_,_)). 586safe_primitive(system:duplicate_term(_,_)). 587safe_primitive(system:copy_term_nat(_,_)). 588safe_primitive(system:size_abstract_term(_,_,_)). 589safe_primitive(numbervars(_,_,_)). 590safe_primitive(system:numbervars(_,_,_,_)). 591safe_primitive(subsumes_term(_,_)). 592safe_primitive(system:term_hash(_,_)). 593safe_primitive(system:term_hash(_,_,_,_)). 594safe_primitive(system:variant_sha1(_,_)). 595safe_primitive(system:variant_hash(_,_)). 596safe_primitive(system:'$term_size'(_,_,_)). 597 598 % dicts 599safe_primitive(system:is_dict(_)). 600safe_primitive(system:is_dict(_,_)). 601safe_primitive(system:get_dict(_,_,_)). 602safe_primitive(system:get_dict(_,_,_,_,_)). 603safe_primitive(system:'$get_dict_ex'(_,_,_)). 604safe_primitive(system:dict_create(_,_,_)). 605safe_primitive(system:dict_pairs(_,_,_)). 606safe_primitive(system:put_dict(_,_,_)). 607safe_primitive(system:put_dict(_,_,_,_)). 608safe_primitive(system:del_dict(_,_,_,_)). 609safe_primitive(system:select_dict(_,_,_)). 610safe_primitive(system:b_set_dict(_,_,_)). 611safe_primitive(system:nb_set_dict(_,_,_)). 612safe_primitive(system:nb_link_dict(_,_,_)). 613safe_primitive(system:(:<(_,_))). 614safe_primitive(system:(>:<(_,_))). 615 % atoms 616safe_primitive(atom_chars(_, _)). 617safe_primitive(atom_codes(_, _)). 618safe_primitive(sub_atom(_,_,_,_,_)). 619safe_primitive(atom_concat(_,_,_)). 620safe_primitive(atom_length(_,_)). 621safe_primitive(char_code(_,_)). 622safe_primitive(system:name(_,_)). 623safe_primitive(system:atomic_concat(_,_,_)). 624safe_primitive(system:atomic_list_concat(_,_)). 625safe_primitive(system:atomic_list_concat(_,_,_)). 626safe_primitive(system:downcase_atom(_,_)). 627safe_primitive(system:upcase_atom(_,_)). 628safe_primitive(system:char_type(_,_)). 629safe_primitive(system:normalize_space(_,_)). 630safe_primitive(system:sub_atom_icasechk(_,_,_)). 631 % numbers 632safe_primitive(number_codes(_,_)). 633safe_primitive(number_chars(_,_)). 634safe_primitive(system:atom_number(_,_)). 635safe_primitive(system:code_type(_,_)). 636 % strings 637safe_primitive(system:atom_string(_,_)). 638safe_primitive(system:number_string(_,_)). 639safe_primitive(system:string_chars(_, _)). 640safe_primitive(system:string_codes(_, _)). 641safe_primitive(system:string_code(_,_,_)). 642safe_primitive(system:sub_string(_,_,_,_,_)). 643safe_primitive(system:split_string(_,_,_,_)). 644safe_primitive(system:atomics_to_string(_,_,_)). 645safe_primitive(system:atomics_to_string(_,_)). 646safe_primitive(system:string_concat(_,_,_)). 647safe_primitive(system:string_length(_,_)). 648safe_primitive(system:string_lower(_,_)). 649safe_primitive(system:string_upper(_,_)). 650safe_primitive(system:term_string(_,_)). 651safe_primitive('$syspreds':term_string(_,_,_)). 652 % Lists 653safe_primitive(length(_,_)). 654 % exceptions 655safe_primitive(throw(_)). 656safe_primitive(system:abort). 657 % misc 658safe_primitive(current_prolog_flag(_,_)). 659safe_primitive(current_op(_,_,_)). 660safe_primitive(system:sleep(_)). 661safe_primitive(system:thread_self(_)). 662safe_primitive(system:get_time(_)). 663safe_primitive(system:statistics(_,_)). 664:- if(current_prolog_flag(threads,true)). 665safe_primitive(system:thread_statistics(Id,_,_)) :- 666 ( var(Id) 667 -> instantiation_error(Id) 668 ; thread_self(Id) 669 ). 670safe_primitive(system:thread_property(Id,_)) :- 671 ( var(Id) 672 -> instantiation_error(Id) 673 ; thread_self(Id) 674 ). 675:- endif. 676safe_primitive(system:format_time(_,_,_)). 677safe_primitive(system:format_time(_,_,_,_)). 678safe_primitive(system:date_time_stamp(_,_)). 679safe_primitive(system:stamp_date_time(_,_,_)). 680safe_primitive(system:strip_module(_,_,_)). 681safe_primitive('$messages':message_to_string(_,_)). 682safe_primitive(system:import_module(_,_)). 683safe_primitive(system:file_base_name(_,_)). 684safe_primitive(system:file_directory_name(_,_)). 685safe_primitive(system:file_name_extension(_,_,_)). 686 687safe_primitive(clause(H,_)) :- safe_clause(H). 688safe_primitive(asserta(X)) :- safe_assert(X). 689safe_primitive(assertz(X)) :- safe_assert(X). 690safe_primitive(retract(X)) :- safe_assert(X). 691safe_primitive(retractall(X)) :- safe_assert(X). 692safe_primitive('$dcg':dcg_translate_rule(_,_)). 693safe_primitive('$syspreds':predicate_property(Pred, _)) :- 694 nonvar(Pred), 695 Pred \= (_:_). 696 697% We need to do data flow analysis to find the tag of the 698% target key before we can conclude that functions on dicts 699% are safe. 700safe_primitive('$dicts':'.'(_,K,_)) :- atom(K). 701safe_primitive('$dicts':'.'(_,K,_)) :- 702 ( nonvar(K) 703 -> dict_built_in(K) 704 ; instantiation_error(K) 705 ). 706 707dict_built_in(get(_)). 708dict_built_in(put(_)). 709dict_built_in(put(_,_)). 710 711% The non-ISO system predicates. These can be redefined, so we must 712% be careful to ensure the system ones are used. 713 714safe_primitive(system:false). 715safe_primitive(system:cyclic_term(_)). 716safe_primitive(system:msort(_,_)). 717safe_primitive(system:sort(_,_,_,_)). 718safe_primitive(system:between(_,_,_)). 719safe_primitive(system:succ(_,_)). 720safe_primitive(system:plus(_,_,_)). 721safe_primitive(system:float_class(_,_)). 722safe_primitive(system:term_variables(_,_)). 723safe_primitive(system:term_variables(_,_,_)). 724safe_primitive(system:'$term_size'(_,_,_)). 725safe_primitive(system:atom_to_term(_,_,_)). 726safe_primitive(system:term_to_atom(_,_)). 727safe_primitive(system:atomic_list_concat(_,_,_)). 728safe_primitive(system:atomic_list_concat(_,_)). 729safe_primitive(system:downcase_atom(_,_)). 730safe_primitive(system:upcase_atom(_,_)). 731safe_primitive(system:is_list(_)). 732safe_primitive(system:memberchk(_,_)). 733safe_primitive(system:'$skip_list'(_,_,_)). 734safe_primitive(system:'$seek_list'(_, _, _, _)). 735 % attributes 736safe_primitive(system:get_attr(_,_,_)). 737safe_primitive(system:get_attrs(_,_)). 738safe_primitive(system:term_attvars(_,_)). 739safe_primitive(system:del_attr(_,_)). 740safe_primitive(system:del_attrs(_)). 741safe_primitive('$attvar':copy_term(_,_,_)). 742 % globals 743safe_primitive(system:b_getval(_,_)). 744safe_primitive(system:b_setval(Var,_)) :- 745 safe_global_var(Var). 746safe_primitive(system:nb_getval(_,_)). 747safe_primitive('$syspreds':nb_setval(Var,_)) :- 748 safe_global_var(Var). 749safe_primitive(system:nb_linkval(Var,_)) :- 750 safe_global_var(Var). 751safe_primitive(system:nb_current(_,_)). 752 % database 753safe_primitive(system:assert(X)) :- 754 safe_assert(X). 755 % Output 756safe_primitive(system:writeln(_)). 757safe_primitive('$messages':print_message(_,_)). 758 759 % Stack limits (down) 760safe_primitive('$syspreds':set_prolog_stack(Stack, limit(ByteExpr))) :- 761 nonvar(Stack), 762 stack_name(Stack), 763 catch(Bytes is ByteExpr, _, fail), 764 prolog_stack_property(Stack, limit(Current)), 765 Bytes =< Current. 766 767stack_name(global). 768stack_name(local). 769stack_name(trail). 770 771safe_primitive('$tabling':abolish_all_tables). 772safe_primitive('$tabling':'$wrap_tabled'(Module:_Head, _Mode)) :- 773 prolog_load_context(module, Module), 774 !. 775safe_primitive('$tabling':'$moded_wrap_tabled'(Module:_Head,_,_,_,_)) :- 776 prolog_load_context(module, Module), 777 !. 778 779 780% use_module/1. We only allow for .pl files that are loaded from 781% relative paths that do not contain /../ 782 783safe_primitive(system:use_module(Spec, _Import)) :- 784 safe_primitive(system:use_module(Spec)). 785safe_primitive(system:load_files(Spec, Options)) :- 786 safe_primitive(system:use_module(Spec)), 787 maplist(safe_load_file_option, Options). 788safe_primitive(system:use_module(Spec)) :- 789 ground(Spec), 790 ( atom(Spec) 791 -> Path = Spec 792 ; Spec =.. [_Alias, Segments], 793 phrase(segments_to_path(Segments), List), 794 atomic_list_concat(List, Path) 795 ), 796 \+ is_absolute_file_name(Path), 797 \+ sub_atom(Path, _, _, _, '/../'), 798 absolute_file_name(Spec, AbsFile, 799 [ access(read), 800 file_type(prolog), 801 file_errors(fail) 802 ]), 803 file_name_extension(_, Ext, AbsFile), 804 save_extension(Ext). 805 806% support predicates for safe_primitive, validating the safety of 807% arguments to certain goals. 808 809segments_to_path(A/B) --> 810 !, 811 segments_to_path(A), 812 [/], 813 segments_to_path(B). 814segments_to_path(X) --> 815 [X]. 816 817save_extension(pl). 818 819safe_load_file_option(if(changed)). 820safe_load_file_option(if(not_loaded)). 821safe_load_file_option(must_be_module(_)). 822safe_load_file_option(optimise(_)). 823safe_load_file_option(silent(_)).
assert(Term)
is safe, which means it asserts in the
current module. Cross-module asserts are considered unsafe. We
only allow for adding facts. In theory, we could also allow for
rules if we prove the safety of the body.832safe_assert(C) :- cyclic_term(C), !, fail. 833safe_assert(X) :- var(X), !, fail. 834safe_assert(_Head:-_Body) :- !, fail. 835safe_assert(_:_) :- !, fail. 836safe_assert(_).
844safe_clause(H) :- var(H), !. 845safe_clause(_:_) :- !, fail. 846safe_clause(_).
854safe_global_var(Name) :- 855 var(Name), 856 !, 857 instantiation_error(Name). 858safe_global_var(Name) :- 859 safe_global_variable(Name).
871safe_meta(system:put_attr(V,M,A), Called) :- 872 !, 873 ( atom(M) 874 -> attr_hook_predicates([ attr_unify_hook(A, _), 875 attribute_goals(V,_,_), 876 project_attributes(_,_) 877 ], M, Called) 878 ; instantiation_error(M) 879 ). 880safe_meta(system:with_output_to(Output, G), [G]) :- 881 safe_output(Output), 882 !. 883safe_meta(system:format(Format, Args), Calls) :- 884 format_calls(Format, Args, Calls). 885safe_meta(system:format(Output, Format, Args), Calls) :- 886 safe_output(Output), 887 format_calls(Format, Args, Calls). 888safe_meta(prolog_debug:debug(_Term, Format, Args), Calls) :- 889 format_calls(Format, Args, Calls). 890safe_meta(system:set_prolog_flag(Flag, Value), []) :- 891 atom(Flag), 892 safe_prolog_flag(Flag, Value). 893safe_meta('$attvar':freeze(_Var,Goal), [Goal]). 894safe_meta(phrase(NT,Xs0,Xs), [Goal]) :- % phrase/2,3 and call_dcg/2,3 895 expand_nt(NT,Xs0,Xs,Goal). 896safe_meta(phrase(NT,Xs0), [Goal]) :- 897 expand_nt(NT,Xs0,[],Goal). 898safe_meta('$dcg':call_dcg(NT,Xs0,Xs), [Goal]) :- 899 expand_nt(NT,Xs0,Xs,Goal). 900safe_meta('$dcg':call_dcg(NT,Xs0), [Goal]) :- 901 expand_nt(NT,Xs0,[],Goal). 902safe_meta('$tabling':abolish_table_subgoals(V), []) :- 903 \+ qualified(V). 904safe_meta('$tabling':current_table(V, _), []) :- 905 \+ qualified(V). 906safe_meta('$tabling':tnot(G), [G]). 907safe_meta('$tabling':not_exists(G), [G]). 908 909qualified(V) :- 910 nonvar(V), 911 V = _:_.
921attr_hook_predicates([], _, []). 922attr_hook_predicates([H|T], M, Called) :- 923 ( predicate_property(M:H, defined) 924 -> Called = [M:H|Rest] 925 ; Called = Rest 926 ), 927 attr_hook_predicates(T, M, Rest).
935expand_nt(NT, _Xs0, _Xs, _NewGoal) :- 936 strip_module(NT, _, Plain), 937 var(Plain), 938 !, 939 instantiation_error(Plain). 940expand_nt(NT, Xs0, Xs, NewGoal) :- 941 dcg_translate_rule((pseudo_nt --> NT), 942 (pseudo_nt(Xs0c,Xsc) :- NewGoal0)), 943 ( var(Xsc), Xsc \== Xs0c 944 -> Xs = Xsc, NewGoal1 = NewGoal0 945 ; NewGoal1 = (NewGoal0, Xsc = Xs) 946 ), 947 ( var(Xs0c) 948 -> Xs0 = Xs0c, 949 NewGoal = NewGoal1 950 ; NewGoal = ( Xs0 = Xs0c, NewGoal1 ) 951 ).
958safe_meta_call(Goal, _, _Called) :- 959 debug(sandbox(meta), 'Safe meta ~p?', [Goal]), 960 fail. 961safe_meta_call(Goal, Context, Called) :- 962 ( safe_meta(Goal, Called) 963 -> true 964 ; safe_meta(Goal, Context, Called) 965 ), 966 !. % call hook 967safe_meta_call(Goal, _, Called) :- 968 Goal = M:Plain, 969 compound(Plain), 970 compound_name_arity(Plain, Name, Arity), 971 safe_meta_predicate(M:Name/Arity), 972 predicate_property(Goal, meta_predicate(Spec)), 973 !, 974 called(Spec, Plain, Called). 975safe_meta_call(M:Goal, _, Called) :- 976 !, 977 generic_goal(Goal, Gen), 978 safe_meta(M:Gen), 979 called(Gen, Goal, Called). 980safe_meta_call(Goal, _, Called) :- 981 generic_goal(Goal, Gen), 982 safe_meta(Gen), 983 called(Gen, Goal, Called). 984 985called(Gen, Goal, Called) :- 986 compound_name_arity(Goal, _, Arity), 987 called(1, Arity, Gen, Goal, Called). 988 989called(I, Arity, Gen, Goal, Called) :- 990 I =< Arity, 991 !, 992 arg(I, Gen, Spec), 993 ( calling_meta_spec(Spec) 994 -> arg(I, Goal, Called0), 995 extend(Spec, Called0, G), 996 Called = [G|Rest] 997 ; Called = Rest 998 ), 999 I2 is I+1, 1000 called(I2, Arity, Gen, Goal, Rest). 1001called(_, _, _, _, []). 1002 1003generic_goal(G, Gen) :- 1004 functor(G, Name, Arity), 1005 functor(Gen, Name, Arity). 1006 1007calling_meta_spec(V) :- var(V), !, fail. 1008calling_meta_spec(I) :- integer(I), !. 1009calling_meta_spec(^). 1010calling_meta_spec(//). 1011 1012 1013extend(^, G, Plain) :- 1014 !, 1015 strip_existential(G, Plain). 1016extend(//, DCG, Goal) :- 1017 !, 1018 ( expand_phrase(call_dcg(DCG,_,_), Goal) 1019 -> true 1020 ; instantiation_error(DCG) % Ask more instantiation. 1021 ). % might not help, but does not harm. 1022extend(0, G, G) :- !. 1023extend(I, M:G0, M:G) :- 1024 !, 1025 G0 =.. List, 1026 length(Extra, I), 1027 append(List, Extra, All), 1028 G =.. All. 1029extend(I, G0, G) :- 1030 G0 =.. List, 1031 length(Extra, I), 1032 append(List, Extra, All), 1033 G =.. All. 1034 1035strip_existential(Var, Var) :- 1036 var(Var), 1037 !. 1038strip_existential(M:G0, M:G) :- 1039 !, 1040 strip_existential(G0, G). 1041strip_existential(_^G0, G) :- 1042 !, 1043 strip_existential(G0, G). 1044strip_existential(G, G).
1048safe_meta((0,0)). 1049safe_meta((0;0)). 1050safe_meta((0->0)). 1051safe_meta(system:(0*->0)). 1052safe_meta(catch(0,*,0)). 1053safe_meta(findall(*,0,*)). 1054safe_meta('$bags':findall(*,0,*,*)). 1055safe_meta(setof(*,^,*)). 1056safe_meta(bagof(*,^,*)). 1057safe_meta('$bags':findnsols(*,*,0,*)). 1058safe_meta('$bags':findnsols(*,*,0,*,*)). 1059safe_meta(system:call_cleanup(0,0)). 1060safe_meta(system:setup_call_cleanup(0,0,0)). 1061safe_meta(system:setup_call_catcher_cleanup(0,0,*,0)). 1062safe_meta('$attvar':call_residue_vars(0,*)). 1063safe_meta('$syspreds':call_with_inference_limit(0,*,*)). 1064safe_meta('$syspreds':call_with_depth_limit(0,*,*)). 1065safe_meta('$syspreds':undo(0)). 1066safe_meta(^(*,0)). 1067safe_meta(\+(0)). 1068safe_meta(call(0)). 1069safe_meta(call(1,*)). 1070safe_meta(call(2,*,*)). 1071safe_meta(call(3,*,*,*)). 1072safe_meta(call(4,*,*,*,*)). 1073safe_meta(call(5,*,*,*,*,*)). 1074safe_meta(call(6,*,*,*,*,*,*)). 1075safe_meta('$tabling':start_tabling(*,0)). 1076safe_meta('$tabling':start_tabling(*,0,*,*)). 1077safe_meta(wfs:call_delays(0,*)).
1084safe_output(Output) :- 1085 var(Output), 1086 !, 1087 instantiation_error(Output). 1088safe_output(atom(_)). 1089safe_output(string(_)). 1090safe_output(codes(_)). 1091safe_output(codes(_,_)). 1092safe_output(chars(_)). 1093safe_output(chars(_,_)). 1094safe_output(current_output). 1095safe_output(current_error).
1101:- public format_calls/3. % used in pengines_io 1102 1103format_calls(Format, _Args, _Calls) :- 1104 var(Format), 1105 !, 1106 instantiation_error(Format). 1107format_calls(Format, Args, Calls) :- 1108 format_types(Format, Types), 1109 ( format_callables(Types, Args, Calls) 1110 -> true 1111 ; throw(error(format_error(Format, Types, Args), _)) 1112 ). 1113 1114format_callables([], [], []). 1115format_callables([callable|TT], [G|TA], [G|TG]) :- 1116 !, 1117 format_callables(TT, TA, TG). 1118format_callables([_|TT], [_|TA], TG) :- 1119 !, 1120 format_callables(TT, TA, TG). 1121 1122 1123 /******************************* 1124 * SAFE COMPILATION HOOKS * 1125 *******************************/ 1126 1127:- multifile 1128 prolog:sandbox_allowed_directive/1, 1129 prolog:sandbox_allowed_goal/1, 1130 prolog:sandbox_allowed_expansion/1.
1136prologsandbox_allowed_directive(Directive) :- 1137 debug(sandbox(directive), 'Directive: ~p', [Directive]), 1138 fail. 1139prologsandbox_allowed_directive(Directive) :- 1140 safe_directive(Directive), 1141 !. 1142prologsandbox_allowed_directive(M:PredAttr) :- 1143 \+ prolog_load_context(module, M), 1144 !, 1145 debug(sandbox(directive), 'Cross-module directive', []), 1146 permission_error(execute, sandboxed_directive, (:- M:PredAttr)). 1147prologsandbox_allowed_directive(M:PredAttr) :- 1148 safe_pattr(PredAttr), 1149 !, 1150 PredAttr =.. [Attr, Preds], 1151 ( safe_pattr(Preds, Attr) 1152 -> true 1153 ; permission_error(execute, sandboxed_directive, (:- M:PredAttr)) 1154 ). 1155prologsandbox_allowed_directive(_:Directive) :- 1156 safe_source_directive(Directive), 1157 !. 1158prologsandbox_allowed_directive(_:Directive) :- 1159 directive_loads_file(Directive, File), 1160 !, 1161 safe_path(File). 1162prologsandbox_allowed_directive(G) :- 1163 safe_goal(G).
Module:Directive
(without :-
wrapper). In almost all
cases, the implementation must verify that the Module is the
current load context as illustrated below. This check is not
performed by the system to allow for cases where particular
cross-module directives are allowed.
sandbox:safe_directive(M:Directive) :- prolog_load_context(module, M), ...
1181safe_pattr(dynamic(_)). 1182safe_pattr(thread_local(_)). 1183safe_pattr(volatile(_)). 1184safe_pattr(discontiguous(_)). 1185safe_pattr(multifile(_)). 1186safe_pattr(public(_)). 1187safe_pattr(meta_predicate(_)). 1188safe_pattr(table(_)). 1189safe_pattr(non_terminal(_)). 1190 1191safe_pattr(Var, _) :- 1192 var(Var), 1193 !, 1194 instantiation_error(Var). 1195safe_pattr((A,B), Attr) :- 1196 !, 1197 safe_pattr(A, Attr), 1198 safe_pattr(B, Attr). 1199safe_pattr(M:G, Attr) :- 1200 !, 1201 ( atom(M), 1202 prolog_load_context(module, M) 1203 -> true 1204 ; Goal =.. [Attr,M:G], 1205 permission_error(directive, sandboxed, (:- Goal)) 1206 ). 1207safe_pattr(_, _). 1208 1209safe_source_directive(op(_,_,Name)) :- 1210 !, 1211 ( atom(Name) 1212 -> true 1213 ; is_list(Name), 1214 maplist(atom, Name) 1215 ). 1216safe_source_directive(set_prolog_flag(Flag, Value)) :- 1217 !, 1218 atom(Flag), ground(Value), 1219 safe_prolog_flag(Flag, Value). 1220safe_source_directive(style_check(_)). 1221safe_source_directive(initialization(_)). % Checked at runtime 1222safe_source_directive(initialization(_,_)). % Checked at runtime 1223 1224directive_loads_file(use_module(library(X)), X). 1225directive_loads_file(use_module(library(X), _Imports), X). 1226directive_loads_file(load_files(library(X), _Options), X). 1227directive_loads_file(ensure_loaded(library(X)), X). 1228directive_loads_file(include(X), X). 1229 1230safe_path(X) :- 1231 var(X), 1232 !, 1233 instantiation_error(X). 1234safe_path(X) :- 1235 ( atom(X) 1236 ; string(X) 1237 ), 1238 !, 1239 \+ sub_atom(X, 0, _, 0, '..'), 1240 \+ sub_atom(X, 0, _, _, '/'), 1241 \+ sub_atom(X, 0, _, _, '../'), 1242 \+ sub_atom(X, _, _, 0, '/..'), 1243 \+ sub_atom(X, _, _, _, '/../'). 1244safe_path(A/B) :- 1245 !, 1246 safe_path(A), 1247 safe_path(B).
1259% misc 1260safe_prolog_flag(generate_debug_info, _). 1261safe_prolog_flag(optimise, _). 1262safe_prolog_flag(occurs_check, _). 1263% syntax 1264safe_prolog_flag(var_prefix, _). 1265safe_prolog_flag(double_quotes, _). 1266safe_prolog_flag(back_quotes, _). 1267safe_prolog_flag(rational_syntax, _). 1268% arithmetic 1269safe_prolog_flag(prefer_rationals, _). 1270safe_prolog_flag(float_overflow, _). 1271safe_prolog_flag(float_zero_div, _). 1272safe_prolog_flag(float_undefined, _). 1273safe_prolog_flag(float_underflow, _). 1274safe_prolog_flag(float_rounding, _). 1275safe_prolog_flag(float_rounding, _). 1276safe_prolog_flag(max_rational_size, _). 1277safe_prolog_flag(max_rational_size_action, _). 1278% tabling 1279safe_prolog_flag(max_answers_for_subgoal,_). 1280safe_prolog_flag(max_answers_for_subgoal_action,_). 1281safe_prolog_flag(max_table_answer_size,_). 1282safe_prolog_flag(max_table_answer_size_action,_). 1283safe_prolog_flag(max_table_subgoal_size,_). 1284safe_prolog_flag(max_table_subgoal_size_action,_).
Our assumption is that external expansion rules are coded safely and we only need to be careful if the sandboxed code defines expansion rules.
1300prologsandbox_allowed_expansion(M:G) :- 1301 prolog_load_context(module, M), 1302 !, 1303 debug(sandbox(expansion), 'Expand in ~p: ~p', [M, G]), 1304 safe_goal(M:G). 1305prologsandbox_allowed_expansion(_,_).
1311prologsandbox_allowed_goal(G) :- 1312 safe_goal(G). 1313 1314 1315 /******************************* 1316 * MESSAGES * 1317 *******************************/ 1318 1319:- multifile 1320 prolog:message//1, 1321 prolog:message_context//1, 1322 prolog:error_message//1. 1323 1324prologmessage(error(instantiation_error, Context)) --> 1325 { nonvar(Context), 1326 Context = sandbox(_Goal,Parents), 1327 numbervars(Context, 1, _) 1328 }, 1329 [ 'Sandbox restriction!'-[], nl, 1330 'Could not derive which predicate may be called from'-[] 1331 ], 1332 ( { Parents == [] } 1333 -> [ 'Search space too large'-[] ] 1334 ; callers(Parents, 10) 1335 ). 1336 1337prologmessage_context(sandbox(_G, [])) --> !. 1338prologmessage_context(sandbox(_G, Parents)) --> 1339 [ nl, 'Reachable from:'-[] ], 1340 callers(Parents, 10). 1341 1342callers([], _) --> !. 1343callers(_, 0) --> !. 1344callers([G|Parents], Level) --> 1345 { NextLevel is Level-1 1346 }, 1347 [ nl, '\t ~p'-[G] ], 1348 callers(Parents, NextLevel). 1349 1350prologmessage(bad_safe_declaration(Goal, File, Line)) --> 1351 [ '~w:~d: Invalid safe_primitive/1 declaration: ~p'- 1352 [File, Line, Goal] ]. 1353 1354prologerror_message(format_error(Format, Types, Args)) --> 1355 format_error(Format, Types, Args). 1356 1357format_error(Format, Types, Args) --> 1358 { length(Types, TypeLen), 1359 length(Args, ArgsLen), 1360 ( TypeLen > ArgsLen 1361 -> Problem = 'not enough' 1362 ; Problem = 'too many' 1363 ) 1364 }, 1365 [ 'format(~q): ~w arguments (found ~w, need ~w)'- 1366 [Format, Problem, ArgsLen, TypeLen] 1367 ]
Sandboxed Prolog code
Prolog is a full-featured Turing complete programming language in which it is easy to write programs that can harm your computer. On the other hand, Prolog is a logic based query language which can be exploited to query data interactively from, e.g., the web. This library provides safe_goal/1, which determines whether it is safe to call its argument.