src/Pure/defs.ML
author obua
Mon, 11 Jul 2005 14:52:55 +0200
changeset 16766 ea667a5426fe
parent 16743 21dbff595bf6
child 16826 ed53f24149f6
permissions -rw-r--r--
Improved implementation of Defs.is_overloaded.
Ignore whitespace changes - Everywhere: Within whitespace: At end of lines:
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
     1
(*  Title:      Pure/General/defs.ML
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
     2
    ID:         $Id$
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
     3
    Author:     Steven Obua, TU Muenchen
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
     4
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
     5
    Checks if definitions preserve consistency of logic by enforcing 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
     6
    that there are no cyclic definitions. The algorithm is described in 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
     7
    "An Algorithm for Determining Definitional Cycles in Higher-Order Logic with Overloading", 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
     8
    Steven Obua, technical report, to be written :-)
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
     9
*)
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
    10
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
    11
signature DEFS = sig
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
    12
    
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
    13
  type graph
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
    14
       
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
    15
  exception DEFS of string
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
    16
  exception CIRCULAR of (typ * string * string) list
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
    17
  exception INFINITE_CHAIN of (typ * string * string) list 
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
    18
  exception FINAL of string * typ
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
    19
  exception CLASH of string * string * string
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
    20
                     
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
    21
  val empty : graph
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
    22
  val declare : graph -> string * typ -> graph  (* exception DEFS *)
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
    23
  val define : graph -> string * typ -> string -> (string * typ) list -> graph 
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
    24
    (* exception DEFS, CIRCULAR, INFINITE_CHAIN, CLASH, FINAL *)   
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
    25
                                                                     
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
    26
  val finalize : graph -> string * typ -> graph (* exception DEFS *)
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
    27
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
    28
  val finals : graph -> (typ list) Symtab.table
16158
2c3565b74b7a Removed final_consts from theory data. Now const_deps deals with final
obua
parents: 16113
diff changeset
    29
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
    30
  val merge : graph -> graph -> graph (* exception CIRCULAR, INFINITE_CHAIN, CLASH *)
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
    31
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
    32
  (* If set to true then the exceptions CIRCULAR and INFINITE_CHAIN return the full
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
    33
     chain of definitions that lead to the exception. In the beginning, chain_history 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
    34
     is initialized with the Isabelle environment variable DEFS_CHAIN_HISTORY. *)
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
    35
  val set_chain_history : bool -> unit
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
    36
  val chain_history : unit -> bool
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
    37
16743
21dbff595bf6 1) all theorems in Orderings can now be given as a parameter
obua
parents: 16384
diff changeset
    38
  datatype overloadingstate = Open | Closed | Final
21dbff595bf6 1) all theorems in Orderings can now be given as a parameter
obua
parents: 16384
diff changeset
    39
  val overloading_info : graph -> string -> (typ * (string*typ) list * overloadingstate) option
21dbff595bf6 1) all theorems in Orderings can now be given as a parameter
obua
parents: 16384
diff changeset
    40
  val is_overloaded : graph -> string -> bool
21dbff595bf6 1) all theorems in Orderings can now be given as a parameter
obua
parents: 16384
diff changeset
    41
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
    42
end
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
    43
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
    44
structure Defs :> DEFS = struct
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
    45
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
    46
type tyenv = Type.tyenv
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
    47
type edgelabel = (int * typ * typ * (typ * string * string) list)
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
    48
16743
21dbff595bf6 1) all theorems in Orderings can now be given as a parameter
obua
parents: 16384
diff changeset
    49
datatype overloadingstate = Open | Closed | Final
16361
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
    50
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
    51
datatype node = Node of
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
    52
         typ  (* most general type of constant *)
16361
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
    53
         * defnode Symtab.table
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
    54
             (* a table of defnodes, each corresponding to 1 definition of the 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
    55
                constant for a particular type, indexed by axiom name *)
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
    56
         * (unit Symtab.table) Symtab.table 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
    57
             (* a table of all back referencing defnodes to this node, 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
    58
                indexed by node name of the defnodes *)
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
    59
         * typ list (* a list of all finalized types *)
16743
21dbff595bf6 1) all theorems in Orderings can now be given as a parameter
obua
parents: 16384
diff changeset
    60
         * overloadingstate
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
    61
     
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
    62
     and defnode = Defnode of
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
    63
         typ  (* type of the constant in this particular definition *)
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
    64
         * (edgelabel list) Symtab.table (* The edges, grouped by nodes. *)
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
    65
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
    66
fun getnode graph noderef = the (Symtab.lookup (graph, noderef))
16361
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
    67
fun get_nodedefs (Node (_, defs, _, _, _)) = defs
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
    68
fun get_defnode (Node (_, defs, _, _, _)) defname = Symtab.lookup (defs, defname)
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
    69
fun get_defnode' graph noderef defname = 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
    70
    Symtab.lookup (get_nodedefs (the (Symtab.lookup (graph, noderef))), defname)
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
    71
16361
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
    72
