This file is indexed.

/usr/share/hol88-2.02.19940316/contrib/convert/unwind.ml is in hol88-contrib-source 2.02.19940316-19.

This file is owned by root:root, with mode 0o644.

The actual contents of the file can be viewed below.

  1
  2
  3
  4
  5
  6
  7
  8
  9
 10
 11
 12
 13
 14
 15
 16
 17
 18
 19
 20
 21
 22
 23
 24
 25
 26
 27
 28
 29
 30
 31
 32
 33
 34
 35
 36
 37
 38
 39
 40
 41
 42
 43
 44
 45
 46
 47
 48
 49
 50
 51
 52
 53
 54
 55
 56
 57
 58
 59
 60
 61
 62
 63
 64
 65
 66
 67
 68
 69
 70
 71
 72
 73
 74
 75
 76
 77
 78
 79
 80
 81
 82
 83
 84
 85
 86
 87
 88
 89
 90
 91
 92
 93
 94
 95
 96
 97
 98
 99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
%< 
---------------------------------

  new-unwind library
  
  unwind.ml
  
  based on HOL88 unwind library   

  Rules for unwinding

  this file uses mk_thm !! 
---------------------------------
>%

let REWRITES_CONV net = \tm. FIRST_CONV (lookup_term net tm) tm;;

%< some useful conversions for getting things into right form for unwinding >% 

%<
   AND_FORALL_CONV -- move universal quantification out of a conjunction
   
 "(!x. t1) /\ ... /\ (!x. tn)" --->
   |- (!x. t1) /\ ... /\ (!x. tn) = !x. t1 /\ ... /\ tn 
>%

%< now we remove the mk_thm ones and use binary conversions for left, right and both
   conversions as in exists_and (?) ones >%

let AND_FORALL_LEFT_CONV t =
 (let xt1,xt2 = dest_conj t
  in
  let x = fst(dest_forall xt1)
  in
  let (th1,th2) = CONJ_PAIR(ASSUME t)
  in
  let th3 = DISCH_ALL(GEN x (CONJ(SPEC x th1)th2))
  in
  let (th4,th5) =
   CONJ_PAIR
    (SPEC x
     (ASSUME
      (mk_forall(x,(mk_conj((snd o dest_forall o concl)th1,
                            concl th2))))))
  in
  let th6 = DISCH_ALL(CONJ(GEN x th4)th5)
  in
  IMP_ANTISYM_RULE th3 th6
 ) ? failwith `AND_FORALL_LEFT_CONV`;;

%( test AND_FORALL_LEFT_CONV "(! (x:*). T) /\ T";;)%

let AND_FORALL_RIGHT_CONV t =
 (let xt1,xt2 = dest_conj t
  in
  let x = fst(dest_forall xt2)
  in
  let (th1,th2) = CONJ_PAIR(ASSUME t)
  in
  let th3 = DISCH_ALL(GEN x (CONJ th1(SPEC x th2)))
  in
  let (th4,th5) =
   CONJ_PAIR
    (SPEC x
     (ASSUME
      (mk_forall(x,(mk_conj(concl th1,
                            (snd o dest_forall o concl)th2))))))
  in
  let th6 = DISCH_ALL(CONJ th4(GEN x th5))
  in
  IMP_ANTISYM_RULE th3 th6
 ) ? failwith `AND_FORALL_RIGHT_CONV`;;

%( test AND_FORALL_RIGHT_CONV "T /\ (! (x:*). T)";;)%

let AND_FORALL_BOTH_CONV t =
 (let xt1,xt2 = dest_conj t
  in
  let x = fst(dest_forall xt2)
  in
  let (th1,th2) = CONJ_PAIR(ASSUME t)
  in
  let th3 = DISCH_ALL(GEN x (CONJ (SPEC x th1)(SPEC x th2)))
  in
  let (th4,th5) =
   CONJ_PAIR
    (SPEC x
     (ASSUME
      (mk_forall(x,(mk_conj((snd o dest_forall o concl)th1,
                            (snd o dest_forall o concl)th2))))))
  in
  let th6 = DISCH_ALL(CONJ (GEN x th4)(GEN x th5))
  in
  IMP_ANTISYM_RULE th3 th6
 ) ? failwith `AND_FORALL_BOTH_CONV`;;

%( test 

AND_FORALL_BOTH_CONV "(! (x:*). T) /\ (! (x:*). T)";;
)%

