1 | % (c) 2009-2024 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(typing_tools,[ | |
6 | is_infinite_type/1, % check if a type is infinite for animation purposes | |
7 | is_provably_finite_type/1, % check if a type is provably finite (not just for animation) | |
8 | is_finite_type_in_context/2, % check if a type is finite, either in animation or proving context | |
9 | ||
10 | type_has_at_least_two_elements/1, | |
11 | non_empty_type/1, | |
12 | ||
13 | valid_ground_type/1, % check if a type is a valid ground type | |
14 | contains_infinite_type/1, | |
15 | any_value_for_type/2, | |
16 | normalize_type/2, | |
17 | create_maximal_type_set/2, % converts sequences to cartesian product | |
18 | create_type_set/2, % keeps sequence types | |
19 | create_type_set/3, % with flag for keeping sequences types or not | |
20 | lift_type_parameters/3 | |
21 | ]). | |
22 | :- use_module(module_information,[module_info/2]). | |
23 | :- module_info(group,typechecker). | |
24 | :- module_info(description,'This module provides utilities for B types.'). | |
25 | ||
26 | %:- use_module(bsyntaxtree, [get_texpr_types/2, syntaxtraversion/6, find_typed_identifier_uses/3]). | |
27 | :- use_module(library(lists), [maplist/2, maplist/3]). | |
28 | ||
29 | :- use_module(kernel_freetypes,[is_infinite_freetype/1, freetype_has_at_least_two_elements/1]). | |
30 | ||
31 | % check if a type is infinite for ProB animation; deferred sets are not counted as infinite here! | |
32 | is_infinite_type(X) :- var(X),!, add_internal_error('Variable as type:',is_infinite_type(X)),fail. | |
33 | is_infinite_type(integer). | |
34 | is_infinite_type(real). | |
35 | is_infinite_type(string). | |
36 | is_infinite_type(freetype(Id)) :- is_infinite_freetype(Id). % will call back is_infinite_type | |
37 | is_infinite_type(global(G)) :- infinite_global_set(G). | |
38 | is_infinite_type(set(X)) :- is_infinite_type(X). | |
39 | is_infinite_type(seq(_)). | |
40 | is_infinite_type(couple(X,Y)) :- (is_infinite_type(X) -> true ; is_infinite_type(Y)). | |
41 | is_infinite_type(record(Fields)) :- | |
42 | ((member(field(_,Type),Fields), is_infinite_type(Type)) -> true). | |
43 | ||
44 | contains_infinite_type([H|T]) :- | |
45 | (is_infinite_type(H) -> true ; contains_infinite_type(T)). | |
46 | ||
47 | :- use_module(b_global_sets,[provably_finite_global_set/1, b_empty_global_set/1, infinite_global_set/1]). | |
48 | ||
49 | % this a finite type for the prover, not just for animation | |
50 | % e.g., deferred sets in Event-B are not finite; in classical B they are in principle finite | |
51 | is_provably_finite_type(X) :- | |
52 | var(X),!,fail. % e.g., in tests 402, 403 this predicate can be called with variables in the type | |
53 | is_provably_finite_type(boolean). | |
54 | is_provably_finite_type(set(X)) :- is_provably_finite_type(X). | |
55 | is_provably_finite_type(couple(X,Y)) :- is_provably_finite_type(X),is_provably_finite_type(Y). | |
56 | is_provably_finite_type(global(G)) :- | |
57 | provably_finite_global_set(G). % Note: in Classical B in principle all SETS are finite ! | |
58 | % note that scope_ DEFINITIONS make the set G finite here: TODO : investigate what we want/need | |
59 | is_provably_finite_type(record(Fields)) :- maplist(finite_field,Fields). | |
60 | is_provably_finite_type(constant([_])). | |
61 | % TODO: freetype | |
62 | ||
63 | finite_field(field(_,Type)) :- is_provably_finite_type(Type). | |
64 | ||
65 | ||
66 | ||
67 | is_finite_type_in_context(animation,Type) :- | |
68 | !, \+ is_infinite_type(Type). % all deferred sets counted as finite here; assumes record_construction already ran | |
69 | is_finite_type_in_context(proving,Type) :- | |
70 | is_provably_finite_type(Type). % here deferred sets can be in principle infinite; see Classical B comment above | |
71 | ||
72 | % ------------------- | |
73 | ||
74 | type_has_at_least_two_elements(X) :- var(X),!,fail. | |
75 | type_has_at_least_two_elements(boolean). | |
76 | type_has_at_least_two_elements(string). | |
77 | type_has_at_least_two_elements(integer). | |
78 | type_has_at_least_two_elements(real). | |
79 | type_has_at_least_two_elements(couple(A,B)) :- | |
80 | ( type_has_at_least_two_elements(A) -> non_empty_type(B) | |
81 | ; type_has_at_least_two_elements(B), non_empty_type(A)). | |
82 | type_has_at_least_two_elements(set(A)) :- non_empty_type(A). | |
83 | type_has_at_least_two_elements(seq(A)) :- non_empty_type(A). | |
84 | type_has_at_least_two_elements(record([field(_,Type)|TF])) :- | |
85 | (type_has_at_least_two_elements(Type) -> true | |
86 | ; type_has_at_least_two_elements(record(TF))). | |
87 | type_has_at_least_two_elements(freetype(Id)) :- | |
88 | freetype_has_at_least_two_elements(Id). | |
89 | type_has_at_least_two_elements(constant([_,_|_])). % type occurs in freetype, but always with one constant | |
90 | ||
91 | ||
92 | % normally all types are non-empty! | |
93 | non_empty_type(X) :- var(X),!,fail. | |
94 | non_empty_type(boolean). | |
95 | non_empty_type(string). | |
96 | non_empty_type(integer). | |
97 | non_empty_type(real). | |
98 | non_empty_type(global(G)) :- \+ b_empty_global_set(G). | |
99 | non_empty_type(set(_)). % always empty set as element of the type | |
100 | non_empty_type(seq(_)). | |
101 | non_empty_type(couple(A,B)) :- non_empty_type(A), non_empty_type(B). | |
102 | non_empty_type(freetype(_)). | |
103 | non_empty_type(record(Fields)) :- maplist(non_empty_field,Fields). | |
104 | non_empty_type(constant([_|_])). % type used in kernel_freetypes | |
105 | ||
106 | non_empty_field(field(_,Type)) :- non_empty_type(Type). | |
107 | ||
108 | % -------------------- | |
109 | ||
110 | :- use_module(error_manager). | |
111 | ||
112 | valid_ground_type(X) :- var(X),!, add_error(valid_ground_type,'Variable as type: ',X),fail. | |
113 | valid_ground_type(X) :- valid_ground_type_aux(X),!. | |
114 | valid_ground_type(X) :- add_error(valid_ground_type,'Illegal type term: ',X),fail. | |
115 | ||
116 | %:- use_module(b_global_sets,[b_global_set/1]). | |
117 | ||
118 | valid_ground_type_aux(any) :- format(user_error,'! Type contains *any*~n',[]). % can happen, e.g., for test 949 due to assertion prj1({{}},BOOL)({}|->TRUE) = {} | |
119 | valid_ground_type_aux(integer). | |
120 | valid_ground_type_aux(real). | |
121 | valid_ground_type_aux(string). | |
122 | valid_ground_type_aux(boolean). | |
123 | valid_ground_type_aux(global(G)) :- atom(G). | |
124 | %bmachine:b_get_machine_set(G). | |
125 | %b_global_sets:b_global_set(G). | |
126 | valid_ground_type_aux(freetype(FT)) :- ground(FT). | |
127 | valid_ground_type_aux(set(X)) :- valid_ground_type(X). | |
128 | valid_ground_type_aux(seq(X)) :- valid_ground_type(X). | |
129 | valid_ground_type_aux(couple(X,Y)) :- valid_ground_type(X), valid_ground_type(Y). | |
130 | valid_ground_type_aux(record(Fields)) :- valid_fields(Fields,'$prev_field_name'). | |
131 | valid_ground_type_aux(constant([X])) :- ground(X). % appears in Z freetype cases, test 738 | |
132 | ||
133 | valid_fields([],_). | |
134 | valid_fields([field(Name,_)|_],_) :- \+ atom(Name),!, | |
135 | add_error(valid_ground_type,'Illegal record field name: ',Name),fail. | |
136 | valid_fields([field(Name,_)|_],PrevName) :- Name @=< PrevName,!, | |
137 | add_error(valid_ground_type,'Record field names not sorted: ',PrevName:Name),fail. | |
138 | valid_fields([field(Name,Type)|T],_) :- | |
139 | valid_ground_type(Type), | |
140 | valid_fields(T,Name). | |
141 | ||
142 | ||
143 | % -------------- | |
144 | ||
145 | :- use_module(kernel_freetypes,[get_freeval_type/3]). | |
146 | :- use_module(b_global_sets,[b_get_fd_type_bounds/3,get_global_type_value/3]). | |
147 | any_value_for_type(T,V) :- if(inst2(T,V),true, (nl,print('*** instantiate_to_any_value failed: '), print(T:V),nl,nl %,trace,inst2(T,V) | |
148 | )). | |
149 | %inst2(_,V) :- ground(V),!. | |
150 | inst2(boolean,V) :- !, inst3(V,pred_true). | |
151 | inst2(pred,V) :- !, inst3(V,pred_true). | |
152 | inst2(integer,V) :- !, V=int(X),inst_fd(X,0). | |
153 | inst2(set(_),V) :- !, inst3(V,[]). % TO DO: what if V already partially instantiated | |
154 | inst2(seq(_),V) :- !, inst3(V,[]). % TO DO: what if V already partially instantiated | |
155 | inst2(couple(TA,TB),V) :- !, V=(A,B), inst2(TA,A), inst2(TB,B). | |
156 | %inst2(real,V) :- !, V=... % TO DO | |
157 | inst2(string,V) :- !, V=string(X), inst3(X,''). | |
158 | inst2(real,V) :- !, V=term(X), (var(X) -> X=floating(0.0) ; X=floating(Y), inst3(Y,0.0)). | |
159 | inst2(global(T),V) :- !, get_global_type_value(V,T,X), | |
160 | b_get_fd_type_bounds(T,LowBnd,_UpBnd), | |
161 | inst_fd(X,LowBnd). | |
162 | inst2(record(Fields),rec(Vals)) :- !, instantiate_fields(Fields,Vals). | |
163 | inst2(constant([A]),V) :- !, V=term(A). | |
164 | inst2(freetype(FT),V) :- !, V=freeval(FT,CASE,Val), | |
165 | (nonvar(CASE) -> (get_freeval_type(FT,CASE,Type) -> any_value_for_type(Type,Val)) % ensure no backtracking | |
166 | ; nonvar(Val) -> print((nonvar_value(V))),nl, get_freeval_type(FT,CASE,Type), any_value_for_type(Type,Val) | |
167 | ; (get_freeval_type(FT,C,Type) -> CASE=C, any_value_for_type(Type,Val)) | |
168 | ). | |
169 | inst2(X,V) :- print(cannot_inst2(X,V)),nl. | |
170 | ||
171 | inst3(X,V) :- (var(X) -> X=V ; true). | |
172 | ||
173 | :- use_module(probsrc(clpfd_interface), [clpfd_some_element_in_domain/2]). | |
174 | inst_fd(X,_) :- nonvar(X),!. | |
175 | inst_fd(X,_Default) :- clpfd_some_element_in_domain(X,El),!, X=El. | |
176 | inst_fd(X,X). | |
177 | ||
178 | instantiate_fields([],[]). | |
179 | instantiate_fields([field(Name,Type)|T],[field(Name,Val)|TV]) :- | |
180 | any_value_for_type(Type,Val), | |
181 | instantiate_fields(T,TV). | |
182 | ||
183 | % ---------------------- | |
184 | ||
185 | % replace seq(X) by set(couple(integer,X)) | |
186 | ||
187 | normalize_type(X,Y) :- | |
188 | (normalize_type_aux(X,Y) -> true ; add_internal_error('Illegal type: ',normalize_type(X,Y)),Y=X). | |
189 | ||
190 | normalize_type_aux(V,R) :- var(V),!,R=V. | |
191 | normalize_type_aux(any,any). | |
192 | normalize_type_aux(pred,pred). | |
193 | normalize_type_aux(subst,subst). | |
194 | normalize_type_aux(boolean,boolean). | |
195 | normalize_type_aux(integer,integer). | |
196 | normalize_type_aux(string,string). | |
197 | normalize_type_aux(real,real). | |
198 | normalize_type_aux(constant(C),constant(C)). | |
199 | normalize_type_aux(global(F),global(F)). | |
200 | normalize_type_aux(freetype(F),freetype(F)). | |
201 | normalize_type_aux(set(X),set(N)) :- normalize_type_aux(X,N). | |
202 | normalize_type_aux(seq(X),set(couple(integer,N))) :- normalize_type_aux(X,N). | |
203 | normalize_type_aux(couple(X,Y),couple(NX,NY)) :- normalize_type_aux(X,NX),normalize_type_aux(Y,NY). | |
204 | normalize_type_aux(record(F),record(NF)) :- normalize_type_fields(F,NF). | |
205 | normalize_type_aux(op(A,B),op(NA,NB)) :- maplist(normalize_type_aux,A,NA), maplist(normalize_type_aux,B,NB). | |
206 | ||
207 | normalize_type_fields(V,R) :- var(V),!,R=V. | |
208 | normalize_type_fields([],[]). | |
209 | normalize_type_fields([field(N,T)|R],[field(N,NT)|RN]) :- normalize_type_aux(T,NT),normalize_type_fields(R,RN). | |
210 | ||
211 | % ------------------------- | |
212 | ||
213 | % usage: lift_type_parameters(couple(t1,t1),[t1],R) --> R=couple(T,T) | |
214 | lift_type_parameters(GroundType,[],LiftedType) :- !, LiftedType=GroundType. | |
215 | lift_type_parameters(Type,TypeParameters,LiftedType) :- | |
216 | sort(TypeParameters,STP), | |
217 | maplist(gen_var,STP,Env), | |
218 | lift_aux(Type,Env,LT), | |
219 | LT=LiftedType. | |
220 | ||
221 | gen_var(ID,ID-_). | |
222 | ||
223 | lift_aux([],_,R) :- !, R=[]. | |
224 | lift_aux([H|T],Env,[LH|LT]) :- !, lift_aux(H,Env,LH), lift_aux(T,Env,LT). | |
225 | lift_aux(Type,Env,Res) :- member(Type-Var,Env),!, Res=Var. | |
226 | lift_aux(set(X),Env,set(LX)) :- !, lift_aux(X,Env,LX). | |
227 | lift_aux(seq(X),Env,seq(LX)) :- !, lift_aux(X,Env,LX). | |
228 | lift_aux(record(X),Env,record(LX)) :- !, lift_aux(X,Env,LX). | |
229 | lift_aux(field(Name,X),Env,field(Name,LX)) :- lift_aux(X,Env,LX). | |
230 | lift_aux(couple(X,Y),Env,couple(NX,NY)) :- !, lift_aux(X,Env,NX), lift_aux(Y,Env,NY). | |
231 | lift_aux(Type,_,Type). | |
232 | ||
233 | % ------------------------- | |
234 | ||
235 | :- use_module(bsyntaxtree, [create_texpr/4]). | |
236 | ||
237 | % translate a ProB type into a B expression so that we can write x:TSet | |
238 | % translate_type: | |
239 | create_type_set(Type,TSet) :- create_type_set(Type,true,TSet). | |
240 | create_type_set(Type,KeepSeq,TSet) :- | |
241 | ( var(Type) -> add_error_and_fail(translate,'type_set Type is variable: ',Type) | |
242 | ; | |
243 | type_set2(Type,KeepSeq,Set,Infos), | |
244 | create_texpr(Set,set(Type),Infos,TSet)). | |
245 | type_set2(set(T),KeepSeq,pow_subset(Set),[]) :- | |
246 | create_type_set(T,KeepSeq,Set). | |
247 | type_set2(seq(T),KeepSeq,Res,Info) :- | |
248 | (KeepSeq = true | |
249 | -> Res=seq(Set), Info=[], create_type_set(T,KeepSeq,Set) % keep sequence types as is | |
250 | ; type_set2(set(couple(integer,T)),KeepSeq,Res,Info)). % write as POW(INTEGER*T) | |
251 | type_set2(couple(TA,TB),KeepSeq,cartesian_product(SetA,SetB),[]) :- | |
252 | create_type_set(TA,KeepSeq,SetA), create_type_set(TB,KeepSeq,SetB). | |
253 | %type_set2(global(G),_,identifier(G),[given_set]). | |
254 | type_set2(global(G),_,value(global_set(G)),[given_set]). % avoids variable capture/clash | |
255 | type_set2(integer,_,integer_set('INTEGER'),[]). | |
256 | type_set2(string,_,string_set,[]). | |
257 | type_set2(real,_,real_set,[]). | |
258 | type_set2(boolean,_,bool_set,[]). | |
259 | type_set2(record(TFields), KeepSeq, struct(Rec),[]) :- | |
260 | create_texpr(rec(SFields),record(TFields),[],Rec), | |
261 | type_set_fields(TFields,KeepSeq,SFields). | |
262 | %type_set2(freetype(Id),identifier(Id),[given_set]). | |
263 | % Missing: no case for constant([C]) term | |
264 | type_set2(freetype(Id),_,freetype_set(Id),[]). | |
265 | type_set2(constant(L),_,value(Terms),[]) :- % these types occur in Event-B for Theory plugin inductive datatypes | |
266 | (var(L) -> add_internal_error('Illegal var constant list: ',type_set2(constant(L),_,value(Terms),[])) ; true), | |
267 | maplist(create_term,L,Terms). | |
268 | create_term(T,term(T)). | |
269 | type_set_fields([],_,[]). | |
270 | type_set_fields([field(Id,Type)|TFrest],KeepSeq,[field(Id,TSet)|EFrest]) :- | |
271 | create_type_set(Type,KeepSeq,TSet), | |
272 | type_set_fields(TFrest,KeepSeq,EFrest). | |
273 | ||
274 | % translate a ProB type to a typed expression representing the maximal type | |
275 | % set_type_to_maximal_texpr | |
276 | create_maximal_type_set(ProBType,TExpr) :- create_type_set(ProBType,false,TExpr). | |
277 | %replace_seq(ProBType,MType),create_type_set(MType,TExpr). | |
278 | ||
279 | % translate a ProB type into a B value of all values of the type is done in b_type2_set | |
280 | ||
281 | ||
282 | ||
283 |