| 5829 |      1 | (*  Title:      Pure/Isar/outer_syntax.ML
 | 
|  |      2 |     ID:         $Id$
 | 
|  |      3 |     Author:     Markus Wenzel, TU Muenchen
 | 
| 8807 |      4 |     License:    GPL (GNU GENERAL PUBLIC LICENSE)
 | 
| 5829 |      5 | 
 | 
|  |      6 | The global Isabelle/Isar outer syntax.
 | 
|  |      7 | *)
 | 
|  |      8 | 
 | 
|  |      9 | signature BASIC_OUTER_SYNTAX =
 | 
|  |     10 | sig
 | 
|  |     11 |   val main: unit -> unit
 | 
| 5883 |     12 |   val loop: unit -> unit
 | 
| 6860 |     13 |   val sync_main: unit -> unit
 | 
|  |     14 |   val sync_loop: unit -> unit
 | 
| 5829 |     15 | end;
 | 
|  |     16 | 
 | 
|  |     17 | signature OUTER_SYNTAX =
 | 
|  |     18 | sig
 | 
|  |     19 |   include BASIC_OUTER_SYNTAX
 | 
| 6722 |     20 |   structure Keyword:
 | 
|  |     21 |     sig
 | 
|  |     22 |       val control: string
 | 
|  |     23 |       val diag: string
 | 
|  |     24 |       val thy_begin: string
 | 
| 7104 |     25 |       val thy_switch: string
 | 
| 6722 |     26 |       val thy_end: string
 | 
|  |     27 |       val thy_heading: string
 | 
|  |     28 |       val thy_decl: string
 | 
| 9588 |     29 |       val thy_script: string
 | 
| 6722 |     30 |       val thy_goal: string
 | 
|  |     31 |       val qed: string
 | 
| 6733 |     32 |       val qed_block: string
 | 
| 8209 |     33 |       val qed_global: string
 | 
| 9552 |     34 |       val prf_heading: string
 | 
| 6722 |     35 |       val prf_goal: string
 | 
|  |     36 |       val prf_block: string
 | 
| 9056 |     37 |       val prf_open: string
 | 
|  |     38 |       val prf_close: string
 | 
| 6722 |     39 |       val prf_chain: string
 | 
|  |     40 |       val prf_decl: string
 | 
| 6868 |     41 |       val prf_asm: string
 | 
| 7676 |     42 |       val prf_asm_goal: string
 | 
| 6722 |     43 |       val prf_script: string
 | 
|  |     44 |       val kinds: string list
 | 
|  |     45 |     end
 | 
| 5829 |     46 |   type token
 | 
|  |     47 |   type parser
 | 
| 6722 |     48 |   val command: string -> string -> string ->
 | 
| 6373 |     49 |     (token list -> (Toplevel.transition -> Toplevel.transition) * token list) -> parser
 | 
| 9132 |     50 |   val markup_command: IsarOutput.markup -> string -> string -> string ->
 | 
| 7789 |     51 |     (token list -> (Toplevel.transition -> Toplevel.transition) * token list) -> parser
 | 
| 6722 |     52 |   val improper_command: string -> string -> string ->
 | 
| 6373 |     53 |     (token list -> (Toplevel.transition -> Toplevel.transition) * token list) -> parser
 | 
| 7026 |     54 |   val dest_keywords: unit -> string list
 | 
|  |     55 |   val dest_parsers: unit -> (string * string * string * bool) list
 | 
| 5883 |     56 |   val print_outer_syntax: unit -> unit
 | 
| 9223 |     57 |   val print_commands: Toplevel.transition -> Toplevel.transition
 | 
| 5829 |     58 |   val add_keywords: string list -> unit
 | 
|  |     59 |   val add_parsers: parser list -> unit
 | 
| 7940 |     60 |   val deps_thy: string -> bool -> Path.T -> string list * Path.T list
 | 
| 6199 |     61 |   val load_thy: string -> bool -> bool -> Path.T -> unit
 | 
| 7333 |     62 |   val isar: bool -> bool -> Toplevel.isar
 | 
| 5829 |     63 | end;
 | 
