Passage de Caml Light a O'Caml: le bootstrap est enfin complet !

git-svn-id: http://caml.inria.fr/svn/ocamldoc/trunk@9823 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Damien Doligez 1999-11-09 15:44:37 +00:00
parent 3501eb0dce
commit ddbf9a5f0c
8 changed files with 128 additions and 115 deletions

View File

@ -5,29 +5,29 @@ all: texquote2 transf htmlquote htmlgen dvi2txt
dvi2txt:
cd dvi_to_txt; ${MAKE}
transf: transf.zo htmltransf.zo transfmain.zo
camlc -o transf -g transf.zo htmltransf.zo transfmain.zo
transf: transf.cmo htmltransf.cmo transfmain.cmo
ocamlc -o transf -g transf.cmo htmltransf.cmo transfmain.cmo
transf.ml: transf.mll
camllex transf.mll
ocamllex transf.mll
htmltransf.ml: htmltransf.mll
camllex htmltransf.mll
ocamllex htmltransf.mll
htmlgen: latexmacros.zo latexscan.zo latexmain.zo
camlc -o htmlgen -g latexmacros.zo latexscan.zo latexmain.zo
htmlgen: latexmacros.cmo latexscan.cmo latexmain.cmo
ocamlc -o htmlgen -g latexmacros.cmo latexscan.cmo latexmain.cmo
latexscan.ml: latexscan.mll
camllex latexscan.mll
ocamllex latexscan.mll
.SUFFIXES:
.SUFFIXES: .ml .zo .mli .zi .c
.SUFFIXES: .ml .cmo .mli .cmi .c
.ml.zo:
camlc -c $<
.ml.cmo:
ocamlc -c $<
.mli.zi:
camlc -c $<
.mli.cmi:
ocamlc -c $<
.c:
$(CC) $(CFLAGS) -o $@ $<
@ -35,11 +35,11 @@ latexscan.ml: latexscan.mll
clean:
rm -f texquote2 transf htmlquote htmlgen dvi2txt
rm -f transf.ml latex.ml
rm -f *.o *.zi *.zo *.zix
rm -f *.o *.cm? *.cmxa
rm -f *~ #*#
cd dvi_to_txt; ${MAKE} clean
latexmacros.zo: latexmacros.zi
latexmain.zo: latexscan.zo
latexscan.zo: latexmacros.zi
transfmain.zo: transf.zo htmltransf.zo
latexmacros.cmo: latexmacros.cmi
latexmain.cmo: latexscan.cmo
latexscan.cmo: latexmacros.cmi
transfmain.cmo: transf.cmo htmltransf.cmo

View File

