34
35:- module(coinduction,
36 [ (coinductive)/1,
37 op(1150, fx, (coinductive))
38 ]). 39:- autoload(library(error),[instantiation_error/1,must_be/2]).
71:- multifile
72 system:term_expansion/2,
73 coinductive_declaration/2.
79head(Var, _) :-
80 var(Var), !, fail.
81head((H:-_B), Head) :-
82 !,
83 head(H, Head).
84head(H, Head) :-
85 ( H = _:_
86 -> Head = H
87 ; prolog_load_context(module, M),
88 Head = M:H
89 ).
98coinductive(Spec) :-
99 throw(error(context_error(nodirective, coinductive(Spec)), _)).
100
101expand_coinductive_declaration(Spec, Clauses) :-
102 prolog_load_context(module, Module),
103 phrase(expand_specs(Spec, Module), Clauses).
104
105expand_specs(Var, _) -->
106 { var(Var),
107 !,
108 instantiation_error(Var)
109 }.
110expand_specs(M:Spec, _) -->
111 !,
112 expand_specs(Spec, M).
113expand_specs((A,B), Module) -->
114 !,
115 expand_specs(A, Module),
116 expand_specs(B, Module).
117expand_specs(Head, Module) -->
118 { valid_pi(Head, Name, Arity),
119 functor(GenHead, Name, Arity)
120 },
121 [ coinduction:coinductive_declaration(GenHead, Module) ].
122
123
124valid_pi(Name/Arity, Name, Arity) :-
125 must_be(atom, Name),
126 must_be(integer, Arity).
135wrap_coinductive(Pred, Term, Clause) :-
136 current_predicate(_, Pred),
137 !,
138 rename_clause(Term, 'coinductive ', Clause).
139wrap_coinductive(Pred, Term, [Wrapper_1,Wrapper_2,FirstClause]) :-
140 Pred = M:Head,
141 functor(Head, Name, Arity),
142 length(Args, Arity),
143 GenHead =.. [Name|Args],
144 atom_concat('coinductive ', Name, WrappedName),
145 WrappedHead =.. [WrappedName|Args],
146 Wrapper_1 = (GenHead :-
147 prolog_current_frame(F),
148 prolog_frame_attribute(F, parent, FP),
149 prolog_frame_attribute(FP, parent_goal, M:GenHead)),
150 Wrapper_2 = (GenHead :- WrappedHead, coinduction:no_lco),
151 rename_clause(Term, 'coinductive ', FirstClause).
152
153:- public no_lco/0. 154
155no_lco.
161rename_clause((Head :- Body), Prefix, (NewHead :- Body)) :-
162 !,
163 rename_clause(Head, Prefix, NewHead).
164rename_clause(M:Head, Prefix, M:NewHead) :-
165 rename_clause(Head, Prefix, NewHead).
166rename_clause(Head, Prefix, NewHead) :-
167 Head =.. [Name|Args],
168 atom_concat(Prefix, Name, WrapName),
169 NewHead =.. [WrapName|Args].
170
171
172 175
176system:term_expansion((:- coinductive(Spec)), Clauses) :-
177 expand_coinductive_declaration(Spec, Clauses).
178system:term_expansion(Term, Wrapper) :-
179 head(Term, Module:Head),
180 coinductive_declaration(Head, Module),
181 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.