let AND_FORALL_CONV = AND_FORALL_BOTH_CONV ORELSEC
                      AND_FORALL_LEFT_CONV ORELSEC
                      AND_FORALL_RIGHT_CONV;;

%( test 
AND_FORALL_CONV "(! (x:*). T) /\ (! (x:*). T)";;
)%

%< mk_thm version eliminated [DES] 31jul90
%  "(!x. t1) /\ ... /\ (!x. tn)" ---> ("x", ["t1"; ... ;"tn"]) %

letrec dest_andl t =
 ((let x1,t1 = dest_forall t
   in
   (x1,[t1])
  )
  ?
  (let first,rest = dest_conj t
   in
   let x1,l1 = dest_andl first
   and x2,l2 = dest_andl rest
   in
   if x1=x2 then (x1, l1@l2) else fail)
 ) ? failwith `dest_andl`;;

% Version of AND_FORALL_CONV below will pull quantifiers out and flatten an
  arbitrary tree of /\s, not just a linear list. %
   
let AND_FORALL_CONV t =
 (let x,l = dest_andl t
  in
  mk_thm([], mk_eq(t,mk_forall(x,list_mk_conj l)))
 ) ? failwith `AND_FORALL_CONV`;;
>%

%<
    FORALL_AND_CONV -- inverse of above

 "!x. t1 /\ ... /\ tn" --->
   |- !x. t1 /\ ... /\ tn =  (!x. t1) /\ ... /\ (!x. tn)