|  |     64 | 
 | 
|  |     65 | structure OuterSyntax: OUTER_SYNTAX =
 | 
|  |     66 | struct
 | 
|  |     67 | 
 | 
| 7750 |     68 | structure T = OuterLex;
 | 
| 6860 |     69 | structure P = OuterParse;
 | 
|  |     70 | 
 | 
| 5829 |     71 | 
 | 
|  |     72 | (** outer syntax **)
 | 
|  |     73 | 
 | 
| 6722 |     74 | (* command keyword classification *)
 | 
|  |     75 | 
 | 
|  |     76 | structure Keyword =
 | 
|  |     77 | struct
 | 
|  |     78 |   val control = "control";
 | 
|  |     79 |   val diag = "diag";
 | 
|  |     80 |   val thy_begin = "theory-begin";
 | 
| 7104 |     81 |   val thy_switch = "theory-switch";
 | 
| 6722 |     82 |   val thy_end = "theory-end";
 | 
|  |     83 |   val thy_heading = "theory-heading";
 | 
|  |     84 |   val thy_decl = "theory-decl";
 | 
| 9588 |     85 |   val thy_script = "theory-script";
 | 
| 6722 |     86 |   val thy_goal = "theory-goal";
 | 
|  |     87 |   val qed = "qed";
 | 
| 6733 |     88 |   val qed_block = "qed-block";
 | 
| 8209 |     89 |   val qed_global = "qed-global";
 | 
| 9552 |     90 |   val prf_heading = "proof-heading";
 | 
| 6722 |     91 |   val prf_goal = "proof-goal";
 | 
|  |     92 |   val prf_block = "proof-block";
 | 
| 9056 |     93 |   val prf_open = "proof-open";
 | 
|  |     94 |   val prf_close = "proof-close";
 | 
| 6722 |     95 |   val prf_chain = "proof-chain";
 | 
|  |     96 |   val prf_decl = "proof-decl";
 | 
| 6868 |     97 |   val prf_asm = "proof-asm";
 | 
| 7676 |     98 |   val prf_asm_goal = "proof-asm-goal";
 | 
| 6722 |     99 |   val prf_script = "proof-script";
 | 
|  |    100 | 
 | 
| 9588 |    101 |   val kinds = [control, diag, thy_begin, thy_switch, thy_end, thy_heading, thy_decl, thy_script,
 | 
|  |    102 |     thy_goal, qed, qed_block, qed_global, prf_heading, prf_goal, prf_block, prf_open, prf_close,
 | 
|  |    103 |     prf_chain, prf_decl, prf_asm, prf_asm_goal, prf_script];
 | 
| 6722 |    104 | end;
 | 
|  |    105 | 
 | 
|  |    106 | 
 | 
| 5829 |    107 | (* parsers *)
 | 
|  |    108 | 
 | 
| 7750 |    109 | type token = T.token;
 | 
| 5829 |    110 | type parser_fn = token list -> (Toplevel.transition -> Toplevel.transition) * token list;
 | 
|  |    111 | 
 | 
|  |    112 | datatype parser =
 | 
| 9132 |    113 |   Parser of string * (string * string * IsarOutput.markup option) * bool * parser_fn;
 | 
| 5829 |    114 | 
 | 
| 7750 |    115 | fun parser int_only markup name comment kind parse =
 | 
|  |    116 |   Parser (name, (comment, kind, markup), int_only, parse);
 | 
| 5829 |    117 | 
 | 
|  |    118 | 
 | 
|  |    119 | (* parse command *)
 | 
|  |    120 | 
 | 
| 6860 |    121 | local
 | 
| 6199 |    122 | 
 | 
| 5829 |    123 | fun command_body cmd (name, _) =
 | 
| 7026 |    124 |   (case cmd name of
 | 
|  |    125 |     Some (int_only, parse) => P.!!! (Scan.prompt (name ^ "# ") (parse >> pair int_only))
 | 
|  |    126 |   | None => sys_error ("no parser for outer syntax command " ^ quote name));
 | 
| 6860 |    127 | 
 | 
|  |    128 | fun terminator false = Scan.succeed ()
 | 