@ -1,9 +1,11 @@
{
open Lexing;;
let need_space =
ref false;;
let addspace () =
if !need_space then begin print_char ` `; need_space := false end;;
if !need_space then begin print_char ' '; need_space := false end;;
}
rule main = parse
@ -23,48 +25,48 @@ rule main = parse
print_string "\\end{rawhtml}%\n";
main lexbuf }
| _ {
print_char (get_lexeme_char lexbuf 0); main lexbuf }
print_char (lexeme_char lexbuf 0); main lexbuf }
| eof {
() }
and syntax = parse
"\\end{syntax}" { () }
| "@" { () }
| `'` {
| '\'' {
addspace();
print_string "<font color=\"blue\"><code>";
inquote lexbuf;
print_string "</code></font>";
need_space := true;
syntax lexbuf }
| `"` {
| '"' {
addspace();
print_string "<font color=\"blue\"><code>";
indoublequote lexbuf;
print_string "</code></font>";
need_space := true;
syntax lexbuf }
| [`a`-`z``-`] + {
| ['a'-'z''-'] + {
addspace();
print_string "<i>";
print_string (get_lexeme lexbuf);
print_string (lexeme lexbuf);
print_string "</i>";
need_space := true;
syntax lexbuf }
| `\\` [`a`-`z``A`-`Z`] + {
begin match get_lexeme lexbuf with
| '\\' ['a'-'z''A'-'Z'] + {
begin match lexeme lexbuf with
"\\ldots" -> print_string "..."; need_space := false
| s -> printf__eprintf "Warning: %s ignored.\n" s
| s -> Printf.eprintf "Warning: %s ignored.\n" s
end;
syntax lexbuf }
| `_` _ {
| '_' _ {
print_string "<SUB>";
print_char(get_lexeme_char lexbuf 1);
print_char(lexeme_char lexbuf 1);
print_string "</SUB>";
syntax lexbuf }
| `^` _ {
| '^' _ {
print_string "<SUP>";
print_char(get_lexeme_char lexbuf 1);
print_char(lexeme_char lexbuf 1);
print_string "</SUP>";
syntax lexbuf }
| ":" {
@ -79,36 +81,37 @@ and syntax = parse
print_string "\n\n";
need_space := false;
syntax lexbuf }
| [ `{` `[` `(`] {
addspace(); print_string (get_lexeme lexbuf); syntax lexbuf }
| [ `}` `]` `)`] {
print_string (get_lexeme lexbuf); syntax lexbuf }
| [ '{' '[' '('] {
addspace(); print_string (lexeme lexbuf); syntax lexbuf }
| [ '}' ']' ')'] {
print_string (lexeme lexbuf); syntax lexbuf }
| "{{" {
addspace(); print_string "{"; syntax lexbuf }
| "}}" {
print_string "}+"; syntax lexbuf }
| "||" {
print_string " | "; need_space := false; syntax lexbuf }
| [ ` ` `\n` `\t` `~`] {
| [ ' ' '\n' '\t' '~'] {
syntax lexbuf }
| [ `,` ] {
print_char(get_lexeme_char lexbuf 0); syntax lexbuf }
| [ ',' ] {
print_char(lexeme_char lexbuf 0); syntax lexbuf }
| _ {
printf__eprintf "Warning: %s ignored at char %d.\n"
(get_lexeme lexbuf) (get_lexeme_start lexbuf);
Printf.eprintf "Warning: %s ignored at char %d.\n"
(lexeme lexbuf) (lexeme_start lexbuf);
syntax lexbuf }
and inquote = parse
`'` { () }
| `&` { print_string "&amp;"; inquote lexbuf }
| `<` { print_string "&lt;"; inquote lexbuf }
| `>` { print_string "&gt;"; inquote lexbuf }
| _ { print_char (get_lexeme_char lexbuf 0); inquote lexbuf }
'\'' { () }
| '&' { print_string "&amp;"; inquote lexbuf }
| '<' { print_string "&lt;"; inquote lexbuf }
| '>' { print_string "&gt;"; inquote lexbuf }
| _ { print_char (lexeme_char lexbuf 0); inquote lexbuf }
and indoublequote = parse
`"` { () }
| `&` { print_string "&amp;"; indoublequote lexbuf }
| `<` { print_string "&lt;"; indoublequote lexbuf }
| `>` { print_string "&gt;"; indoublequote lexbuf }
| _ { print_char (get_lexeme_char lexbuf 0); indoublequote lexbuf }
;;
'"' { () }
| '&' { print_string "&amp;"; indoublequote lexbuf }
| '<' { print_string "&lt;"; indoublequote lexbuf }
| '>' { print_string "&gt;"; indoublequote lexbuf }
| _ { print_char (lexeme_char lexbuf 0); indoublequote lexbuf }

View File

@ -1,11 +1,16 @@
let cmdtable = (hashtbl__new 19 : (string, action list) hashtbl__t);;
type action =
Print of string
| Print_arg
| Skip_arg;;
let cmdtable = (Hashtbl.create 19 : (string, action list) Hashtbl.t);;
let def_macro name action =
hashtbl__add cmdtable name action;;
Hashtbl.add cmdtable name action;;
let find_macro name =
try
hashtbl__find cmdtable name
Hashtbl.find cmdtable name
with Not_found ->
prerr_string "Unknown macro: "; prerr_endline name; [];;

View File

@ -3,6 +3,6 @@ type action =
| Print_arg
| Skip_arg;;
value find_macro: string -> action list;;
val find_macro: string -> action list;;
value def_macro: string -> action list -> unit;;
val def_macro: string -> action list -> unit;;

View File

@ -1,4 +1,4 @@
let main () =
latexscan__main (lexing__create_lexer_channel stdin);;
Latexscan.main (Lexing.from_channel stdin);;
printexc__f main (); exit 0;;
Printexc.print main (); exit 0;;

View File

@ -1,5 +1,6 @@
{
#open "latexmacros";;
open Lexing;;
open Latexmacros;;
let delimiter = ref (char_of_int 0);;
@ -17,7 +18,7 @@ let rindex c s =
let rec find i =
if i < 0 then raise Not_found else
if s.[i] = c then i else find (i-1) in
find (string_length s - 1);;
find (String.length s - 1);;
let first_caml_line = ref true;;
let in_caml = ref false;;
@ -25,24 +26,24 @@ let in_caml = ref false;;
rule main = parse
(* Comments *)
`%` [^ `\n`] * `\n` { main lexbuf }
'%' [^ '\n'] * '\n' { main lexbuf }
(* Paragraphs *)
| "\n\n" `\n` *
| "\n\n" '\n' *
{ print_string "<P>\n"; main lexbuf }
(* Font changes *)
| "{\\it" " "* | "{\\em" " "*
{ print_string "<i>"; upto `}` main lexbuf;
{ print_string "<i>"; upto '}' main lexbuf;
print_string "</i>"; main lexbuf }
| "{\\bf" " "* { print_string "<b>"; upto `}` main lexbuf;
| "{\\bf" " "* { print_string "<b>"; upto '}' main lexbuf;
print_string "</b>"; main lexbuf }
| "{\\rm" " "* { print_string "<u>"; upto `}` main lexbuf;
| "{\\rm" " "* { print_string "<u>"; upto '}' main lexbuf;
print_string "</u>"; main lexbuf }
| "{\\tt" " "* { print_string "<tt>"; upto `}` main lexbuf;
| "{\\tt" " "* { print_string "<tt>"; upto '}' main lexbuf;
print_string "</tt>"; main lexbuf }
| `"` { print_string "<tt>"; indoublequote lexbuf;
| '"' { print_string "<tt>"; indoublequote lexbuf;
print_string "</tt>"; main lexbuf }
(* Verb, verbatim *)
| "\\verb" _ { verb_delim := get_lexeme_char lexbuf 5;
| "\\verb" _ { verb_delim := lexeme_char lexbuf 5;
print_string "<tt>"; inverb lexbuf; print_string "</tt>";
main lexbuf }
| "\\begin{verbatim}"
@ -59,57 +60,57 @@ rule main = parse
| "\\begin{latexonly}"
{ latexonly lexbuf; main lexbuf }
(* Itemize and similar environments *)
| "\\item[" { print_string "<dt>"; upto `]` main lexbuf;
| "\\item[" { print_string "<dt>"; upto ']' main lexbuf;
print_string "<dd>"; main lexbuf }
| "\\item" { print_string "<li>"; main lexbuf }
(* Math mode (hmph) *)
| "$" { main lexbuf }
(* Special characters *)
| "\\char" [`0`-`9`]+
{ let lxm = get_lexeme lexbuf in
let code = sub_string lxm 5 (string_length lxm - 5) in
| "\\char" ['0'-'9']+
{ let lxm = lexeme lexbuf in
let code = String.sub lxm 5 (String.length lxm - 5) in
print_char(char_of_int(int_of_string code));
main lexbuf }
| "<" { print_string "&lt;"; main lexbuf }
| ">" { print_string "&gt;"; main lexbuf }
| "~" { print_string " "; main lexbuf }
(* Definitions of very simple macros *)
| "\\def\\" ([`A`-`Z` `a`-`z`]+ | [^ `A`-`Z` `a`-`z`]) "{" [^ `{` `}`]* "}"
{ let s = get_lexeme lexbuf in
let l = string_length s in
let p = rindex `{` s in
let name = sub_string s 4 (p - 4) in
let expansion = sub_string s (p + 1) (l - p - 2) in
| "\\def\\" (['A'-'Z' 'a'-'z']+ | [^ 'A'-'Z' 'a'-'z']) "{" [^ '{' '}']* "}"
{ let s = lexeme lexbuf in
let l = String.length s in
let p = rindex '{' s in
let name = String.sub s 4 (p - 4) in
let expansion = String.sub s (p + 1) (l - p - 2) in
def_macro name [Print expansion];
main lexbuf }
(* General case for environments and commands *)
| ("\\begin{" | "\\end{") [`A`-`Z` `a`-`z`]+ "}" |
"\\" ([`A`-`Z` `a`-`z`]+ `*`? | [^ `A`-`Z` `a`-`z`])
| ("\\begin{" | "\\end{") ['A'-'Z' 'a'-'z']+ "}" |
"\\" (['A'-'Z' 'a'-'z']+ '*'? | [^ 'A'-'Z' 'a'-'z'])
{ let exec_action = function
Print str -> print_string str
| Print_arg -> print_arg lexbuf
| Skip_arg -> skip_arg lexbuf in
do_list exec_action (find_macro(get_lexeme lexbuf));
List.iter exec_action (find_macro(lexeme lexbuf));
main lexbuf }
(* Default rule for other characters *)
| eof { () }
| _ { let c = get_lexeme_char lexbuf 0 in
| _ { let c = lexeme_char lexbuf 0 in
if c == !delimiter then () else (print_char c; main lexbuf) }
and indoublequote = parse
`"` { () }
'"' { () }
| "<" { print_string "&lt;"; indoublequote lexbuf }
| ">" { print_string "&gt;"; indoublequote lexbuf }
| "&" { print_string "&amp;"; indoublequote lexbuf }
| "\\\"" { print_string "\""; indoublequote lexbuf }
| "\\\\" { print_string "\\"; indoublequote lexbuf }
| _ { print_char(get_lexeme_char lexbuf 0); indoublequote lexbuf }
| _ { print_char(lexeme_char lexbuf 0); indoublequote lexbuf }
and inverb = parse
"<" { print_string "&lt;"; inverb lexbuf }
| ">" { print_string "&gt;"; inverb lexbuf }
| "&" { print_string "&amp;"; inverb lexbuf }
| _ { let c = get_lexeme_char lexbuf 0 in
| _ { let c = lexeme_char lexbuf 0 in
if c == !verb_delim then ()
else (print_char c; inverb lexbuf) }
and inverbatim = parse
@ -117,7 +118,7 @@ and inverbatim = parse
| ">" { print_string "&gt;"; inverbatim lexbuf }
| "&" { print_string "&amp;"; inverbatim lexbuf }
| "\\end{verbatim}" { () }
| _ { print_char(get_lexeme_char lexbuf 0); inverbatim lexbuf }
| _ { print_char(lexeme_char lexbuf 0); inverbatim lexbuf }
and camlprog = parse
"<" { print_string "&lt;"; camlprog lexbuf }
@ -140,25 +141,26 @@ and camlprog = parse
print_string "</FONT>";
in_caml := false
end;
print_char `\n`;
print_char '\n';
camlprog lexbuf }
| _ { print_char(get_lexeme_char lexbuf 0); camlprog lexbuf }
| _ { print_char(lexeme_char lexbuf 0); camlprog lexbuf }
and rawhtml = parse
"\\end{rawhtml}" { () }
| _ { print_char(get_lexeme_char lexbuf 0); rawhtml lexbuf }
| _ { print_char(lexeme_char lexbuf 0); rawhtml lexbuf }
and latexonly = parse
"\\end{latexonly}" { () }
| _ { latexonly lexbuf }
and print_arg = parse
[` ` `\n`] * "{" { upto `}` main lexbuf }
| _ { print_char(get_lexeme_char lexbuf 0); rawhtml lexbuf }
[' ' '\n'] * "{" { upto '}' main lexbuf }
| _ { print_char(lexeme_char lexbuf 0); rawhtml lexbuf }
and skip_arg = parse
"{" { incr brace_nesting; skip_arg lexbuf }
| "}" { decr brace_nesting;
if !brace_nesting > 0 then skip_arg lexbuf }
| _ { skip_arg lexbuf }
;;

View File

@ -1,3 +1,5 @@
{ open Lexing;; }
rule main = parse
"\\begin{syntax}" {
print_string "\\begin{syntax}";
@ -9,7 +11,7 @@ rule main = parse
print_string "\\synt{";
syntax lexbuf }
| _ {
print_char (get_lexeme_char lexbuf 0); main lexbuf }
print_char (lexeme_char lexbuf 0); main lexbuf }
| eof {
() }
@ -20,23 +22,23 @@ and syntax = parse
| "@" {
print_string "}";
main lexbuf }
| `'` {
| '\'' {
print_string "\\token{";
inquote lexbuf }
| `"` {
| '"' {
print_string "\\token{";
indoublequote lexbuf }
| "epsilon" { print_string "\\emptystring"; syntax lexbuf }
| [`a`-`z``-`] + {
| ['a'-'z''-'] + {
print_string "\\nonterm{";
print_string (get_lexeme lexbuf);
print_string (lexeme lexbuf);
print_string"}";
syntax lexbuf }
| `\\` [`a`-`z``A`-`Z`] + {
print_string (get_lexeme lexbuf);
| '\\' ['a'-'z''A'-'Z'] + {
print_string (lexeme lexbuf);
syntax lexbuf }
| [`_` `^`] _ {
print_string (get_lexeme lexbuf);
| ['_' '^'] _ {
print_string (lexeme lexbuf);
syntax lexbuf }
| "{" { print_string "\\brepet{}"; syntax lexbuf }
| "}" { print_string "\\erepet{}"; syntax lexbuf }
@ -51,30 +53,31 @@ and syntax = parse
| "|" { print_string "\\alt{}"; syntax lexbuf }
| ";" { print_string "\\sep{}"; syntax lexbuf }
| _ {
print_char (get_lexeme_char lexbuf 0);
print_char (lexeme_char lexbuf 0);
syntax lexbuf }
and inquote = parse
[`A`-`Z` `a`-`z` `0`-`9`] {
print_char (get_lexeme_char lexbuf 0);
['A'-'Z' 'a'-'z' '0'-'9'] {
print_char (lexeme_char lexbuf 0);
inquote lexbuf }
| `'` {
| '\'' {
print_string "}";
syntax lexbuf }
| _ {
print_string "\\char";
print_int (int_of_char (get_lexeme_char lexbuf 0));
print_int (int_of_char (lexeme_char lexbuf 0));
inquote lexbuf }
and indoublequote = parse
[`A`-`Z` `a`-`z` `0`-`9`] {
print_char (get_lexeme_char lexbuf 0);
['A'-'Z' 'a'-'z' '0'-'9'] {
print_char (lexeme_char lexbuf 0);
indoublequote lexbuf }
| `"` {
| '"' {
print_string "}";
syntax lexbuf }
| _ {
print_string "\\char";
print_int (int_of_char (get_lexeme_char lexbuf 0));
print_int (int_of_char (lexeme_char lexbuf 0));
indoublequote lexbuf }
;;

View File

@ -1,8 +1,8 @@
let main() =
let lexbuf = lexing__create_lexer_channel std_in in
if vect_length sys__command_line >= 2 & sys__command_line.(1) = "-html"
then htmltransf__main lexbuf
else transf__main lexbuf;
let lexbuf = Lexing.from_channel stdin in
if Array.length Sys.argv >= 2 && Sys.argv.(1) = "-html"
then Htmltransf.main lexbuf
else Transf.main lexbuf;
exit 0;;
printexc__f main ();;
Printexc.print main ();;