>%
%< superceded by mk_thm version
let FORALL_AND_CONV t =
 (let x,l = ((I # conjuncts) o dest_forall) t
  in
  SYM(AND_FORALL_CONV(list_mk_conj(map(curry mk_forall x)l)))
 ) ? failwith `AND_FORALL_CONV`;;
>%

let FORALL_AND_CONV t =
 (let x,l = ((I # conjuncts) o dest_forall) t
  in
  mk_thm([],mk_eq(t, list_mk_conj(map(curry mk_forall x)l)))
 ) ? failwith `FORALL_AND_CONV`;;

%< [DES] 27apr89

   EXISTS_FORALL_CONV

   ? s . ! t . ....(s t)....  = ! t . ? st . ....st....

   used after unfolding to bring ! t's to outside

   s and t and unprimed then reprimed to be unique in body
   (avoids ?s'!t'.bdy ===> !t'?s't'.bdy problem as s't' not "legal" var name)
>%

let unprime s = implode(filter (\c.not(c=`'`)) (explode s));;

let EXISTS_FORALL_CONV t =
    let ex,t0 = dest_exists t
    in let un,t1 = dest_forall t0
    in let unty = snd(dest_var un)
    in let newname = mk_var(unprime(fst(dest_var ex))^unprime(fst(dest_var un)),type_of"^ex ^un")
    in let new = variant (frees t1) newname
    in let t2 = subst [new,"^ex ^un"] t1
    in let t3 = mk_forall (un,mk_exists (new,t2))
    in let t4 = mk_eq (t,t3)
    in TAC_PROOF(([],t4),
        EQ_TAC THEN REPEAT STRIP_TAC
        THENL [ EXISTS_TAC "^ex ^un" THEN 
                POP_ASSUM (ACCEPT_TAC o SPEC "^un")
               ;EXISTS_TAC "\ ^un . @ ^new . ^t2"
                THEN BETA_TAC
                THEN POP_ASSUM (ACCEPT_TAC o (GEN "^un") 
                                o SELECT_RULE o (SPEC "^un"))
              ]);;

% line_var "!v1 ... vn. f v1 ... vn = t"  ====> "f"                     %

let line_var tm = fst(strip_comb(lhs(snd(strip_forall tm))));;

% var_name "var" ====> `var`                                            %

let var_name = fst o dest_var;;

% line_name "!v1 ... vn. f v1 ... vn = t"  ====> `f`                    %

let line_name = var_name o line_var;;

% UNWIND CONVERSIONS -------------------------------------------------- %

% UNWIND_ONCE_CONV - Basic conversion for parallel unwinding of lines.  %
%                                                                       %
% DESCRIPTION: tm should be a conjunction, t1 /\ t2 ... /\ tn.          %
%              p:term->bool is a function which is used to partition the%
%              terms (ti) into two sets.  Those ti which p is true of   %
%              are then used as a set of rewrite rules (thus they must  %
%              be equations) to do a top-down one-step parallel rewrite %
%              of the conjunction of the remaining terms.  I.e.         %
%                                                                       %
%              t1 /\ ... /\ eqn1 /\ ... /\ eqni /\ ... /\ tn            %
%              ---------------------------------------------            %
%              |-  t1 /\ ... /\ eqn1 /\ ... /\ eqni /\ ... /\ tn        %
%                   =                                                   %
%                  eqn1 /\ ... /\ eqni /\ ... /\ t1' /\ ... /\ tn'      %
%                                                                       %
%                  where tj' is tj rewritten with the equations eqnx    %

let UNWIND_ONCE_CONV p tm =
    let eqns = conjuncts tm in
    let eq1,eq2 = partition (\tm. ((p tm) ? false)) eqns in
    if (null eq1) or (null eq2) 
       then REFL tm
       else let thm = CONJ_DISCHL eq1
                       (ONCE_DEPTH_CONV
                       (REWRITES_CONV (mk_conv_net (map ASSUME eq1)))
                       (list_mk_conj eq2)) in
            let re = CONJUNCTS_CONV(tm,(lhs(concl thm))) in
            re TRANS thm;;

% Unwind until no change using equations selected by p.                 %
% WARNING -- MAY LOOP!                                                  %

letrec UNWIND_CONV p tm =
       let th = UNWIND_ONCE_CONV p tm in
       if lhs(concl th)=rhs(concl th)
          then th
          else th TRANS (UNWIND_CONV p (rhs(concl th)));;

%< [DES] 27apr89

   UNWIND_EXISTS_ONCE_CONV and UNWIND_EXISTS_CONV
   
  
   ? l1 ... ln . eqn1 /\ ... /\ eqnm
   ----------------------------------------
   |- (? l1 ... ln . eqn1 /\ ... /\ eqnm) =
      (? l1 ... ln . eqn1'/\ ... /\ eqnm')

   where any eqs (li = ti) are used as rewrites
>%

let UNWIND_EXISTS_ONCE_CONV t =
   (let exs,bdy = strip_exists t in
    let th1 = UNWIND_ONCE_CONV (\t.mem (line_var t) exs ? false) bdy in
    LIST_MK_EXISTS exs th1) ? failwith `UNWIND_EXISTS_ONCE_CONV`;;

let UNWIND_EXISTS_CONV t =
   (let exs,bdy = strip_exists t in
    let th1 = UNWIND_CONV (\t.mem (line_var t) exs ? false) bdy in
    LIST_MK_EXISTS exs th1) ? failwith `UNWIND_EXISTS_ONCE_CONV`;;

% UNWIND CONVERSIONS -------------------------------------------------- %

% One-step unwinding of device behaviour with hidden lines using line   %
% equations selected by p.                                              %
let UNWIND_ONCE_RULE p th = 
    let rhs_conv = \rhs. (let lines,eqs = strip_exists rhs in
                          LIST_MK_EXISTS lines (UNWIND_ONCE_CONV p eqs)) in
    RIGHT_CONV_RULE rhs_conv th ?  failwith `UNWIND_ONCE_RULE`;;

% Unwind device behaviour using line equations selected by p until no   %
% change.  WARNING --- MAY LOOP!                                        %
let UNWIND_RULE p th = 
    let rhs_conv = \rhs. (let lines,eqs = strip_exists rhs in
                          LIST_MK_EXISTS lines (UNWIND_CONV p eqs)) in
    RIGHT_CONV_RULE rhs_conv th ?  failwith `UNWIND_RULE`;;

% Unwind all lines (except those in the list l) as much as possible.    %
let UNWIND_ALL_RULE l th = 
    let rhs_conv = 
           \rh. (let lines,eqs = strip_exists rh in
                 let eqns = filter (can line_name) (conjuncts eqs) in
                 let line_names = subtract (map line_name eqns) l in
             let p = \line. \tm. (line_name tm) = line in
             let itfn = \line. \th. th TRANS 
                                    UNWIND_CONV (p line) (rhs(concl th)) in
             LIST_MK_EXISTS lines (itlist itfn line_names (REFL eqs))) in
    RIGHT_CONV_RULE rhs_conv th ?  failwith `UNWIND_ALL_RULE`;;