| 9132 |    129 |   | terminator true = P.group "end of input" (Scan.option P.sync -- P.semicolon >> K ());
 | 
| 6860 |    130 | 
 | 
|  |    131 | in
 | 
| 5829 |    132 | 
 | 
| 6860 |    133 | fun command term cmd =
 | 
| 9132 |    134 |   P.semicolon >> K None ||
 | 
| 6860 |    135 |   P.sync >> K None ||
 | 
| 7026 |    136 |   (P.position P.command :-- command_body cmd) --| terminator term
 | 
| 6860 |    137 |     >> (fn ((name, pos), (int_only, f)) =>
 | 
|  |    138 |       Some (Toplevel.empty |> Toplevel.name name |> Toplevel.position pos |>
 | 
|  |    139 |         Toplevel.interactive int_only |> f));
 | 
| 5829 |    140 | 
 | 
| 6199 |    141 | end;
 | 
|  |    142 | 
 | 
| 5829 |    143 | 
 | 
|  |    144 | 
 | 
| 9132 |    145 | (** global outer syntax **)
 | 
| 5829 |    146 | 
 | 
| 7026 |    147 | local
 | 
|  |    148 | 
 | 
|  |    149 | val global_lexicons = ref (Scan.empty_lexicon, Scan.empty_lexicon);
 | 
| 7750 |    150 | val global_parsers =
 | 
| 9132 |    151 |   ref (Symtab.empty: (((string * string) * (bool * parser_fn)) * IsarOutput.markup option)
 | 
|  |    152 |     Symtab.table);
 | 
|  |    153 | val global_markups = ref ([]: (string * IsarOutput.markup) list);
 | 
| 5952 |    154 | 
 | 
| 7026 |    155 | fun change_lexicons f =
 | 
|  |    156 |   let val lexs = f (! global_lexicons) in
 | 
|  |    157 |     (case (op inter_string) (pairself Scan.dest_lexicon lexs) of
 | 
|  |    158 |       [] => global_lexicons := lexs
 | 
|  |    159 |     | bads => error ("Clash of outer syntax commands and keywords: " ^ commas_quote bads))
 | 
|  |    160 |   end;
 | 
| 5829 |    161 | 
 | 
| 7789 |    162 | fun get_markup (ms, (name, (_, Some m))) = (name, m) :: ms
 | 
|  |    163 |   | get_markup (ms, _) = ms;
 | 
| 7750 |    164 | 
 | 
|  |    165 | fun make_markups () = global_markups := Symtab.foldl get_markup ([], ! global_parsers);
 | 
| 9132 |    166 | fun change_parsers f = (Library.change global_parsers f; make_markups ());
 | 
| 6722 |    167 | 
 | 
| 7026 |    168 | in
 | 
|  |    169 | 
 | 
| 7750 |    170 | 
 | 
| 9132 |    171 | (* access current syntax *)
 | 
| 7026 |    172 | 
 | 
|  |    173 | (*Note: the syntax for files is statically determined at the very
 | 
|  |    174 |   beginning; for interactive processing it may change dynamically.*)
 | 
|  |    175 | 
 | 
|  |    176 | fun get_lexicons () = ! global_lexicons;
 | 
|  |    177 | fun get_parsers () = ! global_parsers;
 | 