fun table_size table = Symtab.foldl (fn (x, _) => x+1) (0, table)
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
    73
        
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
    74
datatype graphaction = Declare of string * typ
16158
2c3565b74b7a Removed final_consts from theory data. Now const_deps deals with final
obua
parents: 16113
diff changeset
    75
		     | Define of string * typ * string * (string * typ) list
2c3565b74b7a Removed final_consts from theory data. Now const_deps deals with final
obua
parents: 16113
diff changeset
    76
		     | Finalize of string * typ
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
    77
16384
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
    78
type graph = int * (string Symtab.table) * (graphaction list) * (node Symtab.table)
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
    79
             
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
    80
val CHAIN_HISTORY = 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
    81
    let
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
    82
      fun f c = if Char.isSpace c then "" else String.str (Char.toUpper c) 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
    83
      val env = String.translate f (getenv "DEFS_CHAIN_HISTORY")
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
    84
    in
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
    85
      ref (env = "ON" orelse env = "TRUE")
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
    86
    end
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
    87
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
    88
fun set_chain_history b = CHAIN_HISTORY := b
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
    89
fun chain_history () = !CHAIN_HISTORY
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
    90
16384
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
    91
val empty = (0, Symtab.empty, [], Symtab.empty)
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
    92
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
    93
exception DEFS of string;
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
    94
exception CIRCULAR of (typ * string * string) list;
16113
692fe6595755 Infinite chains in definitions are now detected, too.
obua
parents: 16108
diff changeset
    95
exception INFINITE_CHAIN of (typ * string * string) list;
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
    96
exception CLASH of string * string * string;
16158
2c3565b74b7a Removed final_consts from theory data. Now const_deps deals with final
obua
parents: 16113
diff changeset
    97
exception FINAL of string * typ;
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
    98
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
    99
