src/Pure/Thy/present.ML
author wenzelm
Wed, 13 Aug 2008 20:57:39 +0200
changeset 27862 8f727f7c8c1d
parent 27491 c8178a6a6480
child 28027 051d5ccbafc5
permissions -rw-r--r--
removed obsolete verbatim_source, results, chapter, section etc.;
removed obsolete results, theorems(s);
moved theorem result hook to proof_display.ML;
     1 (*  Title:      Pure/Thy/present.ML
     2     ID:         $Id$
     3     Author:     Markus Wenzel and Stefan Berghofer, TU Muenchen
     4 
     5 Theory presentation: HTML, graph files, (PDF)LaTeX documents.
     6 *)
     7 
     8 signature BASIC_PRESENT =
     9 sig
    10   val no_document: ('a -> 'b) -> 'a -> 'b
    11 end;
    12 
    13 signature PRESENT =
    14 sig
    15   include BASIC_PRESENT
    16   val session_name: theory -> string
    17   val write_graph: {name: string, ID: string, dir: string, unfold: bool,
    18    path: string, parents: string list} list -> Path.T -> unit
    19   val display_graph: {name: string, ID: string, dir: string, unfold: bool,
    20    path: string, parents: string list} list -> unit
    21   val init: bool -> bool -> string -> bool -> string list -> string list ->
    22     string -> (bool * Path.T) option -> Url.T option * bool -> bool -> theory list -> unit
    23   val finish: unit -> unit
    24   val init_theory: string -> unit
    25   val theory_source: string -> (unit -> HTML.text) -> unit
    26   val theory_output: string -> string -> unit
    27   val begin_theory: int -> Path.T -> (Path.T * bool) list -> theory -> theory
    28   val drafts: string -> Path.T list -> Path.T
    29 end;
    30 
    31 structure Present: PRESENT =
    32 struct
    33 
    34 
    35 (** paths **)
    36 
    37 val output_path = Path.variable "ISABELLE_BROWSER_INFO";
    38 
    39 val tex_ext = Path.ext "tex";
    40 val tex_path = tex_ext o Path.basic;
    41 val html_ext = Path.ext "html";
    42 val html_path = html_ext o Path.basic;
    43 val index_path = Path.basic "index.html";
    44 val readme_html_path = Path.basic "README.html";
    45 val readme_path = Path.basic "README";
    46 val documentN = "document";
    47 val document_path = Path.basic documentN;
    48 val doc_indexN = "session";
    49 val graph_path = Path.basic "session.graph";
    50 val graph_pdf_path = Path.basic "session_graph.pdf";
    51 val graph_eps_path = Path.basic "session_graph.eps";
    52 
    53 val session_path = Path.basic ".session";
    54 val session_entries_path = Path.explode ".session/entries";
    55 val pre_index_path = Path.explode ".session/pre-index";
    56 
    57 fun mk_rel_path [] ys = Path.make ys
    58   | mk_rel_path xs [] = Path.appends (replicate (length xs) Path.parent)
    59   | mk_rel_path (ps as x :: xs) (qs as y :: ys) = if x = y then mk_rel_path xs ys else
    60       Path.appends (replicate (length ps) Path.parent @ [Path.make qs]);
    61 
    62 fun show_path path = Path.implode (Path.append (File.pwd ()) path);
    63 
    64 
    65 
    66 (** additional theory data **)
    67 
    68 structure BrowserInfoData = TheoryDataFun
    69 (
    70   type T = {name: string, session: string list, is_local: bool};
    71   val empty = {name = "", session = [], is_local = false}: T;
    72   val copy = I;
    73   fun extend _ = empty;
    74   fun merge _ _ = empty;
    75 );
    76 
    77 val put_info = BrowserInfoData.put;
    78 val get_info = BrowserInfoData.get;
    79 val session_name = #name o get_info;
    80 
    81 
    82 
    83 (** graphs **)
    84 
    85 type graph_node =
    86   {name: string, ID: string, dir: string, unfold: bool,
    87    path: string, parents: string list};
    88 
    89 fun write_graph gr path =
    90   File.write path (cat_lines (map (fn {name, ID, dir, unfold, path, parents} =>
    91     "\"" ^ name ^ "\" \"" ^ ID ^ "\" \"" ^ dir ^ (if unfold then "\" + \"" else "\" \"") ^
    92     path ^ "\" > " ^ space_implode " " (map Library.quote parents) ^ " ;") gr));
    93 
    94 fun display_graph gr =
    95   let
    96     val _ = writeln "Displaying graph ...";
    97     val path = File.tmp_path (Path.explode "tmp.graph");
    98     val _ = write_graph gr path;
    99     val _ = File.isatool ("browser -c " ^ File.shell_path path ^ " &");
   100   in () end;
   101 
   102 
   103 fun ID_of sess s = space_implode "/" (sess @ [s]);
   104 fun ID_of_thy thy = ID_of (#session (get_info thy)) (Context.theory_name thy);
   105 
   106 
   107 (*retrieve graph data from initial collection of theories*)
   108 fun init_graph remote_path curr_sess = rev o map (fn thy =>
   109   let
   110     val name = Context.theory_name thy;
   111     val {name = sess_name, session, is_local} = get_info thy;
   112     val path' = Path.append (Path.make session) (html_path name);
   113     val entry =
   114      {name = name, ID = ID_of session name, dir = sess_name,
   115       path =
   116         if null session then "" else
   117         if is_some remote_path andalso not is_local then
   118           Url.implode (Url.append (the remote_path) (Url.File
   119             (Path.append (Path.make session) (html_path name))))
   120         else Path.implode (Path.append (mk_rel_path curr_sess session) (html_path name)),
   121       unfold = false,
   122       parents = map ID_of_thy (Theory.parents_of thy)};
   123   in (0, entry) end);
   124 
   125 fun ins_graph_entry (i, entry as {ID, ...}) (gr: (int * graph_node) list) =
   126   (i, entry) :: filter_out (fn (_, entry') => #ID entry' = ID) gr;
   127 
   128 
   129 
   130 (** global browser info state **)
   131 
   132 (* type theory_info *)
   133 
   134 type theory_info = {tex_source: Buffer.T, html_source: Buffer.T, html: Buffer.T};
   135 
   136 fun make_theory_info (tex_source, html_source, html) =
   137   {tex_source = tex_source, html_source = html_source, html = html}: theory_info;
   138 
   139 val empty_theory_info = make_theory_info (Buffer.empty, Buffer.empty, Buffer.empty);
   140 
   141 fun map_theory_info f {tex_source, html_source, html} =
   142   make_theory_info (f (tex_source, html_source, html));
   143 
   144 
   145 (* type browser_info *)
   146 
   147 type browser_info = {theories: theory_info Symtab.table, files: (Path.T * string) list,
   148   tex_index: (int * string) list, html_index: (int * string) list, graph: (int * graph_node) list};
   149 
   150 fun make_browser_info (theories, files, tex_index, html_index, graph) =
   151   {theories = theories, files = files, tex_index = tex_index, html_index = html_index,
   152     graph = graph}: browser_info;
   153 
   154 val empty_browser_info = make_browser_info (Symtab.empty, [], [], [], []);
   155 
   156 fun init_browser_info remote_path curr_sess thys = make_browser_info
   157   (Symtab.empty, [], [], [], init_graph remote_path curr_sess thys);
   158 
   159 fun map_browser_info f {theories, files, tex_index, html_index, graph} =
   160   make_browser_info (f (theories, files, tex_index, html_index, graph));
   161 
   162 
   163 (* state *)
   164 
   165 val browser_info = ref empty_browser_info;
   166 fun change_browser_info f = CRITICAL (fn () => change browser_info (map_browser_info f));
   167 
   168 val suppress_tex_source = ref false;
   169 fun no_document f x = setmp_noncritical suppress_tex_source true f x;
   170 
   171 fun init_theory_info name info =
   172   change_browser_info (fn (theories, files, tex_index, html_index, graph) =>
   173     (Symtab.update (name, info) theories, files, tex_index, html_index, graph));
   174 
   175 fun change_theory_info name f =
   176   change_browser_info (fn (info as (theories, files, tex_index, html_index, graph)) =>
   177     (case Symtab.lookup theories name of
   178       NONE => error ("Browser info: cannot access theory document " ^ quote name)
   179     | SOME info => (Symtab.update (name, map_theory_info f info) theories, files,
   180         tex_index, html_index, graph)));
   181 
   182 
   183 fun add_file file =
   184   change_browser_info (fn (theories, files, tex_index, html_index, graph) =>
   185     (theories, file :: files, tex_index, html_index, graph));
   186 
   187 fun add_tex_index txt =
   188   change_browser_info (fn (theories, files, tex_index, html_index, graph) =>
   189     (theories, files, txt :: tex_index, html_index, graph));
   190 
   191 fun add_html_index txt =
   192   change_browser_info (fn (theories, files, tex_index, html_index, graph) =>
   193     (theories, files, tex_index, txt :: html_index, graph));
   194 
   195 fun add_graph_entry entry =
   196   change_browser_info (fn (theories, files, tex_index, html_index, graph) =>
   197     (theories, files, tex_index, html_index, ins_graph_entry entry graph));
   198 
   199 fun add_tex_source name txt =
   200   if ! suppress_tex_source then ()
   201   else change_theory_info name (fn (tex_source, html_source, html) =>
   202     (Buffer.add txt tex_source, html_source, html));
   203 
   204 fun add_html_source name txt = change_theory_info name (fn (tex_source, html_source, html) =>
   205   (tex_source, Buffer.add txt html_source, html));
   206 
   207 fun add_html name txt = change_theory_info name (fn (tex_source, html_source, html) =>
   208   (tex_source, html_source, Buffer.add txt html));
   209 
   210 
   211 
   212 (** global session state **)
   213 
   214 (* session_info *)
   215 
   216 type session_info =
   217   {name: string, parent: string, session: string, path: string list, html_prefix: Path.T,
   218     info: bool, doc_format: string, doc_graph: bool, documents: (string * string) list,
   219     doc_prefix1: (Path.T * Path.T) option, doc_prefix2: (bool * Path.T) option,
   220     remote_path: Url.T option, verbose: bool, readme: Path.T option};
   221 
   222 fun make_session_info
   223   (name, parent, session, path, html_prefix, info, doc_format, doc_graph, documents,
   224     doc_prefix1, doc_prefix2, remote_path, verbose, readme) =
   225   {name = name, parent = parent, session = session, path = path, html_prefix = html_prefix,
   226     info = info, doc_format = doc_format, doc_graph = doc_graph, documents = documents,
   227     doc_prefix1 = doc_prefix1, doc_prefix2 = doc_prefix2, remote_path = remote_path,
   228     verbose = verbose, readme = readme}: session_info;
   229 
   230 
   231 (* state *)
   232 
   233 val session_info = ref (NONE: session_info option);
   234 
   235 fun with_session x f = (case ! session_info of NONE => x | SOME info => f info);
   236 fun with_context f = f (Context.theory_name (ML_Context.the_global_context ()));
   237 
   238 
   239 
   240 (** document preparation **)
   241 
   242 (* maintain index *)
   243 
   244 val session_entries =
   245   HTML.session_entries o
   246     map (fn name => (Url.File (Path.append (Path.basic name) index_path), name));
   247 
   248 fun get_entries dir =
   249   split_lines (File.read (Path.append dir session_entries_path));
   250 
   251 fun put_entries entries dir =
   252   File.write (Path.append dir session_entries_path) (cat_lines entries);
   253 
   254 
   255 fun create_index dir =
   256   File.read (Path.append dir pre_index_path) ^
   257     session_entries (get_entries dir) ^ HTML.end_document
   258   |> File.write (Path.append dir index_path);
   259 
   260 fun update_index dir name = CRITICAL (fn () =>
   261   (case try get_entries dir of
   262     NONE => warning ("Browser info: cannot access session index of " ^ quote (Path.implode dir))
   263   | SOME es => (put_entries ((remove (op =) name es) @ [name]) dir; create_index dir)));
   264 
   265 
   266 (* document versions *)
   267 
   268 fun read_version str =
   269   (case space_explode "=" str of
   270     [name] => (name, "")
   271   | [name, tags] => (name, tags)
   272   | _ => error ("Malformed document version specification: " ^ quote str));
   273 
   274 fun read_versions strs =
   275   rev (distinct (eq_fst (op =)) (rev ((documentN, "") :: map read_version strs)))
   276   |> filter_out (equal "-" o #2);
   277 
   278 
   279 (* init session *)
   280 
   281 fun name_of_session elems = space_implode "/" ("Isabelle" :: elems);
   282 
   283 fun init build info doc doc_graph doc_versions path name doc_prefix2
   284     (remote_path, first_time) verbose thys = CRITICAL (fn () =>
   285   if not build andalso not info andalso doc = "" andalso is_none doc_prefix2 then
   286     (browser_info := empty_browser_info; session_info := NONE)
   287   else
   288     let
   289       val parent_name = name_of_session (Library.take (length path - 1, path));
   290       val session_name = name_of_session path;
   291       val sess_prefix = Path.make path;
   292       val html_prefix = Path.append (Path.expand output_path) sess_prefix;
   293 
   294       val (doc_prefix1, documents) =
   295         if doc = "" then (NONE, [])
   296         else if not (File.exists document_path) then
   297           (if verbose then Output.std_error "Warning: missing document directory\n" else ();
   298             (NONE, []))
   299         else (SOME (Path.append html_prefix document_path, html_prefix),
   300           read_versions doc_versions);
   301 
   302       val parent_index_path = Path.append Path.parent index_path;
   303       val index_up_lnk = if first_time then
   304           Url.append (the remote_path) (Url.File (Path.append sess_prefix parent_index_path))
   305         else Url.File parent_index_path;
   306       val readme =
   307         if File.exists readme_html_path then SOME readme_html_path
   308         else if File.exists readme_path then SOME readme_path
   309         else NONE;
   310 
   311       val docs =
   312         (case readme of NONE => [] | SOME p => [(Url.File p, "README")]) @
   313         map (fn (name, _) => (Url.File (Path.ext doc (Path.basic name)), name)) documents;
   314       val index_text = HTML.begin_index (index_up_lnk, parent_name)
   315         (Url.File index_path, session_name) docs (Url.explode "medium.html");
   316     in
   317       session_info := SOME (make_session_info (name, parent_name, session_name, path, html_prefix,
   318       info, doc, doc_graph, documents, doc_prefix1, doc_prefix2, remote_path, verbose, readme));
   319       browser_info := init_browser_info remote_path path thys;
   320       add_html_index (0, index_text)
   321     end);
   322 
   323 
   324 (* isatool wrappers *)
   325 
   326 fun isatool_document verbose format name tags path result_path =
   327   let
   328     val s = "\"$ISATOOL\" document -c -o '" ^ format ^ "' \
   329       \-n '" ^ name ^ "' -t '" ^ tags ^ "' " ^ File.shell_path path ^
   330       " 2>&1" ^ (if verbose then "" else " >/dev/null");
   331     val doc_path = Path.append result_path (Path.ext format (Path.basic name));
   332   in
   333     if verbose then writeln s else ();
   334     system s;
   335     File.exists doc_path orelse
   336       error ("No document: " ^ quote (show_path doc_path));
   337     doc_path
   338   end;
   339 
   340 fun isatool_browser graph =
   341   let
   342     val pdf_path = File.tmp_path graph_pdf_path;
   343     val eps_path = File.tmp_path graph_eps_path;
   344     val gr_path = File.tmp_path graph_path;
   345     val s = "browser -o " ^ File.shell_path pdf_path ^ " " ^ File.shell_path gr_path;
   346   in
   347     write_graph graph gr_path;
   348     if File.isatool s <> 0 orelse not (File.exists eps_path) orelse not (File.exists pdf_path)
   349     then error "Failed to prepare dependency graph"
   350     else
   351       let val pdf = File.read pdf_path and eps = File.read eps_path
   352       in File.rm pdf_path; File.rm eps_path; File.rm gr_path; (pdf, eps) end
   353   end;
   354 
   355 
   356 (* finish session -- output all generated text *)
   357 
   358 fun sorted_index index = map snd (sort (int_ord o pairself fst) (rev index));
   359 fun index_buffer index = Buffer.add (implode (sorted_index index)) Buffer.empty;
   360 
   361 fun write_tex src name path =
   362   Buffer.write (Path.append path (tex_path name)) src;
   363 
   364 fun write_tex_index tex_index path =
   365   write_tex (index_buffer tex_index |> Buffer.add Latex.tex_trailer) doc_indexN path;
   366 
   367 
   368 fun finish () = CRITICAL (fn () =>
   369     with_session () (fn {name, info, html_prefix, doc_format, doc_graph,
   370       documents, doc_prefix1, doc_prefix2, path, verbose, readme, ...} =>
   371   let
   372     val {theories, files, tex_index, html_index, graph} = ! browser_info;
   373     val thys = Symtab.dest theories;
   374     val parent_html_prefix = Path.append html_prefix Path.parent;
   375 
   376     fun finish_tex path (a, {tex_source, ...}: theory_info) = write_tex tex_source a path;
   377     fun finish_html (a, {html, ...}: theory_info) =
   378       Buffer.write (Path.append html_prefix (html_path a)) (Buffer.add HTML.end_document html);
   379 
   380     val sorted_graph = sorted_index graph;
   381     val opt_graphs =
   382       if doc_graph andalso (is_some doc_prefix1 orelse is_some doc_prefix2) then
   383         SOME (isatool_browser sorted_graph)
   384       else NONE;
   385 
   386     fun prepare_sources cp path =
   387      (File.mkdir path;
   388       if cp then File.copy_dir document_path path else ();
   389       File.isatool ("latex -o sty " ^ File.shell_path (Path.append path (Path.basic "root.tex")));
   390       (case opt_graphs of NONE => () | SOME (pdf, eps) =>
   391         (File.write (Path.append path graph_pdf_path) pdf;
   392           File.write (Path.append path graph_eps_path) eps));
   393       write_tex_index tex_index path;
   394       List.app (finish_tex path) thys);
   395   in
   396     if info then
   397      (File.mkdir (Path.append html_prefix session_path);
   398       Buffer.write (Path.append html_prefix pre_index_path) (index_buffer html_index);
   399       File.write (Path.append html_prefix session_entries_path) "";
   400       create_index html_prefix;
   401       if length path > 1 then update_index parent_html_prefix name else ();
   402       (case readme of NONE => () | SOME path => File.copy path html_prefix);
   403       write_graph sorted_graph (Path.append html_prefix graph_path);
   404       File.copy (Path.explode "~~/lib/browser/GraphBrowser.jar") html_prefix;
   405       List.app (fn (a, txt) => File.write (Path.append html_prefix (Path.basic a)) txt)
   406         (HTML.applet_pages name (Url.File index_path, name));
   407       File.copy (Path.explode "~~/lib/html/isabelle.css") html_prefix;
   408       List.app finish_html thys;
   409       List.app (uncurry File.write) files;
   410       if verbose then Output.std_error ("Browser info at " ^ show_path html_prefix ^ "\n") else ())
   411     else ();
   412 
   413     (case doc_prefix2 of NONE => () | SOME (cp, path) =>
   414      (prepare_sources cp path;
   415       if verbose then Output.std_error ("Document sources at " ^ show_path path ^ "\n") else ()));
   416 
   417     (case doc_prefix1 of NONE => () | SOME (path, result_path) =>
   418       documents |> List.app (fn (name, tags) =>
   419        let
   420          val _ = prepare_sources true path;
   421          val doc_path = isatool_document true doc_format name tags path result_path;
   422        in
   423          if verbose then Output.std_error ("Document at " ^ show_path doc_path ^ "\n") else ()
   424        end));
   425 
   426     browser_info := empty_browser_info;
   427     session_info := NONE
   428   end));
   429 
   430 
   431 (* theory elements *)
   432 
   433 fun init_theory name = with_session () (fn _ => init_theory_info name empty_theory_info);
   434 
   435 fun theory_source name mk_text =
   436   with_session () (fn _ => add_html_source name (HTML.theory_source (mk_text ())));
   437 
   438 fun theory_output name s =
   439   with_session () (fn _ => add_tex_source name (Latex.isabelle_file name s));
   440 
   441 
   442 fun parent_link remote_path curr_session thy =
   443   let
   444     val {name = _, session, is_local} = get_info thy;
   445     val name = Context.theory_name thy;
   446     val link =
   447       if null session then NONE
   448       else SOME
   449        (if is_some remote_path andalso not is_local then
   450          Url.append (the remote_path) (Url.File (Path.append (Path.make session) (html_path name)))
   451         else Url.File (Path.append (mk_rel_path curr_session session) (html_path name)));
   452   in (link, name) end;
   453 
   454 fun begin_theory update_time dir files thy =
   455     with_session thy (fn {name = sess_name, session, path, html_prefix, remote_path, ...} =>
   456   let
   457     val name = Context.theory_name thy;
   458     val parents = Theory.parents_of thy;
   459     val parent_specs = map (parent_link remote_path path) parents;
   460 
   461     fun prep_file (raw_path, loadit) =
   462       (case ThyLoad.check_ml dir raw_path of
   463         SOME (path, _) =>
   464           let
   465             val base = Path.base path;
   466             val base_html = html_ext base;
   467             val _ = add_file (Path.append html_prefix base_html,
   468               HTML.ml_file (Url.File base) (File.read path));
   469             in (Url.File base_html, Url.File raw_path, loadit) end
   470       | NONE => error ("Browser info: expected to find ML file" ^ quote (Path.implode raw_path)));
   471 
   472     val files_html = map prep_file files;
   473 
   474     fun prep_html_source (tex_source, html_source, html) =
   475       let
   476         val txt = HTML.begin_theory (Url.File index_path, session)
   477           name parent_specs files_html (Buffer.content html_source)
   478       in (tex_source, Buffer.empty, Buffer.add txt html) end;
   479 
   480     val entry =
   481      {name = name, ID = ID_of path name, dir = sess_name, unfold = true,
   482       path = Path.implode (html_path name),
   483       parents = map ID_of_thy parents};
   484   in
   485     change_theory_info name prep_html_source;
   486     add_graph_entry (update_time, entry);
   487     add_html_index (update_time, HTML.theory_entry (Url.File (html_path name), name));
   488     add_tex_index (update_time, Latex.theory_entry name);
   489     put_info {name = sess_name, session = path, is_local = is_some remote_path} thy
   490   end);
   491 
   492 
   493 
   494 (** draft document output **)
   495 
   496 fun drafts doc_format src_paths =
   497   let
   498     fun prep_draft path i =
   499       let
   500         val base = Path.base path;
   501         val name =
   502           (case Path.implode (#1 (Path.split_ext base)) of
   503             "" => "DUMMY" ^ serial_string ()
   504           | s => s);
   505       in
   506         if File.exists path then
   507           (((name, base, File.read path), (i, Latex.theory_entry name)), i + 1)
   508         else error ("Bad file: " ^ quote (Path.implode path))
   509       end;
   510     val (srcs, tex_index) = split_list (fst (fold_map prep_draft src_paths 0));
   511 
   512     val doc_path = File.tmp_path document_path;
   513     val result_path = Path.append doc_path Path.parent;
   514     val _ = File.mkdir doc_path;
   515     val root_path = Path.append doc_path (Path.basic "root.tex");
   516     val _ = File.copy (Path.explode "~~/lib/texinputs/draft.tex") root_path;
   517     val _ = File.isatool ("latex -o sty " ^ File.shell_path root_path);
   518     val _ = File.isatool ("latex -o syms " ^ File.shell_path root_path);
   519 
   520     fun known name =
   521       let val ss = split_lines (File.read (Path.append doc_path (Path.basic name)))
   522       in member (op =) ss end;
   523     val known_syms = known "syms.lst";
   524     val known_ctrls = known "ctrls.lst";
   525 
   526     val _ = srcs |> List.app (fn (name, base, txt) =>
   527       Symbol.explode txt
   528       |> Latex.symbol_source (known_syms, known_ctrls) (Path.implode base)
   529       |> File.write (Path.append doc_path (tex_path name)));
   530     val _ = write_tex_index tex_index doc_path;
   531   in isatool_document false doc_format documentN "" doc_path result_path end;
   532 
   533 
   534 end;
   535 
   536 structure BasicPresent: BASIC_PRESENT = Present;
   537 open BasicPresent;