| 7750 |    178 | fun get_parser () = apsome (#2 o #1) o curry Symtab.lookup (! global_parsers);
 | 
| 7789 |    179 | 
 | 
| 9132 |    180 | fun is_markup kind name =
 | 
|  |    181 |   (case assoc (! global_markups, name) of Some k => k = kind | None => false);
 | 
|  |    182 | fun markup kind = Scan.one (T.is_kind T.Command andf is_markup kind o T.val_of);
 | 
| 5829 |    183 | 
 | 
|  |    184 | 
 | 
|  |    185 | (* augment syntax *)
 | 
|  |    186 | 
 | 
| 7026 |    187 | fun add_keywords keywords = change_lexicons (apfst (fn lex =>
 | 
|  |    188 |   (Scan.extend_lexicon lex (map Symbol.explode keywords))));
 | 
| 5829 |    189 | 
 | 
| 7750 |    190 | fun add_parser (tab, Parser (name, (comment, kind, markup), int_only, parse)) =
 | 
| 5829 |    191 |  (if is_none (Symtab.lookup (tab, name)) then ()
 | 
|  |    192 |   else warning ("Redefined outer syntax command " ^ quote name);
 | 
| 7750 |    193 |   Symtab.update ((name, (((comment, kind), (int_only, parse)), markup)), tab));
 | 
| 5829 |    194 | 
 | 
|  |    195 | fun add_parsers parsers =
 | 
| 7026 |    196 |   (change_parsers (fn tab => foldl add_parser (tab, parsers));
 | 
|  |    197 |     change_lexicons (apsnd (fn lex => Scan.extend_lexicon lex
 | 
|  |    198 |       (map (fn Parser (name, _, _, _) => Symbol.explode name) parsers))));
 | 
|  |    199 | 
 | 
|  |    200 | end;
 | 
| 5829 |    201 | 
 | 
|  |    202 | 
 | 
| 7026 |    203 | (* print syntax *)
 | 
|  |    204 | 
 | 
|  |    205 | fun dest_keywords () = Scan.dest_lexicon (#1 (get_lexicons ()));
 | 
|  |    206 | 
 | 
|  |    207 | fun dest_parsers () =
 | 
| 7750 |    208 |   map (fn (name, (((cmt, kind), (int_only, _)), _)) => (name, cmt, kind, int_only))
 | 
| 7026 |    209 |     (Symtab.dest (get_parsers ()));
 | 
| 5829 |    210 | 
 | 
| 9223 |    211 | fun print_outer_syntax () =
 | 
| 7026 |    212 |   let
 | 
|  |    213 |     fun pretty_cmd (name, comment, _, _) =
 | 
|  |    214 |       Pretty.block [Pretty.str (name ^ ":"), Pretty.brk 2, Pretty.str comment];
 | 
|  |    215 |     val (int_cmds, cmds) = partition #4 (dest_parsers ());
 | 
|  |    216 |   in
 | 
| 8720 |    217 |     [Pretty.strs ("syntax keywords:" :: map quote (dest_keywords ())),
 | 
|  |    218 |       Pretty.big_list "proper commands:" (map pretty_cmd cmds),
 | 
|  |    219 |       Pretty.big_list "improper commands (interactive-only):" (map pretty_cmd int_cmds)]
 | 
| 9223 |    220 |     |> Pretty.chunks |> Pretty.writeln
 | 
| 7026 |    221 |   end;
 | 
| 5829 |    222 | 
 | 
| 9223 |    223 | val print_commands = Toplevel.imperative print_outer_syntax;
 | 
| 7367 |    224 | 
 | 
| 5829 |    225 | 
 | 
|  |    226 | 
 | 
| 9132 |    227 | (** toplevel parsing **)
 | 
| 5829 |    228 | 
 | 
| 9132 |    229 | (* basic sources *)
 | 
| 6860 |    230 | 
 | 
| 7683 |    231 | fun token_source (src, pos) =
 | 
|  |    232 |   src
 | 
|  |    233 |   |> Symbol.source false
 | 
| 7750 |    234 |   |> T.source false (K (get_lexicons ())) pos;
 | 
| 7683 |    235 | 
 | 
| 9132 |    236 | fun toplevel_source term do_recover cmd src =
 | 
|  |    237 |   let
 | 
|  |    238 |     val no_terminator =
 | 
|  |    239 |       Scan.unless P.semicolon (Scan.one (T.not_sync andf T.not_eof));
 | 
| 10749 |    240 |     val recover = Scan.prompt "recover# " (Scan.repeat no_terminator) >> K [None];
 | 
| 9132 |    241 |   in
 | 
|  |    242 |     src
 | 
|  |    243 |     |> Source.source T.stopper
 | 
|  |    244 |       (Scan.bulk (fn xs => P.!!! (command term (cmd ())) xs))
 | 
|  |    245 |       (if do_recover then Some recover else None)
 | 
|  |    246 |     |> Source.mapfilter I
 | 
|  |    247 |   end;
 | 
| 5829 |    248 | 
 | 
| 7746 |    249 | 
 | 
| 9132 |    250 | (* interactive source of toplevel transformers *)
 | 
| 5829 |    251 | 
 | 
| 9132 |    252 | fun isar term no_pos =
 | 
|  |    253 |   Source.tty
 | 
|  |    254 |   |> Symbol.source true
 | 
|  |    255 |   |> T.source true get_lexicons
 | 
|  |    256 |     (if no_pos then Position.none else Position.line_name 1 "stdin")
 | 
|  |    257 |   |> T.source_proper
 | 
|  |    258 |   |> toplevel_source term true get_parser;
 | 
| 6199 |    259 | 
 | 
|  |    260 | 
 | 
| 7746 |    261 | 
 | 
| 9132 |    262 | (** read theory **)
 | 
| 6247 |    263 | 
 | 
| 9132 |    264 | (* deps_thy *)
 | 
| 6199 |    265 | 
 | 
| 7940 |    266 | fun deps_thy name ml path =
 | 
| 6199 |    267 |   let
 | 
| 7735 |    268 |     val src = Source.of_string (File.read path);
 | 
|  |    269 |     val pos = Path.position path;
 | 
| 9132 |    270 |     val (name', parents, files) = ThyHeader.scan (src, pos);
 | 
| 6199 |    271 |     val ml_path = ThyLoad.ml_path name;
 | 
| 7940 |    272 |     val ml_file = if ml andalso is_some (ThyLoad.check_file ml_path) then [ml_path] else [];
 | 
| 6199 |    273 |   in
 | 
|  |    274 |     if name <> name' then
 | 
| 7940 |    275 |       error ("Filename " ^ quote (Path.pack path) ^
 | 
| 8078 |    276 |         " does not agree with theory name " ^ quote name')
 | 
| 6247 |    277 |     else (parents, map (Path.unpack o #1) files @ ml_file)
 | 
| 6199 |    278 |   end;
 | 
|  |    279 | 
 | 
| 7746 |    280 | 
 | 
| 9132 |    281 | (* load_thy *)
 | 
| 6199 |    282 | 
 | 
| 7746 |    283 | local
 | 
|  |    284 | 
 | 
| 7940 |    285 | fun try_ml_file name time =
 | 
| 6199 |    286 |   let
 | 
|  |    287 |     val path = ThyLoad.ml_path name;
 | 
| 7940 |    288 |     val tr = Toplevel.imperative (fn () => ThyInfo.load_file time path);
 | 
| 6247 |    289 |     val tr_name = if time then "time_use" else "use";
 | 
| 6199 |    290 |   in
 | 
| 7243 |    291 |     if is_none (ThyLoad.check_file path) then ()
 | 
| 9132 |    292 |     else Toplevel.excursion [Toplevel.empty |> Toplevel.name tr_name |> tr]
 | 
| 6199 |    293 |   end;
 | 
|  |    294 | 
 | 
| 9132 |    295 | fun parse_thy src =
 | 
|  |    296 |   src
 | 
|  |    297 |   |> T.source_proper
 | 
|  |    298 |   |> toplevel_source false false (K (get_parser ()))
 | 
| 7746 |    299 |   |> Source.exhaust;
 | 
| 5829 |    300 | 
 | 
| 6247 |    301 | fun run_thy name path =
 | 
| 7683 |    302 |   let
 | 
| 7735 |    303 |     val pos = Path.position path;
 | 
| 9132 |    304 |     val text = Library.untabify (explode (File.read path));
 | 
|  |    305 |     val text_src = Source.of_list text;
 | 
|  |    306 |     fun present_text () = Source.exhaust (Symbol.source false text_src);
 | 
| 7683 |    307 |   in
 | 
| 7735 |    308 |     Present.init_theory name;
 | 
| 9132 |    309 |     Present.verbatim_source name present_text;
 | 
|  |    310 |     if ThyHeader.is_old (text_src, pos) then (ThySyn.load_thy name text;
 | 
|  |    311 |       Present.old_symbol_source name present_text)   (*note: text presented twice*)
 | 
|  |    312 |     else
 | 
|  |    313 |       let
 | 
|  |    314 |         val tok_src = Source.exhausted (token_source (text_src, pos));
 | 
|  |    315 |         val out = Toplevel.excursion_result
 | 
|  |    316 |           (IsarOutput.parse_thy markup (#1 (get_lexicons ()))
 | 
|  |    317 |             (parse_thy tok_src) tok_src);
 | 
|  |    318 |       in Present.theory_output name (Buffer.content out) end
 | 
| 6247 |    319 |   end;
 | 
| 6199 |    320 | 
 | 
| 7746 |    321 | in
 | 
|  |    322 | 
 | 
| 6199 |    323 | fun load_thy name ml time path =
 | 
| 6247 |    324 |  (if time then
 | 
|  |    325 |     timeit (fn () =>
 | 
|  |    326 |      (writeln ("\n**** Starting theory " ^ quote name ^ " ****");
 | 
| 9036 |    327 |       run_thy name path;
 | 
| 6247 |    328 |       writeln ("**** Finished theory " ^ quote name ^ " ****\n")))
 | 
|  |    329 |   else run_thy name path;
 | 
|  |    330 |   Context.context (ThyInfo.get_theory name);
 | 
| 7940 |    331 |   if ml then try_ml_file name time else ());
 | 
| 5829 |    332 | 
 | 
| 7746 |    333 | end;
 | 
|  |    334 | 
 | 
| 5829 |    335 | 
 | 
|  |    336 | 
 | 
|  |    337 | (** the read-eval-print loop **)
 | 
|  |    338 | 
 | 
| 5923 |    339 | (* main loop *)
 | 
|  |    340 | 
 | 
| 7333 |    341 | fun gen_loop term no_pos =
 | 
|  |    342 |  (Context.reset_context ();
 | 
|  |    343 |   Toplevel.loop (isar term no_pos));
 | 
| 5829 |    344 | 
 | 
| 7333 |    345 | fun gen_main term no_pos =
 | 
| 5829 |    346 |  (Toplevel.set_state Toplevel.toplevel;
 | 
| 6199 |    347 |   writeln (Session.welcome ());
 | 
| 7333 |    348 |   gen_loop term no_pos);
 | 
| 6860 |    349 | 
 | 
| 7333 |    350 | fun main () = gen_main false false;
 | 
|  |    351 | fun loop () = gen_loop false false;
 | 
|  |    352 | fun sync_main () = gen_main true true;
 | 
|  |    353 | fun sync_loop () = gen_loop true true;
 | 
| 5829 |    354 | 
 | 
|  |    355 | 
 | 
|  |    356 | (* help *)
 | 
|  |    357 | 
 | 
|  |    358 | fun help () =
 | 
|  |    359 |   writeln ("This is Isabelle's underlying ML system (" ^ ml_system ^ ");\n\
 | 
| 9223 |    360 |     \invoke 'Isar.loop();' to get back to the Isar read-eval-print loop.");
 | 
| 5829 |    361 | 
 | 
|  |    362 | 
 | 
| 6373 |    363 | (*final declarations of this structure!*)
 | 
| 7789 |    364 | val command = parser false None;
 | 
| 9132 |    365 | val markup_command = parser false o Some;
 | 
| 7789 |    366 | val improper_command = parser true None;
 | 
| 6685 |    367 | 
 | 
| 6373 |    368 | 
 | 
| 5829 |    369 | end;
 | 
|  |    370 | 
 | 
| 6199 |    371 | (*setup theory syntax dependent operations*)
 | 
|  |    372 | ThyLoad.deps_thy_fn := OuterSyntax.deps_thy;
 | 
|  |    373 | ThyLoad.load_thy_fn := OuterSyntax.load_thy;
 | 
|  |    374 | structure ThyLoad: THY_LOAD = ThyLoad;
 | 
|  |    375 | 
 | 
| 5829 |    376 | structure BasicOuterSyntax: BASIC_OUTER_SYNTAX = OuterSyntax;
 | 
|  |    377 | open BasicOuterSyntax;
 |