1 :- module(prettyprinter, [pretty_print_error/1]).
2 :- use_module(plspec_logger).
3
4
5 pretty_print_error(fail(postcondition_violated(matched_pre(Pre),
6 violated_post(Post),
7 value(Val)))) :- !,
8 log(error, 'A postcondition was violated!', []),
9 log(error, 'The matched precondition was "~w".', [Pre]),
10 log(error, 'However, the postcondition "~w" does not hold.', [Post]),
11 log(error, 'The offending value was: ~w.', [Val]),
12 (debug_argument(Post,'$root',[Val]) -> true ; true).
13 pretty_print_error(fail(prespec_violated(specs(PreSpecs), values(Vals),
14 location(Functor)))) :- !,
15 log(error, 'No precondition was matched in ~w.', [Functor]),
16 log(error, 'Specified preconditions were: ~w.', [PreSpecs]),
17 log(error, 'However, none of these is matched by: ~w.', [Vals]),
18 (debug_arguments(PreSpecs,Functor,Vals) -> true ; true).
19 pretty_print_error(fail(spec_violated(spec(T), value(V), location(Location)))) :- !,
20 log(error, 'An invariant was violated in ~w.', [Location]),
21 log(error, 'The spec was: ~w.', [T]),
22 log(error, 'However, the value was bound to: ~w.', [V]).
23 pretty_print_error(fail(spec_not_found(spec(Spec)))) :- !,
24 %% TODO: not all failures include a location
25 log(error, 'Spec "~w" was not found.', [Spec]).
26 pretty_print_error(fail(spec_not_found(spec(Spec), location(Location)))) :- !,
27 log(error, '~nA spec for ~w was not found.', [Location]),
28 log(error, 'Spec "~w" was not found.', [Spec]).
29 pretty_print_error(X) :-
30 log(error, 'plspec raised an error term that is unhandled.', []),
31 log(error, '~w.', [X]).
32
33 :- use_module(validator,[valid/2,spec_indirection/2]).
34 :- use_module(library(lists),[include/3]).
35
36
37 % debug a single argument and a single specification
38 debug_argument(SpecDef,Position,Arg) :-
39 spec_indirection(SpecDef,SpecRHS),
40 debug_argument(SpecRHS,Position,Arg).
41 debug_argument(one_of(List),Position,Arg) :- !,
42 include(spec_top_level_match(Arg),List,Matches),
43 (Matches==[]
44 -> get_functor(Arg,FA,NA),
45 log(error,'Value at ~w with functor ~w/~w does not match any case of ~w.',[Position,FA,NA,List])
46 ; Matches = [OneMatch]
47 -> debug_argument(OneMatch,Position,Arg)
48 ; fail).
49 debug_argument(compound(Spec),Position,Arg) :- !, functor(Spec,F,N),
50 get_functor(Arg,FA,NA),
51 ( F=FA,N=NA
52 -> Spec =.. [F|Specs], Arg =.. [F|Args],
53 l_debug_arguments(Specs,F/N,1,Args)
54 ; log(error,'Value at ~w with functor ~w/~w does not match functor ~w/~w of ~w.',[Position,FA,NA,F,N,Spec])
55 ).
56 debug_argument(list(Spec),Position,Arg) :- !,
57 ( Arg = [] -> fail
58 ; Arg = [H|T] ->
59 (debug_argument(Spec,Position,H) -> true
60 ; debug_argument(list(Spec),list(Position),T)
61 )
62 ; get_functor(Arg,FA,NA),
63 log(error,'Value at ~w with functor ~w/~w ist not a list.',[Position,FA,NA])
64 ).
65 debug_argument(atom(X),Position,Arg) :- !,
66 Arg \== X,
67 get_functor(Arg,FA,NA),
68 log(error,'Value at ~w with functor ~w/~w does not match atom ~w.',[Position,FA,NA,X]).
69 debug_argument(ground,Position,Arg) :- !,
70 term_variables(Arg,Vars), Vars \==[],
71 get_functor(Arg,FA,NA),
72 log(error,'Value at ~w with functor ~w/~w does have variables ~w and is not ground.',[Position,FA,NA,Vars]).
73 debug_argument(Basic,Position,Arg) :- basic_type(Basic), !,
74 \+ valid(Basic, Arg),
75 get_functor(Arg,FA,NA),
76 log(error,'Value at ~w with functor ~w/~w ist not ~w.',[Position,FA,NA,Basic]).
77
78 % basic plspec types:
79 basic_type(atom).
80 basic_type(atomic).
81 basic_type(float).
82 basic_type(integer).
83 basic_type(nonvar).
84 basic_type(number).
85 basic_type(var).
86
87 % check at the top-level whether a spec potentially matches an argument
88 spec_top_level_match(Arg,R) :- var(Arg),!,R==var.
89 spec_top_level_match(X,atom(X)) :- !.
90 spec_top_level_match(Arg,compound(Spec)) :- functor(Spec,F,N), functor(Arg,F,N).
91 spec_top_level_match(X,T) :- basic_type(T), valid(T,X),!.
92
93
94 % debug a list of argument and a list of specification alternatives
95 debug_arguments([SingleSpec],Position,Args) :-
96 % currently we only support debugging a single list
97 l_debug_arguments(SingleSpec,Position,1,Args).
98
99 % debug a list of specs and a list of (supposedly) matching arguments
100 l_debug_arguments([Spec1|TSpec],Position,ArgNr,[Arg1|TArgs]) :-
101 (valid(Spec1, Arg1)
102 -> A1 is ArgNr+1,
103 l_debug_arguments(TSpec,Position,A1,TArgs)
104 ; get_functor(Arg1,FA,NA),
105 log(error,'Argument ~w of ~w with functor ~w/~w does not match spec ~w.',[ArgNr,Position,FA,NA,Spec1]),
106 \+ basic_type(Spec1), % otherwise we will just repeat the error message
107 debug_argument(Spec1,Position,Arg1)
108 ).
109 % TO DO: treat things like one_of pattern matches
110
111 % a safe version of functor/3 which also works with variables
112 get_functor(X,F,N) :- var(X),!,F='$VAR',N = -1.
113 get_functor(X,F,N) :- functor(X,F,N).