src/Tools/isac/ProgLang/termC.sml
author Walther Neuper <wneuper@ist.tugraz.at>
Fri, 02 Mar 2018 16:19:02 +0100
changeset 59390 f6374c995ac5
parent 59389 627d25067f2f
child 59391 707eb1df5724
permissions -rw-r--r--
TermC: clean signature, partially
neuper@38025
     1
(* Title: extends Isabelle/src/Pure/term.ML
e0726734@41962
     2
   Author: Walther Neuper 1999, Mathias Lehnfeld
neuper@38025
     3
   (c) due to copyright terms
neuper@38025
     4
*)
wneuper@59389
     5
                                          
wneuper@59389
     6
signature TERMC =
wneuper@59389
     7
  sig
wneuper@59390
     8
  (*val bool \<longrightarrow> HOLogic.boolT*)
wneuper@59389
     9
    val const_in: string -> term -> bool
wneuper@59389
    10
    val contains_Var: term -> bool
wneuper@59389
    11
    val dest_binop_typ: typ -> typ * typ * typ
wneuper@59390
    12
    val (*dest_equals'*) dest_equals: term -> term * term
wneuper@59389
    13
    val free2str: term -> string
wneuper@59389
    14
    val ids2str: term -> string list
wneuper@59389
    15
    val ins_concl: term -> term -> term
wneuper@59389
    16
    val inst_abs: 'a -> term -> term
wneuper@59389
    17
    val inst_bdv: (term * term) list -> term -> term
wneuper@59390
    18
 
wneuper@59389
    19
    val int_of_Free: term -> int
wneuper@59390
    20
    val (*int_of_str \<longrightarrow>*) int_of_str_opt: string -> int option
wneuper@59390
    21
    val (*int_of_str' int2str \<longrightarrow>*)int_of_str: string -> int
wneuper@59390
    22
wneuper@59389
    23
    val isalist2list: term -> term list
wneuper@59390
    24
    val list2isalist: typ -> term list -> term
wneuper@59389
    25
    val isapair2pair: term -> term * term
wneuper@59389
    26
    val isastr_of_int: int -> string
wneuper@59390
    27
 
wneuper@59389
    28
    val is_atom: term -> bool
wneuper@59389
    29
    val is_bdv: string -> bool
wneuper@59389
    30
    val is_bdv_subst: term -> bool
wneuper@59389
    31
    val is_equality: term -> bool
wneuper@59389
    32
    val is_expliceq: term -> bool
wneuper@59389
    33
    val is_f_x: term -> bool
wneuper@59389
    34
    val is_list: term -> bool
wneuper@59389
    35
    val is_num: term -> bool
wneuper@59390
    36
    val (*is_no  is_numeral \<longrightarrow>*)is_num': string -> bool
wneuper@59390
    37
wneuper@59389
    38
    val mk_add: term -> term -> term
wneuper@59389
    39
    val mk_free: typ -> string -> term
wneuper@59389
    40
    val mk_equality: term * term -> term
wneuper@59389
    41
    val mk_factroot: string -> typ -> int -> int -> term
wneuper@59389
    42
    val mk_Free: string * typ -> term
wneuper@59389
    43
    val mk_thmid: string -> 'a -> string -> string -> string
wneuper@59390
    44
    val mk_num_op_num(*<-- num_op_num*): typ -> typ -> string * typ -> int -> int -> term
wneuper@59390
    45
    val mk_num_op_var(*<-- num_op_var*): term -> string -> typ -> typ -> int -> term
wneuper@59390
    46
    val mk_var_op_num(*<-- var_op_num*): term -> string -> typ -> typ -> int -> term
wneuper@59390
    47
wneuper@59390
    48
  (*val list_implies: term list * term -> term  --> Logic.list_implies*)
wneuper@59390
    49
    val matches: theory -> term -> term -> bool
wneuper@59389
    50
    val parse: theory -> string -> cterm option
wneuper@59389
    51
    val parseN: theory -> string -> cterm option
wneuper@59389
    52
    val parseNEW: Proof.context -> string -> term option
wneuper@59389
    53
    val parseold: theory -> string -> cterm option
wneuper@59389
    54
    val parse_patt: theory -> string -> term
wneuper@59389
    55
    val perm: term -> term -> bool
wneuper@59390
    56
wneuper@59390
    57
    val calc_equ: string -> int * int -> bool
wneuper@59389
    58
    val power: int -> int -> int
wneuper@59389
    59
    val sign2: int -> int -> int
wneuper@59389
    60
    val squfact: int -> int
wneuper@59390
    61
    val gcd: int -> int -> int
wneuper@59390
    62
wneuper@59389
    63
    val str_of_free_opt: term -> string option
wneuper@59389
    64
    val str_of_int: int -> string
wneuper@59389
    65
    val str2term: string -> term
wneuper@59389
    66
    val strip_imp_prems': term -> term option
wneuper@59389
    67
    val subst_atomic_all: (term * term) list -> term -> bool * term
wneuper@59389
    68
    val term_detail2str: term -> string
wneuper@59389
    69
    val term_of_num: typ -> int -> term
wneuper@59390
    70
wneuper@59390
    71
    val num_str: thm -> thm
wneuper@59390
    72
    val pairt: term -> term -> term
wneuper@59390
    73
    val pairT: typ -> typ -> typ
wneuper@59390
    74
    val strip_trueprop: term -> term
wneuper@59390
    75
wneuper@59389
    76
    val uminus_to_string: term -> term
wneuper@59389
    77
    val var2free: term -> term
wneuper@59389
    78
    val vars: term -> term list
wneuper@59389
    79
(* ---- for tests only: shifted from below to remove the Warning "unused" at fun.def. --------- *)
wneuper@59389
    80
  (* NONE *)
wneuper@59389
    81
(*/-------------------------------------------------------- ! aktivate for Test_Isac BEGIN ---\* )
wneuper@59389
    82
    val --->: typ list * typ -> typ
wneuper@59389
    83
    val -->: typ * typ -> typ
wneuper@59389
    84
    val PairT: typ -> typ -> typ
wneuper@59389
    85
    val T_a2real: typ -> typ
wneuper@59389
    86
    val add_term_vars: term * term list -> term list
wneuper@59389
    87
    val atless: term * term -> bool
wneuper@59389
    88
    val atomt: term -> unit
wneuper@59389
    89
    val atomthm: thm -> unit
wneuper@59389
    90
    val atomty: term -> unit
wneuper@59389
    91
    val atomty_thy: thyID -> term -> unit
wneuper@59389
    92
    val atomtyp: typ -> unit
wneuper@59389
    93
    val atomw: term -> unit
wneuper@59389
    94
    val atomwy: term -> unit
wneuper@59389
    95
    val contains_term: term -> term -> bool
wneuper@59389
    96
    val dest_type: typ -> string
wneuper@59389
    97
    val divisors: int -> int list
wneuper@59389
    98
    val doubles: ''a list -> ''a list
wneuper@59389
    99
    val dummyT: typ
wneuper@59389
   100
    val dvd: int * int -> bool
wneuper@59389
   101
    val eq_set_term: term list * term list -> bool
wneuper@59389
   102
    val false_as_cterm: cterm
wneuper@59389
   103
    val free2int: term -> int
wneuper@59389
   104
    val free2var: term -> term
wneuper@59389
   105
    val get_thm': xstring -> rule
wneuper@59389
   106
    val get_types: term -> (string * typ) list
wneuper@59389
   107
    val insert_aterm: term * term list -> term list
wneuper@59389
   108
    val is_Free: term -> bool
wneuper@59389
   109
    val is_bdv_: term -> bool
wneuper@59389
   110
    val is_fun_id: term -> bool
wneuper@59389
   111
    val lhs_: term -> term
wneuper@59389
   112
    val listType: typ
wneuper@59389
   113
    val list_const: typ -> term
wneuper@59389
   114
    val match_bvs: term * term * (string * string) list -> (string * string) list
wneuper@59389
   115
    val mem_term: term * term list -> bool
wneuper@59389
   116
    val mk_listT: typ -> typ
wneuper@59389
   117
    val mk_prop: term -> term
wneuper@59389
   118
    val mk_subs: ((string * int) * (typ * term)) list -> (term * term) list
wneuper@59389
   119
    val num_of_term: term -> int
wneuper@59389
   120
    val numbers_to_string: term -> term
wneuper@59389
   121
    val raw_pp_typ: typ -> Pretty.T
wneuper@59389
   122
    val ren_inst: ((indexname * typ) list * (indexname * term) list) * term * term * term -> term
wneuper@59389
   123
    val rhs_: term -> term
wneuper@59389
   124
    val scala_of_term: term -> string
wneuper@59389
   125
    val scala_of_typ: typ -> string
wneuper@59389
   126
    val set_types: (string * typ) list -> term -> term
wneuper@59389
   127
    val sign: int -> int
wneuper@59389
   128
    val sqrt: int -> int
wneuper@59389
   129
    val str2termN: string -> term
wneuper@59389
   130
    val str2term_: theory -> string -> term
wneuper@59389
   131
    val str_of_int: int -> string
wneuper@59389
   132
    val strs2terms: string list -> term list
wneuper@59389
   133
    val subset_term: term list * term list -> bool
wneuper@59389
   134
    val subst_bound: term * term -> term
wneuper@59389
   135
    val term_detail2str_thy: thyID -> term -> string
wneuper@59389
   136
    val term_of_num: typ -> int -> term
wneuper@59389
   137
    val term_str: 'a -> term -> string
wneuper@59389
   138
    val term_vars: term -> term list
wneuper@59389
   139
    val true_as_cterm: cterm
wneuper@59389
   140
    val typ_a2real: term -> term
wneuper@59389
   141
    val var_perm: term * term -> bool
wneuper@59389
   142
    val vars_str: term -> string list
wneuper@59389
   143
    val vperm: term * term -> bool
wneuper@59389
   144
    val xless: (string * int) * indexname -> bool
wneuper@59389
   145
( *\--- ! aktivate for Test_Isac END ----------------------------------------------------------/*)
wneuper@59389
   146
  end
wneuper@59389
   147
wneuper@59389
   148
(**)
wneuper@59389
   149
structure TermC(**): TERMC(**) =
wneuper@59389
   150
struct
wneuper@59389
   151
(**)
neuper@38025
   152
neuper@52087
   153
fun isastr_of_int i = if i >= 0 then string_of_int i else "-" ^ string_of_int (abs i)
neuper@52087
   154
neuper@38025
   155
(*
wneuper@59184
   156
> (Thm.global_cterm_of thy) a_term; 
neuper@38025
   157
val it = "empty" : cterm        *)
neuper@38025
   158
neuper@38025
   159
(*2003 fun match thy t pat =
neuper@38025
   160
    (snd (Pattern.match (Sign.tsig_of (sign_of thy)) (pat, t)))
neuper@38025
   161
    handle _ => [];
neuper@38025
   162
fn : theory ->
neuper@38025
   163
     Term.term -> Term.term -> (Term.indexname * Term.term) list*)
neuper@38025
   164
(*see src/Tools/eqsubst.ML fun clean_match*)
neuper@38025
   165
(*2003 fun matches thy tm pa = if match thy tm pa = [] then false else true;*)
neuper@38025
   166
fun matches thy tm pa = 
neuper@38025
   167
    (Pattern.match thy (pa, tm) (Vartab.empty, Vartab.empty); true)
neuper@38025
   168
    handle _ => false
neuper@38025
   169
wneuper@59318
   170
(**
wneuper@59318
   171
  transform  typ / term to a String, which is parsed by Scala
wneuper@59318
   172
  after transport via libisabelle
wneuper@59318
   173
*)
wneuper@59318
   174
fun scala_of_typ (Type (s, typs)) =
wneuper@59318
   175
    enclose "Type(" ")" (quote s ^ ", " ^
wneuper@59318
   176
      (typs |> map scala_of_typ |> commas |> enclose "List(" ")"))
wneuper@59318
   177
  | scala_of_typ (TFree (s, sort)) =
wneuper@59318
   178
    enclose "TFree(" ")" (quote s ^ ", " ^ (sort |> map quote |> commas |> enclose "List(" ")"))
wneuper@59318
   179
  | scala_of_typ (TVar ((s, i), sort)) =
wneuper@59318
   180
    enclose "TVar(" ")" (
wneuper@59318
   181
      enclose "(" ")," (quote s ^ "," ^ quote (string_of_int i)) ^ 
wneuper@59318
   182
      (sort |> map quote |> commas |> enclose "List(" ")"))
wneuper@59318
   183
wneuper@59318
   184
fun scala_of_term (Const (s, T)) =
wneuper@59318
   185
    enclose "Const(" ")" (quote s ^ ", " ^ scala_of_typ T)
wneuper@59318
   186
  | scala_of_term (Free (s, T)) =
wneuper@59318
   187
    enclose "Free(" ")" (quote s ^ ", " ^ scala_of_typ T)
wneuper@59318
   188
  | scala_of_term (Var ((s, i), T)) =
wneuper@59318
   189
    enclose "TVar(" ")" (
wneuper@59318
   190
      enclose "(" ")," (quote s ^ "," ^ quote (string_of_int i)) ^ 
wneuper@59318
   191
      scala_of_typ T)
wneuper@59318
   192
  | scala_of_term (Bound i) = enclose "Bound(" ")" (string_of_int i)
wneuper@59318
   193
  | scala_of_term (Abs (s, T, t)) =
wneuper@59318
   194
    enclose "Abs(" ")" (
wneuper@59318
   195
      quote s ^ ", " ^
wneuper@59318
   196
      scala_of_typ T ^ ", " ^
wneuper@59318
   197
      scala_of_term t)
wneuper@59318
   198
  | scala_of_term (t1 $ t2) =
wneuper@59318
   199
    enclose "App(" ")" (scala_of_term t1 ^ ", " ^ scala_of_term t2)
wneuper@59318
   200
wneuper@59318
   201
(** old versions *)
neuper@38025
   202
fun atomtyp t = (*WN10 see raw_pp_typ*)
neuper@38025
   203
  let
neuper@38025
   204
    fun ato n (Type (s,[])) = 
neuper@38025
   205
      ("\n*** "^indent n^"Type ("^s^",[])")
neuper@38025
   206
      | ato n (Type (s,Ts)) =
neuper@38025
   207
      ("\n*** "^indent n^"Type ("^s^",["^ atol (n+1) Ts)
neuper@38025
   208
neuper@38025
   209
      | ato n (TFree (s,sort)) =
wneuper@59365
   210
      ("\n*** "^indent n^"TFree ("^s^","^ strs2str' sort)
neuper@38025
   211
neuper@38025
   212
      | ato n (TVar ((s,i),sort)) =
neuper@38025
   213
      ("\n*** "^indent n^"TVar (("^s^","^ 
neuper@38025
   214
       string_of_int i ^ strs2str' sort)
neuper@38025
   215
    and atol n [] = 
neuper@38025
   216
      ("\n*** "^indent n^"]")
neuper@38025
   217
      | atol n (T::Ts) = (ato n T ^ atol n Ts)
neuper@38048
   218
in tracing (ato 0 t ^ "\n") end;
neuper@38025
   219
(*
wneuper@59186
   220
> val T = (type_of o Thm.term_of o the o (parse thy)) "a::[real,int] => nat";
neuper@38025
   221
> atomtyp T;
neuper@38025
   222
*** Type (fun,[
neuper@38025
   223
***   Type (RealDef.real,[])
neuper@38025
   224
***   Type (fun,[
neuper@38025
   225
***     Type (IntDef.int,[])
neuper@38025
   226
***     Type (nat,[])
neuper@38025
   227
***     ]
neuper@38025
   228
***   ]
neuper@38025
   229
*)
neuper@38025
   230
neuper@38025
   231
(*Prog.Tutorial.p.34, Makarius 1005 does the above like this..*)
neuper@38025
   232
local
neuper@38025
   233
   fun pp_pair (x, y) = Pretty.list "(" ")" [x, y]
neuper@38025
   234
   fun pp_list xs = Pretty.list "[" "]" xs
neuper@38025
   235
   fun pp_str s   = Pretty.str s
neuper@38025
   236
   fun pp_qstr s = Pretty.quote (pp_str s)
neuper@38025
   237
   fun pp_int i   = pp_str (string_of_int i)
neuper@38025
   238
   fun pp_sort S = pp_list (map pp_qstr S)
neuper@38025
   239
   fun pp_constr a args = Pretty.block [pp_str a, Pretty.brk 1, args]
neuper@38025
   240
in
neuper@38025
   241
fun raw_pp_typ (TVar ((a, i), S)) =
neuper@38025
   242
       pp_constr "TVar" (pp_pair (pp_pair (pp_qstr a, pp_int i), pp_sort S))
neuper@38025
   243
   | raw_pp_typ (TFree (a, S)) =
neuper@38025
   244
       pp_constr "TFree" (pp_pair (pp_qstr a, pp_sort S))
neuper@38025
   245
   | raw_pp_typ (Type (a, tys)) =
neuper@38025
   246
       pp_constr "Type" (pp_pair (pp_qstr a, pp_list (map raw_pp_typ tys)))
neuper@38025
   247
end
neuper@38025
   248
(* install
neuper@38025
   249
PolyML.addPrettyPrinter
neuper@38025
   250
  (fn _ => fn _ => ml_pretty o Pretty.to_ML o raw_pp_typ);
neuper@38025
   251
de-install
neuper@38025
   252
PolyML.addPrettyPrinter
neuper@38025
   253
  (fn _ => fn _ => ml_pretty o Pretty.to_ML o Proof_Display.pp_typ Pure.thy);
neuper@38025
   254
*)
neuper@38025
   255
neuper@38067
   256
local 
neuper@38067
   257
  fun ato (Const (a, _)) n = 
neuper@38025
   258
	           "\n*** " ^ indent n ^ "Const (" ^ a ^ ", _)"
neuper@38025
   259
	  | ato (Free (a, _)) n =  
neuper@38025
   260
	           "\n*** " ^ indent n ^ "Free (" ^ a ^ ", _)"
neuper@38025
   261
	  | ato (Var ((a, i), _)) n =
neuper@38025
   262
	           "\n*** " ^ indent n ^ "Var (" ^ a ^ ", " ^ 
neuper@38025
   263
                                               string_of_int i ^ "), _)"
neuper@38025
   264
	  | ato (Bound i) n = 
neuper@38025
   265
	           "\n*** " ^ indent n ^ "Bound " ^ string_of_int i
neuper@38025
   266
	  | ato (Abs (a, _, body)) n = 
neuper@38025
   267
	           "\n*** " ^ indent n ^ "Abs(" ^ a ^ ", _" ^ ato body (n+1)
neuper@38025
   268
	  | ato (f $ t) n = (ato f n ^ ato t (n + 1))
neuper@38067
   269
in
neuper@38067
   270
fun atomw t = writeln ("\n*** -------------" ^ ato t 0 ^ "\n***");
neuper@38067
   271
fun atomt t = tracing ("\n*** -------------" ^ ato t 0 ^ "\n***");
neuper@38067
   272
end;
neuper@38025
   273
neuper@38025
   274
fun term_detail2str t =
neuper@38025
   275
    let fun ato (Const (a, T)) n = 
neuper@38025
   276
	    "\n*** " ^ indent n ^ "Const (" ^ a ^ ", " ^ string_of_typ T ^ ")"
neuper@38025
   277
	  | ato (Free (a, T)) n =  
neuper@38025
   278
	    "\n*** " ^ indent n ^ "Free (" ^ a ^ ", " ^ string_of_typ T ^ ")"
neuper@38025
   279
	  | ato (Var ((a, i), T)) n =
neuper@38025
   280
	    "\n*** " ^ indent n ^ "Var ((" ^ a ^ ", " ^ string_of_int i ^ "), "^
neuper@38025
   281
	    string_of_typ T ^ ")"
neuper@38025
   282
	  | ato (Bound i) n = 
neuper@38025
   283
	    "\n*** " ^ indent n ^ "Bound " ^ string_of_int i
neuper@38025
   284
	  | ato (Abs(a, T, body))  n = 
neuper@38025
   285
	    "\n*** " ^ indent n ^ "Abs (" ^ a ^ ", " ^ string_of_typ T ^ ",.."
neuper@38025
   286
	    ^ ato body (n + 1)
neuper@38025
   287
	  | ato (f $ t) n = ato f n ^ ato t (n + 1)
neuper@38025
   288
    in "\n*** " ^ ato t 0 ^ "\n***" end;
neuper@42376
   289
fun term_detail2str_thy thy t =
neuper@42376
   290
    let fun ato (Const (a, T)) n = 
neuper@42376
   291
	    "\n*** " ^ indent n ^ "Const (" ^ a ^ ", " ^ string_of_typ_thy thy T ^ ")"
neuper@42376
   292
	  | ato (Free (a, T)) n =  
neuper@42376
   293
	    "\n*** " ^ indent n ^ "Free (" ^ a ^ ", " ^ string_of_typ_thy thy T ^ ")"
neuper@42376
   294
	  | ato (Var ((a, i), T)) n =
neuper@42376
   295
	    "\n*** " ^ indent n ^ "Var ((" ^ a ^ ", " ^ string_of_int i ^ "), "^
neuper@42376
   296
	    string_of_typ_thy thy T ^ ")"
neuper@42376
   297
	  | ato (Bound i) n = 
neuper@42376
   298
	    "\n*** " ^ indent n ^ "Bound " ^ string_of_int i
neuper@42376
   299
	  | ato (Abs(a, T, body))  n = 
neuper@42376
   300
	    "\n*** " ^ indent n ^ "Abs (" ^ a ^ ", " ^ string_of_typ_thy thy T ^ ",.."
neuper@42376
   301
	    ^ ato body (n + 1)
neuper@42376
   302
	  | ato (f $ t) n = ato f n ^ ato t (n + 1)
neuper@42376
   303
    in "\n*** " ^ ato t 0 ^ "\n***" end;
neuper@38067
   304
fun atomwy t = (writeln o term_detail2str) t;
neuper@38067
   305
fun atomty t = (tracing o term_detail2str) t;
neuper@42376
   306
fun atomty_thy thy t = (tracing o (term_detail2str_thy thy)) t;
neuper@38025
   307
neuper@38025
   308
fun term_str thy (Const(s,_)) = s
neuper@38025
   309
  | term_str thy (Free(s,_)) = s
neuper@38025
   310
  | term_str thy (Var((s,i),_)) = s^(string_of_int i)
neuper@38025
   311
  | term_str thy (Bound i) = "B."^(string_of_int i)
neuper@38025
   312
  | term_str thy (Abs(s,_,_)) = s
neuper@38031
   313
  | term_str thy t = error("term_str not for "^term2str t);
neuper@38025
   314
neuper@38025
   315
(*.contains the fst argument the second argument (a leave! of term).*)
neuper@38025
   316
fun contains_term (Abs(_,_,body)) t = contains_term body t 
neuper@38025
   317
  | contains_term (f $ f') t = 
neuper@38025
   318
    contains_term f t orelse contains_term f' t
neuper@38025
   319
  | contains_term s t = t = s;
neuper@38025
   320
(*.contains the term a VAR(("*",_),_) ?.*)
neuper@38025
   321
fun contains_Var (Abs(_,_,body)) = contains_Var body
neuper@38025
   322
  | contains_Var (f $ f') = contains_Var f orelse contains_Var f'
neuper@38025
   323
  | contains_Var (Var _) = true
neuper@38025
   324
  | contains_Var _ = false;
neuper@38025
   325
(* contains_Var (str2term "?z = 3") (*true*);
neuper@38025
   326
   contains_Var (str2term "z = 3")  (*false*);
neuper@38025
   327
   *)
neuper@38025
   328
neuper@38025
   329
(*fun int_of_str str =
neuper@40836
   330
    let val ss = Symbol.explode str
neuper@38025
   331
	val str' = case ss of
neuper@38025
   332
	   "("::s => drop_last s | _ => ss
neuper@38025
   333
    in case BasisLibrary.Int.fromString (implode str') of
neuper@38025
   334
	     SOME i => SOME i
neuper@38025
   335
	   | NONE => NONE end;*)
wneuper@59390
   336
fun int_of_str_opt str =
wneuper@59390
   337
  let
wneuper@59390
   338
    val ss = Symbol.explode str
wneuper@59390
   339
    val str' = case ss of "(" :: s => drop_last s | _ => ss
wneuper@59390
   340
  in (SOME (Thy_Output.integer (implode str'))) handle _ => NONE end;
neuper@38025
   341
(*
neuper@38025
   342
> int_of_str "123";
neuper@38025
   343
val it = SOME 123 : int option
neuper@38025
   344
> int_of_str "(-123)";
neuper@38025
   345
val it = SOME 123 : int option
neuper@38025
   346
> int_of_str "#123";
neuper@38025
   347
val it = NONE : int option
neuper@38025
   348
> int_of_str "-123";
neuper@38025
   349
val it = SOME ~123 : int option
neuper@38025
   350
*)
wneuper@59390
   351
fun int_of_str str = 
wneuper@59390
   352
  case int_of_str_opt str of
wneuper@59390
   353
	  SOME i => i
wneuper@59390
   354
  | NONE => raise TERM ("int_of_string: no int-string",[]);
wneuper@59390
   355
val int_of_str = int_of_str;
neuper@38025
   356
    
wneuper@59390
   357
fun is_num' str = case int_of_str_opt str of
neuper@38025
   358
			 SOME _ => true
neuper@38025
   359
		       | NONE => false;
neuper@52064
   360
(* see /home/neuper/repos/FHpoly/src/HOL/Decision_Procs/Approximation.thy:
neuper@52064
   361
neuper@52064
   362
  val mk_int = HOLogic.mk_number @{typ int} o @{code integer_of_int};
neuper@52064
   363
  val dest_int = @{code int_of_integer} o snd o HOLogic.dest_number;
neuper@52064
   364
neuper@52064
   365
  fun nat_of_term t = @{code nat_of_integer}
neuper@52064
   366
    (HOLogic.dest_nat t handle TERM _ => snd (HOLogic.dest_number t));
neuper@52064
   367
  etc...
neuper@52064
   368
*)
wneuper@59390
   369
fun is_num (Free (s,_)) = if is_num' s then true else false
neuper@38025
   370
  | is_num _ = false;
neuper@38025
   371
(*>
wneuper@59186
   372
> is_num ((Thm.term_of o the o (parse thy)) "#1");
neuper@38025
   373
val it = true : bool
wneuper@59186
   374
> is_num ((Thm.term_of o the o (parse thy)) "#-1");
neuper@38025
   375
val it = true : bool
wneuper@59186
   376
> is_num ((Thm.term_of o the o (parse thy)) "a123");
neuper@38025
   377
val it = false : bool
neuper@38025
   378
*)
neuper@38025
   379
neuper@38025
   380
(*fun int_of_Free (Free (intstr, _)) =
neuper@38025
   381
    (case BasisLibrary.Int.fromString intstr of
neuper@38025
   382
	     SOME i => i
neuper@38031
   383
	   | NONE => error ("int_of_Free ( "^ intstr ^", _)"))
neuper@38031
   384
  | int_of_Free t = error ("int_of_Free ( "^ term2str t ^" )");*)
neuper@38025
   385
fun int_of_Free (Free (intstr, _)) = (Thy_Output.integer intstr
neuper@38031
   386
    handle _ => error ("int_of_Free ( "^ intstr ^", _)"))
neuper@38031
   387
  | int_of_Free t = error ("int_of_Free ( "^ term2str t ^" )");
neuper@38025
   388
neuper@38025
   389
fun vars t =
neuper@38025
   390
  let
neuper@38025
   391
    fun scan vs (Const(s,T)) = vs
wneuper@59390
   392
      | scan vs (t as Free(s,T)) = if is_num' s then vs else t::vs
neuper@38025
   393
      | scan vs (t as Var((s,i),T)) = t::vs
neuper@38025
   394
      | scan vs (Bound i) = vs 
neuper@38025
   395
      | scan vs (Abs(s,T,t)) = scan vs t
neuper@38025
   396
      | scan vs (t1 $ t2) = (scan vs t1) @ (scan vs t2)
neuper@38025
   397
  in (distinct o (scan [])) t end;
neuper@38025
   398
neuper@38025
   399
fun is_Free (Free _) = true
neuper@38025
   400
  | is_Free _ = false;
neuper@38025
   401
fun is_fun_id (Const _) = true
neuper@38025
   402
  | is_fun_id (Free _) = true
neuper@38025
   403
  | is_fun_id _ = false;
neuper@38025
   404
fun is_f_x (f $ x) = is_fun_id f andalso is_Free x
neuper@38025
   405
  | is_f_x _ = false;
neuper@38025
   406
(* is_f_x (str2term "q_0/2 * L * x") (*false*);
neuper@38025
   407
   is_f_x (str2term "M_b x") (*true*);
neuper@38025
   408
  *)
neuper@38025
   409
fun vars_str t =
neuper@38025
   410
  let
neuper@38025
   411
    fun scan vs (Const(s,T)) = vs
wneuper@59390
   412
      | scan vs (t as Free(s,T)) = if is_num' s then vs else s::vs
neuper@38025
   413
      | scan vs (t as Var((s,i),T)) = (s^"_"^(string_of_int i))::vs
neuper@38025
   414
      | scan vs (Bound i) = vs 
neuper@38025
   415
      | scan vs (Abs(s,T,t)) = scan vs t
neuper@38025
   416
      | scan vs (t1 $ t2) = (scan vs t1) @ (scan vs t2)
neuper@38025
   417
  in (distinct o (scan [])) t end;
neuper@38025
   418
neuper@38025
   419
fun ids2str t =
neuper@38025
   420
  let
wneuper@59390
   421
    fun scan vs (Const(s,T)) = if is_num' s then vs else s::vs
wneuper@59390
   422
      | scan vs (t as Free(s,T)) = if is_num' s then vs else s::vs
neuper@38025
   423
      | scan vs (t as Var((s,i),T)) = (s^"_"^(string_of_int i))::vs
neuper@38025
   424
      | scan vs (Bound i) = vs 
neuper@38025
   425
      | scan vs (Abs(s,T,t)) = scan (s::vs) t
neuper@38025
   426
      | scan vs (t1 $ t2) = (scan vs t1) @ (scan vs t2)
neuper@38025
   427
  in (distinct o (scan [])) t end;
neuper@38025
   428
fun is_bdv str =
neuper@40836
   429
    case Symbol.explode str of
neuper@38025
   430
	"b"::"d"::"v"::_ => true
neuper@38025
   431
      | _ => false;
neuper@38025
   432
fun is_bdv_ (Free (s,_)) = is_bdv s
neuper@38025
   433
  | is_bdv_ _ = false;
neuper@38025
   434
neuper@42426
   435
(* is a term a substitution for a bdv as found in programs *)
neuper@42426
   436
fun is_bdv_subst (Const ("List.list.Cons", _) $
neuper@42426
   437
      (Const ("Product_Type.Pair", _) $ Free (str, _) $ _) $ _) = is_bdv str
neuper@42426
   438
  | is_bdv_subst _ = false;
neuper@42426
   439
neuper@38025
   440
fun free2str (Free (s,_)) = s
neuper@52105
   441
  | free2str t = error ("free2str not for " ^ term2str t);
neuper@52103
   442
fun str_of_free_opt (Free (s,_)) = SOME s
neuper@52103
   443
  | str_of_free_opt _ = NONE
wneuper@59390
   444
fun free2int (t as Free (s, _)) = ((int_of_str s)
neuper@52105
   445
    handle _ => error ("free2int: " ^ term_detail2str t))
neuper@52105
   446
  | free2int t = error ("free2int: " ^ term_detail2str t);
neuper@38025
   447
neuper@42360
   448
(*compare Logic.unvarify_global, which rejects Free*)
neuper@38025
   449
fun var2free (t as Const(s,T)) = t
neuper@38025
   450
  | var2free (t as Free(s,T)) = t
neuper@38025
   451
  | var2free (Var((s,i),T)) = Free(s,T)
neuper@38025
   452
  | var2free (t as Bound i) = t 
neuper@38025
   453
  | var2free (Abs(s,T,t)) = Abs(s,T,var2free t)
neuper@38025
   454
  | var2free (t1 $ t2) = (var2free t1) $ (var2free t2);
neuper@38025
   455
  
neuper@38025
   456
(*27.8.01: doesn't find some subterm ???!???*)
neuper@38025
   457
(*2010 free2var -> Logic.varify, but take care of 'Free ("1",_)'*)
neuper@38025
   458
fun free2var (t as Const (s, T)) = t
wneuper@59390
   459
  | free2var (t as Free (s, T)) = if is_num' s then t else Var ((s, 0), T)
neuper@38025
   460
  | free2var (t as Var ((s, i), T)) = t
neuper@38025
   461
  | free2var (t as Bound i) = t 
neuper@38025
   462
  | free2var (Abs (s, T, t)) = Abs (s, T, free2var t)
neuper@38025
   463
  | free2var (t1 $ t2) = (free2var t1) $ (free2var t2);
neuper@38025
   464
  
neuper@38025
   465
neuper@38025
   466
fun mk_listT T = Type ("List.list", [T]);
neuper@38025
   467
fun list_const T = 
neuper@38025
   468
  Const("List.list.Cons", [T, mk_listT T] ---> mk_listT T);
neuper@38025
   469
(*28.8.01: TODO: get type from head of list: 1 arg less!!!*)
neuper@38025
   470
fun list2isalist T [] = Const("List.list.Nil",mk_listT T)
neuper@38025
   471
  | list2isalist T (t::ts) = (list_const T) $ t $ (list2isalist T ts);
neuper@38025
   472
(*
wneuper@59186
   473
> val tt = (Thm.term_of o the o (parse thy)) "R=(R::real)";
neuper@38025
   474
> val TT = type_of tt;
neuper@38025
   475
> val ss = list2isalist TT [tt,tt,tt];
wneuper@59184
   476
> (Thm.global_cterm_of thy) ss;
neuper@38025
   477
val it = "[R = R, R = R, R = R]" : cterm  *)
neuper@38025
   478
neuper@41972
   479
fun isapair2pair (Const ("Product_Type.Pair",_) $ a $ b) = (a,b)
neuper@38025
   480
  | isapair2pair t = 
neuper@38031
   481
    error ("isapair2pair called with "^term2str t);
neuper@38025
   482
neuper@38025
   483
val listType = Type ("List.list",[Type ("bool",[])]);
neuper@38025
   484
fun isalist2list ls =
neuper@38025
   485
  let
neuper@38025
   486
    fun get es (Const("List.list.Cons",_) $ t $ ls) = get (t::es) ls
neuper@38025
   487
      | get es (Const("List.list.Nil",_)) = es
neuper@38025
   488
      | get _ t = 
neuper@38031
   489
	error ("isalist2list applied to NON-list '"^term2str t^"'")
neuper@38025
   490
  in (rev o (get [])) ls end;
neuper@38025
   491
(*      
neuper@38025
   492
> val il = str2term "[a=b,c=d,e=f]";
neuper@38025
   493
> val l = isalist2list il;
neuper@38025
   494
> (tracing o terms2str) l;
neuper@38025
   495
["a = b","c = d","e = f"]
neuper@38025
   496
neuper@38025
   497
> val il = str2term "ss___::bool list";
neuper@38025
   498
> val l = isalist2list il;
neuper@38025
   499
[Free ("ss___", "bool List.list")]
neuper@38025
   500
*)
neuper@38025
   501
neuper@38025
   502
(*review Isabelle2009/src/HOL/Tools/hologic.ML*)
neuper@41924
   503
(*val prop = Type ("HOL.Trueprop",[]);      ~/Diss.99/Integers-Isa/tools.sml*)
neuper@41924
   504
val Trueprop = HOLogic.Trueprop;
neuper@41924
   505
fun mk_prop t = HOLogic.mk_Trueprop t;
wneuper@59333
   506
val true_as_cterm = Thm.global_cterm_of (Thy_Info.get_theory "HOL.HOL") @{term True};
wneuper@59333
   507
val false_as_cterm = Thm.global_cterm_of (Thy_Info.get_theory "HOL.HOL") @{term False};
neuper@38025
   508
neuper@38025
   509
infixr 5 -->;                    (*2002 /Pure/term.ML *)
neuper@38025
   510
infixr --->;			 (*2002 /Pure/term.ML *)
neuper@38025
   511
fun S --> T = Type("fun",[S,T]); (*2002 /Pure/term.ML *)
neuper@38025
   512
val op ---> = foldr (op -->);    (*2002 /Pure/term.ML *)
neuper@38025
   513
neuper@38025
   514
neuper@38025
   515
(** substitution **)
neuper@38025
   516
neuper@38025
   517
fun match_bvs(Abs(x,_,s),Abs(y,_,t), al) =      (* = thm.ML *)
neuper@38025
   518
      match_bvs(s, t, if x="" orelse y="" then al
neuper@38025
   519
                                          else (x,y)::al)
neuper@38025
   520
  | match_bvs(f$s, g$t, al) = match_bvs(f,g,match_bvs(s,t,al))
neuper@38025
   521
  | match_bvs(_,_,al) = al;
neuper@38025
   522
fun ren_inst(insts,prop,pat,obj) =              (* = thm.ML *)
neuper@38025
   523
  let val ren = match_bvs(pat,obj,[])
neuper@38025
   524
      fun renAbs(Abs(x,T,b)) =
neuper@38025
   525
            Abs(case assoc_string(ren,x) of NONE => x 
neuper@38025
   526
	  | SOME(y) => y, T, renAbs(b))
neuper@38025
   527
        | renAbs(f$t) = renAbs(f) $ renAbs(t)
neuper@38025
   528
        | renAbs(t) = t
neuper@38025
   529
  in subst_vars insts (if null(ren) then prop else renAbs(prop)) end;
neuper@38025
   530
neuper@38025
   531
neuper@38025
   532
neuper@38025
   533
neuper@38025
   534
neuper@38025
   535
wneuper@59390
   536
fun dest_equals (Const("HOL.eq",_) $ t $ u)  =  (t,u) (* Pure/logic.ML: Const("=="*)
wneuper@59390
   537
  | dest_equals t = raise TERM ("dest_equals'", [t]);
wneuper@59390
   538
val lhs_ = (fst o dest_equals);
wneuper@59390
   539
val rhs_ = (snd o dest_equals);
neuper@38025
   540
wneuper@59390
   541
fun is_equality (Const("HOL.eq",_) $ _ $ _)  =  true  (* logic.ML: Const("=="*)
neuper@38025
   542
  | is_equality _ = false;
wneuper@59390
   543
fun mk_equality (t,u) = (Const("HOL.eq",[type_of t,type_of u] ---> HOLogic.boolT) $ t $ u); 
wneuper@59390
   544
fun is_expliceq (Const("HOL.eq",_) $ (Free _) $ _)  =  true
neuper@38025
   545
  | is_expliceq _ = false;
wneuper@59390
   546
fun strip_trueprop (Const ("HOL.Trueprop", _) $ t) = t
neuper@38025
   547
  | strip_trueprop t = t;
neuper@38025
   548
(*  | strip_trueprop t = raise TERM("strip_trueprop", [t]);
neuper@38025
   549
*)
neuper@38025
   550
neuper@38025
   551
(*.(A1==>...An==>B) goes to (A1==>...An==>).*)
neuper@38025
   552
fun strip_imp_prems' (Const("==>", T) $ A $ t) = 
neuper@38025
   553
    let fun coll_prems As (Const("==>", _) $ A $ t) = 
neuper@38025
   554
	    coll_prems (As $ (Logic.implies $ A)) t
neuper@38025
   555
	  | coll_prems As _ = SOME As
neuper@38025
   556
    in coll_prems (Logic.implies $ A) t end
neuper@38025
   557
  | strip_imp_prems' _ = NONE;  (* logic.ML: term -> term list*)
neuper@38025
   558
(*
neuper@38025
   559
  val thm = real_mult_div_cancel1;
neuper@38025
   560
  val prop = (#prop o rep_thm) thm;
neuper@38025
   561
  atomt prop;
neuper@38025
   562
*** -------------
neuper@38025
   563
*** Const ( ==>)
neuper@38025
   564
*** . Const ( Trueprop)
neuper@38025
   565
*** . . Const ( Not)
neuper@38025
   566
*** . . . Const ( op =)
neuper@38025
   567
*** . . . . Var ((k, 0), )
neuper@38025
   568
*** . . . . Const ( 0)
neuper@38025
   569
*** . Const ( Trueprop)
neuper@38025
   570
*** . . Const ( op =)                                                          *** .............
neuper@38025
   571
  val SOME t = strip_imp_prems' ((#prop o rep_thm) thm);
neuper@38025
   572
  atomt t;
neuper@38025
   573
*** -------------
neuper@38025
   574
*** Const ( ==>)
neuper@38025
   575
*** . Const ( Trueprop)
neuper@38025
   576
*** . . Const ( Not)
neuper@38025
   577
*** . . . Const ( op =)
neuper@38025
   578
*** . . . . Var ((k, 0), )
neuper@38025
   579
*** . . . . Const ( 0)
neuper@38025
   580
neuper@38025
   581
  val thm = real_le_anti_sym;
neuper@38025
   582
  val prop = (#prop o rep_thm) thm;
neuper@38025
   583
  atomt prop;
neuper@38025
   584
*** -------------
neuper@38025
   585
*** Const ( ==>)
neuper@38025
   586
*** . Const ( Trueprop)
neuper@38025
   587
*** . . Const ( op <=)
neuper@38025
   588
*** . . . Var ((z, 0), )
neuper@38025
   589
*** . . . Var ((w, 0), )
neuper@38025
   590
*** . Const ( ==>)
neuper@38025
   591
*** . . Const ( Trueprop)
neuper@38025
   592
*** . . . Const ( op <=)
neuper@38025
   593
*** . . . . Var ((w, 0), )
neuper@38025
   594
*** . . . . Var ((z, 0), )
neuper@38025
   595
*** . . Const ( Trueprop)
neuper@38025
   596
*** . . . Const ( op =)
neuper@38025
   597
*** .............
neuper@38025
   598
  val SOME t = strip_imp_prems' ((#prop o rep_thm) thm);
neuper@38025
   599
  atomt t;
neuper@38025
   600
*** -------------
neuper@38025
   601
*** Const ( ==>)
neuper@38025
   602
*** . Const ( Trueprop)
neuper@38025
   603
*** . . Const ( op <=)
neuper@38025
   604
*** . . . Var ((z, 0), )
neuper@38025
   605
*** . . . Var ((w, 0), )
neuper@38025
   606
*** . Const ( ==>)
neuper@38025
   607
*** . . Const ( Trueprop)
neuper@38025
   608
*** . . . Const ( op <=)
neuper@38025
   609
*** . . . . Var ((w, 0), )
neuper@38025
   610
*** . . . . Var ((z, 0), )
neuper@38025
   611
*)
neuper@38025
   612
neuper@38025
   613
(*. (A1==>...An==>) (B) goes to (A1==>...An==>B), where B is lowest branch.*)
wneuper@59390
   614
fun ins_concl (Const ("==>", _) $ A $ t) B = Logic.implies $ A $ (ins_concl t B)
wneuper@59390
   615
  | ins_concl (Const ("==>", _) $ A    ) B = Logic.implies $ A $ B
wneuper@59390
   616
  | ins_concl t B =  raise TERM ("ins_concl", [t, B]);
neuper@38025
   617
(*
neuper@38025
   618
  val thm = real_le_anti_sym;
neuper@38025
   619
  val prop = (#prop o rep_thm) thm;
neuper@38025
   620
  val concl = Logic.strip_imp_concl prop;
neuper@38025
   621
  val SOME prems = strip_imp_prems' prop;
neuper@38025
   622
  val prop' = ins_concl prems concl;
neuper@38025
   623
  prop = prop';
neuper@38025
   624
  atomt prop;
neuper@38025
   625
  atomt prop';
neuper@38025
   626
*)
neuper@38025
   627
neuper@38025
   628
neuper@38025
   629
fun vperm (Var _, Var _) = true  (*2002 Pure/thm.ML *)
neuper@38025
   630
  | vperm (Abs (_, _, s), Abs (_, _, t)) = vperm (s, t)
neuper@38025
   631
  | vperm (t1 $ t2, u1 $ u2) = vperm (t1, u1) andalso vperm (t2, u2)
neuper@38025
   632
  | vperm (t, u) = (t = u);
neuper@38025
   633
neuper@38025
   634
(*2002 cp from Pure/term.ML --- since 2009 in Pure/old_term.ML*)
neuper@38025
   635
fun mem_term (_, []) = false
wneuper@59390
   636
  | mem_term (t, t'::ts) = t aconv t' orelse mem_term (t, ts);
wneuper@59390
   637
fun subset_term ([], _) = true
wneuper@59390
   638
  | subset_term (x :: xs, ys) = mem_term (x, ys) andalso subset_term (xs, ys);
neuper@38025
   639
fun eq_set_term (xs, ys) =
neuper@38025
   640
    xs = ys orelse (subset_term (xs, ys) andalso subset_term (ys, xs));
neuper@38025
   641
(*a total, irreflexive ordering on index names*)
neuper@38025
   642
fun xless ((a,i), (b,j): indexname) = i<j  orelse  (i=j andalso a<b);
neuper@38025
   643
(*a partial ordering (not reflexive) for atomic terms*)
neuper@38025
   644
fun atless (Const (a,_), Const (b,_))  =  a<b
neuper@38025
   645
  | atless (Free (a,_), Free (b,_)) =  a<b
neuper@38025
   646
  | atless (Var(v,_), Var(w,_))  =  xless(v,w)
neuper@38025
   647
  | atless (Bound i, Bound j)  =   i<j
neuper@38025
   648
  | atless _  =  false;
neuper@38025
   649
(*insert atomic term into partially sorted list, suppressing duplicates (?)*)
neuper@38025
   650
fun insert_aterm (t,us) =
neuper@38025
   651
  let fun inserta [] = [t]
neuper@38025
   652
        | inserta (us as u::us') =
neuper@38025
   653
              if atless(t,u) then t::us
neuper@38025
   654
              else if t=u then us (*duplicate*)
neuper@38025
   655
              else u :: inserta(us')
neuper@38025
   656
  in  inserta us  end;
neuper@38025
   657
wneuper@59390
   658
(* Accumulates the Vars in the term, suppressing duplicates *)
neuper@38025
   659
fun add_term_vars (t, vars: term list) = case t of
neuper@38025
   660
    Var   _ => insert_aterm(t,vars)
neuper@38025
   661
  | Abs (_,_,body) => add_term_vars(body,vars)
neuper@38025
   662
  | f$t =>  add_term_vars (f, add_term_vars(t, vars))
neuper@38025
   663
  | _ => vars;
wneuper@59390
   664
fun term_vars t = add_term_vars (t, []);
neuper@38025
   665
neuper@38025
   666
neuper@38025
   667
fun var_perm (t, u) = (*2002 Pure/thm.ML *)
neuper@38025
   668
  vperm (t, u) andalso eq_set_term (term_vars t, term_vars u);
neuper@38025
   669
    
neuper@38025
   670
(*2002 fun decomp_simp, Pure/thm.ML *)
wneuper@59390
   671
fun perm lhs rhs = var_perm (lhs, rhs) andalso not (lhs aconv rhs) andalso not (is_Var lhs);
neuper@38025
   672
neuper@38025
   673
neuper@38025
   674
fun str_of_int n = 
neuper@38025
   675
  if n < 0 then "-"^((string_of_int o abs) n)
neuper@38025
   676
  else string_of_int n;
neuper@38025
   677
(*
neuper@38025
   678
> str_of_int 1;
neuper@38025
   679
val it = "1" : string                                                          > str_of_int ~1;
neuper@38025
   680
val it = "-1" : string
neuper@38025
   681
*)
neuper@38025
   682
neuper@38025
   683
neuper@38025
   684
fun power b 0 = 1
neuper@38025
   685
  | power b n = 
neuper@38025
   686
  if n>0 then b*(power b (n-1))
neuper@38031
   687
  else error ("power "^(str_of_int b)^" "^(str_of_int n));
neuper@38025
   688
(*
neuper@38025
   689
> power 2 3;
neuper@38025
   690
val it = 8 : int
neuper@38025
   691
> power ~2 3;
neuper@38025
   692
val it = ~8 : int
neuper@38025
   693
> power ~3 2;
neuper@38025
   694
val it = 9 : int
neuper@38025
   695
> power 3 ~2;
neuper@38025
   696
*)
neuper@38025
   697
fun gcd 0 b = b
neuper@38025
   698
  | gcd a b = if a < b then gcd (b mod a) a
neuper@38025
   699
	      else gcd (a mod b) b;
neuper@38025
   700
fun sign n = if n < 0 then ~1
neuper@38025
   701
	     else if n = 0 then 0 else 1;
neuper@38025
   702
fun sign2 n1 n2 = (sign n1) * (sign n2);
neuper@38025
   703
neuper@38025
   704
infix dvd;
neuper@38025
   705
fun d dvd n = n mod d = 0;
neuper@38025
   706
neuper@38025
   707
fun divisors n =
neuper@38025
   708
  let fun pdiv ds d n = 
neuper@38025
   709
    if d=n then d::ds
neuper@38025
   710
    else if d dvd n then pdiv (d::ds) d (n div d)
neuper@38025
   711
	 else pdiv ds (d+1) n
neuper@38025
   712
  in pdiv [] 2 n end;
neuper@38025
   713
wneuper@59389
   714
(*
neuper@38025
   715
divisors 30;
neuper@38025
   716
divisors 32;
neuper@38025
   717
divisors 60;
neuper@38025
   718
divisors 11;
wneuper@59389
   719
*)
neuper@38025
   720
neuper@38025
   721
fun doubles ds = (* ds is ordered *)
neuper@38025
   722
  let fun dbls ds [] = ds
neuper@38025
   723
	| dbls ds [i] = ds
neuper@38025
   724
	| dbls ds (i::i'::is) = if i=i' then dbls (i::ds) is
neuper@38025
   725
				else dbls ds (i'::is)
neuper@38025
   726
  in dbls [] ds end;
neuper@38025
   727
(*> doubles [2,3,4];
neuper@38025
   728
val it = [] : int list
neuper@38025
   729
> doubles [2,3,3,5,5,7];
neuper@38025
   730
val it = [5,3] : int list*)
neuper@38025
   731
neuper@38025
   732
fun squfact 0 = 0
neuper@38025
   733
  | squfact 1 = 1
neuper@38025
   734
  | squfact n = foldl op* (1, (doubles o divisors) n);
neuper@38025
   735
(*> squfact 30;
neuper@38025
   736
val it = 1 : int
neuper@38025
   737
> squfact 32;
neuper@38025
   738
val it = 4 : int
neuper@38025
   739
> squfact 60;
neuper@38025
   740
val it = 2 : int
neuper@38025
   741
> squfact 11;
neuper@38025
   742
val it = 1 : int*)
neuper@38025
   743
neuper@38025
   744
neuper@38025
   745
fun dest_type (Type(T,[])) = T
neuper@38025
   746
  | dest_type T = 
neuper@38025
   747
    (atomtyp T;
neuper@38031
   748
     error ("... dest_type: not impl. for this type"));
neuper@38025
   749
neuper@38025
   750
fun term_of_num ntyp n = Free (str_of_int n, ntyp);
neuper@38025
   751
neuper@38025
   752
fun pairT T1 T2 = Type ("*", [T1, T2]);
neuper@38025
   753
(*> val t = str2term "(1,2)";
neuper@38025
   754
> type_of t = pairT HOLogic.realT HOLogic.realT;
neuper@38025
   755
val it = true : bool
neuper@38025
   756
*)
neuper@38025
   757
fun PairT T1 T2 = ([T1, T2] ---> Type ("*", [T1, T2]));
neuper@38025
   758
(*> val t = str2term "(1,2)";
neuper@41972
   759
> val Const ("Product_Type.Pair",pT) $ _ $ _ = t;
neuper@38025
   760
> pT = PairT HOLogic.realT HOLogic.realT;
neuper@38025
   761
val it = true : bool
neuper@38025
   762
*)
neuper@38025
   763
fun pairt t1 t2 =
neuper@41972
   764
    Const ("Product_Type.Pair", PairT (type_of t1) (type_of t2)) $ t1 $ t2;
neuper@38025
   765
(*> val t = str2term "(1,2)";
neuper@38025
   766
> val (t1, t2) = (str2term "1", str2term "2");
neuper@38025
   767
> t = pairt t1 t2;
neuper@38025
   768
val it = true : bool*)
neuper@38025
   769
neuper@38025
   770
neuper@38025
   771
fun num_of_term (t as Free (s,_)) = 
wneuper@59390
   772
    (case int_of_str_opt s of
neuper@38025
   773
	 SOME s' => s'
neuper@38031
   774
       | NONE => error ("num_of_term not for "^ term2str t))
neuper@38031
   775
  | num_of_term t = error ("num_of_term not for "^term2str t);
neuper@38025
   776
neuper@38025
   777
fun mk_factroot op_(*=thy.sqrt*) T fact root = 
neuper@38034
   778
  Const ("Groups.times_class.times", [T, T] ---> T) $ (term_of_num T fact) $
neuper@38025
   779
  (Const (op_, T --> T) $ term_of_num T root);
neuper@38025
   780
(*
wneuper@59186
   781
val T =  (type_of o Thm.term_of o the) (parse thy "#12::real");
neuper@38025
   782
val t = mk_factroot "SqRoot.sqrt" T 2 3;
wneuper@59184
   783
(Thm.global_cterm_of thy) t;
neuper@38025
   784
val it = "#2 * sqrt #3 " : cterm
neuper@38025
   785
*)
wneuper@59390
   786
fun mk_var_op_num v op_ optype ntyp n = Const (op_, optype) $ v $ Free (str_of_int  n, ntyp);
wneuper@59390
   787
fun mk_num_op_var v op_ optype ntyp n = Const (op_, optype) $ Free (str_of_int n, ntyp) $ v;
wneuper@59390
   788
fun mk_num_op_num T1 T2 (op_, Top) n1 n2 =
wneuper@59390
   789
  Const (op_, Top) $ Free (str_of_int n1, T1) $ Free (str_of_int n2, T2);
neuper@38025
   790
(*
wneuper@59390
   791
> val t = mk_num_op_num "Int" 3 4;
neuper@38025
   792
> atomty t;
wneuper@59184
   793
> string_of_cterm ((Thm.global_cterm_of thy) t);
neuper@38025
   794
*)
neuper@38025
   795
neuper@41931
   796
neuper@41931
   797
neuper@38025
   798
fun const_in str (Const _) = false
neuper@38025
   799
  | const_in str (Free (s,_)) = if strip_thy s = str then true else false
neuper@38025
   800
  | const_in str (Bound _) = false
neuper@38025
   801
  | const_in str (Var _) = false
neuper@38025
   802
  | const_in str (Abs (_,_,body)) = const_in str body
neuper@38025
   803
  | const_in str (f$u) = const_in str f orelse const_in str u;
neuper@38025
   804
(*
wneuper@59186
   805
> val t = (Thm.term_of o the o (parse thy)) "6 + 5 * sqrt 4 + 3";
neuper@38025
   806
> const_in "sqrt" t;
neuper@38025
   807
val it = true : bool
wneuper@59186
   808
> val t = (Thm.term_of o the o (parse thy)) "6 + 5 * 4 + 3";
neuper@38025
   809
> const_in "sqrt" t;
neuper@38025
   810
val it = false : bool
neuper@38025
   811
*)
neuper@38025
   812
neuper@38025
   813
(*used for calculating built in binary operations in Isabelle2002->Float.ML*)
neuper@38025
   814
(*fun calc "Groups.plus_class.plus"  (n1, n2) = n1+n2
neuper@38025
   815
  | calc "Groups.minus_class.minus"  (n1, n2) = n1-n2
neuper@38034
   816
  | calc "Groups.times_class.times"  (n1, n2) = n1*n2
wneuper@59360
   817
  | calc "Rings.divide_class.divide"(n1, n2) = n1 div n2
neuper@38025
   818
  | calc "Atools.pow"(n1, n2) = power n1 n2
neuper@38031
   819
  | calc op_ _ = error ("calc: operator = "^op_^" not defined");-----*)
neuper@38046
   820
fun calc_equ "less"  (n1, n2) = n1 < n2
neuper@38046
   821
  | calc_equ "less_eq" (n1, n2) = n1 <= n2
wneuper@59390
   822
  | calc_equ op_ _ = error ("calc_equ: operator = " ^ op_ ^ " not defined");
neuper@38025
   823
fun sqrt (n:int) = if n < 0 then 0
neuper@38025
   824
    (*FIXME ~~~*)  else (trunc o Math.sqrt o Real.fromInt) n;
neuper@38025
   825
neuper@38025
   826
fun mk_thmid thmid op_ n1 n2 = 
neuper@38025
   827
  thmid ^ (strip_thy n1) ^ "_" ^ (strip_thy n2);
neuper@38025
   828
neuper@38025
   829
fun dest_binop_typ (Type("fun",[range,Type("fun",[arg2,arg1])])) =
neuper@38025
   830
  (arg1,arg2,range)
neuper@38031
   831
  | dest_binop_typ _ = error "dest_binop_typ: not binary";
neuper@38025
   832
(* -----
wneuper@59186
   833
> val t = (Thm.term_of o the o (parse thy)) "#3^#4";
neuper@38025
   834
> val hT = type_of (head_of t);
neuper@38025
   835
> dest_binop_typ hT;
neuper@38025
   836
val it = ("'a","nat","'a") : typ * typ * typ
neuper@38025
   837
 ----- *)
neuper@38025
   838
neuper@38025
   839
neuper@38025
   840
(** transform binary numeralsstrings **)
neuper@38025
   841
(*Makarius 100308, hacked by WN*)
neuper@38025
   842
val numbers_to_string =
neuper@38025
   843
  let
neuper@38025
   844
    fun dest_num t =
neuper@38025
   845
      (case try HOLogic.dest_number t of
neuper@38025
   846
        SOME (T, i) =>
neuper@38025
   847
          (*if T = @{typ int} orelse T = @{typ real} then WN*)
neuper@38025
   848
            SOME (Free (signed_string_of_int i, T))
neuper@38025
   849
          (*else NONE  WN*)
neuper@38025
   850
      | NONE => NONE);
neuper@38025
   851
neuper@38025
   852
    fun to_str (Abs (x, T, b)) = Abs (x, T, to_str b)
neuper@38025
   853
      | to_str (t as (u1 $ u2)) =
neuper@38025
   854
          (case dest_num t of
neuper@38025
   855
            SOME t' => t'
neuper@38025
   856
          | NONE => to_str u1 $ to_str u2)
neuper@38025
   857
      | to_str t = perhaps dest_num t;
neuper@38025
   858
  in to_str end
neuper@38025
   859
neuper@38025
   860
(*.make uminus uniform: 
neuper@38025
   861
   Const ("uminus", _) $ Free ("2", "RealDef.real") --> Free ("-2", _)
neuper@38025
   862
to be used immediately before evaluation of numerals; 
neuper@38025
   863
see Scripts/calculate.sml .*)
neuper@38025
   864
(*2002 fun(*app_num_tr'2 (Const("0",T)) = Free("0",T)
neuper@38025
   865
  | app_num_tr'2 (Const("1",T)) = Free("1",T)
neuper@38025
   866
  |*)app_num_tr'2 (t as Const("uminus",_) $ Free(s,T)) = 
wneuper@59390
   867
    (case int_of_str_opt s of SOME i => 
neuper@38025
   868
			  if i > 0 then Free("-"^s,T) else Free(s,T)
neuper@38025
   869
		       | NONE => t)
neuper@38025
   870
(*| app_num_tr'2 (t as Const(s,T)) = t
neuper@38025
   871
  | app_num_tr'2 (Const("Numeral.number_of",Type ("fun", [_, T])) $ t) = 
neuper@38025
   872
    Free(NumeralSyntax.dest_bin_str t, T)
neuper@38025
   873
  | app_num_tr'2 (t as Free(s,T)) = t
neuper@38025
   874
  | app_num_tr'2 (t as Var(n,T)) = t
neuper@38025
   875
  | app_num_tr'2 (t as Bound i) = t
neuper@38025
   876
*)| app_num_tr'2 (Abs(s,T,body)) = Abs(s,T, app_num_tr'2 body)
neuper@38025
   877
  | app_num_tr'2 (t1 $ t2) = (app_num_tr'2 t1) $ (app_num_tr'2 t2)
neuper@38025
   878
  | app_num_tr'2 t = t;
neuper@38025
   879
*)
neuper@38025
   880
val uminus_to_string =
neuper@38025
   881
    let
neuper@38025
   882
	fun dest_num t =
neuper@38025
   883
	    (case t of
neuper@38025
   884
		 (Const ("Groups.uminus_class.uminus", _) $ Free (s, T)) => 
wneuper@59390
   885
		 (case int_of_str_opt s of
neuper@38025
   886
		      SOME i => 
neuper@38025
   887
		      SOME (Free (signed_string_of_int (~1 * i), T))
neuper@38025
   888
		    | NONE => NONE)
neuper@38025
   889
	       | _ => NONE);
neuper@38025
   890
	    
neuper@38025
   891
	fun to_str (Abs (x, T, b)) = Abs (x, T, to_str b)
neuper@38025
   892
	  | to_str (t as (u1 $ u2)) =
neuper@38025
   893
            (case dest_num t of
neuper@38025
   894
		 SOME t' => t'
neuper@38025
   895
               | NONE => to_str u1 $ to_str u2)
neuper@38025
   896
	  | to_str t = perhaps dest_num t;
neuper@38025
   897
    in to_str end;
neuper@38025
   898
neuper@38025
   899
neuper@38025
   900
(*2002 fun num_str thm =
neuper@38025
   901
  let 
neuper@38025
   902
    val {sign_ref = sign_ref, der = der, maxidx = maxidx,
neuper@38025
   903
	    shyps = shyps, hyps = hyps, (*tpairs = tpairs,*) prop = prop} = 
wneuper@59185
   904
	Thm.rep_thm_G thm;
neuper@38025
   905
    val prop' = app_num_tr'1 prop;
wneuper@59185
   906
  in Thm.assbl_thm sign_ref der maxidx shyps hyps (*tpairs*) prop' end;*)
neuper@38025
   907
fun num_str thm =
neuper@38025
   908
  let val (deriv, 
wneuper@59333
   909
	   {cert = cert, tags = tags, maxidx = maxidx, shyps = shyps, 
wneuper@59185
   910
	    hyps = hyps, tpairs = tpairs, prop = prop}) = Thm.rep_thm_G thm
neuper@38025
   911
    val prop' = numbers_to_string prop;
wneuper@59333
   912
  in Thm.assbl_thm deriv cert tags maxidx shyps hyps tpairs prop' end;
neuper@38025
   913
neuper@38025
   914
fun get_thm' xstring = (*?covers 2009 Thm?!, replaces 2002 fun get_thm :
neuper@38025
   915
val it = fn : theory -> xstring -> Thm.thm*)
neuper@38025
   916
    Thm (xstring, 
neuper@48761
   917
	 num_str (Proof_Context.get_thm (thy2ctxt' "Isac") xstring)); 
neuper@38025
   918
neuper@38025
   919
(** get types of Free and Abs for parse' **)
neuper@38025
   920
(*11.1.00: not used, fix-typed +,*,-,^ instead *)
neuper@38025
   921
neuper@38025
   922
val dummyT = Type ("dummy",[]);
neuper@38025
   923
val dummyT = TVar (("DUMMY",0),[]);
neuper@38025
   924
neuper@38025
   925
(* assumes only 1 type for numerals 
neuper@38025
   926
   and different identifiers for Const, Free and Abs *)
neuper@38025
   927
fun get_types t = 
neuper@38025
   928
  let
neuper@38025
   929
    fun get ts  (Const(s,T)) = (s,T)::ts
wneuper@59390
   930
      | get ts  (Free(s,T)) = if is_num' s 
neuper@38025
   931
				then ("#",T)::ts else (s,T)::ts
neuper@38025
   932
      | get ts  (Var(n,T)) = ts
neuper@38025
   933
      | get ts  (Bound i) = ts
neuper@38025
   934
      | get ts  (Abs(s,T,body)) = get ((s,T)::ts)  body
neuper@38025
   935
      | get ts  (t1 $ t2) = (get ts  t1) @ (get ts  t2)
neuper@38025
   936
  in distinct (get [] t) end;
neuper@38025
   937
(*
wneuper@59186
   938
val t = (Thm.term_of o the o (parse thy)) "sqrt(#9+#4*x)=sqrt x + sqrt(#-3+x)";
neuper@38025
   939
get_types t;
neuper@38025
   940
*)
neuper@38025
   941
neuper@38025
   942
(*11.1.00: not used, fix-typed +,*,-,^ instead *)
neuper@38025
   943
fun set_types al (Const(s,T)) = 
neuper@38025
   944
    (case assoc (al,s) of
neuper@38025
   945
       SOME T' => Const(s,T')
neuper@38025
   946
     | NONE => (warning ("set_types: no type for "^s); Const(s,dummyT)))
neuper@38025
   947
  | set_types al (Free(s,T)) = 
wneuper@59390
   948
  if is_num' s then
neuper@38025
   949
    (case assoc (al,"#") of
neuper@38025
   950
      SOME T' => Free(s,T')
neuper@38025
   951
    | NONE => (warning ("set_types: no type for numerals"); Free(s,T)))
neuper@38025
   952
  else (case assoc (al,s) of
neuper@38025
   953
	       SOME T' => Free(s,T')
neuper@38025
   954
	     | NONE => (warning ("set_types: no type for "^s); Free(s,T)))
neuper@38025
   955
  | set_types al (Var(n,T)) = Var(n,T)
neuper@38025
   956
  | set_types al (Bound i) = Bound i
neuper@38025
   957
  | set_types al (Abs(s,T,body)) = 
neuper@38025
   958
		 (case assoc (al,s) of
neuper@38025
   959
		    SOME T'  => Abs(s,T', set_types al body)
neuper@38025
   960
		  | NONE => (warning ("set_types: no type for "^s);
neuper@38025
   961
			     Abs(s,T, set_types al body)))
neuper@38025
   962
  | set_types al (t1 $ t2) = (set_types al t1) $ (set_types al t2);
neuper@38025
   963
(*
wneuper@59186
   964
val t = (Thm.term_of o the o (parse thy)) "sqrt(#9+#4*x)=sqrt x + sqrt(#-3+x)";
neuper@38025
   965
val al = get_types t;
neuper@38025
   966
wneuper@59186
   967
val t = (Thm.term_of o the o (parse thy)) "x = #0 + #-1 * #-4";
neuper@38025
   968
atomty t;                         (* 'a *)
neuper@38025
   969
val t' = set_types al t;
neuper@38025
   970
atomty t';                        (*real*)
wneuper@59184
   971
(Thm.global_cterm_of thy) t';
neuper@38025
   972
val it = "x = #0 + #-1 * #-4" : cterm
neuper@38025
   973
wneuper@59186
   974
val t = (Thm.term_of o the o (parse thy)) 
neuper@38025
   975
  "#5 * x + x ^^^ #2 = (#2 + x) ^^^ #2";
neuper@38025
   976
atomty t;
neuper@38025
   977
val t' = set_types al t;
neuper@38025
   978
atomty t';
wneuper@59184
   979
(Thm.global_cterm_of thy) t';
neuper@38025
   980
uncaught exception TYPE               (*^^^ is new, NOT in al*)
neuper@38025
   981
*)
neuper@38025
   982
      
neuper@38025
   983
neuper@38025
   984
(** from Descript.ML **)
neuper@38025
   985
neuper@38025
   986
(** decompose an isa-list to an ML-list 
neuper@38025
   987
    i.e. [] belong to the meta-language, too **)
neuper@38025
   988
neuper@38025
   989
fun is_list ((Const("List.list.Cons",_)) $ _ $ _) = true
neuper@38025
   990
  | is_list _ = false;
neuper@38025
   991
(* val (SOME ct) = parse thy "lll::real list";
neuper@38025
   992
> val ty = (#t o rep_cterm) ct;
neuper@38025
   993
> is_list ty;
neuper@38025
   994
val it = false : bool
neuper@38025
   995
> val (SOME ct) = parse thy "[lll]";
neuper@38025
   996
> val ty = (#t o rep_cterm) ct;
neuper@38025
   997
> is_list ty;
neuper@38025
   998
val it = true : bool *)
neuper@38025
   999
neuper@38025
  1000
neuper@38025
  1001
neuper@38025
  1002
fun mk_Free (s,T) = Free(s,T);
neuper@38025
  1003
fun mk_free T s =  Free(s,T);
neuper@38025
  1004
neuper@38025
  1005
(*Special case: one argument cp from Isabelle2002/src/Pure/term.ML*)
neuper@38025
  1006
fun subst_bound (arg, t) : term = (*WN100908 neglects 'raise Same.SAME'*)
neuper@38025
  1007
  let fun subst (t as Bound i, lev) =
neuper@38025
  1008
            if i<lev then  t    (*var is locally bound*)
neuper@38025
  1009
            else  if i=lev then incr_boundvars lev arg
neuper@38025
  1010
                           else Bound(i-1)  (*loose: change it*)
neuper@38025
  1011
        | subst (Abs(a,T,body), lev) = Abs(a, T,  subst(body,lev+1))
neuper@38025
  1012
        | subst (f$t, lev) =  subst(f,lev)  $  subst(t,lev)
neuper@38025
  1013
        | subst (t,lev) = t
neuper@38025
  1014
  in  subst (t,0)  end;
neuper@38025
  1015
neuper@38025
  1016
(*instantiate let; necessary for ass_up*)
neuper@38025
  1017
fun inst_abs thy (Const sT) = Const sT  (*TODO.WN100907 drop thy*)
neuper@38025
  1018
  | inst_abs thy (Free sT) = Free sT
neuper@38025
  1019
  | inst_abs thy (Bound n) = Bound n
neuper@38025
  1020
  | inst_abs thy (Var iT) = Var iT
neuper@41968
  1021
  | inst_abs thy (Const ("HOL.Let",T1) $ e $ (Abs (v, T2, b))) = 
neuper@38025
  1022
    let val b' = subst_bound (Free (v, T2), b);
neuper@38025
  1023
    (*fun variant_abs: term.ML*)
neuper@41968
  1024
    in Const ("HOL.Let", T1) $ inst_abs thy e $ (Abs (v, T2, inst_abs thy b')) end
neuper@38025
  1025
  | inst_abs thy (t1 $ t2) = inst_abs thy t1 $ inst_abs thy t2
neuper@38025
  1026
  | inst_abs thy t = t;
neuper@38025
  1027
(*val scr =    
neuper@38025
  1028
   "Script Make_fun_by_explicit (f_::real) (v_::real) (eqs_::bool list) = \
neuper@38025
  1029
   \ (let h_ = (hd o (filterVar f_)) eqs_;                    \
neuper@38025
  1030
   \      e_1 = hd (dropWhile (ident h_) eqs_);       \
neuper@38025
  1031
   \      vs_ = dropWhile (ident f_) (Vars h_);                \
neuper@38025
  1032
   \      v_1 = hd (dropWhile (ident v_) vs_);                \
neuper@38025
  1033
   \      (s_1::bool list)=(SubProblem(DiffApp_,[univar,equation],[no_met])\
neuper@38025
  1034
   \                          [BOOL e_1, REAL v_1])\
neuper@38025
  1035
   \ in Substitute [(v_1 = (rhs o hd) s_1)] h_)";
wneuper@59186
  1036
> val ttt = (Thm.term_of o the o (parse thy)) scr;
neuper@38025
  1037
> tracing(term2str ttt);
neuper@38025
  1038
> atomt ttt;
neuper@38025
  1039
*** -------------
neuper@38025
  1040
*** Const ( DiffApp.Make'_fun'_by'_explicit)
neuper@38025
  1041
*** . Free ( f_, )
neuper@38025
  1042
*** . Free ( v_, )
neuper@38025
  1043
*** . Free ( eqs_, )
neuper@38025
  1044
*** . Const ( Let)
neuper@38025
  1045
*** . . Const ( Fun.op o)
neuper@38025
  1046
*** . . . Const ( List.hd)
neuper@38025
  1047
*** . . . Const ( DiffApp.filterVar)
neuper@38025
  1048
*** . . . . Free ( f_, )
neuper@38025
  1049
*** . . . Free ( eqs_, )
neuper@38025
  1050
*** . . Abs( h_,..
neuper@38025
  1051
*** . . . Const ( Let)
neuper@38025
  1052
*** . . . . Const ( List.hd)
neuper@38025
  1053
*** . . . . . Const ( List.dropWhile)
neuper@38025
  1054
*** . . . . . . Const ( Atools.ident)
neuper@38025
  1055
*** . . . . . . . Bound 0                     <---- Free ( h_, )
neuper@38025
  1056
*** . . . . . . Free ( eqs_, )
neuper@38025
  1057
*** . . . . Abs( e_1,..
neuper@38025
  1058
*** . . . . . Const ( Let)
neuper@38025
  1059
*** . . . . . . Const ( List.dropWhile)
neuper@38025
  1060
*** . . . . . . . Const ( Atools.ident)
neuper@38025
  1061
*** . . . . . . . . Free ( f_, )
neuper@38025
  1062
*** . . . . . . . Const ( Tools.Vars)
neuper@38025
  1063
*** . . . . . . . . Bound 1                       <---- Free ( h_, )
neuper@38025
  1064
*** . . . . . . Abs( vs_,..
neuper@38025
  1065
*** . . . . . . . Const ( Let)
neuper@38025
  1066
*** . . . . . . . . Const ( List.hd)
neuper@38025
  1067
*** . . . . . . . . . Const ( List.dropWhile)
neuper@38025
  1068
*** . . . . . . . . . . Const ( Atools.ident)
neuper@38025
  1069
*** . . . . . . . . . . . Free ( v_, )
neuper@38025
  1070
*** . . . . . . . . . . Bound 0                   <---- Free ( vs_, )
neuper@38025
  1071
*** . . . . . . . . Abs( v_1,..
neuper@38025
  1072
*** . . . . . . . . . Const ( Let)
neuper@38025
  1073
*** . . . . . . . . . . Const ( Script.SubProblem)
neuper@38025
  1074
*** . . . . . . . . . . . Const ( Pair)
neuper@38025
  1075
*** . . . . . . . . . . . . Free ( DiffApp_, )
neuper@38025
  1076
*** . . . . . . . . . . . . Const ( Pair)
neuper@38025
  1077
*** . . . . . . . . . . . . . Const ( List.list.Cons)
neuper@38025
  1078
*** . . . . . . . . . . . . . . Free ( univar, )
neuper@38025
  1079
*** . . . . . . . . . . . . . . Const ( List.list.Cons)
neuper@38025
  1080
*** . . . . . . . . . . . . . . . Free ( equation, )
neuper@38025
  1081
*** . . . . . . . . . . . . . . . Const ( List.list.Nil)
neuper@38025
  1082
*** . . . . . . . . . . . . . Const ( List.list.Cons)
neuper@38025
  1083
*** . . . . . . . . . . . . . . Free ( no_met, )
neuper@38025
  1084
*** . . . . . . . . . . . . . . Const ( List.list.Nil)
neuper@38025
  1085
*** . . . . . . . . . . . Const ( List.list.Cons)
neuper@38025
  1086
*** . . . . . . . . . . . . Const ( Script.BOOL)
neuper@38025
  1087
*** . . . . . . . . . . . . . Bound 2                   <----- Free ( e_1, )
neuper@38025
  1088
*** . . . . . . . . . . . . Const ( List.list.Cons)
neuper@38025
  1089
*** . . . . . . . . . . . . . Const ( Script.real_)
neuper@38025
  1090
*** . . . . . . . . . . . . . . Bound 0                 <----- Free ( v_1, )
neuper@38025
  1091
*** . . . . . . . . . . . . . Const ( List.list.Nil)
neuper@38025
  1092
*** . . . . . . . . . . Abs( s_1,..
neuper@38025
  1093
*** . . . . . . . . . . . Const ( Script.Substitute)
neuper@38025
  1094
*** . . . . . . . . . . . . Const ( List.list.Cons)
neuper@38025
  1095
*** . . . . . . . . . . . . . Const ( Pair)
neuper@38025
  1096
*** . . . . . . . . . . . . . . Bound 1                 <----- Free ( v_1, )
neuper@38025
  1097
*** . . . . . . . . . . . . . . Const ( Fun.op o)
neuper@38025
  1098
*** . . . . . . . . . . . . . . . Const ( Tools.rhs)
neuper@38025
  1099
*** . . . . . . . . . . . . . . . Const ( List.hd)
neuper@38025
  1100
*** . . . . . . . . . . . . . . . Bound 0               <----- Free ( s_1, )
neuper@38025
  1101
*** . . . . . . . . . . . . . Const ( List.list.Nil)
neuper@38025
  1102
*** . . . . . . . . . . . . Bound 4                     <----- Free ( h_, )
neuper@38025
  1103
neuper@38025
  1104
> val ttt' = inst_abs thy ttt;
neuper@38025
  1105
> tracing(term2str ttt');
neuper@38025
  1106
Script Make_fun_by_explicit f_ v_ eqs_ =  
neuper@38025
  1107
  ... as above ...
neuper@38025
  1108
> atomt ttt';
neuper@38025
  1109
*** -------------
neuper@38025
  1110
*** Const ( DiffApp.Make'_fun'_by'_explicit)
neuper@38025
  1111
*** . Free ( f_, )
neuper@38025
  1112
*** . Free ( v_, )
neuper@38025
  1113
*** . Free ( eqs_, )
neuper@38025
  1114
*** . Const ( Let)
neuper@38025
  1115
*** . . Const ( Fun.op o)
neuper@38025
  1116
*** . . . Const ( List.hd)
neuper@38025
  1117
*** . . . Const ( DiffApp.filterVar)
neuper@38025
  1118
*** . . . . Free ( f_, )
neuper@38025
  1119
*** . . . Free ( eqs_, )
neuper@38025
  1120
*** . . Abs( h_,..
neuper@38025
  1121
*** . . . Const ( Let)
neuper@38025
  1122
*** . . . . Const ( List.hd)
neuper@38025
  1123
*** . . . . . Const ( List.dropWhile)
neuper@38025
  1124
*** . . . . . . Const ( Atools.ident)
neuper@38025
  1125
*** . . . . . . . Free ( h_, )                <---- Bound 0
neuper@38025
  1126
*** . . . . . . Free ( eqs_, )
neuper@38025
  1127
*** . . . . Abs( e_1,..
neuper@38025
  1128
*** . . . . . Const ( Let)
neuper@38025
  1129
*** . . . . . . Const ( List.dropWhile)
neuper@38025
  1130
*** . . . . . . . Const ( Atools.ident)
neuper@38025
  1131
*** . . . . . . . . Free ( f_, )
neuper@38025
  1132
*** . . . . . . . Const ( Tools.Vars)
neuper@38025
  1133
*** . . . . . . . . Free ( h_, )                  <---- Bound 1
neuper@38025
  1134
*** . . . . . . Abs( vs_,..
neuper@38025
  1135
*** . . . . . . . Const ( Let)
neuper@38025
  1136
*** . . . . . . . . Const ( List.hd)
neuper@38025
  1137
*** . . . . . . . . . Const ( List.dropWhile)
neuper@38025
  1138
*** . . . . . . . . . . Const ( Atools.ident)
neuper@38025
  1139
*** . . . . . . . . . . . Free ( v_, )
neuper@38025
  1140
*** . . . . . . . . . . Free ( vs_, )             <---- Bound 0
neuper@38025
  1141
*** . . . . . . . . Abs( v_1,..
neuper@38025
  1142
*** . . . . . . . . . Const ( Let)
neuper@38025
  1143
*** . . . . . . . . . . Const ( Script.SubProblem)
neuper@38025
  1144
*** . . . . . . . . . . . Const ( Pair)
neuper@38025
  1145
*** . . . . . . . . . . . . Free ( DiffApp_, )
neuper@38025
  1146
*** . . . . . . . . . . . . Const ( Pair)
neuper@38025
  1147
*** . . . . . . . . . . . . . Const ( List.list.Cons)
neuper@38025
  1148
*** . . . . . . . . . . . . . . Free ( univar, )
neuper@38025
  1149
*** . . . . . . . . . . . . . . Const ( List.list.Cons)
neuper@38025
  1150
*** . . . . . . . . . . . . . . . Free ( equation, )
neuper@38025
  1151
*** . . . . . . . . . . . . . . . Const ( List.list.Nil)
neuper@38025
  1152
*** . . . . . . . . . . . . . Const ( List.list.Cons)
neuper@38025
  1153
*** . . . . . . . . . . . . . . Free ( no_met, )
neuper@38025
  1154
*** . . . . . . . . . . . . . . Const ( List.list.Nil)
neuper@38025
  1155
*** . . . . . . . . . . . Const ( List.list.Cons)
neuper@38025
  1156
*** . . . . . . . . . . . . Const ( Script.BOOL)
neuper@38025
  1157
*** . . . . . . . . . . . . . Free ( e_1, )             <----- Bound 2
neuper@38025
  1158
*** . . . . . . . . . . . . Const ( List.list.Cons)
neuper@38025
  1159
*** . . . . . . . . . . . . . Const ( Script.real_)
neuper@38025
  1160
*** . . . . . . . . . . . . . . Free ( v_1, )           <----- Bound 0
neuper@38025
  1161
*** . . . . . . . . . . . . . Const ( List.list.Nil)
neuper@38025
  1162
*** . . . . . . . . . . Abs( s_1,..
neuper@38025
  1163
*** . . . . . . . . . . . Const ( Script.Substitute)
neuper@38025
  1164
*** . . . . . . . . . . . . Const ( List.list.Cons)
neuper@38025
  1165
*** . . . . . . . . . . . . . Const ( Pair)
neuper@38025
  1166
*** . . . . . . . . . . . . . . Free ( v_1, )           <----- Bound 1
neuper@38025
  1167
*** . . . . . . . . . . . . . . Const ( Fun.op o)
neuper@38025
  1168
*** . . . . . . . . . . . . . . . Const ( Tools.rhs)
neuper@38025
  1169
*** . . . . . . . . . . . . . . . Const ( List.hd)
neuper@38025
  1170
*** . . . . . . . . . . . . . . . Free ( s_1, )         <----- Bound 0
neuper@38025
  1171
*** . . . . . . . . . . . . . Const ( List.list.Nil)
neuper@38025
  1172
*** . . . . . . . . . . . . Free ( h_, )                <----- Bound 4
neuper@38025
  1173
neuper@38025
  1174
Note numbering of de Bruijn indexes !
neuper@38025
  1175
neuper@38025
  1176
Script Make_fun_by_explicit f_ v_ eqs_ =
neuper@38025
  1177
 let h_ = (hd o filterVar f_) eqs_; 
neuper@38025
  1178
     e_1 = hd (dropWhile (ident h_ BOUND_0) eqs_);
neuper@38025
  1179
     vs_ = dropWhile (ident f_) (Vars h_ BOUND_1);
neuper@38025
  1180
     v_1 = hd (dropWhile (ident v_) vs_ BOUND_0);
neuper@38025
  1181
     s_1 =
neuper@38025
  1182
       SubProblem (DiffApp_, [univar, equation], [no_met])
neuper@38025
  1183
        [BOOL e_1 BOUND_2, REAL v_1 BOUND_0]
neuper@38025
  1184
 in Substitute [(v_1 BOUND_1 = (rhs o hd) s_1 BOUND_0)] h_ BOUND_4
neuper@38025
  1185
*)
neuper@38025
  1186
neuper@38037
  1187
(* for parse and parse_patt: fix all types to real *)
neuper@38025
  1188
fun T_a2real (Type (s, [])) = 
neuper@38037
  1189
    if s = "'a" orelse s = "'b" orelse s = "'c" then HOLogic.realT 
neuper@38037
  1190
    else Type (s, [])
neuper@38025
  1191
  | T_a2real (Type (s, Ts)) = Type (s, map T_a2real Ts)
neuper@38025
  1192
  | T_a2real (TFree (s, srt)) = 
neuper@38037
  1193
    if s = "'a" orelse s = "'b" orelse s = "'c" then HOLogic.realT 
neuper@38037
  1194
    else TFree (s, srt)
neuper@38037
  1195
  | T_a2real (TVar ((s, i), srt)) = 
neuper@38037
  1196
    if s = "'a" orelse s = "'b" orelse s = "'c" then HOLogic.realT 
neuper@38037
  1197
    else TVar ((s, i), srt)
neuper@38037
  1198
  | T_a2real (TVar (("DUMMY",_), srt)) = HOLogic.realT;
neuper@38025
  1199
neuper@38025
  1200
(*FIXME .. fixes the type (+see Typefix.thy*)
neuper@38025
  1201
fun typ_a2real (Const( s, T)) = (Const( s, T_a2real T)) 
neuper@38025
  1202
  | typ_a2real (Free( s, T)) = (Free( s, T_a2real T))
neuper@38025
  1203
  | typ_a2real (Var( n, T)) = (Var( n, T_a2real T))
neuper@38025
  1204
  | typ_a2real (Bound i) = (Bound i)
neuper@38025
  1205
  | typ_a2real (Abs(s,T,t)) = Abs(s, T, typ_a2real t)
neuper@38025
  1206
  | typ_a2real (t1 $ t2) = (typ_a2real t1) $ (typ_a2real t2);
neuper@38025
  1207
neuper@38025
  1208
neuper@38037
  1209
(* before 2002 *)
neuper@38025
  1210
fun parseold thy str = 
neuper@38025
  1211
  (let val t = ((*typ_a2real o*) numbers_to_string) 
neuper@38025
  1212
		   (Syntax.read_term_global thy str)
wneuper@59184
  1213
   in SOME (Thm.global_cterm_of thy t) end)
neuper@38025
  1214
    handle _ => NONE;
neuper@38025
  1215
(*2002 fun parseN thy str = 
neuper@38025
  1216
  (let 
neuper@38025
  1217
     val sgn = sign_of thy;
neuper@38025
  1218
     val t = ((*typ_a2real o app_num_tr'1 o*) term_of) 
neuper@38025
  1219
       (read_cterm sgn (str,(TVar(("DUMMY",0),[]))));
wneuper@59184
  1220
   in SOME (Thm.global_cterm_of sgn t) end)
neuper@38025
  1221
     handle _ => NONE;*)
neuper@38025
  1222
fun parseN thy str = 
neuper@38025
  1223
  (let val t = (*(typ_a2real o numbers_to_string)*) 
neuper@38025
  1224
	   (Syntax.read_term_global thy str)
wneuper@59184
  1225
   in SOME (Thm.global_cterm_of thy t) end)
neuper@38025
  1226
    handle _ => NONE;
neuper@38025
  1227
(*2002 fun parse thy str = 
neuper@38025
  1228
  (let 
neuper@38025
  1229
     val sgn = sign_of thy;
wneuper@59186
  1230
     val t = (typ_a2real o app_num_tr'1 o Thm.term_of) 
neuper@38025
  1231
       (read_cterm sgn (str,(TVar(("DUMMY",0),[]))));
wneuper@59184
  1232
   in SOME (Thm.global_cterm_of sgn t) end) (*FIXXXXME 10.8.02: return term !!!*)
neuper@38025
  1233
     handle _ => NONE;*)
neuper@38025
  1234
(*2010 fun parse thy str = 
neuper@38025
  1235
  (let val t = (typ_a2real o app_num_tr'1) (Syntax.read_term_global thy str)
wneuper@59184
  1236
   in SOME (Thm.global_cterm_of thy t) end) (*FIXXXXME 10.8.02: return term !!!*)
neuper@38025
  1237
     handle _ => NONE;*)
neuper@38025
  1238
fun parse thy str = 
neuper@38025
  1239
  (let val t = (typ_a2real o numbers_to_string) 
neuper@38025
  1240
		   (Syntax.read_term_global thy str)
wneuper@59184
  1241
   in SOME (Thm.global_cterm_of thy t) end) (*FIXXXXME 10.8.02: return term !!!*)
neuper@38025
  1242
     handle _ => NONE;
neuper@38025
  1243
(*
neuper@38025
  1244
> val (SOME ct) = parse thy "(-#5)^^^#3"; 
wneuper@59186
  1245
> atomty (Thm.term_of ct);
neuper@38025
  1246
*** -------------
neuper@38025
  1247
*** Const ( Nat.op ^, ['a, nat] => 'a)
neuper@38025
  1248
***   Const ( uminus, 'a => 'a)
neuper@38025
  1249
***     Free ( #5, 'a)
neuper@38025
  1250
***   Free ( #3, nat)                
neuper@38025
  1251
> val (SOME ct) = parse thy "R=R"; 
wneuper@59186
  1252
> atomty (Thm.term_of ct);
neuper@38025
  1253
*** -------------
neuper@38025
  1254
*** Const ( op =, [real, real] => bool)
neuper@38025
  1255
***   Free ( R, real)
neuper@38025
  1256
***   Free ( R, real)
neuper@38025
  1257
neuper@38025
  1258
THIS IS THE OUTPUT FOR VERSION (3) above at typ_a2real !!!!!
neuper@38025
  1259
*** -------------
neuper@38025
  1260
*** Const ( op =, [RealDef.real, RealDef.real] => bool)
neuper@38025
  1261
***   Free ( R, RealDef.real)
neuper@38025
  1262
***   Free ( R, RealDef.real)                  *)
neuper@38025
  1263
neuper@41931
  1264
(*WN110317 parseNEW will replace parse after introduction of ctxt completed*)
bonzai@41949
  1265
fun parseNEW ctxt str = SOME (Syntax.read_term ctxt str |> numbers_to_string)
bonzai@41949
  1266
      handle _ => NONE;
neuper@41931
  1267
neuper@48879
  1268
(* parse term patterns; Var ("v",_), i.e. "?v", are required for instantiation
neuper@48879
  1269
  WN130613 probably compare to 
neuper@48879
  1270
  http://www.mail-archive.com/isabelle-dev@mailbroy.informatik.tu-muenchen.de/msg04249.html*)
neuper@38037
  1271
fun parse_patt thy str = (thy, str) |>> thy2ctxt 
neuper@48761
  1272
                                    |-> Proof_Context.read_term_pattern
neuper@41931
  1273
                                    |> numbers_to_string (*TODO drop*)
neuper@41931
  1274
                                    |> typ_a2real;       (*TODO drop*)
neuper@38025
  1275
neuper@38025
  1276
(*version for testing local to theories*)
wneuper@59186
  1277
fun str2term_ thy str = (Thm.term_of o the o (parse thy)) str;
neuper@42017
  1278
(*WN110520
wneuper@59352
  1279
fun str2term str = (Thm.term_of o the o (parse (Thy_Info_get_theory "Isac"))) str;*)
wneuper@59352
  1280
fun str2term str = parse_patt (Thy_Info_get_theory "Isac") str
neuper@38025
  1281
fun strs2terms ss = map str2term ss;
wneuper@59352
  1282
fun str2termN str = (Thm.term_of o the o (parseN (Thy_Info_get_theory "Isac"))) str;
neuper@38025
  1283
neuper@38025
  1284
(*+ makes a substitution from the output of Pattern.match +*)
neuper@38025
  1285
(*fun mk_subs ((id, _):indexname, t:term) = (Free (id,type_of t), t);*)
neuper@38025
  1286
fun mk_subs (subs: ((string * int) * (Term.typ * Term.term)) list) =
neuper@38025
  1287
let fun mk_sub ((id, _), (ty, tm)) = (Free (id, ty), tm) in
neuper@38025
  1288
map mk_sub subs end;
neuper@38025
  1289
wneuper@59187
  1290
val atomthm = atomt o #prop o Thm.rep_thm;
neuper@38025
  1291
neuper@38025
  1292
(*.instantiate #prop thm with bound variables (as Free).*)
neuper@38025
  1293
fun inst_bdv [] t = t : term
neuper@38025
  1294
  | inst_bdv (instl: (term*term) list) t =
neuper@38025
  1295
      let fun subst (v as Var((s,_),T)) = 
neuper@40836
  1296
	      (case Symbol.explode s of
neuper@38025
  1297
		   "b"::"d"::"v"::_ => 
neuper@38025
  1298
		   if_none (assoc(instl,Free(s,T))) (Free(s,T))
neuper@38025
  1299
		 | _ => v)
neuper@38025
  1300
            | subst (Abs(a,T,body)) = Abs(a, T, subst body)
neuper@38025
  1301
            | subst (f$t') = subst f $ subst t'
neuper@38025
  1302
            | subst t = if_none (assoc(instl,t)) t
neuper@38025
  1303
      in  subst t  end;
neuper@38025
  1304
neuper@38025
  1305
neuper@38025
  1306
(*WN050829 caution: is_atom (str2term"q_0/2 * L * x") = true !!!
neuper@38025
  1307
  use length (vars term) = 1 instead*)
neuper@38025
  1308
fun is_atom (Const ("Float.Float",_) $ _) = true
neuper@38025
  1309
  | is_atom (Const ("ComplexI.I'_'_",_)) = true
neuper@38034
  1310
  | is_atom (Const ("Groups.times_class.times",_) $ t $ Const ("ComplexI.I'_'_",_)) = is_atom t
neuper@38025
  1311
  | is_atom (Const ("Groups.plus_class.plus",_) $ t1 $ Const ("ComplexI.I'_'_",_)) = is_atom t1
neuper@38025
  1312
  | is_atom (Const ("Groups.plus_class.plus",_) $ t1 $ 
neuper@38034
  1313
		   (Const ("Groups.times_class.times",_) $ t2 $ Const ("ComplexI.I'_'_",_))) = 
neuper@38025
  1314
    is_atom t1 andalso is_atom t2
neuper@38025
  1315
  | is_atom (Const _) = true
neuper@38025
  1316
  | is_atom (Free _) = true
neuper@38025
  1317
  | is_atom (Var _) = true
neuper@38025
  1318
  | is_atom _ = false;
neuper@38025
  1319
(* val t = str2term "q_0/2 * L * x";
neuper@38025
  1320
neuper@38025
  1321
neuper@38025
  1322
*)
neuper@38025
  1323
(*val t = str2term "Float ((1,2),(0,0))";
neuper@38025
  1324
> is_atom t;
neuper@38025
  1325
val it = true : bool
neuper@38025
  1326
> val t = str2term "Float ((1,2),(0,0)) * I__";
neuper@38025
  1327
> is_atom t;
neuper@38025
  1328
val it = true : bool
neuper@38025
  1329
> val t = str2term "Float ((1,2),(0,0)) + Float ((3,4),(0,0)) * I__";
neuper@38025
  1330
> is_atom t;
neuper@38025
  1331
val it = true : bool
neuper@38025
  1332
> val t = str2term "1 + 2*I__";
neuper@38034
  1333
> val Const ("Groups.plus_class.plus",_) $ t1 $ (Const ("Groups.times_class.times",_) $ t2 $ Const ("ComplexI.I'_'_",_)) = t;
neuper@38025
  1334
*)
neuper@38025
  1335
neuper@38025
  1336
(*.adaption from Isabelle/src/Pure/term.ML; reports if ALL Free's
neuper@38025
  1337
   have found a substitution (required for evaluating the preconditions
neuper@38025
  1338
   of _incomplete_ models).*)
neuper@38025
  1339
fun subst_atomic_all [] t = (false, (*TODO may be 'true' for some terms ?*)
neuper@38025
  1340
			     t : term)
neuper@38025
  1341
  | subst_atomic_all (instl: (term*term) list) t =
neuper@38025
  1342
      let fun subst (Abs(a,T,body)) = 
neuper@38025
  1343
	      let val (all, body') = subst body
neuper@38025
  1344
	      in (all, Abs(a, T, body')) end
neuper@38025
  1345
            | subst (f$tt) = 
neuper@38025
  1346
	      let val (all1, f') = subst f
neuper@38025
  1347
		  val (all2, tt') = subst tt
neuper@38025
  1348
	      in (all1 andalso all2, f' $ tt') end
neuper@38025
  1349
            | subst (t as Free _) = 
neuper@38025
  1350
	      if is_num t then (true, t) (*numerals cannot be subst*)
neuper@38025
  1351
	      else (case assoc(instl,t) of
neuper@38025
  1352
					 SOME t' => (true, t')
neuper@38025
  1353
				       | NONE => (false, t))
neuper@38025
  1354
            | subst t = (true, if_none (assoc(instl,t)) t)
neuper@38025
  1355
      in  subst t  end;
neuper@38025
  1356
neuper@38025
  1357
(*.add two terms with a type given.*)
neuper@38025
  1358
fun mk_add t1 t2 =
neuper@38025
  1359
    let val T1 = type_of t1
neuper@38025
  1360
	val T2 = type_of t2
neuper@38025
  1361
    in if T1 <> T2 then raise TYPE ("mk_add gets ",[T1, T2],[t1,t2])
neuper@38025
  1362
       else (Const ("Groups.plus_class.plus", [T1, T2] ---> T1) $ t1 $ t2)
neuper@38025
  1363
    end;
wneuper@59389
  1364
wneuper@59389
  1365
end