src/Pure/Thy/thy_syntax.ML
author wenzelm
Mon, 31 May 2010 21:06:57 +0200
changeset 37216 3165bc303f66
parent 37198 953fc4983439
child 38681 f96394dba335
permissions -rw-r--r--
modernized some structure names, keeping a few legacy aliases;
     1 (*  Title:      Pure/Thy/thy_syntax.ML
     2     Author:     Makarius
     3 
     4 Superficial theory syntax: tokens and spans.
     5 *)
     6 
     7 signature THY_SYNTAX =
     8 sig
     9   val token_source: Scan.lexicon * Scan.lexicon -> Position.T -> (string, 'a) Source.source ->
    10     (Token.T, (Symbol_Pos.T, Position.T * (Symbol.symbol, (string, 'a)
    11       Source.source) Source.source) Source.source) Source.source
    12   val parse_tokens: Scan.lexicon * Scan.lexicon -> Position.T -> string -> Token.T list
    13   val present_token: Token.T -> output
    14   val report_token: Token.T -> unit
    15   datatype span_kind = Command of string | Ignored | Malformed
    16   type span
    17   val span_kind: span -> span_kind
    18   val span_content: span -> Token.T list
    19   val span_range: span -> Position.range
    20   val span_source: (Token.T, 'a) Source.source -> (span, (Token.T, 'a) Source.source) Source.source
    21   val parse_spans: Scan.lexicon * Scan.lexicon -> Position.T -> string -> span list
    22   val present_span: span -> output
    23   val report_span: span -> unit
    24   val unit_source: (span, 'a) Source.source ->
    25     (span * span list * bool, (span, 'a) Source.source) Source.source
    26 end;
    27 
    28 structure Thy_Syntax: THY_SYNTAX =
    29 struct
    30 
    31 (** tokens **)
    32 
    33 (* parse *)
    34 
    35 fun token_source lexs pos src =
    36   Symbol.source {do_recover = true} src
    37   |> Token.source {do_recover = SOME false} (K lexs) pos;
    38 
    39 fun parse_tokens lexs pos str =
    40   Source.of_string str
    41   |> token_source lexs pos
    42   |> Source.exhaust;
    43 
    44 
    45 (* present *)
    46 
    47 local
    48 
    49 val token_kind_markup =
    50  fn Token.Command       => Markup.command
    51   | Token.Keyword       => Markup.keyword
    52   | Token.Ident         => Markup.ident
    53   | Token.LongIdent     => Markup.ident
    54   | Token.SymIdent      => Markup.ident
    55   | Token.Var           => Markup.var
    56   | Token.TypeIdent     => Markup.tfree
    57   | Token.TypeVar       => Markup.tvar
    58   | Token.Nat           => Markup.ident
    59   | Token.String        => Markup.string
    60   | Token.AltString     => Markup.altstring
    61   | Token.Verbatim      => Markup.verbatim
    62   | Token.Space         => Markup.none
    63   | Token.Comment       => Markup.comment
    64   | Token.InternalValue => Markup.none
    65   | Token.Malformed     => Markup.malformed
    66   | Token.Error _       => Markup.malformed
    67   | Token.Sync          => Markup.control
    68   | Token.EOF           => Markup.control;
    69 
    70 fun token_markup tok =
    71   if Token.keyword_with (not o Syntax.is_identifier) tok then Markup.operator
    72   else
    73     let
    74       val kind = Token.kind_of tok;
    75       val props =
    76         if kind = Token.Command then
    77           (case Keyword.command_keyword (Token.content_of tok) of
    78             SOME k => Markup.properties [(Markup.kindN, Keyword.kind_of k)]
    79           | NONE => I)
    80         else I;
    81     in props (token_kind_markup kind) end;
    82 
    83 in
    84 
    85 fun present_token tok =
    86   Markup.enclose (token_markup tok) (Output.output (Token.unparse tok));
    87 
    88 fun report_token tok =
    89   Position.report (token_markup tok) (Token.position_of tok);
    90 
    91 end;
    92 
    93 
    94 
    95 (** spans **)
    96 
    97 (* type span *)
    98 
    99 datatype span_kind = Command of string | Ignored | Malformed;
   100 datatype span = Span of span_kind * Token.T list;
   101 
   102 fun span_kind (Span (k, _)) = k;
   103 fun span_content (Span (_, toks)) = toks;
   104 
   105 fun span_range span =
   106   (case span_content span of
   107     [] => (Position.none, Position.none)
   108   | toks =>
   109       let
   110         val start_pos = Token.position_of (hd toks);
   111         val end_pos = Token.end_position_of (List.last toks);
   112       in (start_pos, end_pos) end);
   113 
   114 
   115 (* parse *)
   116 
   117 local
   118 
   119 val is_whitespace = Token.is_kind Token.Space orf Token.is_kind Token.Comment;
   120 
   121 val body =
   122   Scan.unless (Scan.many is_whitespace -- Scan.ahead (Parse.command || Parse.eof)) Parse.not_eof;
   123 
   124 val span =
   125   Scan.ahead Parse.command -- Parse.not_eof -- Scan.repeat body
   126     >> (fn ((name, c), bs) => Span (Command name, c :: bs)) ||
   127   Scan.many1 is_whitespace >> (fn toks => Span (Ignored, toks)) ||
   128   Scan.repeat1 body >> (fn toks => Span (Malformed, toks));
   129 
   130 in
   131 
   132 fun span_source src = Source.source Token.stopper (Scan.bulk span) NONE src;
   133 
   134 end;
   135 
   136 fun parse_spans lexs pos str =
   137   Source.of_string str
   138   |> token_source lexs pos
   139   |> span_source
   140   |> Source.exhaust;
   141 
   142 
   143 (* present *)
   144 
   145 local
   146 
   147 fun kind_markup (Command name) = Markup.command_span name
   148   | kind_markup Ignored = Markup.ignored_span
   149   | kind_markup Malformed = Markup.malformed_span;
   150 
   151 in
   152 
   153 fun present_span span =
   154   Markup.enclose (kind_markup (span_kind span)) (implode (map present_token (span_content span)));
   155 
   156 fun report_span span =
   157   Position.report (kind_markup (span_kind span)) (Position.encode_range (span_range span));
   158 
   159 end;
   160 
   161 
   162 
   163 (** units: commands with proof **)
   164 
   165 (* scanning spans *)
   166 
   167 val eof = Span (Command "", []);
   168 
   169 fun is_eof (Span (Command "", _)) = true
   170   | is_eof _ = false;
   171 
   172 val not_eof = not o is_eof;
   173 
   174 val stopper = Scan.stopper (K eof) is_eof;
   175 
   176 
   177 (* unit_source *)
   178 
   179 local
   180 
   181 fun command_with pred = Scan.one (fn (Span (Command name, _)) => pred name | _ => false);
   182 
   183 val proof = Scan.pass 1 (Scan.repeat (Scan.depend (fn d =>
   184   if d <= 0 then Scan.fail
   185   else
   186     command_with Keyword.is_qed_global >> pair ~1 ||
   187     command_with Keyword.is_proof_goal >> pair (d + 1) ||
   188     (if d = 0 then Scan.fail else command_with Keyword.is_qed >> pair (d - 1)) ||
   189     Scan.unless (command_with Keyword.is_theory) (Scan.one not_eof) >> pair d)) -- Scan.state);
   190 
   191 val unit =
   192   command_with Keyword.is_theory_goal -- proof >> (fn (a, (bs, d)) => (a, bs, d >= 0)) ||
   193   Scan.one not_eof >> (fn a => (a, [], true));
   194 
   195 in
   196 
   197 fun unit_source src = Source.source stopper (Scan.bulk unit) NONE src;
   198 
   199 end;
   200 
   201 end;