fun def_err s = raise (DEFS s)
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   100
16361
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   101
fun no_forwards defs = 
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   102
    Symtab.foldl 
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   103
    (fn (closed, (_, Defnode (_, edges))) => 
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   104
        if not closed then false else Symtab.is_empty edges)
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   105
    (true, defs)
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   106
16384
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   107
exception No_Change;
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   108
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   109
fun map_nc f list = 
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   110
    let 
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   111
      val changed = ref false
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   112
      fun f' x = 
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   113
          let 
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   114
            val x' = f x  
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   115
            val _ = changed := true
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   116
          in
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   117
            x'
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   118
          end handle No_Change => x
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   119
      val list' = map f' list
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   120
    in
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   121
      if !changed then list' else raise No_Change
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   122
    end
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   123
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   124
fun checkT' (t as (Type (a, Ts))) = (Type (a, map_nc checkT' Ts) handle No_Change => t)
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   125
  | checkT' (t as (TVar ((a, 0), []))) = raise No_Change
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   126
  | checkT' (t as (TVar ((a, 0), _))) = TVar ((a, 0), [])
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   127
  | checkT' (t as (TFree (a, _))) = TVar ((a, 0), [])
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   128
  | checkT' _ = def_err "type is not clean"
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   129
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   130
fun checkT t = Term.compress_type (checkT' t handle No_Change => t)
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   131
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   132
fun rename ty1 ty2 = incr_tvar ((maxidx_of_typ ty1)+1) ty2;  
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   133
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   134
fun subst_incr_tvar inc t =
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   135
    if (inc > 0) then 
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   136
      let
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   137
	val tv = typ_tvars t
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   138
	val t' = incr_tvar inc t
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   139
	fun update_subst (((n,i), _), s) =
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   140
	    Vartab.update (((n, i), ([], TVar ((n, i+inc), []))), s)
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   141
      in
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   142
	(t',List.foldl update_subst Vartab.empty tv)
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   143
      end	
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   144
    else
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   145
      (t, Vartab.empty)
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   146
    
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   147
fun subst s ty = Envir.norm_type s ty
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   148
                 
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   149
fun subst_history s history = map (fn (ty, cn, dn) => (subst s ty, cn, dn)) history
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   150
                              
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   151
fun is_instance instance_ty general_ty =
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   152
    Type.typ_instance Type.empty_tsig (instance_ty, general_ty)
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   153
    
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   154
fun is_instance_r instance_ty general_ty =
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   155
    is_instance instance_ty (rename instance_ty general_ty)
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   156
    
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   157
fun unify ty1 ty2 = 
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   158
    SOME (fst (Type.unify Type.empty_tsig (Vartab.empty, 0) (ty1, ty2)))
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   159
    handle Type.TUNIFY => NONE
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   160
                            
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   161
(* 
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   162
   Unifies ty1 and ty2, renaming ty1 and ty2 so that they have greater indices than max and 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   163
   so that they are different. All indices in ty1 and ty2 are supposed to be less than or 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   164
   equal to max.
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   165
   Returns SOME (max', s1, s2), so that s1(ty1) = s2(ty2) and max' is greater or equal than 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   166
   all indices in s1, s2, ty1, ty2.
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   167
*)
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   168
fun unify_r max ty1 ty2 = 
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   169
    let
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   170
      val max = Int.max(max, 0)
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   171
      val max1 = max (* >= maxidx_of_typ ty1 *)
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   172
      val max2 = max (* >= maxidx_of_typ ty2 *)
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   173
      val max = Int.max(max, Int.max (max1, max2))
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   174
      val (ty1, s1) = subst_incr_tvar (max + 1) ty1
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   175
      val (ty2, s2) = subst_incr_tvar (max + max1 + 2) ty2
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   176
      val max = max + max1 + max2 + 2	
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   177
      fun merge a b = Vartab.merge (fn _ => false) (a, b)
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   178
    in
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   179
      case unify ty1 ty2 of
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   180
	NONE => NONE
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   181
      | SOME s => SOME (max, merge s1 s, merge s2 s)
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   182
    end
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   183
    
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   184
fun can_be_unified_r ty1 ty2 =
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   185
    let
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   186
      val ty2 = rename ty1 ty2
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   187
    in
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   188
      case unify ty1 ty2 of
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   189
	NONE => false
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   190
      | _ => true
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   191
    end
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   192
    
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   193
fun can_be_unified ty1 ty2 =
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   194
    case unify ty1 ty2 of
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   195
      NONE => false
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   196
    | _ => true
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   197
           
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   198
structure Inttab = TableFun(type key = int val ord = int_ord);
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   199
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   200
fun normalize_edge_idx (edge as (maxidx, u1, v1, history)) =
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   201
    if maxidx <= 1000000 then edge else
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   202
    let
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   203
      
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   204
      fun idxlist idx extract_ty inject_ty (tab, max) ts = 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   205
          foldr 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   206
            (fn (e, ((tab, max), ts)) => 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   207
                let
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   208
                  val ((tab, max), ty) = idx (tab, max) (extract_ty e)
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   209
                  val e = inject_ty (ty, e)
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   210
                in
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   211
                  ((tab, max), e::ts)
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   212
                end)
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   213
            ((tab,max), []) ts
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   214
          
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   215
      fun idx (tab,max) (TVar ((a,i),_)) = 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   216
          (case Inttab.lookup (tab, i) of 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   217
             SOME j => ((tab, max), TVar ((a,j),[]))
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   218
           | NONE => ((Inttab.update ((i, max), tab), max+1), TVar ((a,max),[])))
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   219
        | idx (tab,max) (Type (t, ts)) = 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   220
          let 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   221
            val ((tab, max), ts) = idxlist idx I fst (tab, max) ts
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   222
          in
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   223
            ((tab,max), Type (t, ts))
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   224
          end
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   225
        | idx (tab, max) ty = ((tab, max), ty)
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   226
      
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   227
      val ((tab,max), u1) = idx (Inttab.empty, 0) u1
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   228
      val ((tab,max), v1) = idx (tab, max) v1
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   229
      val ((tab,max), history) = 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   230
          idxlist idx
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   231
            (fn (ty,_,_) => ty) 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   232
            (fn (ty, (_, s1, s2)) => (ty, s1, s2)) 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   233
            (tab, max) history
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   234
    in
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   235
      (max, u1, v1, history)
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   236
    end
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   237
                        
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   238
fun compare_edges (e1 as (maxidx1, u1, v1, history1)) (e2 as (maxidx2, u2, v2, history2)) =
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   239
    let
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   240
      val t1 = u1 --> v1
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   241
      val t2 = incr_tvar (maxidx1+1) (u2 --> v2)
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   242
    in
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   243
      if (is_instance t1 t2) then
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   244
	(if is_instance t2 t1 then
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   245
	   SOME (int_ord (length history2, length history1))
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   246
	 else
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   247
	   SOME LESS)
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   248
      else if (is_instance t2 t1) then
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   249
	SOME GREATER
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   250
      else
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   251
	NONE
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   252
    end
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   253
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   254
fun merge_edges_1 (x, []) = [x]
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   255
  | merge_edges_1 (x, (y::ys)) = 
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   256
    (case compare_edges x y of
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   257
       SOME LESS => (y::ys)
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   258
     | SOME EQUAL => (y::ys)
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   259
     | SOME GREATER => merge_edges_1 (x, ys)
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   260
     | NONE => y::(merge_edges_1 (x, ys)))
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   261
    
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   262
fun merge_edges xs ys = foldl merge_edges_1 xs ys
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   263
16384
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   264
fun declare' (g as (cost, axmap, actions, graph)) (cty as (name, ty)) =
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   265
    (cost, axmap, (Declare cty)::actions, 
16361
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   266
     Symtab.update_new ((name, Node (ty, Symtab.empty, Symtab.empty, [], Open)), graph))
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   267
    handle Symtab.DUP _ => 
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   268
           let
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   269
             val (Node (gty, _, _, _, _)) = the (Symtab.lookup(graph, name))
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   270
           in
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   271
             if is_instance_r ty gty andalso is_instance_r gty ty then
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   272
               g
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   273
             else
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   274
               def_err "constant is already declared with different type"
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   275
           end
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   276
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   277
fun declare g (name, ty) = declare' g (name, checkT ty)
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   278
16384
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   279
val axcounter = ref (IntInf.fromInt 0)
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   280
fun newaxname axmap axname =
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   281
    let
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   282
      val c = !axcounter
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   283
      val _ = axcounter := c+1
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   284
      val axname' = axname^"_"^(IntInf.toString c)
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   285
    in
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   286
      (Symtab.update ((axname', axname), axmap), axname')
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   287
    end
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   288
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   289
fun translate_ex axmap x = 
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   290
    let
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   291
      fun translate (ty, nodename, axname) = 
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   292
          (ty, nodename, the (Symtab.lookup (axmap, axname)))
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   293
    in
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   294
      case x of
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   295
        INFINITE_CHAIN chain => raise (INFINITE_CHAIN (map translate chain))
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   296
      | CIRCULAR cycle => raise (CIRCULAR (map translate cycle))
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   297
      | _ => raise x
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   298
    end
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   299
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   300
fun define' (cost, axmap, actions, graph) (mainref, ty) axname body =
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   301
    let
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   302
      val mainnode  = (case Symtab.lookup (graph, mainref) of 
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   303
			 NONE => def_err ("constant "^mainref^" is not declared")
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   304
		       | SOME n => n)
16361
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   305
      val (Node (gty, defs, backs, finals, _)) = mainnode
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   306
      val _ = (if is_instance_r ty gty then () 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   307
               else def_err "type of constant does not match declared type")
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   308
      fun check_def (s, Defnode (ty', _)) = 
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   309
          (if can_be_unified_r ty ty' then 
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   310
	     raise (CLASH (mainref, axname, s))
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   311
	   else if s = axname then
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   312
	     def_err "name of axiom is already used for another definition of this constant"
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   313
	   else false)	
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   314
      val _ = Symtab.exists check_def defs
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   315
      fun check_final finalty = 
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   316
	  (if can_be_unified_r finalty ty then
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   317
	     raise (FINAL (mainref, finalty))
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   318
	   else
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   319
	     true)
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   320
      val _ = forall check_final finals
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   321
	             
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   322
      (* now we know that the only thing that can prevent acceptance of the definition 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   323
         is a cyclic dependency *)
16361
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   324
              
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   325
      fun insert_edges edges (nodename, links) =
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   326
          (if links = [] then 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   327
             edges
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   328
           else
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   329
             let
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   330
               val links = map normalize_edge_idx links
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   331
             in
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   332
               Symtab.update ((nodename, 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   333
	                       case Symtab.lookup (edges, nodename) of
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   334
	                         NONE => links
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   335
	                       | SOME links' => merge_edges links' links),
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   336
                              edges)
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   337
             end)
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   338
	 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   339
      fun make_edges ((bodyn, bodyty), edges) =
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   340
	  let
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   341
	    val bnode = 
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   342
		(case Symtab.lookup (graph, bodyn) of 
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   343
		   NONE => def_err "body of constant definition references undeclared constant"
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   344
		 | SOME x => x)
16361
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   345
	    val (Node (general_btyp, bdefs, bbacks, bfinals, closed)) = bnode
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   346
	  in
16361
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   347
            if closed = Final then edges else
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   348
	    case unify_r 0 bodyty general_btyp of
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   349
	      NONE => edges
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   350
	    | SOME (maxidx, sigma1, sigma2) => 
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   351
              if exists (is_instance_r bodyty) bfinals then 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   352
                edges
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   353
              else
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   354
	        let
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   355
		  fun insert_trans_edges ((step1, edges), (nodename, links)) =
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   356
                      let
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   357
                        val (maxidx1, alpha1, beta1, defname) = step1
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   358
                        fun connect (maxidx2, alpha2, beta2, history) = 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   359
		            case unify_r (Int.max (maxidx1, maxidx2)) beta1 alpha2 of
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   360
		              NONE => NONE
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   361
		            | SOME (max, sleft, sright) =>				  
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   362
			      SOME (max, subst sleft alpha1, subst sright beta2, 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   363
                                    if !CHAIN_HISTORY then   
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   364
			              ((subst sleft beta1, bodyn, defname)::
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   365
				       (subst_history sright history))
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   366
                                    else [])            
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   367
                        val links' = List.mapPartial connect links
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   368
                      in
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   369
                        (step1, insert_edges edges (nodename, links'))
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   370
                      end
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   371
                                                                
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   372
                  fun make_edges' ((swallowed, edges),
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   373
                                   (def_name, Defnode (def_ty, def_edges))) =
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   374
		      if swallowed then
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   375
		        (swallowed, edges)
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   376
		      else 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   377
		        (case unify_r 0 bodyty def_ty of
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   378
			   NONE => (swallowed, edges)
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   379
		         | SOME (maxidx, sigma1, sigma2) => 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   380
			   (is_instance_r bodyty def_ty,
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   381
                            snd (Symtab.foldl insert_trans_edges 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   382
                              (((maxidx, subst sigma1 ty, subst sigma2 def_ty, def_name),
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   383
                                edges), def_edges))))
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   384
          	  val (swallowed, edges) = Symtab.foldl make_edges' ((false, edges), bdefs)
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   385
	        in
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   386
		  if swallowed then 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   387
		    edges
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   388
		  else 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   389
                    insert_edges edges 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   390
                    (bodyn, [(maxidx, subst sigma1 ty, subst sigma2 general_btyp,[])])
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   391
	        end
16361
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   392
	  end                    
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   393
          
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   394
      val edges = foldl make_edges Symtab.empty body
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   395
                  				               
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   396
      (* We also have to add the backreferences that this new defnode induces. *)  
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   397
      fun install_backrefs (graph, (noderef, links)) =
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   398
          if links <> [] then
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   399
            let
16361
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   400
              val (Node (ty, defs, backs, finals, closed)) = getnode graph noderef
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   401
              val _ = if closed = Final then 
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   402
                        sys_error ("install_backrefs: closed node cannot be updated") 
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   403
                      else ()
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   404
              val defnames =
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   405
                  (case Symtab.lookup (backs, mainref) of
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   406
                     NONE => Symtab.empty
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   407
                   | SOME s => s)
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   408
              val defnames' = Symtab.update_new ((axname, ()), defnames)
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   409
              val backs' = Symtab.update ((mainref,defnames'), backs)
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   410
            in
16361
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   411
              Symtab.update ((noderef, Node (ty, defs, backs', finals, closed)), graph)
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   412
            end
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   413
          else
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   414
            graph
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   415
            
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   416
      val graph = Symtab.foldl install_backrefs (graph, edges)
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   417
                  
16361
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   418
      val (Node (_, _, backs, _, closed)) = getnode graph mainref
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   419
      val closed = 
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   420
          if closed = Final then sys_error "define: closed node" 
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   421
          else if closed = Open andalso is_instance_r gty ty then Closed else closed
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   422
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   423
      val thisDefnode = Defnode (ty, edges)
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   424
      val graph = Symtab.update ((mainref, Node (gty, Symtab.update_new 
16361
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   425
        ((axname, thisDefnode), defs), backs, finals, closed)), graph)
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   426
		                
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   427
      (* Now we have to check all backreferences to this node and inform them about 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   428
         the new defnode. In this section we also check for circularity. *)
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   429
      fun update_backrefs ((backs, graph), (noderef, defnames)) =
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   430
	  let
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   431
	    fun update_defs ((defnames, graph),(defname, _)) =
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   432
		let
16361
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   433
                  val (Node (nodety, nodedefs, nodebacks, nodefinals, closed)) = 
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   434
                      getnode graph noderef
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   435
                  val _ = if closed = Final then sys_error "update_defs: closed node" else ()
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   436
		  val (Defnode (def_ty, defnode_edges)) = 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   437
                      the (Symtab.lookup (nodedefs, defname))
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   438
		  val edges = the (Symtab.lookup (defnode_edges, mainref))
16361
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   439
                  val refclosed = ref false
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   440
 					
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   441
	          (* the type of thisDefnode is ty *)
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   442
		  fun update (e as (max, alpha, beta, history), (changed, edges)) = 
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   443
		      case unify_r max beta ty of
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   444
			NONE => (changed, e::edges)
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   445
		      | SOME (max', s_beta, s_ty) =>
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   446
			let
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   447
			  val alpha' = subst s_beta alpha
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   448
			  val ty' = subst s_ty ty				      
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   449
			  val _ = 
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   450
			      if noderef = mainref andalso defname = axname then
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   451
				(case unify alpha' ty' of
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   452
				   NONE => 
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   453
				   if (is_instance_r ty' alpha') then
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   454
				     raise (INFINITE_CHAIN (
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   455
					    (alpha', mainref, axname)::
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   456
					    (subst_history s_beta history)@
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   457
					    [(ty', mainref, axname)]))
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   458
				   else ()
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   459
				 | SOME s => 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   460
                                   raise (CIRCULAR (
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   461
					  (subst s alpha', mainref, axname)::
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   462
					  (subst_history s (subst_history s_beta history))@
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   463
					  [(subst s ty', mainref, axname)])))
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   464
			      else ()                             
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   465
			in
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   466
			  if is_instance_r beta ty then
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   467
			    (true, edges)
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   468
			  else
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   469
			    (changed, e::edges)
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   470
			end		    			   			       
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   471
                  
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   472
                  val (changed, edges') = foldl update (false, []) edges
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   473
                  val defnames' = if edges' = [] then 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   474
                                    defnames 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   475
                                  else 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   476
                                    Symtab.update ((defname, ()), defnames)
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   477
                in
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   478
                  if changed then
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   479
                    let
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   480
                      val defnode_edges' = 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   481
                          if edges' = [] then
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   482
                            Symtab.delete mainref defnode_edges
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   483
                          else
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   484
                            Symtab.update ((mainref, edges'), defnode_edges)
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   485
                      val defnode' = Defnode (def_ty, defnode_edges')
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   486
                      val nodedefs' = Symtab.update ((defname, defnode'), nodedefs)
16361
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   487
                      val closed = if closed = Closed andalso Symtab.is_empty defnode_edges'
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   488
                                      andalso no_forwards nodedefs' 
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   489
                                   then Final else closed
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   490
                      val graph' = 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   491
                          Symtab.update 
16361
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   492
                            ((noderef, 
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   493
                              Node (nodety, nodedefs', nodebacks, nodefinals, closed)),graph) 
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   494
                    in
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   495
                      (defnames', graph')
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   496
                    end
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   497
                  else
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   498
                    (defnames', graph)
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   499
                end
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   500
		    
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   501
	    val (defnames', graph') = Symtab.foldl update_defs 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   502
                                                   ((Symtab.empty, graph), defnames)
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   503
	  in
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   504
	    if Symtab.is_empty defnames' then 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   505
	      (backs, graph')
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   506
	    else
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   507
	      let
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   508
		val backs' = Symtab.update_new ((noderef, defnames'), backs)
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   509
	      in
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   510
		(backs', graph')
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   511
	      end
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   512
	  end
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   513
        
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   514
      val (backs, graph) = Symtab.foldl update_backrefs ((Symtab.empty, graph), backs)
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   515
                                        						 
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   516
      (* If a Circular exception is thrown then we never reach this point. *)
16361
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   517
      val (Node (gty, defs, _, finals, closed)) = getnode graph mainref
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   518
      val closed = if closed = Closed andalso no_forwards defs then Final else closed
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   519
      val graph = Symtab.update ((mainref, Node (gty, defs, backs, finals, closed)), graph) 
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   520
      val actions' = (Define (mainref, ty, axname, body))::actions
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   521
    in	    
16384
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   522
      (cost+3, axmap, actions', graph)
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   523
    end handle ex => translate_ex axmap ex
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   524
    
16384
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   525
fun define (g as (cost, axmap, actions, graph)) (mainref, ty) axname body =
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   526
    let
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   527
      val ty = checkT ty
16361
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   528
      fun checkbody (n, t) = 
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   529
          let 
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   530
            val (Node (_, _, _,_, closed)) = getnode graph n
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   531
          in
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   532
            case closed of
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   533
              Final => NONE
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   534
            | _ => SOME (n, checkT t)
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   535
          end
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   536
      val body = distinct (List.mapPartial checkbody body)
16384
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   537
      val (axmap, axname) = newaxname axmap axname
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   538
    in
16384
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   539
      define' (cost, axmap, actions, graph) (mainref, ty) axname body
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   540
    end
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   541
16384
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   542
fun finalize' (cost, axmap, history, graph) (noderef, ty) = 
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   543
    case Symtab.lookup (graph, noderef) of 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   544
      NONE => def_err ("cannot finalize constant "^noderef^"; it is not declared")
16361
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   545
    | SOME (Node (nodety, defs, backs, finals, closed)) =>
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   546
      let 
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   547
	val _ = 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   548
            if (not (is_instance_r ty nodety)) then
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   549
	      def_err ("only type instances of the declared constant "^
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   550
                       noderef^" can be finalized")
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   551
	    else ()
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   552
	val _ = Symtab.exists 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   553
                  (fn (def_name, Defnode (def_ty, _)) =>  
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   554
		      if can_be_unified_r ty def_ty then 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   555
			def_err ("cannot finalize constant "^noderef^
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   556
                                 "; clash with definition "^def_name)
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   557
		      else 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   558
			false)
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   559
		  defs 
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   560
        
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   561
        fun update_finals [] = SOME [ty]
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   562
          | update_finals (final_ty::finals) = 
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   563
            (if is_instance_r ty final_ty then NONE
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   564
             else
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   565
               case update_finals finals of
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   566
                 NONE => NONE
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   567
               | (r as SOME finals) =>
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   568
                 if (is_instance_r final_ty ty) then
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   569
                   r
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   570
                 else
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   571
                   SOME (final_ty :: finals))                              
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   572
      in    
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   573
        case update_finals finals of
16384
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   574
          NONE => (cost, axmap, history, graph)
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   575
        | SOME finals => 
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   576
	  let
16361
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   577
            val closed = if closed = Open andalso is_instance_r nodety ty then 
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   578
                           Closed else 
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   579
                         closed
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   580
	    val graph = Symtab.update ((noderef, Node(nodety, defs, backs, finals, closed)), 
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   581
                                       graph)
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   582
	                
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   583
	    fun update_backref ((graph, backs), (backrefname, backdefnames)) =
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   584
		let
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   585
		  fun update_backdef ((graph, defnames), (backdefname, _)) = 
16158
2c3565b74b7a Removed final_consts from theory data. Now const_deps deals with final
obua
parents: 16113
diff changeset
   586
	              let 
16361
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   587
			val (backnode as Node (backty, backdefs, backbacks, 
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   588
                                               backfinals, backclosed)) = 
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   589
                            getnode graph backrefname
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   590
			val (Defnode (def_ty, all_edges)) = 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   591
                            the (get_defnode backnode backdefname)
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   592
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   593
			val (defnames', all_edges') = 
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   594
			    case Symtab.lookup (all_edges, noderef) of
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   595
			      NONE => sys_error "finalize: corrupt backref"
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   596
			    | SOME edges =>
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   597
			      let
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   598
				val edges' = List.filter (fn (_, _, beta, _) => 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   599
                                                             not (is_instance_r beta ty)) edges
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   600
			      in
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   601
				if edges' = [] then 
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   602
				  (defnames, Symtab.delete noderef all_edges)
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   603
				else
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   604
				  (Symtab.update ((backdefname, ()), defnames), 
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   605
				   Symtab.update ((noderef, edges'), all_edges))
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   606
			      end
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   607
			val defnode' = Defnode (def_ty, all_edges')
16361
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   608
                        val backdefs' = Symtab.update ((backdefname, defnode'), backdefs)
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   609
                        val backclosed' = if backclosed = Closed andalso 
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   610
                                             Symtab.is_empty all_edges'
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   611
                                             andalso no_forwards backdefs'
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   612
                                          then Final else backclosed
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   613
			val backnode' = 
16361
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   614
                            Node (backty, backdefs', backbacks, backfinals, backclosed')
16158
2c3565b74b7a Removed final_consts from theory data. Now const_deps deals with final
obua
parents: 16113
diff changeset
   615
		      in
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   616
			(Symtab.update ((backrefname, backnode'), graph), defnames') 
16158
2c3565b74b7a Removed final_consts from theory data. Now const_deps deals with final
obua
parents: 16113
diff changeset
   617
		      end
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   618
	              
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   619
		  val (graph', defnames') = 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   620
                      Symtab.foldl update_backdef ((graph, Symtab.empty), backdefnames)
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   621
		in
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   622
		  (graph', if Symtab.is_empty defnames' then backs 
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   623
			   else Symtab.update ((backrefname, defnames'), backs))
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   624
		end
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   625
	    val (graph', backs') = Symtab.foldl update_backref ((graph, Symtab.empty), backs)
16361
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   626
	    val Node ( _, defs, _, _, closed) = getnode graph' noderef
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   627
            val closed = if closed = Closed andalso no_forwards defs then Final else closed
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   628
	    val graph' = Symtab.update ((noderef, Node (nodety, defs, backs', 
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   629
                                                        finals, closed)), graph')
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   630
            val history' = (Finalize (noderef, ty)) :: history
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   631
	  in
16384
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   632
	    (cost+1, axmap, history', graph')
16158
2c3565b74b7a Removed final_consts from theory data. Now const_deps deals with final
obua
parents: 16113
diff changeset
   633
	  end
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   634
      end
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   635
 
16361
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   636
fun finalize g (noderef, ty) = finalize' g (noderef, checkT ty) 
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   637
16361
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   638
fun merge' (Declare cty, g) = declare' g cty
16384
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   639
  | merge' (Define (name, ty, axname, body), g as (_,_, _, graph)) = 
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   640
    (case Symtab.lookup (graph, name) of
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   641
       NONE => define' g (name, ty) axname body
16361
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   642
     | SOME (Node (_, defs, _, _, _)) => 
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   643
       (case Symtab.lookup (defs, axname) of
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   644
	  NONE => define' g (name, ty) axname body
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   645
	| SOME _ => g))
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   646
  | merge' (Finalize finals, g) = finalize' g finals 
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   647
                       
16384
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   648
fun merge (g1 as (cost1, _, actions1, _)) (g2 as (cost2, _, actions2, _)) =
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   649
    if cost1 < cost2 then
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   650
      foldr merge' g2 actions1
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   651
    else
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   652
      foldr merge' g1 actions2
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   653
                           
16384
90c51c932154 internalize axiom names in Defs.define; compress types via Term.compress_type
obua
parents: 16361
diff changeset
   654
fun finals (_, _, history, graph) = 
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   655
    Symtab.foldl 
16361
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   656
      (fn (finals, (name, Node(_, _, _, ftys, _))) => 
cb31cb768a6c further optimizations of cycle test
obua
parents: 16308
diff changeset
   657
          Symtab.update_new ((name, ftys), finals)) 
16198
cfd070a2cc4d Integrates cycle detection in definitions with finalconsts
obua
parents: 16177
diff changeset
   658
      (Symtab.empty, graph)
16158
2c3565b74b7a Removed final_consts from theory data. Now const_deps deals with final
obua
parents: 16113
diff changeset
   659
16743
21dbff595bf6 1) all theorems in Orderings can now be given as a parameter
obua
parents: 16384
diff changeset
   660
fun overloading_info (_, axmap, _, graph) c = 
21dbff595bf6 1) all theorems in Orderings can now be given as a parameter
obua
parents: 16384
diff changeset
   661
    let
21dbff595bf6 1) all theorems in Orderings can now be given as a parameter
obua
parents: 16384
diff changeset
   662
      fun translate (ax, Defnode (ty, _)) = (the (Symtab.lookup (axmap, ax)), ty)
21dbff595bf6 1) all theorems in Orderings can now be given as a parameter
obua
parents: 16384
diff changeset
   663
    in
21dbff595bf6 1) all theorems in Orderings can now be given as a parameter
obua
parents: 16384
diff changeset
   664
      case Symtab.lookup (graph, c) of
21dbff595bf6 1) all theorems in Orderings can now be given as a parameter
obua
parents: 16384
diff changeset
   665
        NONE => NONE
21dbff595bf6 1) all theorems in Orderings can now be given as a parameter
obua
parents: 16384
diff changeset
   666
      | SOME (Node (ty, defnodes, _, _, state)) =>
21dbff595bf6 1) all theorems in Orderings can now be given as a parameter
obua
parents: 16384
diff changeset
   667
        SOME (ty, map translate (Symtab.dest defnodes), state)
21dbff595bf6 1) all theorems in Orderings can now be given as a parameter
obua
parents: 16384
diff changeset
   668
    end
21dbff595bf6 1) all theorems in Orderings can now be given as a parameter
obua
parents: 16384
diff changeset
   669
      
16766
ea667a5426fe Improved implementation of Defs.is_overloaded.
obua
parents: 16743
diff changeset
   670
exception Overloaded;
ea667a5426fe Improved implementation of Defs.is_overloaded.
obua
parents: 16743
diff changeset
   671
fun is_overloaded (_, _, _, graph) c = 
ea667a5426fe Improved implementation of Defs.is_overloaded.
obua
parents: 16743
diff changeset
   672
    let 
ea667a5426fe Improved implementation of Defs.is_overloaded.
obua
parents: 16743
diff changeset
   673
      fun count (c, _) = if c = 1 then raise Overloaded else c+1
ea667a5426fe Improved implementation of Defs.is_overloaded.
obua
parents: 16743
diff changeset
   674
    in
ea667a5426fe Improved implementation of Defs.is_overloaded.
obua
parents: 16743
diff changeset
   675
      case Symtab.lookup (graph, c) of
ea667a5426fe Improved implementation of Defs.is_overloaded.
obua
parents: 16743
diff changeset
   676
        NONE => false
ea667a5426fe Improved implementation of Defs.is_overloaded.
obua
parents: 16743
diff changeset
   677
      | SOME (Node (_, defnodes, _, _, _)) =>
ea667a5426fe Improved implementation of Defs.is_overloaded.
obua
parents: 16743
diff changeset
   678
        ((Symtab.foldl count (0, defnodes); false) handle Overloaded => true)
ea667a5426fe Improved implementation of Defs.is_overloaded.
obua
parents: 16743
diff changeset
   679
    end
16743
21dbff595bf6 1) all theorems in Orderings can now be given as a parameter
obua
parents: 16384
diff changeset
   680
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   681
end;
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   682
		
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   683
(*
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   684
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   685
fun tvar name = TVar ((name, 0), [])
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   686
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   687
val bool = Type ("bool", [])
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   688
val int = Type ("int", [])
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   689
val lam = Type("lam", [])
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   690
val alpha = tvar "'a"
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   691
val beta = tvar "'b"
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   692
val gamma = tvar "'c"
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   693
fun pair a b = Type ("pair", [a,b])
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   694
fun prm a = Type ("prm", [a])
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   695
val name = Type ("name", [])
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   696
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   697
val _ = print "make empty"
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   698
val g = Defs.empty 
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   699
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   700
val _ = print "declare perm"
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   701
val g = Defs.declare g ("perm", prm alpha --> beta --> beta)
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   702
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   703
val _ = print "declare permF"
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   704
val g = Defs.declare g ("permF", prm alpha --> lam --> lam)
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   705
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   706
val _ = print "define perm (1)"
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   707
val g = Defs.define g ("perm", prm alpha --> (beta --> gamma) --> (beta --> gamma)) "perm_fun" 
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   708
        [("perm", prm alpha --> gamma --> gamma), ("perm", prm alpha --> beta --> beta)]
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   709
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   710
val _ = print "define permF (1)"
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   711
val g = Defs.define g ("permF", prm alpha --> lam --> lam) "permF_app"
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   712
        ([("perm", prm alpha --> lam --> lam),
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   713
         ("perm", prm alpha --> lam --> lam),
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   714
         ("perm", prm alpha --> lam --> lam),
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   715
         ("perm", prm alpha --> name --> name)])
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   716
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   717
val _ = print "define perm (2)"
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   718
val g = Defs.define g ("perm", prm alpha --> lam --> lam) "perm_lam"
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   719
        [("permF", (prm alpha --> lam --> lam))]
16108
cf468b93a02e Implement cycle-free overloading, so that definitions cannot harm consistency any more (except of course via interaction with axioms).
obua
parents:
diff changeset
   720
16308
636a1a84977a 1) Fixed bug in Defs.merge_edges_1.
obua
parents: 16198
diff changeset
   721
*)