hi so i tried Ciao, and it has a module called fsyntax, which lets you use the last argument of predicates as a “return value”
is there such a modules for SWI? would it be possible to write one?
hi so i tried Ciao, and it has a module called fsyntax, which lets you use the last argument of predicates as a “return value”
is there such a modules for SWI? would it be possible to write one?
The fsyntax looks handy. This does remind me of the func pack available for swi-prolog, but honestly the syntax and documentation is a little cryptic to me. However I think that library is suppose to provide similar functionality. The $ syntax is something I’ve seen in R as well.
For some cases a DCG could be all you need, since
chain --> first, second, third.
is literally the same as
chain(A, B) :-
first(A, C),
second(C, D),
third(D, B).
Sure. SWI-Prolog already has the Dict.Func functions and same infra structure can be reused to define other constructs that act as function. It is mainly a matter of choosing a syntax. The func pack is one. I don’t think it uses the low-level functional notation syntax support as that probably did no exist back then.
how could one do it? would it be via term_expansion/2
?
See boot/expand.pl
. It might be enough to define extra clauses for the predicate '$expand':function/2
, where the first is the term that must be interpreted as a function and the second is (I think) the module in which context the expansion takes place. So, I one could do
:- multifile '$expand':function/2.
'$expand':function($(_), _).
$(Term, Result) :- call(Term, Result).
And now this works
?- member(X, $append([1,2], [3])).
X = 1 ;
X = 2 ;
X = 3.
wow, there already is a syntax in SWI. thank you
i also noticed that :=
is already an operator. however, using it just… defines a predicate named (:=)/2
?- [user].
|: says(cat) := meow.
|: says(dog) := woof.
|: ^D% user://1 compiled 0.01 sec, 2 clauses
true.
?- says(cat, What).
ERROR: Unknown procedure: says/2 (DWIM could not correct goal)
?- :=(says(cat), What).
What = meow.
i did something… not sure how correct is this tho
functor_from_to_args(From-To, From, To, []).
functor_from_to_args(term_position(_, _, From, To, Args), From, To, Args).
fun_pos(
term_position(From, To, _, _, [HeadPos, ResultPos]),
term_position(From, To, FunctorFrom, FunctorTo, ArgsResult)
) :- functor_from_to_args(HeadPos, FunctorFrom, FunctorTo, Args), append(Args, [ResultPos], ArgsResult).
user:term_expansion(F := Result, T0, P, T1) :-
F =.. F_, append(F_, [Result], P_), P =.. P_,
( fun_pos(T0, T1) -> true ; true ).
Operators have no relation to functions/functional notation. They are just syntactic sugar, transforming e.g. 1+2 into +(1,2). + in Prolog in general does not mean addition. Only when used as argument to is/2, >/2
and similar arithmetic predicate, these predicates interpret the + as addition.
Great, together with a bunch of code gives us little option to comment What did you try to achieve and how did it (not) work?
it adds the part after :=
as an argument:
?- [user].
|: not(no) := yes.
|: not(yes) := maybe_later.
|: ^D% user://3 compiled 0.00 sec, 2 clauses
true.
?- listing(not/2).
not(no, yes).
not(yes, maybe_later).