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-2023, 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. 572safe_primitive(system:current_arithmetic_function(_)). 573safe_primitive(system:bounded_number(_,_,_)). 574safe_primitive(system:float_class(_,_)). 575safe_primitive(system:float_parts(_,_,_,_)). 576 577 % term-handling 578safe_primitive(arg(_,_,_)). 579safe_primitive(system:setarg(_,_,_)). 580safe_primitive(system:nb_setarg(_,_,_)). 581safe_primitive(system:nb_linkarg(_,_,_)). 582safe_primitive(functor(_,_,_)). 583safe_primitive(system:functor(_,_,_,_)). 584safe_primitive(_ =.. _). 585safe_primitive(system:compound_name_arity(_,_,_)). 586safe_primitive(system:compound_name_arguments(_,_,_)). 587safe_primitive(system:'$filled_array'(_,_,_,_)). 588safe_primitive(copy_term(_,_)). 589safe_primitive(system:copy_term(_,_,_,_)). 590safe_primitive(system:duplicate_term(_,_)). 591safe_primitive(system:copy_term_nat(_,_)). 592safe_primitive(system:size_abstract_term(_,_,_)). 593safe_primitive(numbervars(_,_,_)). 594safe_primitive(system:numbervars(_,_,_,_)). 595safe_primitive(subsumes_term(_,_)). 596safe_primitive(system:term_hash(_,_)). 597safe_primitive(system:term_hash(_,_,_,_)). 598safe_primitive(system:variant_sha1(_,_)). 599safe_primitive(system:variant_hash(_,_)). 600safe_primitive(system:'$term_size'(_,_,_)). 601 602 % dicts 603safe_primitive(system:is_dict(_)). 604safe_primitive(system:is_dict(_,_)). 605safe_primitive(system:get_dict(_,_,_)). 606safe_primitive(system:get_dict(_,_,_,_,_)). 607safe_primitive(system:'$get_dict_ex'(_,_,_)). 608safe_primitive(system:dict_create(_,_,_)). 609safe_primitive(system:dict_pairs(_,_,_)). 610safe_primitive(system:put_dict(_,_,_)). 611safe_primitive(system:put_dict(_,_,_,_)). 612safe_primitive(system:del_dict(_,_,_,_)). 613safe_primitive(system:select_dict(_,_,_)). 614safe_primitive(system:b_set_dict(_,_,_)). 615safe_primitive(system:nb_set_dict(_,_,_)). 616safe_primitive(system:nb_link_dict(_,_,_)). 617safe_primitive(system:(:<(_,_))). 618safe_primitive(system:(>:<(_,_))). 619 % atoms 620safe_primitive(atom_chars(_, _)). 621safe_primitive(atom_codes(_, _)). 622safe_primitive(sub_atom(_,_,_,_,_)). 623safe_primitive(atom_concat(_,_,_)). 624safe_primitive(atom_length(_,_)). 625safe_primitive(char_code(_,_)). 626safe_primitive(system:name(_,_)). 627safe_primitive(system:atomic_concat(_,_,_)). 628safe_primitive(system:atomic_list_concat(_,_)). 629safe_primitive(system:atomic_list_concat(_,_,_)). 630safe_primitive(system:downcase_atom(_,_)). 631safe_primitive(system:upcase_atom(_,_)). 632safe_primitive(system:char_type(_,_)). 633safe_primitive(system:normalize_space(_,_)). 634safe_primitive(system:sub_atom_icasechk(_,_,_)). 635 % numbers 636safe_primitive(number_codes(_,_)). 637safe_primitive(number_chars(_,_)). 638safe_primitive(system:atom_number(_,_)). 639safe_primitive(system:code_type(_,_)). 640 % strings 641safe_primitive(system:atom_string(_,_)). 642safe_primitive(system:number_string(_,_)). 643safe_primitive(system:string_chars(_, _)). 644safe_primitive(system:string_codes(_, _)). 645safe_primitive(system:string_code(_,_,_)). 646safe_primitive(system:sub_string(_,_,_,_,_)). 647safe_primitive(system:split_string(_,_,_,_)). 648safe_primitive(system:atomics_to_string(_,_,_)). 649safe_primitive(system:atomics_to_string(_,_)). 650safe_primitive(system:string_concat(_,_,_)). 651safe_primitive(system:string_length(_,_)). 652safe_primitive(system:string_lower(_,_)). 653safe_primitive(system:string_upper(_,_)). 654safe_primitive(system:term_string(_,_)). 655safe_primitive('$syspreds':term_string(_,_,_)). 656 % Lists 657safe_primitive(length(_,_)). 658 % exceptions 659safe_primitive(throw(_)). 660safe_primitive(system:abort). 661 % misc 662safe_primitive(current_prolog_flag(_,_)). 663safe_primitive(current_op(_,_,_)). 664safe_primitive(system:sleep(_)). 665safe_primitive(system:thread_self(_)). 666safe_primitive(system:get_time(_)). 667safe_primitive(system:statistics(_,_)). 668:- if(current_prolog_flag(threads,true)). 669safe_primitive(system:thread_statistics(Id,_,_)) :- 670 ( var(Id) 671 -> instantiation_error(Id) 672 ; thread_self(Id) 673 ). 674safe_primitive(system:thread_property(Id,_)) :- 675 ( var(Id) 676 -> instantiation_error(Id) 677 ; thread_self(Id) 678 ). 679:- endif. 680safe_primitive(system:format_time(_,_,_)). 681safe_primitive(system:format_time(_,_,_,_)). 682safe_primitive(system:date_time_stamp(_,_)). 683safe_primitive(system:stamp_date_time(_,_,_)). 684safe_primitive(system:strip_module(_,_,_)). 685safe_primitive('$messages':message_to_string(_,_)). 686safe_primitive(system:import_module(_,_)). 687safe_primitive(system:file_base_name(_,_)). 688safe_primitive(system:file_directory_name(_,_)). 689safe_primitive(system:file_name_extension(_,_,_)). 690 691safe_primitive(clause(H,_)) :- safe_clause(H). 692safe_primitive(asserta(X)) :- safe_assert(X). 693safe_primitive(assertz(X)) :- safe_assert(X). 694safe_primitive(retract(X)) :- safe_assert(X). 695safe_primitive(retractall(X)) :- safe_assert(X). 696safe_primitive('$dcg':dcg_translate_rule(_,_)). 697safe_primitive('$syspreds':predicate_property(Pred, _)) :- 698 nonvar(Pred), 699 Pred \= (_:_). 700 701% We need to do data flow analysis to find the tag of the 702% target key before we can conclude that functions on dicts 703% are safe. 704safe_primitive('$dicts':'.'(_,K,_)) :- atom(K). 705safe_primitive('$dicts':'.'(_,K,_)) :- 706 ( nonvar(K) 707 -> dict_built_in(K) 708 ; instantiation_error(K) 709 ). 710 711dict_built_in(get(_)). 712dict_built_in(put(_)). 713dict_built_in(put(_,_)). 714 715% The non-ISO system predicates. These can be redefined, so we must 716% be careful to ensure the system ones are used. 717 718safe_primitive(system:false). 719safe_primitive(system:cyclic_term(_)). 720safe_primitive(system:msort(_,_)). 721safe_primitive(system:sort(_,_,_,_)). 722safe_primitive(system:between(_,_,_)). 723safe_primitive(system:succ(_,_)). 724safe_primitive(system:plus(_,_,_)). 725safe_primitive(system:float_class(_,_)). 726safe_primitive(system:term_variables(_,_)). 727safe_primitive(system:term_variables(_,_,_)). 728safe_primitive(system:'$term_size'(_,_,_)). 729safe_primitive(system:atom_to_term(_,_,_)). 730safe_primitive(system:term_to_atom(_,_)). 731safe_primitive(system:atomic_list_concat(_,_,_)). 732safe_primitive(system:atomic_list_concat(_,_)). 733safe_primitive(system:downcase_atom(_,_)). 734safe_primitive(system:upcase_atom(_,_)). 735safe_primitive(system:is_list(_)). 736safe_primitive(system:memberchk(_,_)). 737safe_primitive(system:'$skip_list'(_,_,_)). 738safe_primitive(system:'$seek_list'(_, _, _, _)). 739 % attributes 740safe_primitive(system:get_attr(_,_,_)). 741safe_primitive(system:get_attrs(_,_)). 742safe_primitive(system:term_attvars(_,_)). 743safe_primitive(system:del_attr(_,_)). 744safe_primitive(system:del_attrs(_)). 745safe_primitive('$attvar':copy_term(_,_,_)). 746 % globals 747safe_primitive(system:b_getval(_,_)). 748safe_primitive(system:b_setval(Var,_)) :- 749 safe_global_var(Var). 750safe_primitive(system:nb_getval(_,_)). 751safe_primitive('$syspreds':nb_setval(Var,_)) :- 752 safe_global_var(Var). 753safe_primitive(system:nb_linkval(Var,_)) :- 754 safe_global_var(Var). 755safe_primitive(system:nb_current(_,_)). 756 % database 757safe_primitive(system:assert(X)) :- 758 safe_assert(X). 759 % Output 760safe_primitive(system:writeln(_)). 761safe_primitive('$messages':print_message(_,_)). 762 763 % Stack limits (down) 764safe_primitive('$syspreds':set_prolog_stack(Stack, limit(ByteExpr))) :- 765 nonvar(Stack), 766 stack_name(Stack), 767 catch(Bytes is ByteExpr, _, fail), 768 prolog_stack_property(Stack, limit(Current)), 769 Bytes =< Current. 770 771stack_name(global). 772stack_name(local). 773stack_name(trail). 774 775safe_primitive('$tabling':abolish_all_tables). 776safe_primitive('$tabling':'$wrap_tabled'(Module:_Head, _Mode)) :- 777 prolog_load_context(module, Module), 778 !. 779safe_primitive('$tabling':'$moded_wrap_tabled'(Module:_Head,_,_,_,_)) :- 780 prolog_load_context(module, Module), 781 !. 782 783 784% use_module/1. We only allow for .pl files that are loaded from 785% relative paths that do not contain /../ 786 787safe_primitive(system:use_module(Spec, _Import)) :- 788 safe_primitive(system:use_module(Spec)). 789safe_primitive(system:load_files(Spec, Options)) :- 790 safe_primitive(system:use_module(Spec)), 791 maplist(safe_load_file_option, Options). 792safe_primitive(system:use_module(Spec)) :- 793 ground(Spec), 794 ( atom(Spec) 795 -> Path = Spec 796 ; Spec =.. [_Alias, Segments], 797 phrase(segments_to_path(Segments), List), 798 atomic_list_concat(List, Path) 799 ), 800 \+ is_absolute_file_name(Path), 801 \+ sub_atom(Path, _, _, _, '/../'), 802 absolute_file_name(Spec, AbsFile, 803 [ access(read), 804 file_type(prolog), 805 file_errors(fail) 806 ]), 807 file_name_extension(_, Ext, AbsFile), 808 save_extension(Ext). 809 810% support predicates for safe_primitive, validating the safety of 811% arguments to certain goals. 812 813segments_to_path(A/B) --> 814 !, 815 segments_to_path(A), 816 [/], 817 segments_to_path(B). 818segments_to_path(X) --> 819 [X]. 820 821save_extension(pl). 822 823safe_load_file_option(if(changed)). 824safe_load_file_option(if(not_loaded)). 825safe_load_file_option(must_be_module(_)). 826safe_load_file_option(optimise(_)). 827safe_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.836safe_assert(C) :- cyclic_term(C), !, fail. 837safe_assert(X) :- var(X), !, fail. 838safe_assert(_Head:-_Body) :- !, fail. 839safe_assert(_:_) :- !, fail. 840safe_assert(_).
848safe_clause(H) :- var(H), !. 849safe_clause(_:_) :- !, fail. 850safe_clause(_).
858safe_global_var(Name) :- 859 var(Name), 860 !, 861 instantiation_error(Name). 862safe_global_var(Name) :- 863 safe_global_variable(Name).
875safe_meta(system:put_attr(V,M,A), Called) :- 876 !, 877 ( atom(M) 878 -> attr_hook_predicates([ attr_unify_hook(A, _), 879 attribute_goals(V,_,_), 880 project_attributes(_,_) 881 ], M, Called) 882 ; instantiation_error(M) 883 ). 884safe_meta(system:with_output_to(Output, G), [G]) :- 885 safe_output(Output), 886 !. 887safe_meta(system:format(Format, Args), Calls) :- 888 format_calls(Format, Args, Calls). 889safe_meta(system:format(Output, Format, Args), Calls) :- 890 safe_output(Output), 891 format_calls(Format, Args, Calls). 892safe_meta(prolog_debug:debug(_Term, Format, Args), Calls) :- 893 format_calls(Format, Args, Calls). 894safe_meta(system:set_prolog_flag(Flag, Value), []) :- 895 atom(Flag), 896 safe_prolog_flag(Flag, Value). 897safe_meta('$attvar':freeze(_Var,Goal), [Goal]). 898safe_meta(phrase(NT,Xs0,Xs), [Goal]) :- % phrase/2,3 and call_dcg/2,3 899 expand_nt(NT,Xs0,Xs,Goal). 900safe_meta(phrase(NT,Xs0), [Goal]) :- 901 expand_nt(NT,Xs0,[],Goal). 902safe_meta('$dcg':call_dcg(NT,Xs0,Xs), [Goal]) :- 903 expand_nt(NT,Xs0,Xs,Goal). 904safe_meta('$dcg':call_dcg(NT,Xs0), [Goal]) :- 905 expand_nt(NT,Xs0,[],Goal). 906safe_meta('$tabling':abolish_table_subgoals(V), []) :- 907 \+ qualified(V). 908safe_meta('$tabling':current_table(V, _), []) :- 909 \+ qualified(V). 910safe_meta('$tabling':tnot(G), [G]). 911safe_meta('$tabling':not_exists(G), [G]). 912 913qualified(V) :- 914 nonvar(V), 915 V = _:_.
925attr_hook_predicates([], _, []). 926attr_hook_predicates([H|T], M, Called) :- 927 ( predicate_property(M:H, defined) 928 -> Called = [M:H|Rest] 929 ; Called = Rest 930 ), 931 attr_hook_predicates(T, M, Rest).
939expand_nt(NT, _Xs0, _Xs, _NewGoal) :- 940 strip_module(NT, _, Plain), 941 var(Plain), 942 !, 943 instantiation_error(Plain). 944expand_nt(NT, Xs0, Xs, NewGoal) :- 945 dcg_translate_rule((pseudo_nt --> NT), 946 (pseudo_nt(Xs0c,Xsc) :- NewGoal0)), 947 ( var(Xsc), Xsc \== Xs0c 948 -> Xs = Xsc, NewGoal1 = NewGoal0 949 ; NewGoal1 = (NewGoal0, Xsc = Xs) 950 ), 951 ( var(Xs0c) 952 -> Xs0 = Xs0c, 953 NewGoal = NewGoal1 954 ; NewGoal = ( Xs0 = Xs0c, NewGoal1 ) 955 ).
962safe_meta_call(Goal, _, _Called) :- 963 debug(sandbox(meta), 'Safe meta ~p?', [Goal]), 964 fail. 965safe_meta_call(Goal, Context, Called) :- 966 ( safe_meta(Goal, Called) 967 -> true 968 ; safe_meta(Goal, Context, Called) 969 ), 970 !. % call hook 971safe_meta_call(Goal, _, Called) :- 972 Goal = M:Plain, 973 compound(Plain), 974 compound_name_arity(Plain, Name, Arity), 975 safe_meta_predicate(M:Name/Arity), 976 predicate_property(Goal, meta_predicate(Spec)), 977 !, 978 called(Spec, Plain, Called). 979safe_meta_call(M:Goal, _, Called) :- 980 !, 981 generic_goal(Goal, Gen), 982 safe_meta(M:Gen), 983 called(Gen, Goal, Called). 984safe_meta_call(Goal, _, Called) :- 985 generic_goal(Goal, Gen), 986 safe_meta(Gen), 987 called(Gen, Goal, Called). 988 989called(Gen, Goal, Called) :- 990 compound_name_arity(Goal, _, Arity), 991 called(1, Arity, Gen, Goal, Called). 992 993called(I, Arity, Gen, Goal, Called) :- 994 I =< Arity, 995 !, 996 arg(I, Gen, Spec), 997 ( calling_meta_spec(Spec) 998 -> arg(I, Goal, Called0), 999 extend(Spec, Called0, G), 1000 Called = [G|Rest] 1001 ; Called = Rest 1002 ), 1003 I2 is I+1, 1004 called(I2, Arity, Gen, Goal, Rest). 1005called(_, _, _, _, []). 1006 1007generic_goal(G, Gen) :- 1008 functor(G, Name, Arity), 1009 functor(Gen, Name, Arity). 1010 1011calling_meta_spec(V) :- var(V), !, fail. 1012calling_meta_spec(I) :- integer(I), !. 1013calling_meta_spec(^). 1014calling_meta_spec(//). 1015 1016 1017extend(^, G, Plain) :- 1018 !, 1019 strip_existential(G, Plain). 1020extend(//, DCG, Goal) :- 1021 !, 1022 ( expand_phrase(call_dcg(DCG,_,_), Goal) 1023 -> true 1024 ; instantiation_error(DCG) % Ask more instantiation. 1025 ). % might not help, but does not harm. 1026extend(0, G, G) :- !. 1027extend(I, M:G0, M:G) :- 1028 !, 1029 G0 =.. List, 1030 length(Extra, I), 1031 append(List, Extra, All), 1032 G =.. All. 1033extend(I, G0, G) :- 1034 G0 =.. List, 1035 length(Extra, I), 1036 append(List, Extra, All), 1037 G =.. All. 1038 1039strip_existential(Var, Var) :- 1040 var(Var), 1041 !. 1042strip_existential(M:G0, M:G) :- 1043 !, 1044 strip_existential(G0, G). 1045strip_existential(_^G0, G) :- 1046 !, 1047 strip_existential(G0, G). 1048strip_existential(G, G).
1052safe_meta((0,0)). 1053safe_meta((0;0)). 1054safe_meta((0->0)). 1055safe_meta(system:(0*->0)). 1056safe_meta(catch(0,*,0)). 1057safe_meta(findall(*,0,*)). 1058safe_meta('$bags':findall(*,0,*,*)). 1059safe_meta(setof(*,^,*)). 1060safe_meta(bagof(*,^,*)). 1061safe_meta('$bags':findnsols(*,*,0,*)). 1062safe_meta('$bags':findnsols(*,*,0,*,*)). 1063safe_meta(system:call_cleanup(0,0)). 1064safe_meta(system:setup_call_cleanup(0,0,0)). 1065safe_meta(system:setup_call_catcher_cleanup(0,0,*,0)). 1066safe_meta('$attvar':call_residue_vars(0,*)). 1067safe_meta('$syspreds':call_with_inference_limit(0,*,*)). 1068safe_meta('$syspreds':call_with_depth_limit(0,*,*)). 1069safe_meta('$syspreds':undo(0)). 1070safe_meta(^(*,0)). 1071safe_meta(\+(0)). 1072safe_meta(call(0)). 1073safe_meta(call(1,*)). 1074safe_meta(call(2,*,*)). 1075safe_meta(call(3,*,*,*)). 1076safe_meta(call(4,*,*,*,*)). 1077safe_meta(call(5,*,*,*,*,*)). 1078safe_meta(call(6,*,*,*,*,*,*)). 1079safe_meta('$tabling':start_tabling(*,0)). 1080safe_meta('$tabling':start_tabling(*,0,*,*)). 1081safe_meta(wfs:call_delays(0,*)).
1088safe_output(Output) :- 1089 var(Output), 1090 !, 1091 instantiation_error(Output). 1092safe_output(atom(_)). 1093safe_output(string(_)). 1094safe_output(codes(_)). 1095safe_output(codes(_,_)). 1096safe_output(chars(_)). 1097safe_output(chars(_,_)). 1098safe_output(current_output). 1099safe_output(current_error).
1105:- public format_calls/3. % used in pengines_io 1106 1107format_calls(Format, Args, Calls) :- 1108 is_list(Args), 1109 !, 1110 format_types(Format, Types), 1111 ( format_callables(Types, Args, Calls) 1112 -> true 1113 ; throw(error(format_error(Format, Types, Args), _)) 1114 ). 1115format_calls(Format, Arg, Calls) :- 1116 format_calls(Format, [Arg], Calls). 1117 1118format_callables([], [], []). 1119format_callables([callable|TT], [G|TA], [G|TG]) :- 1120 !, 1121 format_callables(TT, TA, TG). 1122format_callables([_|TT], [_|TA], TG) :- 1123 !, 1124 format_callables(TT, TA, TG). 1125 1126 1127 /******************************* 1128 * SAFE COMPILATION HOOKS * 1129 *******************************/ 1130 1131:- multifile 1132 prolog:sandbox_allowed_directive/1, 1133 prolog:sandbox_allowed_goal/1, 1134 prolog:sandbox_allowed_expansion/1.
1140prologsandbox_allowed_directive(Directive) :- 1141 debug(sandbox(directive), 'Directive: ~p', [Directive]), 1142 fail. 1143prologsandbox_allowed_directive(Directive) :- 1144 safe_directive(Directive), 1145 !. 1146prologsandbox_allowed_directive(M:PredAttr) :- 1147 \+ prolog_load_context(module, M), 1148 !, 1149 debug(sandbox(directive), 'Cross-module directive', []), 1150 permission_error(execute, sandboxed_directive, (:- M:PredAttr)). 1151prologsandbox_allowed_directive(M:PredAttr) :- 1152 safe_pattr(PredAttr), 1153 !, 1154 PredAttr =.. [Attr, Preds], 1155 ( safe_pattr(Preds, Attr) 1156 -> true 1157 ; permission_error(execute, sandboxed_directive, (:- M:PredAttr)) 1158 ). 1159prologsandbox_allowed_directive(_:Directive) :- 1160 safe_source_directive(Directive), 1161 !. 1162prologsandbox_allowed_directive(_:Directive) :- 1163 directive_loads_file(Directive, File), 1164 !, 1165 safe_path(File). 1166prologsandbox_allowed_directive(G) :- 1167 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), ...
1185safe_pattr(dynamic(_)). 1186safe_pattr(thread_local(_)). 1187safe_pattr(volatile(_)). 1188safe_pattr(discontiguous(_)). 1189safe_pattr(multifile(_)). 1190safe_pattr(public(_)). 1191safe_pattr(meta_predicate(_)). 1192safe_pattr(table(_)). 1193safe_pattr(non_terminal(_)). 1194 1195safe_pattr(Var, _) :- 1196 var(Var), 1197 !, 1198 instantiation_error(Var). 1199safe_pattr((A,B), Attr) :- 1200 !, 1201 safe_pattr(A, Attr), 1202 safe_pattr(B, Attr). 1203safe_pattr(M:G, Attr) :- 1204 !, 1205 ( atom(M), 1206 prolog_load_context(module, M) 1207 -> true 1208 ; Goal =.. [Attr,M:G], 1209 permission_error(directive, sandboxed, (:- Goal)) 1210 ). 1211safe_pattr(_, _). 1212 1213safe_source_directive(op(_,_,Name)) :- 1214 !, 1215 ( atom(Name) 1216 -> true 1217 ; is_list(Name), 1218 maplist(atom, Name) 1219 ). 1220safe_source_directive(set_prolog_flag(Flag, Value)) :- 1221 !, 1222 atom(Flag), ground(Value), 1223 safe_prolog_flag(Flag, Value). 1224safe_source_directive(style_check(_)). 1225safe_source_directive(initialization(_)). % Checked at runtime 1226safe_source_directive(initialization(_,_)). % Checked at runtime 1227 1228directive_loads_file(use_module(library(X)), X). 1229directive_loads_file(use_module(library(X), _Imports), X). 1230directive_loads_file(load_files(library(X), _Options), X). 1231directive_loads_file(ensure_loaded(library(X)), X). 1232directive_loads_file(include(X), X). 1233 1234safe_path(X) :- 1235 var(X), 1236 !, 1237 instantiation_error(X). 1238safe_path(X) :- 1239 ( atom(X) 1240 ; string(X) 1241 ), 1242 !, 1243 \+ sub_atom(X, 0, _, 0, '..'), 1244 \+ sub_atom(X, 0, _, _, '/'), 1245 \+ sub_atom(X, 0, _, _, '../'), 1246 \+ sub_atom(X, _, _, 0, '/..'), 1247 \+ sub_atom(X, _, _, _, '/../'). 1248safe_path(A/B) :- 1249 !, 1250 safe_path(A), 1251 safe_path(B).
1263% misc 1264safe_prolog_flag(generate_debug_info, _). 1265safe_prolog_flag(optimise, _). 1266safe_prolog_flag(occurs_check, _). 1267safe_prolog_flag(write_attributes, _). 1268% syntax 1269safe_prolog_flag(var_prefix, _). 1270safe_prolog_flag(double_quotes, _). 1271safe_prolog_flag(back_quotes, _). 1272safe_prolog_flag(rational_syntax, _). 1273% arithmetic 1274safe_prolog_flag(prefer_rationals, _). 1275safe_prolog_flag(float_overflow, _). 1276safe_prolog_flag(float_zero_div, _). 1277safe_prolog_flag(float_undefined, _). 1278safe_prolog_flag(float_underflow, _). 1279safe_prolog_flag(float_rounding, _). 1280safe_prolog_flag(float_rounding, _). 1281safe_prolog_flag(max_rational_size, _). 1282safe_prolog_flag(max_rational_size_action, _). 1283% tabling 1284safe_prolog_flag(max_answers_for_subgoal,_). 1285safe_prolog_flag(max_answers_for_subgoal_action,_). 1286safe_prolog_flag(max_table_answer_size,_). 1287safe_prolog_flag(max_table_answer_size_action,_). 1288safe_prolog_flag(max_table_subgoal_size,_). 1289safe_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.
1305prologsandbox_allowed_expansion(M:G) :- 1306 prolog_load_context(module, M), 1307 !, 1308 debug(sandbox(expansion), 'Expand in ~p: ~p', [M, G]), 1309 safe_goal(M:G). 1310prologsandbox_allowed_expansion(_,_).
1316prologsandbox_allowed_goal(G) :- 1317 safe_goal(G). 1318 1319 1320 /******************************* 1321 * MESSAGES * 1322 *******************************/ 1323 1324:- multifile 1325 prolog:message//1, 1326 prolog:message_context//1, 1327 prolog:error_message//1. 1328 1329prologmessage(error(instantiation_error, Context)) --> 1330 { nonvar(Context), 1331 Context = sandbox(_Goal,Parents), 1332 numbervars(Context, 1, _) 1333 }, 1334 [ 'Sandbox restriction!'-[], nl, 1335 'Could not derive which predicate may be called from'-[] 1336 ], 1337 ( { Parents == [] } 1338 -> [ 'Search space too large'-[] ] 1339 ; callers(Parents, 10) 1340 ). 1341 1342prologmessage_context(sandbox(_G, [])) --> !. 1343prologmessage_context(sandbox(_G, Parents)) --> 1344 [ nl, 'Reachable from:'-[] ], 1345 callers(Parents, 10). 1346 1347callers([], _) --> !. 1348callers(_, 0) --> !. 1349callers([G|Parents], Level) --> 1350 { NextLevel is Level-1 1351 }, 1352 [ nl, '\t ~p'-[G] ], 1353 callers(Parents, NextLevel). 1354 1355prologmessage(bad_safe_declaration(Goal, File, Line)) --> 1356 [ '~w:~d: Invalid safe_primitive/1 declaration: ~p'- 1357 [File, Line, Goal] ]. 1358 1359prologerror_message(format_error(Format, Types, Args)) --> 1360 format_error(Format, Types, Args). 1361 1362format_error(Format, Types, Args) --> 1363 { length(Types, TypeLen), 1364 length(Args, ArgsLen), 1365 ( TypeLen > ArgsLen 1366 -> Problem = 'not enough' 1367 ; Problem = 'too many' 1368 ) 1369 }, 1370 [ 'format(~q): ~w arguments (found ~w, need ~w)'- 1371 [Format, Problem, ArgsLen, TypeLen] 1372 ]
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.