34
35:- module(coinduction,
36 [ (coinductive)/1,
37 op(1150, fx, (coinductive))
38 ]). 39:- use_module(library(error)).
70:- multifile
71 system:term_expansion/2,
72 coinductive_declaration/2.
78head(Var, _) :-
79 var(Var), !, fail.
80head((H:-_B), Head) :-
81 !,
82 head(H, Head).
83head(H, Head) :-
84 ( H = _:_
85 -> Head = H
86 ; prolog_load_context(module, M),
87 Head = M:H
88 ).
97coinductive(Spec) :-
98 throw(error(context_error(nodirective, coinductive(Spec)), _)).
99
100expand_coinductive_declaration(Spec, Clauses) :-
101 prolog_load_context(module, Module),
102 phrase(expand_specs(Spec, Module), Clauses).
103
104expand_specs(Var, _) -->
105 { var(Var),
106 !,
107 instantiation_error(Var)
108 }.
109expand_specs(M:Spec, _) -->
110 !,
111 expand_specs(Spec, M).
112expand_specs((A,B), Module) -->
113 !,
114 expand_specs(A, Module),
115 expand_specs(B, Module).
116expand_specs(Head, Module) -->
117 { valid_pi(Head, Name, Arity),
118 functor(GenHead, Name, Arity)
119 },
120 [ coinduction:coinductive_declaration(GenHead, Module) ].
121
122
123valid_pi(Name/Arity, Name, Arity) :-
124 must_be(atom, Name),
125 must_be(integer, Arity).
134wrap_coinductive(Pred, Term, Clause) :-
135 current_predicate(_, Pred),
136 !,
137 rename_clause(Term, 'coinductive ', Clause).
138wrap_coinductive(Pred, Term, [Wrapper_1,Wrapper_2,FirstClause]) :-
139 Pred = M:Head,
140 functor(Head, Name, Arity),
141 length(Args, Arity),
142 GenHead =.. [Name|Args],
143 atom_concat('coinductive ', Name, WrappedName),
144 WrappedHead =.. [WrappedName|Args],
145 Wrapper_1 = (GenHead :-
146 prolog_current_frame(F),
147 prolog_frame_attribute(F, parent, FP),
148 prolog_frame_attribute(FP, parent_goal, M:GenHead)),
149 Wrapper_2 = (GenHead :- WrappedHead, coinduction:no_lco),
150 rename_clause(Term, 'coinductive ', FirstClause).
151
152:- public no_lco/0. 153
154no_lco.
160rename_clause((Head :- Body), Prefix, (NewHead :- Body)) :-
161 !,
162 rename_clause(Head, Prefix, NewHead).
163rename_clause(M:Head, Prefix, M:NewHead) :-
164 rename_clause(Head, Prefix, NewHead).
165rename_clause(Head, Prefix, NewHead) :-
166 Head =.. [Name|Args],
167 atom_concat(Prefix, Name, WrapName),
168 NewHead =.. [WrapName|Args].
169
170
171 174
175system:term_expansion((:- coinductive(Spec)), Clauses) :-
176 expand_coinductive_declaration(Spec, Clauses).
177system:term_expansion(Term, Wrapper) :-
178 head(Term, Module:Head),
179 coinductive_declaration(Head, Module),
180 wrap_coinductive(Module:Head, Term, Wrapper)
Co-Logic Programming
This simple module implements the directive coinductive/1 as described in "Co-Logic Programming: Extending Logic Programming with Coinduction" by Luke Simon et al. The idea behind coinduction is that a goal succeeds if it unifies to a parent goal. This enables some interesting programs, notably on infinite trees (cyclic terms).
This predicate is true for any cyclic list containing only 1-s, regardless of the cycle-length.
Stratification is not checked or enforced in any other way and thus left as a responsibility to the user.