src/Tools/isac/ProgLang/termC.sml
author Walther Neuper <wneuper@ist.tugraz.at>
Wed, 07 Mar 2018 14:20:33 +0100
changeset 59394 2e087ded4a48
parent 59393 4274a44ec183
child 59395 862eb17f9e16
permissions -rw-r--r--
TermC: clean source file
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@59393
    16
    val inst_abs: term -> term
wneuper@59389
    17
    val inst_bdv: (term * term) list -> term -> term
wneuper@59390
    18
 
wneuper@59392
    19
    val term_of_num: typ -> int -> term
wneuper@59392
    20
    val (*num_of_term \<longrightarrow>*) num_of_term: term -> int
wneuper@59390
    21
    val (*int_of_str \<longrightarrow>*) int_of_str_opt: string -> int option
wneuper@59390
    22
    val (*int_of_str' int2str \<longrightarrow>*)int_of_str: string -> int
wneuper@59392
    23
    val isastr_of_int: int -> string
wneuper@59390
    24
wneuper@59389
    25
    val isalist2list: term -> term list
wneuper@59390
    26
    val list2isalist: typ -> term list -> term
wneuper@59389
    27
    val isapair2pair: term -> term * term
wneuper@59390
    28
 
wneuper@59389
    29
    val is_atom: term -> bool
wneuper@59389
    30
    val is_bdv: string -> bool
wneuper@59389
    31
    val is_bdv_subst: term -> bool
wneuper@59389
    32
    val is_equality: term -> bool
wneuper@59389
    33
    val is_expliceq: term -> bool
wneuper@59389
    34
    val is_f_x: term -> bool
wneuper@59389
    35
    val is_list: term -> bool
wneuper@59389
    36
    val is_num: term -> bool
wneuper@59390
    37
    val (*is_no  is_numeral \<longrightarrow>*)is_num': string -> bool
wneuper@59390
    38
wneuper@59389
    39
    val mk_add: term -> term -> term
wneuper@59389
    40
    val mk_free: typ -> string -> term
wneuper@59389
    41
    val mk_equality: term * term -> term
wneuper@59389
    42
    val mk_factroot: string -> typ -> int -> int -> term
wneuper@59389
    43
    val mk_Free: string * typ -> term
wneuper@59392
    44
    val mk_thmid: string -> string -> string -> string
wneuper@59390
    45
    val mk_num_op_num(*<-- num_op_num*): typ -> typ -> string * typ -> int -> int -> term
wneuper@59390
    46
    val mk_num_op_var(*<-- num_op_var*): term -> string -> typ -> typ -> int -> term
wneuper@59390
    47
    val mk_var_op_num(*<-- var_op_num*): term -> string -> typ -> typ -> int -> term
wneuper@59390
    48
wneuper@59390
    49
  (*val list_implies: term list * term -> term  --> Logic.list_implies*)
wneuper@59390
    50
    val matches: theory -> term -> term -> bool
wneuper@59389
    51
    val parse: theory -> string -> cterm option
wneuper@59389
    52
    val parseN: theory -> string -> cterm option
wneuper@59389
    53
    val parseNEW: Proof.context -> string -> term option
wneuper@59389
    54
    val parseold: theory -> string -> cterm option
wneuper@59389
    55
    val parse_patt: theory -> string -> term
wneuper@59389
    56
    val perm: term -> term -> bool
wneuper@59390
    57
wneuper@59390
    58
    val calc_equ: string -> int * int -> bool
wneuper@59389
    59
    val power: int -> int -> int
wneuper@59391
    60
    val sign_mult: int -> int -> int
wneuper@59389
    61
    val squfact: int -> int
wneuper@59390
    62
    val gcd: int -> int -> int
wneuper@59390
    63
wneuper@59389
    64
    val str_of_free_opt: term -> string option
wneuper@59389
    65
    val str_of_int: int -> string
wneuper@59389
    66
    val str2term: string -> term
wneuper@59389
    67
    val strip_imp_prems': term -> term option
wneuper@59389
    68
    val subst_atomic_all: (term * term) list -> term -> bool * term
wneuper@59389
    69
    val term_detail2str: term -> string
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@59392
    80
    val atomtyp(*<-- atom_typ TODO*): typ -> unit
wneuper@59392
    81
    val scala_of_term: term -> string
wneuper@59392
    82
    val atomty: term -> unit
wneuper@59392
    83
    val atomw: term -> unit
wneuper@59392
    84
    val atomwy: term -> unit
wneuper@59392
    85
    val atomty_thy: thyID -> term -> unit
wneuper@59392
    86
    val free2var: term -> term
wneuper@59392
    87
    val sign: int -> int
wneuper@59392
    88
    val sqrt: int -> int
wneuper@59389
    89
(*/-------------------------------------------------------- ! aktivate for Test_Isac BEGIN ---\* )
wneuper@59392
    90
(*============================================= shift up during Test_Isac ======================
wneuper@59389
    91
    val --->: typ list * typ -> typ
wneuper@59389
    92
    val -->: typ * typ -> typ
wneuper@59389
    93
    val PairT: typ -> typ -> typ
wneuper@59389
    94
    val T_a2real: typ -> typ
wneuper@59389
    95
    val add_term_vars: term * term list -> term list
wneuper@59389
    96
    val atless: term * term -> bool
wneuper@59389
    97
    val atomt: term -> unit
wneuper@59389
    98
    val atomthm: thm -> unit
wneuper@59389
    99
    val contains_term: term -> term -> bool
wneuper@59389
   100
    val divisors: int -> int list
wneuper@59389
   101
    val doubles: ''a list -> ''a list
wneuper@59389
   102
    val dvd: int * int -> bool
wneuper@59389
   103
    val eq_set_term: term list * term list -> bool
wneuper@59389
   104
    val insert_aterm: term * term list -> term list
wneuper@59389
   105
    val is_Free: term -> bool
wneuper@59389
   106
    val is_fun_id: term -> bool
wneuper@59389
   107
    val list_const: typ -> term
wneuper@59389
   108
    val mem_term: term * term list -> bool
wneuper@59389
   109
    val mk_listT: typ -> typ
wneuper@59389
   110
    val mk_subs: ((string * int) * (typ * term)) list -> (term * term) list
wneuper@59389
   111
    val numbers_to_string: term -> term
wneuper@59389
   112
    val raw_pp_typ: typ -> Pretty.T
wneuper@59389
   113
    val scala_of_typ: typ -> string
wneuper@59389
   114
    val str2termN: string -> term
wneuper@59389
   115
    val str2term_: theory -> string -> term
wneuper@59389
   116
    val str_of_int: int -> string
wneuper@59389
   117
    val strs2terms: string list -> term list
wneuper@59389
   118
    val subset_term: term list * term list -> bool
wneuper@59389
   119
    val subst_bound: term * term -> term
wneuper@59389
   120
    val term_detail2str_thy: thyID -> term -> string
wneuper@59389
   121
    val term_of_num: typ -> int -> term
wneuper@59389
   122
    val term_vars: term -> term list
wneuper@59389
   123
    val typ_a2real: term -> term
wneuper@59389
   124
    val var_perm: term * term -> bool
wneuper@59389
   125
    val vperm: term * term -> bool
wneuper@59389
   126
    val xless: (string * int) * indexname -> bool
wneuper@59392
   127
*============================================= shift up during Test_Isac ======================*)
wneuper@59389
   128
( *\--- ! aktivate for Test_Isac END ----------------------------------------------------------/*)
wneuper@59389
   129
  end
wneuper@59389
   130
wneuper@59389
   131
(**)
wneuper@59389
   132
structure TermC(**): TERMC(**) =
wneuper@59389
   133
struct
wneuper@59389
   134
(**)
neuper@38025
   135
neuper@52087
   136
fun isastr_of_int i = if i >= 0 then string_of_int i else "-" ^ string_of_int (abs i)
neuper@52087
   137
neuper@38025
   138
fun matches thy tm pa = 
neuper@38025
   139
    (Pattern.match thy (pa, tm) (Vartab.empty, Vartab.empty); true)
wneuper@59392
   140
    handle Pattern.MATCH => false
neuper@38025
   141
wneuper@59392
   142
(** transform  typ / term to a String to be parsed by Scala after transport via libisabelle **)
wneuper@59392
   143
wneuper@59318
   144
fun scala_of_typ (Type (s, typs)) =
wneuper@59318
   145
    enclose "Type(" ")" (quote s ^ ", " ^
wneuper@59318
   146
      (typs |> map scala_of_typ |> commas |> enclose "List(" ")"))
wneuper@59318
   147
  | scala_of_typ (TFree (s, sort)) =
wneuper@59318
   148
    enclose "TFree(" ")" (quote s ^ ", " ^ (sort |> map quote |> commas |> enclose "List(" ")"))
wneuper@59318
   149
  | scala_of_typ (TVar ((s, i), sort)) =
wneuper@59318
   150
    enclose "TVar(" ")" (
wneuper@59318
   151
      enclose "(" ")," (quote s ^ "," ^ quote (string_of_int i)) ^ 
wneuper@59318
   152
      (sort |> map quote |> commas |> enclose "List(" ")"))
wneuper@59318
   153
fun scala_of_term (Const (s, T)) =
wneuper@59318
   154
    enclose "Const(" ")" (quote s ^ ", " ^ scala_of_typ T)
wneuper@59318
   155
  | scala_of_term (Free (s, T)) =
wneuper@59318
   156
    enclose "Free(" ")" (quote s ^ ", " ^ scala_of_typ T)
wneuper@59318
   157
  | scala_of_term (Var ((s, i), T)) =
wneuper@59318
   158
    enclose "TVar(" ")" (
wneuper@59318
   159
      enclose "(" ")," (quote s ^ "," ^ quote (string_of_int i)) ^ 
wneuper@59318
   160
      scala_of_typ T)
wneuper@59318
   161
  | scala_of_term (Bound i) = enclose "Bound(" ")" (string_of_int i)
wneuper@59318
   162
  | scala_of_term (Abs (s, T, t)) =
wneuper@59318
   163
    enclose "Abs(" ")" (
wneuper@59318
   164
      quote s ^ ", " ^
wneuper@59318
   165
      scala_of_typ T ^ ", " ^
wneuper@59318
   166
      scala_of_term t)
wneuper@59318
   167
  | scala_of_term (t1 $ t2) =
wneuper@59318
   168
    enclose "App(" ")" (scala_of_term t1 ^ ", " ^ scala_of_term t2)
wneuper@59318
   169
wneuper@59392
   170
(* see structure's bare bones.
wneuper@59392
   171
   for Isabelle standard output compare 2017 "structure ML_PP" *)
wneuper@59392
   172
fun atomtyp t =
neuper@38025
   173
  let
wneuper@59392
   174
    fun ato n (Type (s, [])) = "\n*** " ^ indent n ^ "Type (" ^ s ^",[])"
wneuper@59392
   175
      | ato n (Type (s, Ts)) = "\n*** " ^ indent n ^ "Type (" ^ s ^ ",[" ^ atol (n + 1) Ts
wneuper@59392
   176
      | ato n (TFree (s, sort)) = "\n*** " ^ indent n ^ "TFree (" ^ s ^ "," ^ strs2str' sort
wneuper@59392
   177
      | ato n (TVar ((s, i), sort)) =
wneuper@59392
   178
        "\n*** " ^ indent n ^ "TVar ((" ^ s ^ "," ^ string_of_int i ^ strs2str' sort
wneuper@59392
   179
    and atol n [] = "\n*** " ^ indent n ^ "]"
wneuper@59392
   180
      | atol n (T :: Ts) = (ato n T ^ atol n Ts)
neuper@38048
   181
in tracing (ato 0 t ^ "\n") end;
neuper@38025
   182
neuper@38067
   183
local 
wneuper@59392
   184
  fun ato (Const (a, _)) n = "\n*** " ^ indent n ^ "Const (" ^ a ^ ", _)"
wneuper@59392
   185
	  | ato (Free (a, _)) n = "\n*** " ^ indent n ^ "Free (" ^ a ^ ", _)"
neuper@38025
   186
	  | ato (Var ((a, i), _)) n =
wneuper@59392
   187
	    "\n*** " ^ indent n ^ "Var (" ^ a ^ ", " ^ string_of_int i ^ "), _)"
wneuper@59392
   188
	  | ato (Bound i) n = "\n*** " ^ indent n ^ "Bound " ^ string_of_int i
wneuper@59392
   189
	  | ato (Abs (a, _, body)) n = "\n*** " ^ indent n ^ "Abs(" ^ a ^ ", _" ^ ato body (n+1)
neuper@38025
   190
	  | ato (f $ t) n = (ato f n ^ ato t (n + 1))
neuper@38067
   191
in
wneuper@59392
   192
  fun atomw t = writeln ("\n*** -------------" ^ ato t 0 ^ "\n***");
wneuper@59392
   193
  fun atomt t = tracing ("\n*** -------------" ^ ato t 0 ^ "\n***");
neuper@38067
   194
end;
neuper@38025
   195
neuper@38025
   196
fun term_detail2str t =
wneuper@59392
   197
  let 
wneuper@59392
   198
    fun ato (Const (a, T)) n = "\n*** " ^ indent n ^ "Const (" ^ a ^ ", " ^ string_of_typ T ^ ")"
wneuper@59392
   199
      | ato (Free (a, T)) n = "\n*** " ^ indent n ^ "Free (" ^ a ^ ", " ^ string_of_typ T ^ ")"
wneuper@59392
   200
      | ato (Var ((a, i), T)) n =
wneuper@59392
   201
        "\n*** " ^ indent n ^ "Var ((" ^ a ^ ", " ^ string_of_int i ^ "), " ^ string_of_typ T ^ ")"
wneuper@59392
   202
      | ato (Bound i) n = "\n*** " ^ indent n ^ "Bound " ^ string_of_int i
wneuper@59392
   203
      | ato (Abs(a, T, body))  n = 
wneuper@59392
   204
        "\n*** " ^ indent n ^ "Abs (" ^ a ^ ", " ^ string_of_typ T ^ ",.." ^ ato body (n + 1)
wneuper@59392
   205
      | ato (f $ t) n = ato f n ^ ato t (n + 1)
wneuper@59392
   206
  in "\n*** " ^ ato t 0 ^ "\n***" end;
neuper@42376
   207
fun term_detail2str_thy thy t =
wneuper@59392
   208
  let
wneuper@59392
   209
    fun ato (Const (a, T)) n =
wneuper@59392
   210
        "\n*** " ^ indent n ^ "Const (" ^ a ^ ", " ^ string_of_typ_thy thy T ^ ")"
wneuper@59392
   211
  	  | ato (Free (a, T)) n =
wneuper@59392
   212
  	     "\n*** " ^ indent n ^ "Free (" ^ a ^ ", " ^ string_of_typ_thy thy T ^ ")"
wneuper@59392
   213
  	  | ato (Var ((a, i), T)) n =
wneuper@59392
   214
  	    "\n*** " ^ indent n ^ "Var ((" ^ a ^ ", " ^ string_of_int i ^ "), " ^
wneuper@59392
   215
  	    string_of_typ_thy thy T ^ ")"
wneuper@59392
   216
  	  | ato (Bound i) n = 
wneuper@59392
   217
  	    "\n*** " ^ indent n ^ "Bound " ^ string_of_int i
wneuper@59392
   218
  	  | ato (Abs(a, T, body))  n = 
wneuper@59392
   219
  	    "\n*** " ^ indent n ^ "Abs (" ^ a ^ ", " ^ string_of_typ_thy thy T ^ ",.." ^
wneuper@59392
   220
  	    ato body (n + 1)
wneuper@59392
   221
  	  | ato (f $ t) n = ato f n ^ ato t (n + 1)
wneuper@59392
   222
  in "\n*** " ^ ato t 0 ^ "\n***" end;
neuper@38067
   223
fun atomwy t = (writeln o term_detail2str) t;
neuper@38067
   224
fun atomty t = (tracing o term_detail2str) t;
neuper@42376
   225
fun atomty_thy thy t = (tracing o (term_detail2str_thy thy)) t;
neuper@38025
   226
wneuper@59392
   227
(* contains the term a VAR(("*",_),_) ? *)
neuper@38025
   228
fun contains_Var (Abs(_,_,body)) = contains_Var body
neuper@38025
   229
  | contains_Var (f $ f') = contains_Var f orelse contains_Var f'
neuper@38025
   230
  | contains_Var (Var _) = true
neuper@38025
   231
  | contains_Var _ = false;
neuper@38025
   232
wneuper@59392
   233
fun str_of_int n = 
wneuper@59392
   234
  if n < 0 then "-" ^ ((string_of_int o abs) n)
wneuper@59392
   235
  else string_of_int n;
wneuper@59392
   236
val int_of_str = Thy_Output.integer;
wneuper@59392
   237
fun int_of_str_opt str = 
wneuper@59390
   238
  let
wneuper@59390
   239
    val ss = Symbol.explode str
wneuper@59392
   240
    val ss' = case ss of "(" :: s => drop_last s | _ => ss
wneuper@59392
   241
    val (sign, istr) = case ss' of "-" :: istr => (~1, istr) | _ => (1, ss')
wneuper@59392
   242
  in
wneuper@59392
   243
    case Library.read_int istr of (i, []) => SOME (sign * i) | _ => NONE
wneuper@59392
   244
  end;
wneuper@59392
   245
fun is_num' str = case int_of_str_opt str of SOME _ => true | NONE => false;
wneuper@59392
   246
fun is_num (Free (s, _)) = if is_num' s then true else false | is_num _ = false;
wneuper@59392
   247
fun term_of_num ntyp n = Free (str_of_int n, ntyp);
wneuper@59392
   248
fun num_of_term (t as (Free (istr, _))) = 
wneuper@59392
   249
    (case int_of_str_opt istr of SOME i => i | NONE => raise TERM ("num_of_term: NOT int ", [t]))
wneuper@59392
   250
  | num_of_term t = raise TERM ("num_of_term: NOT Free ", [t])
neuper@52064
   251
wneuper@59392
   252
fun is_Free (Free _) = true | is_Free _ = false;
neuper@38025
   253
fun is_fun_id (Const _) = true
neuper@38025
   254
  | is_fun_id (Free _) = true
neuper@38025
   255
  | is_fun_id _ = false;
neuper@38025
   256
fun is_f_x (f $ x) = is_fun_id f andalso is_Free x
neuper@38025
   257
  | is_f_x _ = false;
wneuper@59392
   258
wneuper@59392
   259
fun vars t =
neuper@38025
   260
  let
wneuper@59392
   261
    fun scan vs (Const _) = vs
wneuper@59392
   262
      | scan vs (t as Free (s, _)) = if is_num' s then vs else t :: vs
wneuper@59392
   263
      | scan vs (t as Var _) = t :: vs
wneuper@59392
   264
      | scan vs (Bound _) = vs 
wneuper@59392
   265
      | scan vs (Abs (_, _, t)) = scan vs t
neuper@38025
   266
      | scan vs (t1 $ t2) = (scan vs t1) @ (scan vs t2)
neuper@38025
   267
  in (distinct o (scan [])) t end;
wneuper@59392
   268
(* bypass Isabelle's Pretty, which requires ctxt *)
neuper@38025
   269
fun ids2str t =
neuper@38025
   270
  let
wneuper@59392
   271
    fun scan vs (Const (s, _)) = if is_num' s then vs else s :: vs
wneuper@59392
   272
      | scan vs (Free (s, _)) = if is_num' s then vs else s :: vs
wneuper@59392
   273
      | scan vs (Var ((s, i), _)) = (s ^ "_" ^ string_of_int i) :: vs
wneuper@59392
   274
      | scan vs (Bound _) = vs 
wneuper@59392
   275
      | scan vs (Abs (s, _, t)) = scan (s :: vs) t
neuper@38025
   276
      | scan vs (t1 $ t2) = (scan vs t1) @ (scan vs t2)
neuper@38025
   277
  in (distinct o (scan [])) t end;
wneuper@59392
   278
fun is_bdv str = case Symbol.explode str of "b"::"d"::"v"::_ => true | _ => false;
wneuper@59394
   279
(* instantiate #prop thm with bound variables (as Free) *)
wneuper@59394
   280
fun inst_bdv [] t = t
wneuper@59394
   281
  | inst_bdv (instl: (term*term) list) t =
wneuper@59394
   282
    let
wneuper@59394
   283
      fun subst (v as Var((s, _), T)) = 
wneuper@59394
   284
          (case Symbol.explode s of
wneuper@59394
   285
            "b"::"d"::"v"::_ => if_none (assoc(instl,Free(s,T))) (Free(s,T))
wneuper@59394
   286
          | _ => v)
wneuper@59394
   287
        | subst (Abs(a, T, body)) = Abs(a, T, subst body)
wneuper@59394
   288
        | subst (f $ t') = subst f $ subst t'
wneuper@59394
   289
        | subst t = if_none (assoc (instl, t)) t
wneuper@59394
   290
    in  subst t  end;
neuper@38025
   291
neuper@42426
   292
(* is a term a substitution for a bdv as found in programs *)
neuper@42426
   293
fun is_bdv_subst (Const ("List.list.Cons", _) $
neuper@42426
   294
      (Const ("Product_Type.Pair", _) $ Free (str, _) $ _) $ _) = is_bdv str
neuper@42426
   295
  | is_bdv_subst _ = false;
neuper@42426
   296
wneuper@59392
   297
fun free2str (Free (s, _)) = s
neuper@52105
   298
  | free2str t = error ("free2str not for " ^ term2str t);
wneuper@59392
   299
fun str_of_free_opt (Free (s, _)) = SOME s
neuper@52103
   300
  | str_of_free_opt _ = NONE
neuper@38025
   301
wneuper@59392
   302
(* compare Logic.unvarify_global, which rejects Free *)
wneuper@59392
   303
fun var2free (t as Const _) = t
wneuper@59392
   304
  | var2free (t as Free _) = t
wneuper@59392
   305
  | var2free (Var((s, _), T)) = Free (s,T)
wneuper@59392
   306
  | var2free (t as Bound _) = t 
wneuper@59392
   307
  | var2free (Abs(s, T, t)) = Abs(s, T, var2free t)
neuper@38025
   308
  | var2free (t1 $ t2) = (var2free t1) $ (var2free t2);
neuper@38025
   309
  
wneuper@59392
   310
(* Logic.varify does NOT take care of 'Free ("1", _)'*)
wneuper@59392
   311
fun free2var (t as Const _) = t
wneuper@59390
   312
  | free2var (t as Free (s, T)) = if is_num' s then t else Var ((s, 0), T)
wneuper@59392
   313
  | free2var (t as Var _) = t
wneuper@59392
   314
  | free2var (t as Bound _) = t 
neuper@38025
   315
  | free2var (Abs (s, T, t)) = Abs (s, T, free2var t)
neuper@38025
   316
  | free2var (t1 $ t2) = (free2var t1) $ (free2var t2);
neuper@38025
   317
neuper@38025
   318
fun mk_listT T = Type ("List.list", [T]);
wneuper@59392
   319
fun list_const T = Const ("List.list.Cons", [T, mk_listT T] ---> mk_listT T);
wneuper@59392
   320
fun list2isalist T [] = Const ("List.list.Nil", mk_listT T)
wneuper@59392
   321
  | list2isalist T (t :: ts) = (list_const T) $ t $ (list2isalist T ts);
neuper@38025
   322
wneuper@59392
   323
fun isapair2pair (Const ("Product_Type.Pair",_) $ a $ b) = (a, b)
neuper@38025
   324
  | isapair2pair t = 
neuper@38031
   325
    error ("isapair2pair called with "^term2str t);
neuper@38025
   326
fun isalist2list ls =
neuper@38025
   327
  let
wneuper@59392
   328
    fun get es (Const("List.list.Cons", _) $ t $ ls) = get (t :: es) ls
wneuper@59392
   329
      | get es (Const("List.list.Nil", _)) = es
wneuper@59392
   330
      | get _ t = error ("isalist2list applied to NON-list '"^term2str t^"'")
neuper@38025
   331
  in (rev o (get [])) ls end;
neuper@38025
   332
wneuper@59392
   333
fun is_list ((Const ("List.list.Cons", _)) $ _ $ _) = true
wneuper@59392
   334
  | is_list _ = false;
wneuper@59392
   335
fun dest_binop_typ (Type ("fun", [range, Type ("fun", [arg2, arg1])])) = (arg1, arg2, range)
wneuper@59392
   336
  | dest_binop_typ _ = raise ERROR "dest_binop_typ: not binary";
wneuper@59392
   337
fun dest_equals (Const("HOL.eq", _) $ t $ u)  =  (t, u) (* Pure/logic.ML: Const ("==", ..*)
wneuper@59390
   338
  | dest_equals t = raise TERM ("dest_equals'", [t]);
wneuper@59390
   339
fun is_equality (Const("HOL.eq",_) $ _ $ _)  =  true  (* logic.ML: Const("=="*)
neuper@38025
   340
  | is_equality _ = false;
wneuper@59392
   341
fun mk_equality (t, u) = (Const("HOL.eq", [type_of t, type_of u] ---> HOLogic.boolT) $ t $ u); 
wneuper@59390
   342
fun is_expliceq (Const("HOL.eq",_) $ (Free _) $ _)  =  true
neuper@38025
   343
  | is_expliceq _ = false;
wneuper@59390
   344
fun strip_trueprop (Const ("HOL.Trueprop", _) $ t) = t
neuper@38025
   345
  | strip_trueprop t = t;
neuper@38025
   346
wneuper@59392
   347
(* (A1==>...An==>B) goes to (A1==>...An==>)   Pure/logic.ML: term -> term list*)
wneuper@59392
   348
fun strip_imp_prems' (Const ("==>", _) $ A $ t) = 
wneuper@59392
   349
    let
wneuper@59392
   350
      fun coll_prems As (Const("==>", _) $ A $ t) = 
wneuper@59392
   351
          coll_prems (As $ (Logic.implies $ A)) t
wneuper@59392
   352
        | coll_prems As _ = SOME As
neuper@38025
   353
    in coll_prems (Logic.implies $ A) t end
wneuper@59392
   354
  | strip_imp_prems' _ = NONE;  (* *)
neuper@38025
   355
wneuper@59392
   356
(* (A1==>...An==>) (B) goes to (A1==>...An==>B), where B is lowest branch, 2002 Pure/thm.ML *)
wneuper@59390
   357
fun ins_concl (Const ("==>", _) $ A $ t) B = Logic.implies $ A $ (ins_concl t B)
wneuper@59390
   358
  | ins_concl (Const ("==>", _) $ A    ) B = Logic.implies $ A $ B
wneuper@59390
   359
  | ins_concl t B =  raise TERM ("ins_concl", [t, B]);
neuper@38025
   360
wneuper@59392
   361
fun vperm (Var _, Var _) = true  (* 2002 Pure/thm.ML *)
neuper@38025
   362
  | vperm (Abs (_, _, s), Abs (_, _, t)) = vperm (s, t)
neuper@38025
   363
  | vperm (t1 $ t2, u1 $ u2) = vperm (t1, u1) andalso vperm (t2, u2)
neuper@38025
   364
  | vperm (t, u) = (t = u);
neuper@38025
   365
neuper@38025
   366
(*2002 cp from Pure/term.ML --- since 2009 in Pure/old_term.ML*)
neuper@38025
   367
fun mem_term (_, []) = false
wneuper@59392
   368
  | mem_term (t, t' :: ts) = t aconv t' orelse mem_term (t, ts);
wneuper@59390
   369
fun subset_term ([], _) = true
wneuper@59390
   370
  | subset_term (x :: xs, ys) = mem_term (x, ys) andalso subset_term (xs, ys);
neuper@38025
   371
fun eq_set_term (xs, ys) =
neuper@38025
   372
    xs = ys orelse (subset_term (xs, ys) andalso subset_term (ys, xs));
neuper@38025
   373
(*a total, irreflexive ordering on index names*)
wneuper@59392
   374
fun xless ((a, i), (b, j): indexname) = i<j  orelse  (i = j andalso a < b);
neuper@38025
   375
(*a partial ordering (not reflexive) for atomic terms*)
wneuper@59392
   376
fun atless (Const (a, _), Const (b, _)) = a < b
wneuper@59392
   377
  | atless (Free (a, _), Free (b, _)) = a < b
wneuper@59392
   378
  | atless (Var (v, _), Var (w, _)) = xless (v, w)
wneuper@59392
   379
  | atless (Bound i, Bound j) =  i < j
wneuper@59392
   380
  | atless _ = false;
neuper@38025
   381
(*insert atomic term into partially sorted list, suppressing duplicates (?)*)
neuper@38025
   382
fun insert_aterm (t,us) =
neuper@38025
   383
  let fun inserta [] = [t]
neuper@38025
   384
        | inserta (us as u::us') =
neuper@38025
   385
              if atless(t,u) then t::us
neuper@38025
   386
              else if t=u then us (*duplicate*)
wneuper@59392
   387
              else u :: inserta us'
wneuper@59392
   388
  in inserta us end;
neuper@38025
   389
wneuper@59390
   390
(* Accumulates the Vars in the term, suppressing duplicates *)
neuper@38025
   391
fun add_term_vars (t, vars: term list) = case t of
wneuper@59392
   392
    Var   _ => insert_aterm (t, vars)
wneuper@59392
   393
  | Abs (_, _, body) => add_term_vars (body, vars)
wneuper@59392
   394
  | f$t =>  add_term_vars (f, add_term_vars (t, vars))
neuper@38025
   395
  | _ => vars;
wneuper@59390
   396
fun term_vars t = add_term_vars (t, []);
neuper@38025
   397
wneuper@59392
   398
(*2002 Pure/thm.ML *)
wneuper@59392
   399
fun var_perm (t, u) = vperm (t, u) andalso eq_set_term (term_vars t, term_vars u);
neuper@38025
   400
(*2002 fun decomp_simp, Pure/thm.ML *)
wneuper@59390
   401
fun perm lhs rhs = var_perm (lhs, rhs) andalso not (lhs aconv rhs) andalso not (is_Var lhs);
neuper@38025
   402
wneuper@59392
   403
(* TODO: shift to calculate.sml? *)
wneuper@59392
   404
fun calc_equ "less"  (n1, n2) = n1 < n2
wneuper@59392
   405
  | calc_equ "less_eq" (n1, n2) = n1 <= n2
wneuper@59392
   406
  | calc_equ op_ _ = error ("calc_equ: operator = " ^ op_ ^ " not defined");
wneuper@59392
   407
fun sqrt (n:int) = if n < 0 then 0 else (trunc o Math.sqrt o Real.fromInt (*FIXME*)) n;
wneuper@59391
   408
fun power _ 0 = 1
neuper@38025
   409
  | power b n = 
wneuper@59391
   410
    if n > 0 then b* (power b (n - 1))
wneuper@59391
   411
    else error ("power " ^ str_of_int b ^ " " ^ str_of_int n);
neuper@38025
   412
fun gcd 0 b = b
wneuper@59392
   413
  | gcd a b = if a < b then gcd (b mod a) a else gcd (a mod b) b;
wneuper@59392
   414
fun sign n =
wneuper@59392
   415
  if n < 0 then ~1
wneuper@59392
   416
	else if n = 0 then 0 else 1;
wneuper@59391
   417
fun sign_mult n1 n2 = (sign n1) * (sign n2);
neuper@38025
   418
neuper@38025
   419
infix dvd;
neuper@38025
   420
fun d dvd n = n mod d = 0;
neuper@38025
   421
fun divisors n =
neuper@38025
   422
  let fun pdiv ds d n = 
wneuper@59392
   423
    if d = n then d :: ds
wneuper@59392
   424
    else if d dvd n then pdiv (d :: ds) d (n div d)
wneuper@59392
   425
	 else pdiv ds (d + 1) n
neuper@38025
   426
  in pdiv [] 2 n end;
neuper@38025
   427
neuper@38025
   428
fun doubles ds = (* ds is ordered *)
neuper@38025
   429
  let fun dbls ds [] = ds
wneuper@59392
   430
	| dbls ds [ _ ] = ds
wneuper@59392
   431
	| dbls ds (i :: i' :: is) = if i = i' then dbls (i :: ds) is
neuper@38025
   432
				else dbls ds (i'::is)
neuper@38025
   433
  in dbls [] ds end;
neuper@38025
   434
fun squfact 0 = 0
neuper@38025
   435
  | squfact 1 = 1
neuper@38025
   436
  | squfact n = foldl op* (1, (doubles o divisors) n);
neuper@38025
   437
neuper@38025
   438
neuper@38025
   439
fun pairT T1 T2 = Type ("*", [T1, T2]);
neuper@38025
   440
fun PairT T1 T2 = ([T1, T2] ---> Type ("*", [T1, T2]));
wneuper@59392
   441
fun pairt t1 t2 = Const ("Product_Type.Pair", PairT (type_of t1) (type_of t2)) $ t1 $ t2;
neuper@38025
   442
neuper@38025
   443
fun mk_factroot op_(*=thy.sqrt*) T fact root = 
neuper@38034
   444
  Const ("Groups.times_class.times", [T, T] ---> T) $ (term_of_num T fact) $
wneuper@59392
   445
    (Const (op_, T --> T) $ term_of_num T root);
wneuper@59390
   446
fun mk_var_op_num v op_ optype ntyp n = Const (op_, optype) $ v $ Free (str_of_int  n, ntyp);
wneuper@59390
   447
fun mk_num_op_var v op_ optype ntyp n = Const (op_, optype) $ Free (str_of_int n, ntyp) $ v;
wneuper@59390
   448
fun mk_num_op_num T1 T2 (op_, Top) n1 n2 =
wneuper@59390
   449
  Const (op_, Top) $ Free (str_of_int n1, T1) $ Free (str_of_int n2, T2);
wneuper@59392
   450
fun mk_thmid thmid n1 n2 = 
wneuper@59392
   451
  thmid ^ (strip_thy n1) ^ "_" ^ (strip_thy n2);
wneuper@59392
   452
fun mk_add t1 t2 =
wneuper@59392
   453
  let
wneuper@59392
   454
    val (T1, T2) = (type_of t1, type_of t2)
wneuper@59392
   455
  in
wneuper@59392
   456
    if T1 <> T2 then raise TYPE ("mk_add gets ", [T1, T2], [t1,t2])
wneuper@59392
   457
    else (Const ("Groups.plus_class.plus", [T1, T2] ---> T1) $ t1 $ t2)
wneuper@59392
   458
  end;
neuper@38025
   459
wneuper@59392
   460
fun const_in _ (Const _) = false
wneuper@59392
   461
  | const_in str (Free (s, _)) = if strip_thy s = str then true else false
wneuper@59392
   462
  | const_in _ (Bound _) = false
wneuper@59392
   463
  | const_in _ (Var _) = false
wneuper@59392
   464
  | const_in str (Abs (_, _, body)) = const_in str body
wneuper@59392
   465
  | const_in str (f $ u) = const_in str f orelse const_in str u;
neuper@41931
   466
neuper@41931
   467
neuper@38025
   468
neuper@38025
   469
neuper@38025
   470
neuper@38025
   471
(** transform binary numeralsstrings **)
neuper@38025
   472
(*Makarius 100308, hacked by WN*)
neuper@38025
   473
val numbers_to_string =
neuper@38025
   474
  let
neuper@38025
   475
    fun dest_num t =
neuper@38025
   476
      (case try HOLogic.dest_number t of
neuper@38025
   477
        SOME (T, i) =>
neuper@38025
   478
          (*if T = @{typ int} orelse T = @{typ real} then WN*)
neuper@38025
   479
            SOME (Free (signed_string_of_int i, T))
neuper@38025
   480
          (*else NONE  WN*)
neuper@38025
   481
      | NONE => NONE);
neuper@38025
   482
    fun to_str (Abs (x, T, b)) = Abs (x, T, to_str b)
neuper@38025
   483
      | to_str (t as (u1 $ u2)) =
neuper@38025
   484
          (case dest_num t of
neuper@38025
   485
            SOME t' => t'
neuper@38025
   486
          | NONE => to_str u1 $ to_str u2)
neuper@38025
   487
      | to_str t = perhaps dest_num t;
neuper@38025
   488
  in to_str end
neuper@38025
   489
val uminus_to_string =
wneuper@59392
   490
  let
wneuper@59392
   491
	  fun dest_num t =
wneuper@59392
   492
	    case t of
wneuper@59392
   493
	      (Const ("Groups.uminus_class.uminus", _) $ Free (s, T)) => 
wneuper@59392
   494
	        (case int_of_str_opt s of
wneuper@59392
   495
	          SOME i => SOME (Free (signed_string_of_int (~1 * i), T))
wneuper@59392
   496
	        | NONE => NONE)
wneuper@59392
   497
	    | _ => NONE;
wneuper@59392
   498
    fun to_str (Abs (x, T, b)) = Abs (x, T, to_str b)
wneuper@59392
   499
      | to_str (t as (u1 $ u2)) =
wneuper@59392
   500
          (case dest_num t of SOME t' => t' | NONE => to_str u1 $ to_str u2)
wneuper@59392
   501
      | to_str t = perhaps dest_num t;
wneuper@59392
   502
  in to_str end;
neuper@38025
   503
fun num_str thm =
wneuper@59392
   504
  let
wneuper@59392
   505
    val (deriv, 
wneuper@59333
   506
	   {cert = cert, tags = tags, maxidx = maxidx, shyps = shyps, 
wneuper@59185
   507
	    hyps = hyps, tpairs = tpairs, prop = prop}) = Thm.rep_thm_G thm
neuper@38025
   508
    val prop' = numbers_to_string prop;
wneuper@59333
   509
  in Thm.assbl_thm deriv cert tags maxidx shyps hyps tpairs prop' end;
neuper@38025
   510
wneuper@59392
   511
fun mk_Free (s,T) = Free (s, T);
wneuper@59392
   512
fun mk_free T s =  Free (s, T);
neuper@38025
   513
neuper@38025
   514
(*Special case: one argument cp from Isabelle2002/src/Pure/term.ML*)
wneuper@59392
   515
fun subst_bound (arg, t) =
wneuper@59392
   516
  let
wneuper@59392
   517
    fun subst (t as Bound i, lev) =
wneuper@59392
   518
        if i < lev then t (*var is locally bound*)
wneuper@59392
   519
        else if i = lev then incr_boundvars lev arg
wneuper@59392
   520
        else Bound (i - 1) (*loose: change it*)
wneuper@59392
   521
      | subst (Abs(a, T, body), lev) = Abs (a, T, subst (body, lev + 1))
wneuper@59392
   522
      | subst (f$t, lev) =  subst(f, lev)  $  subst(t, lev)
wneuper@59392
   523
      | subst (t, _) = t
wneuper@59392
   524
  in subst (t, 0)  end;
neuper@38025
   525
wneuper@59392
   526
(* instantiate let; necessary for ass_up *)
wneuper@59394
   527
fun inst_abs (Const sT) = Const sT
wneuper@59393
   528
  | inst_abs (Free sT) = Free sT
wneuper@59393
   529
  | inst_abs (Bound n) = Bound n
wneuper@59393
   530
  | inst_abs (Var iT) = Var iT
wneuper@59393
   531
  | inst_abs (Const ("HOL.Let",T1) $ e $ (Abs (v, T2, b))) = 
wneuper@59394
   532
    let val b' = subst_bound (Free (v, T2), b); (*fun variant_abs: term.ML*)
wneuper@59393
   533
    in Const ("HOL.Let", T1) $ inst_abs e $ (Abs (v, T2, inst_abs b')) end
wneuper@59393
   534
  | inst_abs (t1 $ t2) = inst_abs t1 $ inst_abs t2
wneuper@59393
   535
  | inst_abs t = t;
neuper@38025
   536
neuper@38037
   537
(* for parse and parse_patt: fix all types to real *)
neuper@38025
   538
fun T_a2real (Type (s, [])) = 
wneuper@59394
   539
    if s = "'a" orelse s = "'b" orelse s = "'c" then HOLogic.realT else Type (s, [])
neuper@38025
   540
  | T_a2real (Type (s, Ts)) = Type (s, map T_a2real Ts)
neuper@38025
   541
  | T_a2real (TFree (s, srt)) = 
wneuper@59394
   542
    if s = "'a" orelse s = "'b" orelse s = "'c" then HOLogic.realT else TFree (s, srt)
wneuper@59394
   543
  | T_a2real (TVar (("DUMMY", _), _)) = HOLogic.realT
neuper@38037
   544
  | T_a2real (TVar ((s, i), srt)) = 
wneuper@59394
   545
    if s = "'a" orelse s = "'b" orelse s = "'c" then HOLogic.realT else TVar ((s, i), srt)
neuper@38025
   546
fun typ_a2real (Const( s, T)) = (Const( s, T_a2real T)) 
neuper@38025
   547
  | typ_a2real (Free( s, T)) = (Free( s, T_a2real T))
neuper@38025
   548
  | typ_a2real (Var( n, T)) = (Var( n, T_a2real T))
neuper@38025
   549
  | typ_a2real (Bound i) = (Bound i)
neuper@38025
   550
  | typ_a2real (Abs(s,T,t)) = Abs(s, T, typ_a2real t)
neuper@38025
   551
  | typ_a2real (t1 $ t2) = (typ_a2real t1) $ (typ_a2real t2);
neuper@38025
   552
wneuper@59394
   553
(* TODO clarify parse with Test_Isac *)
wneuper@59394
   554
fun parseold thy str = (* before 2002 *)
wneuper@59394
   555
  (let val t = ((*typ_a2real o*) numbers_to_string) (Syntax.read_term_global thy str)
wneuper@59184
   556
   in SOME (Thm.global_cterm_of thy t) end)
wneuper@59394
   557
  handle _(*EXN? ..Inner syntax error Failed to parse term*) => NONE;
wneuper@59394
   558
fun parseN thy str = (* introduced 2002 *)
wneuper@59394
   559
  (let val t = (*(typ_a2real o numbers_to_string)*) (Syntax.read_term_global thy str)
wneuper@59184
   560
   in SOME (Thm.global_cterm_of thy t) end)
wneuper@59394
   561
  handle _(*EXN? ..Inner syntax error Failed to parse term*) => NONE;
wneuper@59394
   562
fun parse thy str = (* introduced 2010 *)
wneuper@59394
   563
  (let val t = (typ_a2real o numbers_to_string) (Syntax.read_term_global thy str)
wneuper@59394
   564
   in SOME (Thm.global_cterm_of thy t) end)
wneuper@59394
   565
  handle _(*EXN? ..Inner syntax error Failed to parse term*) => NONE;
neuper@38025
   566
neuper@41931
   567
(*WN110317 parseNEW will replace parse after introduction of ctxt completed*)
bonzai@41949
   568
fun parseNEW ctxt str = SOME (Syntax.read_term ctxt str |> numbers_to_string)
wneuper@59394
   569
   handle _ => NONE;
neuper@48879
   570
(* parse term patterns; Var ("v",_), i.e. "?v", are required for instantiation
neuper@48879
   571
  WN130613 probably compare to 
neuper@48879
   572
  http://www.mail-archive.com/isabelle-dev@mailbroy.informatik.tu-muenchen.de/msg04249.html*)
wneuper@59394
   573
fun parse_patt thy str =
wneuper@59394
   574
  (thy, str) |>> thy2ctxt 
wneuper@59394
   575
             |-> Proof_Context.read_term_pattern
wneuper@59394
   576
             |> numbers_to_string (*TODO drop*)
wneuper@59394
   577
             |> typ_a2real;       (*TODO drop*)
wneuper@59394
   578
fun str2term str = parse_patt (Thy_Info_get_theory "Isac") str
neuper@38025
   579
wneuper@59394
   580
(* TODO decide with Test_Isac *)
wneuper@59394
   581
fun is_atom t = length (vars t) = 1
neuper@38025
   582
fun is_atom (Const ("Float.Float",_) $ _) = true
neuper@38025
   583
  | is_atom (Const ("ComplexI.I'_'_",_)) = true
neuper@38034
   584
  | is_atom (Const ("Groups.times_class.times",_) $ t $ Const ("ComplexI.I'_'_",_)) = is_atom t
neuper@38025
   585
  | is_atom (Const ("Groups.plus_class.plus",_) $ t1 $ Const ("ComplexI.I'_'_",_)) = is_atom t1
neuper@38025
   586
  | is_atom (Const ("Groups.plus_class.plus",_) $ t1 $ 
neuper@38034
   587
		   (Const ("Groups.times_class.times",_) $ t2 $ Const ("ComplexI.I'_'_",_))) = 
neuper@38025
   588
    is_atom t1 andalso is_atom t2
neuper@38025
   589
  | is_atom (Const _) = true
neuper@38025
   590
  | is_atom (Free _) = true
neuper@38025
   591
  | is_atom (Var _) = true
neuper@38025
   592
  | is_atom _ = false;
neuper@38025
   593
wneuper@59394
   594
(* from Pure/term.ML; reports if ALL Free's have found a substitution
wneuper@59394
   595
   (required for evaluating the preconditions of _incomplete_ models) *)
wneuper@59394
   596
fun subst_atomic_all [] t = (false (*TODO may be 'true' for some terms ?*), t)
wneuper@59394
   597
  | subst_atomic_all instl t =
wneuper@59394
   598
    let
wneuper@59394
   599
      fun subst (Abs (a, T, body)) = 
wneuper@59394
   600
          let
wneuper@59394
   601
            val (all, body') = subst body
wneuper@59394
   602
          in (all, Abs(a, T, body')) end
wneuper@59394
   603
        | subst (f$tt) = 
wneuper@59394
   604
	        let
wneuper@59394
   605
	          val (all1, f') = subst f
wneuper@59394
   606
	          val (all2, tt') = subst tt
wneuper@59394
   607
	        in (all1 andalso all2, f' $ tt') end
wneuper@59394
   608
        | subst (t as Free _) = 
wneuper@59394
   609
	        if is_num t then (true, t) (*numerals cannot be subst*)
wneuper@59394
   610
	        else (case assoc (instl, t) of
wneuper@59394
   611
					  SOME t' => (true, t')
wneuper@59394
   612
				  | NONE => (false, t))
wneuper@59394
   613
        | subst t = (true, if_none (assoc(instl,t)) t)
wneuper@59394
   614
    in subst t end;
wneuper@59389
   615
wneuper@59389
   616
end