1 % (c) 2009-2022 Lehrstuhl fuer Softwaretechnik und Programmiersprachen,
2 % Heinrich Heine Universitaet Duesseldorf
3 % This software is licenced under EPL 1.0 (http://www.eclipse.org/org/documents/epl-v10.html)
4
5 :- module(consistencycheck,[check_z_structure/3,
6 check_z_structuret/3,
7 check_z_substructure/4,
8 check_z_substructuret/4]).
9
10 :- use_module(probsrc(tools)).
11 :- use_module(probsrc(error_manager)).
12 :- use_module(library(lists)).
13 :- use_module(library(terms)).
14 :- use_module(prozsrc(z_tools)).
15
16 :- use_module(probsrc(module_information)).
17 :- module_info(group,proz).
18 :- module_info(description,'This module provides functionality to check whether the internal data structures of ProZ are consistent.').
19
20 check_z_structure(Z,Comment,Assertions) :- check_z_substructure(Z,list(top),Comment,Assertions).
21 check_z_structuret(Z,Comment,Assertions) :- check_z_substructuret(Z,list(top),Comment,Assertions).
22
23 check_z_substructure(Z,Pos,Comment,Assertions) :- checkzstr(Z,untyped,Pos,Comment,Assertions).
24 check_z_substructuret(Z,Pos,Comment,Assertions) :- checkzstr(Z,typed,Pos,Comment,Assertions).
25
26 :- dynamic errorl/2.
27 error(Msg,Expr) :- assertz(errorl(Msg,Expr)),fail.
28 error(Msg1,Msg2,Expr) :- ajoin([Msg1,Msg2],Msg),error(Msg,Expr).
29
30 checkzstr(Z,Mode,Pos,_,Assertions) :- retractall(errorl(_,_)),czstr(Z,Pos,Mode,Assertions),!.
31 checkzstr(_,_,_,Comment,_) :- errorl(Msg,Expr),
32 atom_concat(Comment,': ',M1),atom_concat(M1,Msg,M),
33 add_error(consistencycheck,M,Expr),fail.
34
35 %czstr1(Z,_,_,_) :- \+ ground(Z),!,error('specification not ground', Z).
36 %czstr1(Z,Pos,Mode,Assertions) :- czstr(Z,Pos,Mode,Assertions).
37
38 czstr([],list(_),_,_) :- !.
39 czstr([E|Rest],list(Type),Mode,Assertions) :-
40 !,czstr(E,Type,Mode,Assertions),czstr(Rest,list(Type),Mode,Assertions).
41
42 czstr(Expr,number,_,_) :- !,(number(Expr) -> true; error('number expected:',Expr)).
43 czstr(Expr,name,_,_) :- !,(Expr=name(N,D)->true;error('name expected:',Expr)),catom(N),catom(D).
44 czstr(Expr,shead,M,Assertions) :-
45 !,(Expr=shead(N,P)->true;error('shead expected:',Expr)),
46 catom(N),czstr(P,list(name),M,Assertions).
47 czstr(Expr,lhs,M,Assertions) :-
48 !,(Expr=lhs(N,P)->true;error('lhs expected:',Expr)),
49 czstr(N,name,M,Assertions),czstr(P,list(name),M,Assertions).
50 czstr(Expr,token,_,_) :- !,catom(Expr).
51 czstr(Expr,type,_,Assertions) :-
52 ? !,(checktype(expr,Expr,Assertions)->true;error('invalid type:',Expr)).
53 czstr(Expr,Type,untyped,Assertions) :-
54 !,czstr2(Expr,Type,untyped,Assertions).
55 czstr(ti(Expr,TypeExpr),Type,typed,Assertions) :-
56 !,
57 ? (checktype(Type,TypeExpr,Assertions)->true;error('invalid type in mode ',Type,TypeExpr)),
58 czstr2(Expr,Type,typed,Assertions).
59 czstr(Expr,_,typed,_) :- error('type info expected',Expr).
60
61 catom(A) :- (atom(A) -> true; error('atom expected:',A)).
62
63 czstr2(Expr,Type,Mode,Assertions) :-
64 same_functor(Expr,TInfo),
65 ? (zstrcheck(TInfo,Type,Labels) ->
66 true;error('unexpected expression in mode ',Type,Expr)),!,
67 check_labels(Assertions,Labels,Expr),
68 Expr =.. [_|Args],
69 TInfo =.. [_|ArgTypes],
70 (same_length(Args,ArgTypes)->true;error('unexpected number of arguments',Expr)),
71 czstr_l(Args,ArgTypes,Mode,Assertions).
72 czstr_l([],[],_,_).
73 czstr_l([E|ERest],[Type|TRest],Mode,Assertions) :-
74 czstr(E,Type,Mode,Assertions),
75 czstr_l(ERest,TRest,Mode,Assertions).
76
77 zstrcheck(ref(name,list(expr)),expr,[]).
78 zstrcheck(number(number),expr,[]).
79 zstrcheck(apply(expr,expr),expr,[]).
80 zstrcheck(inop(name,expr,expr),expr,[]).
81 zstrcheck(ingen(name,expr,expr),expr,[]).
82 zstrcheck(postop(name,expr),expr,[]).
83 zstrcheck(pregen(name,expr),expr,[]).
84 zstrcheck(inrel(name,expr,expr),pred,[]).
85 zstrcheck(prerel(name,expr),pred,[]).
86 zstrcheck(equal(expr,expr),pred,[]).
87 zstrcheck(member(expr,expr),pred,[]).
88 zstrcheck(power(expr),expr,[]).
89 zstrcheck(cross(list(expr)),expr,[]).
90 zstrcheck(tuple(list(expr)),expr,[]).
91 zstrcheck(if(pred,expr,expr),expr,[]).
92 zstrcheck(ext(list(expr)),expr,[]).
93 zstrcheck(seq(list(expr)),expr,[]).
94 zstrcheck(bag(list(expr)),expr,[]).
95 zstrcheck(theta(token,token,list(rename)),expr,[]).
96 zstrcheck(sexpr(sexpr),expr,[]).
97 zstrcheck(select(expr,name),expr,[]).
98 zstrcheck(lambda(body,expr),expr,[]).
99 zstrcheck(comp(body,opt),expr,[]).
100 zstrcheck(reclet(expr,expr),expr,[]).
101 zstrcheck(just(expr),opt,[]).
102 zstrcheck(nothing,opt,[]).
103 zstrcheck(mu(body,opt),expr,[]).
104 zstrcheck(falsity,pred,[]).
105 zstrcheck(truth,pred,[]).
106 zstrcheck(forall(body,pred),pred,[]).
107 zstrcheck(exists(body,pred),pred,[]).
108 zstrcheck(exists1(body,pred),pred,[]).
109 zstrcheck(and(pred,pred),pred,[]).
110 zstrcheck(or(pred,pred),pred,[]).
111 zstrcheck(implies(pred,pred),pred,[]).
112 zstrcheck(equiv(pred,pred),pred,[]).
113 zstrcheck(not(pred),pred,[]).
114 zstrcheck(spred(sexpr),pred,[]).
115 zstrcheck(letexpr(list(letdef),expr),expr,[]).
116 zstrcheck(letpred(list(letdef),pred),pred,[]).
117 zstrcheck(letdef(name,expr),letdef,[]).
118 zstrcheck(sref(token,token,list(expr),list(rename)),sexpr,[scalc]).
119 zstrcheck(sand(sexpr,sexpr),sexpr,[scalc]).
120 zstrcheck(sor(sexpr,sexpr),sexpr,[scalc]).
121 zstrcheck(simplies(sexpr,sexpr),sexpr,[scalc]).
122 zstrcheck(sequiv(sexpr,sexpr),sexpr,[scalc]).
123 zstrcheck(snot(sexpr),sexpr,[scalc]).
124 zstrcheck(sforall(body,sexpr),sexpr,[scalc]).
125 zstrcheck(sexists(body,sexpr),sexpr,[scalc]).
126 zstrcheck(sexists1(body,sexpr),sexpr,[scalc]).
127 zstrcheck(hide(sexpr,list(name)),sexpr,[scalc]).
128 zstrcheck(fatsemi(sexpr,sexpr),sexpr,[scalc]).
129 zstrcheck(project(sexpr,sexpr),sexpr,[scalc]).
130 zstrcheck(pre(sexpr),sexpr,[scalc]).
131 zstrcheck(pipe(sexpr,sexpr),sexpr,[scalc]).
132 zstrcheck(text(body),sexpr,[scalc]).
133
134 zstrcheck(sdef(shead,body),top,[]).
135 zstrcheck(defeq(shead,sexpr),top,[]).
136 zstrcheck(eqeq(lhs,expr),top,[]).
137 zstrcheck(define(list(name),body),top,[]).
138 zstrcheck(axdef(body),top,[]).
139 zstrcheck(pred(pred),top,[]).
140 zstrcheck(given(list(name)),top,[]).
141 zstrcheck(data(name,list(arm)),top,[]).
142 zstrcheck(arm(name,opt),arm,[]).
143
144 zstrcheck(body(list(decl),list(pred)),body,[]).
145 zstrcheck(body(list(decl),list(pred)),sexpr,[]).
146 zstrcheck(decl(list(name),expr),decl,[]).
147 zstrcheck(sdecl(sexpr),decl,[]).
148
149 zstrcheck(rename(name,name),rename,[]).
150
151 % internal constructs
152 zstrcheck(namedset(name,list(name)),top,[]).
153 zstrcheck(binding(list(bfield)),expr,[]).
154 zstrcheck(bindfield(name,expr),bfield,[]).
155
156 zstrcheck(basetype(type),expr,[]).
157
158 zstrcheck(ftconstant(name,name),expr,[]).
159 zstrcheck(ftconstructor(name,name,expr),expr,[]).
160 zstrcheck(ftdestructor(name,name,expr),expr,[]).
161 zstrcheck(ftcase(name,name,expr),pred,[]).
162
163 checktype(pred,bool,_).
164 checktype(top,none,_).
165 checktype(opt,none,_).
166 checktype(arm,none,_).
167 checktype(letdef,none,_).
168 checktype(bfield,none,_).
169 ?checktype(sexpr,set(schema(S)),Assertions) :- checkschematype(S,Assertions).
170 ?checktype(body,set(schema(S)),Assertions) :- checkschematype(S,Assertions).
171 checktype(decl,none,_).
172 checktype(expr,num,_).
173 checktype(expr,given(N),Assertions) :- czstr(N,name,typed,Assertions).
174 checktype(expr,freetype(N),Assertions) :- czstr(N,name,typed,Assertions).
175 ?checktype(expr,set(T),Assertions) :- checktype(expr,T,Assertions).
176 ?checktype(expr,tuple(L),Assertions) :- checktype_l(L,Assertions).
177 ?checktype(expr,schema(F),Assertions) :- checkschematype(F,Assertions).
178 checktype(expr,param(_),_).
179
180 checktype_l([],_).
181 checktype_l([E|Rest],Assertions) :-
182 ? checktype(expr,E,Assertions),checktype_l(Rest,Assertions).
183 checkschematype([],_).
184 checkschematype([field(N,T)|Rest],Assertions) :-
185 czstr(N,name,typed,Assertions),
186 ? checktype(expr,T,Assertions),
187 ? checkschematype(Rest,Assertions).
188
189
190 check_labels([],_,_).
191 check_labels([label(L)|Rest],Labels,Expr) :-
192 !,(member(L,Labels) ->
193 !,check_labels(Rest,Labels,Expr);
194 (atom_concat('label not present: ',L,Msg),
195 error(Msg,Expr))).
196 check_labels([nlabel(L)|Rest],Labels,Expr) :-
197 !,(member(L,Labels) ->
198 (!,atom_concat('label present: ',L,Msg),
199 error(Msg,Expr));
200 check_labels(Rest,Labels,Expr)).
201 check_labels([Assertion|_],_,Expr) :-
202 atom_concat('unmatched assertion: ',Assertion,Msg),
203 error(Msg,Expr).