fix bad calls (obs from Paulo Moura).

This commit is contained in:
Costa Vitor 2009-06-08 14:13:31 -05:00
parent 982cf95bf6
commit 1e55e2f388
5 changed files with 12 additions and 10 deletions

View File

@ -1,4 +1,6 @@
:- module(apply,[]).
:- reexport(library(apply_macros), :- reexport(library(apply_macros),
[maplist/3, [maplist/3,
include/3, include/3,

View File

@ -5,6 +5,8 @@
%% %%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
:- module(expand_macros, []).
:- use_module(library(lists), [append/3]). :- use_module(library(lists), [append/3]).
:- use_module(library(charsio), [format_to_chars/3, read_from_chars/2]). :- use_module(library(charsio), [format_to_chars/3, read_from_chars/2]).
:- use_module(library(error), [must_be/2]). :- use_module(library(error), [must_be/2]).
@ -394,6 +396,7 @@ user:goal_expansion(sumnodes(Meta, Term, AccIn, AccOut), Mod, Goal) :-
), ),
RecursiveCall) RecursiveCall)
], Module). ], Module).
:- unhide('$translate_rule'). :- unhide('$translate_rule').
% stolen from SWI-Prolog % stolen from SWI-Prolog
user:goal_expansion(phrase(NT,Xs), Mod, NTXsNil) :- user:goal_expansion(phrase(NT,Xs), Mod, NTXsNil) :-

View File

@ -38,7 +38,8 @@
numlist/3 numlist/3
]). ]).
:- ensure_loaded(library(error)). :- ensure_loaded(library(error),
[must_be/2]).
% append(Prefix, Suffix, Combined) % append(Prefix, Suffix, Combined)

View File

@ -5,7 +5,6 @@
:- module( undgraphs, :- module( undgraphs,
[ [
undgraph_new/1,
undgraph_add_edge/4, undgraph_add_edge/4,
undgraph_add_edges/3, undgraph_add_edges/3,
undgraph_add_vertices/3, undgraph_add_vertices/3,
@ -13,13 +12,10 @@
undgraph_del_edges/3, undgraph_del_edges/3,
undgraph_del_vertex/3, undgraph_del_vertex/3,
undgraph_del_vertices/3, undgraph_del_vertices/3,
undgraph_edge/3,
undgraph_edges/2, undgraph_edges/2,
undgraph_neighbors/3, undgraph_neighbors/3,
undgraph_neighbours/3, undgraph_neighbours/3,
undgraph_complement/2,
undgraph_components/2, undgraph_components/2,
dgraph_to_undgraph/2,
undgraph_min_tree/2]). undgraph_min_tree/2]).
:- reexport( library(dgraphs), :- reexport( library(dgraphs),
@ -60,6 +56,7 @@
:- use_module(library(rbtrees), :- use_module(library(rbtrees),
[ rb_delete/4, [ rb_delete/4,
rb_delete/3,
rb_insert/4, rb_insert/4,
rb_in/3, rb_in/3,
rb_partial_map/4 rb_partial_map/4

View File

@ -15,8 +15,6 @@
wundgraph_neighbours/3, wundgraph_neighbours/3,
wundgraph_wneighbors/3, wundgraph_wneighbors/3,
wundgraph_wneighbours/3, wundgraph_wneighbours/3,
wdgraph_to_wundgraph/2,
wundgraph_to_undgraph/2,
wundgraph_min_tree/3, wundgraph_min_tree/3,
wundgraph_max_tree/3]). wundgraph_max_tree/3]).
@ -46,7 +44,8 @@
wdgraph_del_edges/3, wdgraph_del_edges/3,
wdgraph_del_vertex/3, wdgraph_del_vertex/3,
wdgraph_edges/2, wdgraph_edges/2,
wdgraph_neighbors/3, wdgraph_neighbours/3,
wdgraph_wneighbours/3,
wdgraph_symmetric_closure/2 wdgraph_symmetric_closure/2
]). ]).
@ -98,7 +97,7 @@ wundgraph_neighbours(V,Vertices,Children) :-
Children = Children0 Children = Children0
). ).
wundgraph_neighbors(V,Vertices,Children) :- wundgraph_neighbors(V,Vertices,Children) :-
wdgraph_neighbors(V,Vertices,Children0), wdgraph_neighbours(V,Vertices,Children0),
( (
wdel_me(Children0,V,Children) wdel_me(Children0,V,Children)
-> ->
@ -117,7 +116,7 @@ wundgraph_wneighbours(V,Vertices,Children) :-
Children = Children0 Children = Children0
). ).
wundgraph_wneighbors(V,Vertices,Children) :- wundgraph_wneighbors(V,Vertices,Children) :-
wdgraph_wneighbors(V,Vertices,Children0), wdgraph_wneighbours(V,Vertices,Children0),
( (
del_me(Children0,V,Children) del_me(Children0,V,Children)
-> ->