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