src/Pure/Thy/thy_output.ML
author wenzelm
Tue, 03 May 2011 22:27:32 +0200
changeset 43542 04dfffda5671
parent 43487 92715b528e78
child 44450 9864182c6bad
permissions -rw-r--r--
more conventional naming scheme: names_long, names_short, names_unique;
     1 (*  Title:      Pure/Thy/thy_output.ML
     2     Author:     Markus Wenzel, TU Muenchen
     3 
     4 Theory document output with antiquotations.
     5 *)
     6 
     7 signature THY_OUTPUT =
     8 sig
     9   val display_default: bool Unsynchronized.ref
    10   val quotes_default: bool Unsynchronized.ref
    11   val indent_default: int Unsynchronized.ref
    12   val source_default: bool Unsynchronized.ref
    13   val break_default: bool Unsynchronized.ref
    14   val display: bool Config.T
    15   val quotes: bool Config.T
    16   val indent: int Config.T
    17   val source: bool Config.T
    18   val break: bool Config.T
    19   val add_wrapper: ((unit -> string) -> unit -> string) -> Proof.context -> Proof.context
    20   val add_option: string -> (string -> Proof.context -> Proof.context) -> unit
    21   val defined_command: string -> bool
    22   val defined_option: string -> bool
    23   val print_antiquotations: unit -> unit
    24   val boolean: string -> bool
    25   val integer: string -> int
    26   val antiquotation: string -> 'a context_parser ->
    27     ({source: Args.src, state: Toplevel.state, context: Proof.context} -> 'a -> string) -> unit
    28   datatype markup = Markup | MarkupEnv | Verbatim
    29   val modes: string list Unsynchronized.ref
    30   val eval_antiq: Scan.lexicon -> Toplevel.state -> Symbol_Pos.T list * Position.range -> string
    31   val eval_antiquote: Scan.lexicon -> Toplevel.state -> Symbol_Pos.text * Position.T -> string
    32   val present_thy: Scan.lexicon -> (string -> string list) -> (markup -> string -> bool) ->
    33     (Toplevel.transition * Toplevel.state) list -> (Token.T, 'a) Source.source -> Buffer.T
    34   val pretty_text: Proof.context -> string -> Pretty.T
    35   val pretty_term: Proof.context -> term -> Pretty.T
    36   val pretty_thm: Proof.context -> thm -> Pretty.T
    37   val str_of_source: Args.src -> string
    38   val maybe_pretty_source: (Proof.context -> 'a -> Pretty.T) -> Proof.context ->
    39     Args.src -> 'a list -> Pretty.T list
    40   val output: Proof.context -> Pretty.T list -> string
    41 end;
    42 
    43 structure Thy_Output: THY_OUTPUT =
    44 struct
    45 
    46 (** global options **)
    47 
    48 val display_default = Unsynchronized.ref false;
    49 val quotes_default = Unsynchronized.ref false;
    50 val indent_default = Unsynchronized.ref 0;
    51 val source_default = Unsynchronized.ref false;
    52 val break_default = Unsynchronized.ref false;
    53 
    54 val display = Attrib.setup_config_bool (Binding.name "thy_output_display") (fn _ => ! display_default);
    55 val quotes = Attrib.setup_config_bool (Binding.name "thy_output_quotes") (fn _ => ! quotes_default);
    56 val indent = Attrib.setup_config_int (Binding.name "thy_output_indent") (fn _ => ! indent_default);
    57 val source = Attrib.setup_config_bool (Binding.name "thy_output_source") (fn _ => ! source_default);
    58 val break = Attrib.setup_config_bool (Binding.name "thy_output_break") (fn _ => ! break_default);
    59 
    60 
    61 structure Wrappers = Proof_Data
    62 (
    63   type T = ((unit -> string) -> unit -> string) list;
    64   fun init _ = [];
    65 );
    66 
    67 fun add_wrapper wrapper = Wrappers.map (cons wrapper);
    68 
    69 val wrap = Wrappers.get #> fold (fn wrapper => fn f => wrapper f);
    70 
    71 
    72 
    73 (** maintain global antiquotations **)
    74 
    75 local
    76 
    77 val global_commands =
    78   Unsynchronized.ref
    79     (Symtab.empty: (Args.src -> Toplevel.state -> Proof.context -> string) Symtab.table);
    80 
    81 val global_options =
    82   Unsynchronized.ref (Symtab.empty: (string -> Proof.context -> Proof.context) Symtab.table);
    83 
    84 fun add_item kind name item tab =
    85  (if not (Symtab.defined tab name) then ()
    86   else warning ("Redefined document antiquotation " ^ kind ^ ": " ^ quote name);
    87   Symtab.update (name, item) tab);
    88 
    89 in
    90 
    91 fun add_command name cmd =
    92   CRITICAL (fn () => Unsynchronized.change global_commands (add_item "command" name cmd));
    93 fun add_option name opt =
    94   CRITICAL (fn () => Unsynchronized.change global_options (add_item "option" name opt));
    95 
    96 fun defined_command name = Symtab.defined (! global_commands) name;
    97 fun defined_option name = Symtab.defined (! global_options) name;
    98 
    99 fun command src =
   100   let val ((name, _), pos) = Args.dest_src src in
   101     (case Symtab.lookup (! global_commands) name of
   102       NONE => error ("Unknown document antiquotation: " ^ quote name ^ Position.str_of pos)
   103     | SOME f =>
   104        (Position.report pos (Markup.doc_antiq name);
   105         (fn state => fn ctxt => f src state ctxt handle ERROR msg =>
   106           cat_error msg ("The error(s) above occurred in document antiquotation: " ^
   107             quote name ^ Position.str_of pos))))
   108   end;
   109 
   110 fun option (name, s) ctxt =
   111   (case Symtab.lookup (! global_options) name of
   112     NONE => error ("Unknown document antiquotation option: " ^ quote name)
   113   | SOME opt => opt s ctxt);
   114 
   115 
   116 fun print_antiquotations () =
   117  [Pretty.big_list "document antiquotation commands:"
   118     (map Pretty.str (sort_strings (Symtab.keys (! global_commands)))),
   119   Pretty.big_list "document antiquotation options:"
   120     (map Pretty.str (sort_strings (Symtab.keys (! global_options))))]
   121  |> Pretty.chunks |> Pretty.writeln;
   122 
   123 end;
   124 
   125 fun antiquotation name scan out =
   126   add_command name
   127     (fn src => fn state => fn ctxt =>
   128       let val (x, ctxt') = Args.context_syntax "document antiquotation" scan src ctxt
   129       in out {source = src, state = state, context = ctxt'} x end);
   130 
   131 
   132 
   133 (** syntax of antiquotations **)
   134 
   135 (* option values *)
   136 
   137 fun boolean "" = true
   138   | boolean "true" = true
   139   | boolean "false" = false
   140   | boolean s = error ("Bad boolean value: " ^ quote s);
   141 
   142 fun integer s =
   143   let
   144     fun int ss =
   145       (case Library.read_int ss of (i, []) => i
   146       | _ => error ("Bad integer value: " ^ quote s));
   147   in (case Symbol.explode s of "-" :: ss => ~ (int ss) | ss => int ss) end;
   148 
   149 
   150 (* outer syntax *)
   151 
   152 local
   153 
   154 val property =
   155   Parse.xname -- Scan.optional (Parse.$$$ "=" |-- Parse.!!! Parse.xname) "";
   156 
   157 val properties =
   158   Scan.optional (Parse.$$$ "[" |-- Parse.!!! (Parse.enum "," property --| Parse.$$$ "]")) [];
   159 
   160 in
   161 
   162 val antiq =
   163   Parse.!!!
   164     (Parse.position Parse.liberal_name -- properties -- Args.parse --| Scan.ahead Parse.eof)
   165   >> (fn (((x, pos), y), z) => (y, Args.src ((x, z), pos)));
   166 
   167 end;
   168 
   169 
   170 (* eval_antiquote *)
   171 
   172 val modes = Unsynchronized.ref ([]: string list);
   173 
   174 fun eval_antiq lex state (ss, (pos, _)) =
   175   let
   176     val (opts, src) = Token.read_antiq lex antiq (ss, pos);
   177     fun cmd ctxt = wrap ctxt (fn () => command src state ctxt) ();
   178     val preview_ctxt = fold option opts (Toplevel.presentation_context_of state);
   179     val print_ctxt = Context_Position.set_visible false preview_ctxt;
   180     val _ = cmd preview_ctxt;
   181   in Print_Mode.with_modes (! modes @ Latex.modes) (fn () => cmd print_ctxt) () end;
   182 
   183 fun eval_antiquote lex state (txt, pos) =
   184   let
   185     fun expand (Antiquote.Text ss) = Symbol_Pos.content ss
   186       | expand (Antiquote.Antiq antiq) = eval_antiq lex state antiq
   187       | expand (Antiquote.Open _) = ""
   188       | expand (Antiquote.Close _) = "";
   189     val ants = Antiquote.read (Symbol_Pos.explode (txt, pos), pos);
   190   in
   191     if Toplevel.is_toplevel state andalso not (forall Antiquote.is_text ants) then
   192       error ("Unknown context -- cannot expand document antiquotations" ^ Position.str_of pos)
   193     else implode (map expand ants)
   194   end;
   195 
   196 
   197 
   198 (** present theory source **)
   199 
   200 (*NB: arranging white space around command spans is a black art.*)
   201 
   202 (* presentation tokens *)
   203 
   204 datatype token =
   205     NoToken
   206   | BasicToken of Token.T
   207   | MarkupToken of string * (string * Position.T)
   208   | MarkupEnvToken of string * (string * Position.T)
   209   | VerbatimToken of string * Position.T;
   210 
   211 fun output_token lex state =
   212   let val eval = eval_antiquote lex state in
   213     fn NoToken => ""
   214      | BasicToken tok => Latex.output_basic tok
   215      | MarkupToken (cmd, txt) => Latex.output_markup cmd (eval txt)
   216      | MarkupEnvToken (cmd, txt) => Latex.output_markup_env cmd (eval txt)
   217      | VerbatimToken txt => Latex.output_verbatim (eval txt)
   218   end;
   219 
   220 fun basic_token pred (BasicToken tok) = pred tok
   221   | basic_token _ _ = false;
   222 
   223 val improper_token = basic_token (not o Token.is_proper);
   224 val comment_token = basic_token Token.is_comment;
   225 val blank_token = basic_token Token.is_blank;
   226 val newline_token = basic_token Token.is_newline;
   227 
   228 
   229 (* command spans *)
   230 
   231 type command = string * Position.T * string list;   (*name, position, tags*)
   232 type source = (token * (string * int)) list;        (*token, markup flag, meta-comment depth*)
   233 
   234 datatype span = Span of command * (source * source * source * source) * bool;
   235 
   236 fun make_span cmd src =
   237   let
   238     fun take_newline (tok :: toks) =
   239           if newline_token (fst tok) then ([tok], toks, true)
   240           else ([], tok :: toks, false)
   241       | take_newline [] = ([], [], false);
   242     val (((src_prefix, src_main), src_suffix1), (src_suffix2, src_appendix, newline)) =
   243       src
   244       |> take_prefix (improper_token o fst)
   245       ||>> take_suffix (improper_token o fst)
   246       ||>> take_prefix (comment_token o fst)
   247       ||> take_newline;
   248   in Span (cmd, (src_prefix, src_main, src_suffix1 @ src_suffix2, src_appendix), newline) end;
   249 
   250 
   251 (* present spans *)
   252 
   253 local
   254 
   255 fun err_bad_nesting pos =
   256   error ("Bad nesting of commands in presentation" ^ pos);
   257 
   258 fun edge which f (x: string option, y) =
   259   if x = y then I
   260   else (case which (x, y) of NONE => I | SOME txt => Buffer.add (f txt));
   261 
   262 val begin_tag = edge #2 Latex.begin_tag;
   263 val end_tag = edge #1 Latex.end_tag;
   264 fun open_delim delim e = edge #2 Latex.begin_delim e #> delim #> edge #2 Latex.end_delim e;
   265 fun close_delim delim e = edge #1 Latex.begin_delim e #> delim #> edge #1 Latex.end_delim e;
   266 
   267 in
   268 
   269 fun present_span lex default_tags span state state'
   270     (tag_stack, active_tag, newline, buffer, present_cont) =
   271   let
   272     val present = fold (fn (tok, (flag, 0)) =>
   273         Buffer.add (output_token lex state' tok)
   274         #> Buffer.add flag
   275       | _ => I);
   276 
   277     val Span ((cmd_name, cmd_pos, cmd_tags), srcs, span_newline) = span;
   278 
   279     val (tag, tags) = tag_stack;
   280     val tag' = try hd (fold Keyword.update_tags cmd_tags (the_list tag));
   281 
   282     val active_tag' =
   283       if is_some tag' then tag'
   284       else if cmd_name = "end" andalso not (Toplevel.is_toplevel state') then NONE
   285       else try hd (default_tags cmd_name);
   286     val edge = (active_tag, active_tag');
   287 
   288     val newline' =
   289       if is_none active_tag' then span_newline else newline;
   290 
   291     val nesting = Toplevel.level state' - Toplevel.level state;
   292     val tag_stack' =
   293       if nesting = 0 andalso not (Toplevel.is_proof state) then tag_stack
   294       else if nesting >= 0 then (tag', replicate nesting tag @ tags)
   295       else
   296         (case drop (~ nesting - 1) tags of
   297           tgs :: tgss => (tgs, tgss)
   298         | [] => err_bad_nesting (Position.str_of cmd_pos));
   299 
   300     val buffer' =
   301       buffer
   302       |> end_tag edge
   303       |> close_delim (fst present_cont) edge
   304       |> snd present_cont
   305       |> open_delim (present (#1 srcs)) edge
   306       |> begin_tag edge
   307       |> present (#2 srcs);
   308     val present_cont' =
   309       if newline then (present (#3 srcs), present (#4 srcs))
   310       else (I, present (#3 srcs) #> present (#4 srcs));
   311   in (tag_stack', active_tag', newline', buffer', present_cont') end;
   312 
   313 fun present_trailer ((_, tags), active_tag, _, buffer, present_cont) =
   314   if not (null tags) then err_bad_nesting " at end of theory"
   315   else
   316     buffer
   317     |> end_tag (active_tag, NONE)
   318     |> close_delim (fst present_cont) (active_tag, NONE)
   319     |> snd present_cont;
   320 
   321 end;
   322 
   323 
   324 (* present_thy *)
   325 
   326 datatype markup = Markup | MarkupEnv | Verbatim;
   327 
   328 local
   329 
   330 val space_proper =
   331   Scan.one Token.is_blank -- Scan.many Token.is_comment -- Scan.one Token.is_proper;
   332 
   333 val is_improper = not o (Token.is_proper orf Token.is_begin_ignore orf Token.is_end_ignore);
   334 val improper = Scan.many is_improper;
   335 val improper_end = Scan.repeat (Scan.unless space_proper (Scan.one is_improper));
   336 val blank_end = Scan.repeat (Scan.unless space_proper (Scan.one Token.is_blank));
   337 
   338 val opt_newline = Scan.option (Scan.one Token.is_newline);
   339 
   340 val ignore =
   341   Scan.depend (fn d => opt_newline |-- Scan.one Token.is_begin_ignore
   342     >> pair (d + 1)) ||
   343   Scan.depend (fn d => Scan.one Token.is_end_ignore --|
   344     (if d = 0 then Scan.fail_with (K "Bad nesting of meta-comments") else opt_newline)
   345     >> pair (d - 1));
   346 
   347 val tag = (improper -- Parse.$$$ "%" -- improper) |-- Parse.!!! (Parse.tag_name --| blank_end);
   348 
   349 val locale =
   350   Scan.option ((Parse.$$$ "(" -- improper -- Parse.$$$ "in") |--
   351     Parse.!!! (improper |-- Parse.xname --| (improper -- Parse.$$$ ")")));
   352 
   353 in
   354 
   355 fun present_thy lex default_tags is_markup command_results src =
   356   let
   357     (* tokens *)
   358 
   359     val ignored = Scan.state --| ignore
   360       >> (fn d => (NONE, (NoToken, ("", d))));
   361 
   362     fun markup mark mk flag = Scan.peek (fn d =>
   363       improper |--
   364         Parse.position
   365           (Scan.one (Token.is_kind Token.Command andf is_markup mark o Token.content_of)) --
   366       Scan.repeat tag --
   367       Parse.!!!! ((improper -- locale -- improper) |-- Parse.doc_source --| improper_end)
   368       >> (fn (((tok, pos), tags), txt) =>
   369         let val name = Token.content_of tok
   370         in (SOME (name, pos, tags), (mk (name, txt), (flag, d))) end));
   371 
   372     val command = Scan.peek (fn d =>
   373       Parse.position (Scan.one (Token.is_kind Token.Command)) --
   374       Scan.repeat tag
   375       >> (fn ((tok, pos), tags) =>
   376         let val name = Token.content_of tok
   377         in (SOME (name, pos, tags), (BasicToken tok, (Latex.markup_false, d))) end));
   378 
   379     val cmt = Scan.peek (fn d =>
   380       Parse.$$$ "--" |-- Parse.!!!! (improper |-- Parse.doc_source)
   381       >> (fn txt => (NONE, (MarkupToken ("cmt", txt), ("", d)))));
   382 
   383     val other = Scan.peek (fn d =>
   384        Parse.not_eof >> (fn tok => (NONE, (BasicToken tok, ("", d)))));
   385 
   386     val token =
   387       ignored ||
   388       markup Markup MarkupToken Latex.markup_true ||
   389       markup MarkupEnv MarkupEnvToken Latex.markup_true ||
   390       markup Verbatim (VerbatimToken o #2) "" ||
   391       command || cmt || other;
   392 
   393 
   394     (* spans *)
   395 
   396     val is_eof = fn (_, (BasicToken x, _)) => Token.is_eof x | _ => false;
   397     val stopper = Scan.stopper (K (NONE, (BasicToken Token.eof, ("", 0)))) is_eof;
   398 
   399     val cmd = Scan.one (is_some o fst);
   400     val non_cmd = Scan.one (is_none o fst andf not o is_eof) >> #2;
   401 
   402     val comments = Scan.many (comment_token o fst o snd);
   403     val blank = Scan.one (blank_token o fst o snd);
   404     val newline = Scan.one (newline_token o fst o snd);
   405     val before_cmd =
   406       Scan.option (newline -- comments) --
   407       Scan.option (newline -- comments) --
   408       Scan.option (blank -- comments) -- cmd;
   409 
   410     val span =
   411       Scan.repeat non_cmd -- cmd --
   412         Scan.repeat (Scan.unless before_cmd non_cmd) --
   413         Scan.option (newline >> (single o snd))
   414       >> (fn (((toks1, (cmd, tok2)), toks3), tok4) =>
   415           make_span (the cmd) (toks1 @ (tok2 :: (toks3 @ the_default [] tok4))));
   416 
   417     val spans =
   418       src
   419       |> Source.filter (not o Token.is_semicolon)
   420       |> Source.source' 0 Token.stopper (Scan.error (Scan.bulk token)) NONE
   421       |> Source.source stopper (Scan.error (Scan.bulk span)) NONE
   422       |> Source.exhaust;
   423 
   424 
   425     (* present commands *)
   426 
   427     fun present_command tr span st st' =
   428       Toplevel.setmp_thread_position tr (present_span lex default_tags span st st');
   429 
   430     fun present _ [] = I
   431       | present st (((tr, st'), span) :: rest) = present_command tr span st st' #> present st' rest;
   432   in
   433     if length command_results = length spans then
   434       ((NONE, []), NONE, true, Buffer.empty, (I, I))
   435       |> present Toplevel.toplevel (command_results ~~ spans)
   436       |> present_trailer
   437     else error "Messed-up outer syntax for presentation"
   438   end;
   439 
   440 end;
   441 
   442 
   443 
   444 (** setup default output **)
   445 
   446 (* options *)
   447 
   448 val _ = add_option "show_types" (Config.put show_types o boolean);
   449 val _ = add_option "show_sorts" (Config.put show_sorts o boolean);
   450 val _ = add_option "show_structs" (Config.put show_structs o boolean);
   451 val _ = add_option "show_question_marks" (Config.put show_question_marks o boolean);
   452 val _ = add_option "show_abbrevs" (Config.put show_abbrevs o boolean);
   453 val _ = add_option "names_long" (Config.put Name_Space.names_long o boolean);
   454 val _ = add_option "names_short" (Config.put Name_Space.names_short o boolean);
   455 val _ = add_option "names_unique" (Config.put Name_Space.names_unique o boolean);
   456 val _ = add_option "eta_contract" (Config.put Syntax_Trans.eta_contract o boolean);
   457 val _ = add_option "display" (Config.put display o boolean);
   458 val _ = add_option "break" (Config.put break o boolean);
   459 val _ = add_option "quotes" (Config.put quotes o boolean);
   460 val _ = add_option "mode" (add_wrapper o Print_Mode.with_modes o single);
   461 val _ = add_option "margin" (add_wrapper o setmp_CRITICAL Pretty.margin_default o integer);
   462 val _ = add_option "indent" (Config.put indent o integer);
   463 val _ = add_option "source" (Config.put source o boolean);
   464 val _ = add_option "goals_limit" (Config.put Goal_Display.goals_limit o integer);
   465 
   466 
   467 (* basic pretty printing *)
   468 
   469 fun tweak_line ctxt s =
   470   if Config.get ctxt display then s else Symbol.strip_blanks s;
   471 
   472 fun pretty_text ctxt =
   473   Pretty.chunks o map Pretty.str o map (tweak_line ctxt) o Library.split_lines;
   474 
   475 fun pretty_term ctxt t = Syntax.pretty_term (Variable.auto_fixes t ctxt) t;
   476 
   477 fun pretty_thm ctxt = pretty_term ctxt o Thm.full_prop_of;
   478 
   479 fun pretty_term_style ctxt (style, t) =
   480   pretty_term ctxt (style t);
   481 
   482 fun pretty_thm_style ctxt (style, th) =
   483   pretty_term ctxt (style (Thm.full_prop_of th));
   484 
   485 fun pretty_term_typ ctxt (style, t) =
   486   let val t' = style t
   487   in pretty_term ctxt (Type.constraint (Term.fastype_of t') t') end;
   488 
   489 fun pretty_term_typeof ctxt (style, t) =
   490   Syntax.pretty_typ ctxt (Term.fastype_of (style t));
   491 
   492 fun pretty_const ctxt c =
   493   let
   494     val t = Const (c, Consts.type_scheme (Proof_Context.consts_of ctxt) c)
   495       handle TYPE (msg, _, _) => error msg;
   496     val ([t'], _) = Variable.import_terms true [t] ctxt;
   497   in pretty_term ctxt t' end;
   498 
   499 fun pretty_abbrev ctxt s =
   500   let
   501     val t = Syntax.read_term (Proof_Context.set_mode Proof_Context.mode_abbrev ctxt) s;
   502     fun err () = error ("Abbreviated constant expected: " ^ Syntax.string_of_term ctxt t);
   503     val (head, args) = Term.strip_comb t;
   504     val (c, T) = Term.dest_Const head handle TERM _ => err ();
   505     val (U, u) = Consts.the_abbreviation (Proof_Context.consts_of ctxt) c
   506       handle TYPE _ => err ();
   507     val t' = Term.betapplys (Envir.expand_atom T (U, u), args);
   508     val eq = Logic.mk_equals (t, t');
   509     val ctxt' = Variable.auto_fixes eq ctxt;
   510   in Proof_Context.pretty_term_abbrev ctxt' eq end;
   511 
   512 fun pretty_class ctxt =
   513   Pretty.str o Proof_Context.extern_class ctxt o Proof_Context.read_class ctxt;
   514 
   515 fun pretty_type ctxt s =
   516   let val Type (name, _) = Proof_Context.read_type_name_proper ctxt false s
   517   in Pretty.str (Proof_Context.extern_type ctxt name) end;
   518 
   519 fun pretty_prf full ctxt = Proof_Syntax.pretty_proof_of ctxt full;
   520 
   521 fun pretty_theory ctxt name =
   522   (Theory.requires (Proof_Context.theory_of ctxt) name "presentation"; Pretty.str name);
   523 
   524 
   525 (* default output *)
   526 
   527 val str_of_source = space_implode " " o map Token.unparse o #2 o #1 o Args.dest_src;
   528 
   529 fun maybe_pretty_source pretty ctxt src xs =
   530   map (pretty ctxt) xs  (*always pretty in order to exhibit errors!*)
   531   |> (if Config.get ctxt source then K [pretty_text ctxt (str_of_source src)] else I);
   532 
   533 fun output ctxt prts =
   534   prts
   535   |> (if Config.get ctxt quotes then map Pretty.quote else I)
   536   |> (if Config.get ctxt display then
   537     map (Output.output o Pretty.string_of o Pretty.indent (Config.get ctxt indent))
   538     #> space_implode "\\isasep\\isanewline%\n"
   539     #> enclose "\\begin{isabelle}%\n" "%\n\\end{isabelle}"
   540   else
   541     map (Output.output o (if Config.get ctxt break then Pretty.string_of else Pretty.str_of))
   542     #> space_implode "\\isasep\\isanewline%\n"
   543     #> enclose "\\isa{" "}");
   544 
   545 
   546 
   547 (** concrete antiquotations **)
   548 
   549 (* basic entities *)
   550 
   551 local
   552 
   553 fun basic_entities name scan pretty = antiquotation name scan
   554   (fn {source, context, ...} => output context o maybe_pretty_source pretty context source);
   555 
   556 fun basic_entities_style name scan pretty = antiquotation name scan
   557   (fn {source, context, ...} => fn (style, xs) =>
   558     output context
   559       (maybe_pretty_source (fn ctxt => fn x => pretty ctxt (style, x)) context source xs));
   560 
   561 fun basic_entity name scan = basic_entities name (scan >> single);
   562 
   563 in
   564 
   565 val _ = basic_entities_style "thm" (Term_Style.parse -- Attrib.thms) pretty_thm_style;
   566 val _ = basic_entity "prop" (Term_Style.parse -- Args.prop) pretty_term_style;
   567 val _ = basic_entity "term" (Term_Style.parse -- Args.term) pretty_term_style;
   568 val _ = basic_entity "term_type" (Term_Style.parse -- Args.term) pretty_term_typ;
   569 val _ = basic_entity "typeof" (Term_Style.parse -- Args.term) pretty_term_typeof;
   570 val _ = basic_entity "const" (Args.const_proper false) pretty_const;
   571 val _ = basic_entity "abbrev" (Scan.lift Args.name_source) pretty_abbrev;
   572 val _ = basic_entity "typ" Args.typ_abbrev Syntax.pretty_typ;
   573 val _ = basic_entity "class" (Scan.lift Args.name) pretty_class;
   574 val _ = basic_entity "type" (Scan.lift Args.name) pretty_type;
   575 val _ = basic_entity "text" (Scan.lift Args.name) pretty_text;
   576 val _ = basic_entities "prf" Attrib.thms (pretty_prf false);
   577 val _ = basic_entities "full_prf" Attrib.thms (pretty_prf true);
   578 val _ = basic_entity "theory" (Scan.lift Args.name) pretty_theory;
   579 val _ = basic_entities_style "thm_style" (Term_Style.parse_bare -- Attrib.thms) pretty_thm_style;
   580 val _ = basic_entity "term_style" (Term_Style.parse_bare -- Args.term) pretty_term_style;
   581 
   582 end;
   583 
   584 
   585 (* goal state *)
   586 
   587 local
   588 
   589 fun proof_state state =
   590   (case try Toplevel.proof_of state of
   591     SOME prf => prf
   592   | _ => error "No proof state");
   593 
   594 fun goal_state name main_goal = antiquotation name (Scan.succeed ())
   595   (fn {state, context = ctxt, ...} => fn () => output ctxt
   596     [Pretty.chunks
   597       (Proof.pretty_goals main_goal (Proof.map_context (K ctxt) (proof_state state)))]);
   598 
   599 in
   600 
   601 val _ = goal_state "goals" true;
   602 val _ = goal_state "subgoals" false;
   603 
   604 end;
   605 
   606 
   607 (* embedded lemma *)
   608 
   609 val _ = Keyword.keyword "by";
   610 
   611 val _ = antiquotation "lemma"
   612   (Args.prop -- Scan.lift (Args.$$$ "by" |-- Method.parse -- Scan.option Method.parse))
   613   (fn {source, context, ...} => fn (prop, methods) =>
   614     let
   615       val prop_src =
   616         (case Args.dest_src source of ((a, arg :: _), pos) => Args.src ((a, [arg]), pos));
   617       val _ = context
   618         |> Proof.theorem NONE (K I) [[(prop, [])]]
   619         |> Proof.global_terminal_proof methods;
   620     in output context (maybe_pretty_source pretty_term context prop_src [prop]) end);
   621 
   622 
   623 (* ML text *)
   624 
   625 val verb_text =
   626   split_lines
   627   #> map (space_implode "\\verb,|," o map (enclose "\\verb|" "|") o space_explode "|")
   628   #> space_implode "\\isasep\\isanewline%\n";
   629 
   630 local
   631 
   632 fun ml_text name ml = antiquotation name (Scan.lift Args.name_source_position)
   633   (fn {context, ...} => fn (txt, pos) =>
   634    (ML_Context.eval_in (SOME context) false pos (ml pos txt);
   635     Symbol_Pos.content (Symbol_Pos.explode (txt, pos))
   636     |> (if Config.get context quotes then quote else I)
   637     |> (if Config.get context display then enclose "\\begin{verbatim}\n" "\n\\end{verbatim}"
   638         else verb_text)));
   639 
   640 fun ml_enclose bg en pos txt =
   641   ML_Lex.read Position.none bg @ ML_Lex.read pos txt @ ML_Lex.read Position.none en;
   642 
   643 in
   644 
   645 val _ = ml_text "ML" (ml_enclose "fn _ => (" ");");
   646 val _ = ml_text "ML_type" (ml_enclose "val _ = NONE : (" ") option;");
   647 val _ = ml_text "ML_struct" (ml_enclose "functor XXX() = struct structure XX = " " end;");
   648 
   649 val _ = ml_text "ML_functor"   (* FIXME formal treatment of functor name (!?) *)
   650   (fn pos => fn txt =>
   651     ML_Lex.read Position.none ("ML_Env.check_functor " ^
   652       ML_Syntax.print_string (Symbol_Pos.content (Symbol_Pos.explode (txt, pos)))));
   653 
   654 val _ = ml_text "ML_text" (K (K []));
   655 
   656 end;
   657 
   658 
   659 (* files *)
   660 
   661 val _ = antiquotation "file" (Scan.lift Args.name)
   662   (fn {context, ...} => fn path =>
   663     if File.exists (Path.explode path) then verb_text path
   664     else error ("Bad file: " ^ quote path));
   665 
   666 end;