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) 2010-2024, University of Amsterdam 7 SWI-Prolog Solutions b.v. 8 All rights reserved. 9 10 Redistribution and use in source and binary forms, with or without 11 modification, are permitted provided that the following conditions 12 are met: 13 14 1. Redistributions of source code must retain the above copyright 15 notice, this list of conditions and the following disclaimer. 16 17 2. Redistributions in binary form must reproduce the above copyright 18 notice, this list of conditions and the following disclaimer in 19 the documentation and/or other materials provided with the 20 distribution. 21 22 THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS 23 "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT 24 LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS 25 FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE 26 COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, 27 INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, 28 BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; 29 LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER 30 CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT 31 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN 32 ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE 33 POSSIBILITY OF SUCH DAMAGE. 34*/ 35 36:- module(block_directive, 37 [ (block)/1, % +Heads 38 op(1150, fx, (block)) 39 ]). 40:- use_module(library(prolog_wrap), []). % make sure it is loaded 41:- autoload(library(error), [instantiation_error/1, domain_error/2]). 42:- autoload(library(lists), [append/3]).
53:- op(1150, fx, user:(block)). 54 55:- multifile 56 user:term_expansion/2, 57 block_declaration/2. % Head, Module 58 59head(Var, _) :- 60 var(Var), !, fail. 61head((H:-_B), Head) :- 62 !, 63 head(H, Head). 64head(H, Head) :- 65 ( H = _:_ 66 -> Head = H 67 ; prolog_load_context(module, M), 68 Head = M:H 69 ).
true
. A
blockspec evaluated to true
iff all arguments specified as `-' are
unbound.
Multiple BlockSpecs for a single predicate can appear in one or more
:- block
declarations. The predicate is suspended untill all mode
patterns that apply to it are satisfied.
The implementation is realised by creating a wrapper that checks the block conditions and either calls the original predicate immediately (if none of the block conditions were true) or uses attributed variables to delay re-evaluating the block condition until any of the arguments in question are bound.
93block(Spec) :- 94 throw(error(context_error(nodirective, block(Spec)), _)). 95 96expand_block_declaration(Spec, Clauses) :- 97 prolog_load_context(module, Module), 98 phrase(expand_specs(Spec, Module), Clauses). 99 100expand_specs(Var, _) --> 101 { var(Var), 102 !, 103 instantiation_error(Var) 104 }. 105expand_specs(M:Spec, _) --> 106 !, 107 expand_specs(Spec, M). 108expand_specs((A,B), Module) --> 109 !, 110 expand_specs(A, Module), 111 expand_specs(B, Module). 112expand_specs(Head, Module) --> 113 { valid_head(Head), 114 functor(Head, Name, Arity), 115 functor(GenHead, Name, Arity), 116 Clause = '$block_pred'(Head) 117 }, 118 ( { current_predicate(Module:'$block_pred'/1) } 119 -> [] 120 ; [ (:- discontiguous('$block_pred'/1)), 121 (:- public('$block_pred'/1)) 122 ] 123 ), 124 ( { prolog_load_context(module, Module) } 125 -> [ Clause ] 126 ; [ Module:Clause ] 127 ), 128 [ block_directive:block_declaration(GenHead, Module) ]. 129 130valid_head(Head) :- 131 callable(Head), 132 forall(arg(_, Head, A), block_arg(A)). 133 134block_arg(A) :- 135 var(A), 136 !, 137 instantiation_error(A). 138block_arg(-) :- !. 139block_arg(+) :- !. 140block_arg(?) :- !. 141block_arg(A) :- 142 domain_error(block_argument, A).
150block_wrapper_clauses(Module, Head, Clauses) :-
151 functor(Head, Name, Arity),
152 atom_concat('$block_helper$', Name, HelperName),
153 functor(HelperHead, HelperName, Arity),
154 ( current_predicate(_, Module:HelperHead)
155 -> Clauses = []
156 ; findall(Wrapper,
157 block_wrapper_clause(Module, Name, HelperHead, Wrapper),
158 Clauses)
159 ).
-
, so that once any of them are bound, the
predicate is called again and the block conditions are re-evaluated.
If no block condition was true, the helper predicate fails.
Finally, an initialization clause is generated that sets up the actual wrapper. This wrapper first calls the helper predicate to check all block conditions and delay the call if necessary. If the helper predicate fails (i. e. no block condition was true), the wrapped predicate is called immediately.
The wrapper must be set up in an initialization clause and not as part of the term expansion, because wrap_predicate/4 wrappers are not retained in saved states, which would cause block declarations to break when loading a saved state.
181block_wrapper_clause(Module, Name, HelperHead, (HelperHead :- GenBody)) :- 182 HelperHead =.. [_|HelperArgs], 183 length(HelperArgs, Arity), 184 functor(BlockHead, Name, Arity), 185 Module:'$block_pred'(BlockHead), 186 BlockHead =.. [_|BlockArgs], 187 find_args_to_block_on(BlockArgs, HelperArgs, ToBlockOn), 188 args_to_var_conditions(ToBlockOn, GenBody, GenBody1), 189 GenBody1 = (!, GenBody2), 190 MainHead =.. [Name|HelperArgs], 191 args_to_suspend_calls(ToBlockOn, _IsAlreadyUnblocked, Module:MainHead, GenBody2, true). 192block_wrapper_clause(Module, Name, HelperHead, (:- initialization WrapCall)) :- 193 HelperHead =.. [_|HelperArgs], 194 ToWrapHead =.. [Name|HelperArgs], 195 atom_concat('$block_wrapper$', Name, WrapperName), 196 WrapCall = @(prolog_wrap:wrap_predicate(ToWrapHead, WrapperName, Wrapped, 197 (HelperHead -> true ; Wrapped)), 198 Module).
-
, indicating that
the argument is part of the block condition.206find_args_to_block_on([], [], []) :- !. 207find_args_to_block_on([-|MoreBlockArgs], [Arg|MoreHeadArgs], [Arg|MoreToBlockOn]) :- 208 !, 209 find_args_to_block_on(MoreBlockArgs, MoreHeadArgs, MoreToBlockOn). 210find_args_to_block_on([_|MoreBlockArgs], [_|MoreHeadArgs], ToBlockOn) :- 211 find_args_to_block_on(MoreBlockArgs, MoreHeadArgs, ToBlockOn).
This effectively generates an unrolled version of maplist(var,
ArgsToBlockOn), ConditionsTail
.
221args_to_var_conditions([], Tail, Tail) :- !. 222args_to_var_conditions([Arg|MoreArgs], Conditions, Tail) :- 223 Conditions = (var(Arg), MoreConditions), 224 args_to_var_conditions(MoreArgs, MoreConditions, Tail).
234args_to_suspend_calls([], _, _, Tail, Tail) :- !. 235args_to_suspend_calls([Arg|MoreArgs], IsAlreadyUnblocked, BlockedGoal, SuspendCalls, Tail) :- 236 SuspendCalls = ('$suspend'(Arg, block_directive, block_directive:unblock(IsAlreadyUnblocked, BlockedGoal)), MoreSuspendCalls), 237 args_to_suspend_calls(MoreArgs, IsAlreadyUnblocked, BlockedGoal, MoreSuspendCalls, Tail). 238 239 240attr_unify_hook(call(ThisGoals), NewVar) :- 241 var(NewVar), 242 !, 243 ( get_attr(NewVar, block_directive, call(OtherGoals)) 244 -> put_attr(NewVar, block_directive, call((ThisGoals, OtherGoals))) 245 ; put_attr(NewVar, block_directive, call(ThisGoals)) 246 ). 247attr_unify_hook(call(Goals), _) :- . 248 249:- public unblock/2. 250unblock(IsAlreadyUnblocked, _) :- IsAlreadyUnblocked == (-), !. 251unblock(-, BlockedGoal) :- . 252 253attribute_goals(Var) --> 254 {get_attr(Var, block_directive, call(Goals))}, 255 !, 256 render_block_goals(Goals). 257 258render_block_goals((Left, Right)) --> 259 render_block_goals(Left), 260 render_block_goals(Right). 261render_block_goals(block_directive:unblock(IsAlreadyUnblocked, BlockedGoal)) --> 262 ( {IsAlreadyUnblocked == (-)} 263 -> [] 264 ; [BlockedGoal] 265 ). 266 267 /******************************* 268 * EXPANSION HOOKS * 269 *******************************/ 270 271systemterm_expansion((:- block(Spec)), Clauses) :- 272 expand_block_declaration(Spec, Clauses). 273systemterm_expansion(Term, Clauses) :- 274 head(Term, Module:Head), 275 block_declaration(Head, Module), 276 block_wrapper_clauses(Module, Head, WrapperClauses), 277 append(WrapperClauses, [Term], Clauses)
Block: declare suspending predicates
This module provides SICStus Prolog-compatible
:- block BlockSpec, ...
declarations for delaying predicate calls if certain arguments are unbound.