Skip to content

Commit

Permalink
FIXED: check_predicate_options/0: avoid several false warnings.
Browse files Browse the repository at this point in the history
  • Loading branch information
JanWielemaker committed Sep 6, 2023
1 parent 7a1af96 commit fb7f860
Show file tree
Hide file tree
Showing 2 changed files with 15 additions and 5 deletions.
1 change: 1 addition & 0 deletions boot/predopts.pl
Original file line number Diff line number Diff line change
Expand Up @@ -92,6 +92,7 @@
functor(THead, Name, Arity),
Clause = ('$pred_option'(Head, pass_to(PI0, Arg), Opt, Seen) :-
\+ memberchk(PI-Arg, Seen),
ignore(predicate_property(M:THead, _)),
predicate_options:pred_option(TM:THead, Opt, [PI-Arg|Seen]))
},
[ M:Clause ].
Expand Down
19 changes: 14 additions & 5 deletions library/predicate_options.pl
Original file line number Diff line number Diff line change
Expand Up @@ -303,8 +303,8 @@
).


pred_option(M:Head, Option) :-
pred_option(M:Head, Option, []).
pred_option(Head, Option) :-
pred_option(Head, Option, []).

pred_option(M:Head, Option, Seen) :-
( has_static_option_decl(M),
Expand Down Expand Up @@ -340,13 +340,18 @@
system:predicate_option_type(callable+_N, Arg) :-
!,
must_be(callable, Arg).
system:predicate_option_type(list, Arg) :-
!,
must_be(list_or_partial_list, Arg).
system:predicate_option_type(list(Type), Arg) :-
!,
must_be(list_or_partial_list(Type), Arg).
system:predicate_option_type(Type, Arg) :-
must_be(Type, Arg).

system:predicate_option_mode(Mode, Arg) :-
system:predicate_option_mode(_Mode, Arg) :-
var(Arg),
!,
add_attr(Arg, option_mode(Mode)).
!.
system:predicate_option_mode(Mode, Arg) :-
check_mode(Mode, Arg).

Expand Down Expand Up @@ -679,6 +684,10 @@
!,
check_body(A, M, PA, Action),
check_body(B, M, PB, Action).
check_body((A;B), M, term_position(_,_,_,_,[PA,PB]), Action) :-
!,
\+ \+ check_body(A, M, PA, Action),
\+ \+ check_body(B, M, PB, Action).
check_body(A=B, _, _, _) :- % partial evaluation
unify_with_occurs_check(A,B),
!.
Expand Down

0 comments on commit fb7f860

Please sign in to comment.