src/Pure/context.ML
author wenzelm
Wed, 06 Jul 2011 20:46:06 +0200
changeset 44563 85388f5570c4
parent 44481 16482dc641d4
child 47876 421760a1efe7
permissions -rw-r--r--
prefer Synchronized.var;
     1 (*  Title:      Pure/context.ML
     2     Author:     Markus Wenzel, TU Muenchen
     3 
     4 Generic theory contexts with unique identity, arbitrarily typed data,
     5 monotonic development graph and history support.  Generic proof
     6 contexts with arbitrarily typed data.
     7 
     8 Firm naming conventions:
     9    thy, thy', thy1, thy2: theory
    10    ctxt, ctxt', ctxt1, ctxt2: Proof.context
    11    context: Context.generic
    12 *)
    13 
    14 signature BASIC_CONTEXT =
    15 sig
    16   type theory
    17   type theory_ref
    18   exception THEORY of string * theory list
    19   structure Proof: sig type context end
    20   structure Proof_Context:
    21   sig
    22     val theory_of: Proof.context -> theory
    23     val init_global: theory -> Proof.context
    24   end
    25 end;
    26 
    27 signature CONTEXT =
    28 sig
    29   include BASIC_CONTEXT
    30   (*theory context*)
    31   val timing: bool Unsynchronized.ref
    32   type pretty
    33   val parents_of: theory -> theory list
    34   val ancestors_of: theory -> theory list
    35   val theory_name: theory -> string
    36   val is_stale: theory -> bool
    37   val is_draft: theory -> bool
    38   val reject_draft: theory -> theory
    39   val PureN: string
    40   val display_names: theory -> string list
    41   val pretty_thy: theory -> Pretty.T
    42   val string_of_thy: theory -> string
    43   val pretty_abbrev_thy: theory -> Pretty.T
    44   val str_of_thy: theory -> string
    45   val get_theory: theory -> string -> theory
    46   val this_theory: theory -> string -> theory
    47   val deref: theory_ref -> theory
    48   val check_thy: theory -> theory_ref
    49   val eq_thy: theory * theory -> bool
    50   val subthy: theory * theory -> bool
    51   val joinable: theory * theory -> bool
    52   val merge: theory * theory -> theory
    53   val merge_refs: theory_ref * theory_ref -> theory_ref
    54   val copy_thy: theory -> theory
    55   val checkpoint_thy: theory -> theory
    56   val finish_thy: theory -> theory
    57   val begin_thy: (theory -> pretty) -> string -> theory list -> theory
    58   (*proof context*)
    59   val raw_transfer: theory -> Proof.context -> Proof.context
    60   (*generic context*)
    61   datatype generic = Theory of theory | Proof of Proof.context
    62   val cases: (theory -> 'a) -> (Proof.context -> 'a) -> generic -> 'a
    63   val mapping: (theory -> theory) -> (Proof.context -> Proof.context) -> generic -> generic
    64   val mapping_result: (theory -> 'a * theory) -> (Proof.context -> 'a * Proof.context) ->
    65     generic -> 'a * generic
    66   val the_theory: generic -> theory
    67   val the_proof: generic -> Proof.context
    68   val map_theory: (theory -> theory) -> generic -> generic
    69   val map_proof: (Proof.context -> Proof.context) -> generic -> generic
    70   val map_theory_result: (theory -> 'a * theory) -> generic -> 'a * generic
    71   val map_proof_result: (Proof.context -> 'a * Proof.context) -> generic -> 'a * generic
    72   val theory_map: (generic -> generic) -> theory -> theory
    73   val proof_map: (generic -> generic) -> Proof.context -> Proof.context
    74   val theory_of: generic -> theory  (*total*)
    75   val proof_of: generic -> Proof.context  (*total*)
    76   (*pretty printing context*)
    77   val pretty: Proof.context -> pretty
    78   val pretty_global: theory -> pretty
    79   val pretty_context: (theory -> Proof.context) -> pretty -> Proof.context
    80   (*thread data*)
    81   val thread_data: unit -> generic option
    82   val the_thread_data: unit -> generic
    83   val set_thread_data: generic option -> unit
    84   val setmp_thread_data: generic option -> ('a -> 'b) -> 'a -> 'b
    85   val >> : (generic -> generic) -> unit
    86   val >>> : (generic -> 'a * generic) -> 'a
    87 end;
    88 
    89 signature PRIVATE_CONTEXT =
    90 sig
    91   include CONTEXT
    92   structure Theory_Data:
    93   sig
    94     val declare: Position.T -> Object.T -> (Object.T -> Object.T) ->
    95       (pretty -> Object.T * Object.T -> Object.T) -> serial
    96     val get: serial -> (Object.T -> 'a) -> theory -> 'a
    97     val put: serial -> ('a -> Object.T) -> 'a -> theory -> theory
    98   end
    99   structure Proof_Data:
   100   sig
   101     val declare: (theory -> Object.T) -> serial
   102     val get: serial -> (Object.T -> 'a) -> Proof.context -> 'a
   103     val put: serial -> ('a -> Object.T) -> 'a -> Proof.context -> Proof.context
   104   end
   105 end;
   106 
   107 structure Context: PRIVATE_CONTEXT =
   108 struct
   109 
   110 (*** theory context ***)
   111 
   112 (** theory data **)
   113 
   114 (* data kinds and access methods *)
   115 
   116 val timing = Unsynchronized.ref false;
   117 
   118 (*private copy avoids potential conflict of table exceptions*)
   119 structure Datatab = Table(type key = int val ord = int_ord);
   120 
   121 datatype pretty = Pretty of Object.T;
   122 
   123 local
   124 
   125 type kind =
   126  {pos: Position.T,
   127   empty: Object.T,
   128   extend: Object.T -> Object.T,
   129   merge: pretty -> Object.T * Object.T -> Object.T};
   130 
   131 val kinds = Synchronized.var "Theory_Data" (Datatab.empty: kind Datatab.table);
   132 
   133 fun invoke name f k x =
   134   (case Datatab.lookup (Synchronized.value kinds) k of
   135     SOME kind =>
   136       if ! timing andalso name <> "" then
   137         Timing.cond_timeit true ("Theory_Data." ^ name ^ Position.str_of (#pos kind))
   138           (fn () => f kind x)
   139       else f kind x
   140   | NONE => raise Fail "Invalid theory data identifier");
   141 
   142 in
   143 
   144 fun invoke_empty k = invoke "" (K o #empty) k ();
   145 val invoke_extend = invoke "extend" #extend;
   146 fun invoke_merge pp = invoke "merge" (fn kind => #merge kind pp);
   147 
   148 fun declare_theory_data pos empty extend merge =
   149   let
   150     val k = serial ();
   151     val kind = {pos = pos, empty = empty, extend = extend, merge = merge};
   152     val _ = Synchronized.change kinds (Datatab.update (k, kind));
   153   in k end;
   154 
   155 val extend_data = Datatab.map invoke_extend;
   156 fun merge_data pp = Datatab.join (invoke_merge pp) o pairself extend_data;
   157 
   158 end;
   159 
   160 
   161 
   162 (** datatype theory **)
   163 
   164 datatype theory =
   165   Theory of
   166    (*identity*)
   167    {self: theory Unsynchronized.ref option,  (*dynamic self reference -- follows theory changes*)
   168     draft: bool,                  (*draft mode -- linear destructive changes*)
   169     id: serial,                   (*identifier*)
   170     ids: unit Inttab.table} *     (*cumulative identifiers of non-drafts -- symbolic body content*)
   171    (*data*)
   172    Object.T Datatab.table *       (*body content*)
   173    (*ancestry*)
   174    {parents: theory list,         (*immediate predecessors*)
   175     ancestors: theory list} *     (*all predecessors -- canonical reverse order*)
   176    (*history*)
   177    {name: string,                 (*official theory name*)
   178     stage: int};                  (*checkpoint counter*)
   179 
   180 exception THEORY of string * theory list;
   181 
   182 fun rep_theory (Theory args) = args;
   183 
   184 val identity_of = #1 o rep_theory;
   185 val data_of = #2 o rep_theory;
   186 val ancestry_of = #3 o rep_theory;
   187 val history_of = #4 o rep_theory;
   188 
   189 fun make_identity self draft id ids = {self = self, draft = draft, id = id, ids = ids};
   190 fun make_ancestry parents ancestors = {parents = parents, ancestors = ancestors};
   191 fun make_history name stage = {name = name, stage = stage};
   192 
   193 val the_self = the o #self o identity_of;
   194 val parents_of = #parents o ancestry_of;
   195 val ancestors_of = #ancestors o ancestry_of;
   196 val theory_name = #name o history_of;
   197 
   198 
   199 (* staleness *)
   200 
   201 fun eq_id (i: int, j) = i = j;
   202 
   203 fun is_stale
   204     (Theory ({self =
   205         SOME (Unsynchronized.ref (Theory ({id = id', ...}, _, _, _))), id, ...}, _, _, _)) =
   206       not (eq_id (id, id'))
   207   | is_stale (Theory ({self = NONE, ...}, _, _, _)) = true;
   208 
   209 fun vitalize (thy as Theory ({self = SOME r, ...}, _, _, _)) = (r := thy; thy)
   210   | vitalize (thy as Theory ({self = NONE, draft, id, ids}, data, ancestry, history)) =
   211       let
   212         val r = Unsynchronized.ref thy;
   213         val thy' = Theory (make_identity (SOME r) draft id ids, data, ancestry, history);
   214       in r := thy'; thy' end;
   215 
   216 
   217 (* draft mode *)
   218 
   219 val is_draft = #draft o identity_of;
   220 
   221 fun reject_draft thy =
   222   if is_draft thy then
   223     raise THEORY ("Illegal draft theory -- stable checkpoint required", [thy])
   224   else thy;
   225 
   226 
   227 (* names *)
   228 
   229 val PureN = "Pure";
   230 val draftN = "#";
   231 val finished = ~1;
   232 
   233 fun display_names thy =
   234   let
   235     val draft = if is_draft thy then [draftN] else [];
   236     val {stage, ...} = history_of thy;
   237     val name =
   238       if stage = finished then theory_name thy
   239       else theory_name thy ^ ":" ^ string_of_int stage;
   240     val ancestor_names = map theory_name (ancestors_of thy);
   241     val stale = if is_stale thy then ["!"] else [];
   242   in rev (stale @ draft @ [name] @ ancestor_names) end;
   243 
   244 val pretty_thy = Pretty.str_list "{" "}" o display_names;
   245 val string_of_thy = Pretty.string_of o pretty_thy;
   246 
   247 fun pretty_abbrev_thy thy =
   248   let
   249     val names = display_names thy;
   250     val n = length names;
   251     val abbrev = if n > 5 then "..." :: List.drop (names, n - 5) else names;
   252   in Pretty.str_list "{" "}" abbrev end;
   253 
   254 val str_of_thy = Pretty.str_of o pretty_abbrev_thy;
   255 
   256 fun get_theory thy name =
   257   if theory_name thy <> name then
   258     (case find_first (fn thy' => theory_name thy' = name) (ancestors_of thy) of
   259       SOME thy' => thy'
   260     | NONE => error ("Unknown ancestor theory " ^ quote name))
   261   else if #stage (history_of thy) = finished then thy
   262   else error ("Unfinished theory " ^ quote name);
   263 
   264 fun this_theory thy name =
   265   if theory_name thy = name then thy
   266   else get_theory thy name;
   267 
   268 
   269 (* theory references *)
   270 
   271 (*theory_ref provides a safe way to store dynamic references to a
   272   theory in external data structures -- a plain theory value would
   273   become stale as the self reference moves on*)
   274 
   275 datatype theory_ref = Theory_Ref of theory Unsynchronized.ref;
   276 
   277 fun deref (Theory_Ref (Unsynchronized.ref thy)) = thy;
   278 
   279 fun check_thy thy =  (*thread-safe version*)
   280   let val thy_ref = Theory_Ref (the_self thy) in
   281     if is_stale thy then error ("Stale theory encountered:\n" ^ string_of_thy thy)
   282     else thy_ref
   283   end;
   284 
   285 
   286 (* build ids *)
   287 
   288 fun insert_id draft id ids =
   289   if draft then ids
   290   else Inttab.update (id, ()) ids;
   291 
   292 fun merge_ids
   293     (Theory ({draft = draft1, id = id1, ids = ids1, ...}, _, _, _))
   294     (Theory ({draft = draft2, id = id2, ids = ids2, ...}, _, _, _)) =
   295   Inttab.merge (K true) (ids1, ids2)
   296   |> insert_id draft1 id1
   297   |> insert_id draft2 id2;
   298 
   299 
   300 (* equality and inclusion *)
   301 
   302 val eq_thy = eq_id o pairself (#id o identity_of);
   303 
   304 fun proper_subthy (Theory ({id, ...}, _, _, _), Theory ({ids, ...}, _, _, _)) =
   305   Inttab.defined ids id;
   306 
   307 fun subthy thys = eq_thy thys orelse proper_subthy thys;
   308 
   309 fun joinable (thy1, thy2) = subthy (thy1, thy2) orelse subthy (thy2, thy1);
   310 
   311 
   312 (* consistent ancestors *)
   313 
   314 fun extend_ancestors thy thys =
   315   if member eq_thy thys thy then
   316     raise THEORY ("Duplicate theory node", thy :: thys)
   317   else thy :: thys;
   318 
   319 fun extend_ancestors_of thy = extend_ancestors thy (ancestors_of thy);
   320 
   321 val merge_ancestors = merge (fn (thy1, thy2) =>
   322   eq_thy (thy1, thy2) orelse
   323     theory_name thy1 = theory_name thy2 andalso
   324       raise THEORY ("Inconsistent theory versions", [thy1, thy2]));
   325 
   326 
   327 (* trivial merge *)
   328 
   329 fun merge (thy1, thy2) =
   330   if eq_thy (thy1, thy2) then thy1
   331   else if proper_subthy (thy2, thy1) then thy1
   332   else if proper_subthy (thy1, thy2) then thy2
   333   else error (cat_lines ["Attempt to perform non-trivial merge of theories:",
   334     str_of_thy thy1, str_of_thy thy2]);
   335 
   336 fun merge_refs (ref1, ref2) =
   337   if ref1 = ref2 then ref1
   338   else check_thy (merge (deref ref1, deref ref2));
   339 
   340 
   341 
   342 (** build theories **)
   343 
   344 (* primitives *)
   345 
   346 local
   347   val lock = Mutex.mutex ();
   348 in
   349   fun SYNCHRONIZED e = Simple_Thread.synchronized "theory" lock e;
   350 end;
   351 
   352 fun create_thy self draft ids data ancestry history =
   353   let val identity = make_identity self draft (serial ()) ids;
   354   in vitalize (Theory (identity, data, ancestry, history)) end;
   355 
   356 fun change_thy draft' f thy =
   357   let
   358     val Theory ({self, draft, id, ids}, data, ancestry, history) = thy;
   359     val (self', data', ancestry') =
   360       if draft then (self, data, ancestry)    (*destructive change!*)
   361       else if #stage history > 0
   362       then (NONE, data, ancestry)
   363       else (NONE, extend_data data, make_ancestry [thy] (extend_ancestors_of thy));
   364     val ids' = insert_id draft id ids;
   365     val data'' = f data';
   366     val thy' = SYNCHRONIZED (fn () =>
   367       (check_thy thy; create_thy self' draft' ids' data'' ancestry' history));
   368   in thy' end;
   369 
   370 val name_thy = change_thy false I;
   371 val extend_thy = change_thy true I;
   372 val modify_thy = change_thy true;
   373 
   374 fun copy_thy thy =
   375   let
   376     val Theory ({draft, id, ids, ...}, data, ancestry, history) = thy;
   377     val ids' = insert_id draft id ids;
   378     val thy' = SYNCHRONIZED (fn () =>
   379       (check_thy thy; create_thy NONE true ids' data ancestry history));
   380   in thy' end;
   381 
   382 val pre_pure_thy = create_thy NONE true Inttab.empty
   383   Datatab.empty (make_ancestry [] []) (make_history PureN 0);
   384 
   385 
   386 (* named theory nodes *)
   387 
   388 fun merge_thys pp (thy1, thy2) =
   389   let
   390     val ids = merge_ids thy1 thy2;
   391     val data = merge_data (pp thy1) (data_of thy1, data_of thy2);
   392     val ancestry = make_ancestry [] [];
   393     val history = make_history "" 0;
   394     val thy' = SYNCHRONIZED (fn () =>
   395      (check_thy thy1; check_thy thy2; create_thy NONE true ids data ancestry history));
   396   in thy' end;
   397 
   398 fun maximal_thys thys =
   399   thys |> filter_out (fn thy => exists (fn thy' => proper_subthy (thy, thy')) thys);
   400 
   401 fun begin_thy pp name imports =
   402   if name = "" orelse name = draftN then error ("Bad theory name: " ^ quote name)
   403   else
   404     let
   405       val parents = maximal_thys (distinct eq_thy imports);
   406       val ancestors =
   407         Library.foldl merge_ancestors ([], map ancestors_of parents)
   408         |> fold extend_ancestors parents;
   409 
   410       val Theory ({ids, ...}, data, _, _) =
   411         (case parents of
   412           [] => error "No parent theories"
   413         | [thy] => extend_thy thy
   414         | thy :: thys => Library.foldl (merge_thys pp) (thy, thys));
   415 
   416       val ancestry = make_ancestry parents ancestors;
   417       val history = make_history name 0;
   418       val thy' = SYNCHRONIZED (fn () =>
   419         (map check_thy imports; create_thy NONE true ids data ancestry history));
   420     in thy' end;
   421 
   422 
   423 (* history stages *)
   424 
   425 fun history_stage f thy =
   426   let
   427     val {name, stage} = history_of thy;
   428     val _ = stage = finished andalso raise THEORY ("Theory already finished", [thy]);
   429     val history' = make_history name (f stage);
   430     val thy' as Theory (identity', data', ancestry', _) = name_thy thy;
   431     val thy'' = SYNCHRONIZED (fn () =>
   432       (check_thy thy'; vitalize (Theory (identity', data', ancestry', history'))));
   433   in thy'' end;
   434 
   435 fun checkpoint_thy thy =
   436   if is_draft thy then history_stage (fn stage => stage + 1) thy
   437   else thy;
   438 
   439 val finish_thy = history_stage (fn _ => finished);
   440 
   441 
   442 (* theory data *)
   443 
   444 structure Theory_Data =
   445 struct
   446 
   447 val declare = declare_theory_data;
   448 
   449 fun get k dest thy =
   450   (case Datatab.lookup (data_of thy) k of
   451     SOME x => x
   452   | NONE => invoke_empty k) |> dest;
   453 
   454 fun put k mk x = modify_thy (Datatab.update (k, mk x));
   455 
   456 end;
   457 
   458 
   459 
   460 (*** proof context ***)
   461 
   462 (* datatype Proof.context *)
   463 
   464 structure Proof =
   465 struct
   466   datatype context = Context of Object.T Datatab.table * theory_ref;
   467 end;
   468 
   469 fun theory_of_proof (Proof.Context (_, thy_ref)) = deref thy_ref;
   470 fun data_of_proof (Proof.Context (data, _)) = data;
   471 fun map_prf f (Proof.Context (data, thy_ref)) = Proof.Context (f data, thy_ref);
   472 
   473 
   474 (* proof data kinds *)
   475 
   476 local
   477 
   478 val kinds = Synchronized.var "Proof_Data" (Datatab.empty: (theory -> Object.T) Datatab.table);
   479 
   480 fun invoke_init k =
   481   (case Datatab.lookup (Synchronized.value kinds) k of
   482     SOME init => init
   483   | NONE => raise Fail "Invalid proof data identifier");
   484 
   485 fun init_data thy =
   486   Datatab.map (fn k => fn _ => invoke_init k thy) (Synchronized.value kinds);
   487 
   488 fun init_new_data data thy =
   489   Datatab.merge (K true) (data, init_data thy);
   490 
   491 in
   492 
   493 fun raw_transfer thy' (Proof.Context (data, thy_ref)) =
   494   let
   495     val thy = deref thy_ref;
   496     val _ = subthy (thy, thy') orelse error "transfer proof context: not a super theory";
   497     val _ = check_thy thy;
   498     val data' = init_new_data data thy';
   499     val thy_ref' = check_thy thy';
   500   in Proof.Context (data', thy_ref') end;
   501 
   502 structure Proof_Context =
   503 struct
   504   val theory_of = theory_of_proof;
   505   fun init_global thy = Proof.Context (init_data thy, check_thy thy);
   506 end;
   507 
   508 structure Proof_Data =
   509 struct
   510 
   511 fun declare init =
   512   let
   513     val k = serial ();
   514     val _ = Synchronized.change kinds (Datatab.update (k, init));
   515   in k end;
   516 
   517 fun get k dest prf =
   518   dest (case Datatab.lookup (data_of_proof prf) k of
   519     SOME x => x
   520   | NONE => invoke_init k (Proof_Context.theory_of prf));   (*adhoc value*)
   521 
   522 fun put k mk x = map_prf (Datatab.update (k, mk x));
   523 
   524 end;
   525 
   526 end;
   527 
   528 
   529 
   530 (*** generic context ***)
   531 
   532 datatype generic = Theory of theory | Proof of Proof.context;
   533 
   534 fun cases f _ (Theory thy) = f thy
   535   | cases _ g (Proof prf) = g prf;
   536 
   537 fun mapping f g = cases (Theory o f) (Proof o g);
   538 fun mapping_result f g = cases (apsnd Theory o f) (apsnd Proof o g);
   539 
   540 val the_theory = cases I (fn _ => error "Ill-typed context: theory expected");
   541 val the_proof = cases (fn _ => error "Ill-typed context: proof expected") I;
   542 
   543 fun map_theory f = Theory o f o the_theory;
   544 fun map_proof f = Proof o f o the_proof;
   545 
   546 fun map_theory_result f = apsnd Theory o f o the_theory;
   547 fun map_proof_result f = apsnd Proof o f o the_proof;
   548 
   549 fun theory_map f = the_theory o f o Theory;
   550 fun proof_map f = the_proof o f o Proof;
   551 
   552 val theory_of = cases I Proof_Context.theory_of;
   553 val proof_of = cases Proof_Context.init_global I;
   554 
   555 
   556 (* pretty printing context *)
   557 
   558 exception PRETTY of generic;
   559 
   560 val pretty = Pretty o PRETTY o Proof;
   561 val pretty_global = Pretty o PRETTY o Theory;
   562 
   563 fun pretty_context init (Pretty (PRETTY context)) = cases init I context;
   564 
   565 
   566 
   567 (** thread data **)
   568 
   569 local val tag = Universal.tag () : generic option Universal.tag in
   570 
   571 fun thread_data () =
   572   (case Thread.getLocal tag of
   573     SOME (SOME context) => SOME context
   574   | _ => NONE);
   575 
   576 fun the_thread_data () =
   577   (case thread_data () of
   578     SOME context => context
   579   | _ => error "Unknown context");
   580 
   581 fun set_thread_data context = Thread.setLocal (tag, context);
   582 fun setmp_thread_data context = Library.setmp_thread_data tag (thread_data ()) context;
   583 
   584 end;
   585 
   586 fun >>> f =
   587   let
   588     val (res, context') = f (the_thread_data ());
   589     val _ = set_thread_data (SOME context');
   590   in res end;
   591 
   592 nonfix >>;
   593 fun >> f = >>> (fn context => ((), f context));
   594 
   595 val _ = set_thread_data (SOME (Theory pre_pure_thy));
   596 
   597 end;
   598 
   599 structure Basic_Context: BASIC_CONTEXT = Context;
   600 open Basic_Context;
   601 
   602 
   603 
   604 (*** type-safe interfaces for data declarations ***)
   605 
   606 (** theory data **)
   607 
   608 signature THEORY_DATA_PP_ARGS =
   609 sig
   610   type T
   611   val empty: T
   612   val extend: T -> T
   613   val merge: Context.pretty -> T * T -> T
   614 end;
   615 
   616 signature THEORY_DATA_ARGS =
   617 sig
   618   type T
   619   val empty: T
   620   val extend: T -> T
   621   val merge: T * T -> T
   622 end;
   623 
   624 signature THEORY_DATA =
   625 sig
   626   type T
   627   val get: theory -> T
   628   val put: T -> theory -> theory
   629   val map: (T -> T) -> theory -> theory
   630 end;
   631 
   632 functor Theory_Data_PP(Data: THEORY_DATA_PP_ARGS): THEORY_DATA =
   633 struct
   634 
   635 type T = Data.T;
   636 exception Data of T;
   637 
   638 val kind =
   639   Context.Theory_Data.declare
   640     (Position.thread_data ())
   641     (Data Data.empty)
   642     (fn Data x => Data (Data.extend x))
   643     (fn pp => fn (Data x1, Data x2) => Data (Data.merge pp (x1, x2)));
   644 
   645 val get = Context.Theory_Data.get kind (fn Data x => x);
   646 val put = Context.Theory_Data.put kind Data;
   647 fun map f thy = put (f (get thy)) thy;
   648 
   649 end;
   650 
   651 functor Theory_Data(Data: THEORY_DATA_ARGS): THEORY_DATA =
   652   Theory_Data_PP
   653   (
   654     type T = Data.T;
   655     val empty = Data.empty;
   656     val extend = Data.extend;
   657     fun merge _ = Data.merge;
   658   );
   659 
   660 
   661 
   662 (** proof data **)
   663 
   664 signature PROOF_DATA_ARGS =
   665 sig
   666   type T
   667   val init: theory -> T
   668 end;
   669 
   670 signature PROOF_DATA =
   671 sig
   672   type T
   673   val get: Proof.context -> T
   674   val put: T -> Proof.context -> Proof.context
   675   val map: (T -> T) -> Proof.context -> Proof.context
   676 end;
   677 
   678 functor Proof_Data(Data: PROOF_DATA_ARGS): PROOF_DATA =
   679 struct
   680 
   681 type T = Data.T;
   682 exception Data of T;
   683 
   684 val kind = Context.Proof_Data.declare (Data o Data.init);
   685 
   686 val get = Context.Proof_Data.get kind (fn Data x => x);
   687 val put = Context.Proof_Data.put kind Data;
   688 fun map f prf = put (f (get prf)) prf;
   689 
   690 end;
   691 
   692 
   693 
   694 (** generic data **)
   695 
   696 signature GENERIC_DATA_ARGS =
   697 sig
   698   type T
   699   val empty: T
   700   val extend: T -> T
   701   val merge: T * T -> T
   702 end;
   703 
   704 signature GENERIC_DATA =
   705 sig
   706   type T
   707   val get: Context.generic -> T
   708   val put: T -> Context.generic -> Context.generic
   709   val map: (T -> T) -> Context.generic -> Context.generic
   710 end;
   711 
   712 functor Generic_Data(Data: GENERIC_DATA_ARGS): GENERIC_DATA =
   713 struct
   714 
   715 structure Thy_Data = Theory_Data(Data);
   716 structure Prf_Data = Proof_Data(type T = Data.T val init = Thy_Data.get);
   717 
   718 type T = Data.T;
   719 
   720 fun get (Context.Theory thy) = Thy_Data.get thy
   721   | get (Context.Proof prf) = Prf_Data.get prf;
   722 
   723 fun put x (Context.Theory thy) = Context.Theory (Thy_Data.put x thy)
   724   | put x (Context.Proof prf) = Context.Proof (Prf_Data.put x prf);
   725 
   726 fun map f ctxt = put (f (get ctxt)) ctxt;
   727 
   728 end;
   729 
   730 (*hide private interface*)
   731 structure Context: CONTEXT = Context;
   732