(* rm -r man2 ocamlc unix.cma str.cma index.ml ./a.out cp man/*.css man/.ht* man/*.gif man2 *) type refer = {file: string; ident: string; tO: string; ex: bool};; let odn = "man" and ndn = "man2" and sbs = String.sub (* and ps i x = print_char '\n'; print_int i; print_string ("<*"^x^"*>"); x and pi i x = print_string ("<|"); print_int i; print_char ' '; print_int(x); print_string ("|>"); x *) in let zf ff = (let rec z pn = (Unix.mkdir (ndn^"/"^pn) 0o755); let dh = Unix.opendir (odn^"/"^pn) in try while 0=0 do (let fn = Unix.readdir dh in let ln = pn^fn in if String.get fn 0 = '.' then () else (if Sys.is_directory (odn^"/"^ln) then (z (ln^"/")) else (if (let l = String.length fn in ((l>6) && (sbs fn (l-5) 5) = ".html")) then ff ln) )) done with End_of_file -> () in z) in let ndx = ref [] in (let df = let sre = Str.regexp_case_fold in let w = sre "\\1" and wr = sre "[^#]*#\\([^\"]+\\)\">\\1" in (fun fn -> let iF = open_in (odn^"/"^fn) and oF = open_out (ndn^"/"^fn) and isc = ref false and recent = ref "" in try while 0=0 do (let iLine = (input_line iF) in if iLine = "" then (isc := false; output_string oF (iLine^"\n")) else (let oLine = ref "" and lc = ref 0 in (try while 0=0 do (let ni = (Str.search_forward w iLine !lc) in let isname = String.get iLine (ni + 6) = 'N' and ime = (Str.match_end ()) in if Str.string_match (if isname then wn else wr) iLine ime then ( let mg = Str.matched_group 1 iLine in oLine := !oLine ^ ((sbs iLine !lc (ni - !lc)) ^ (if isname then (isc := true; (sbs iLine ni ((Str.group_end 1) - ni)) ^ "\" href=i.html#" ^ mg ^ ">" ^ mg ^ "") else (sbs iLine ni ((Str.match_end ()) - ni)))); if isname then recent := mg else (ndx := {file = fn; ident = mg; tO = !recent; ex = !isc}::!ndx); lc := (Str.match_end ())) else (let ns = ni + 1 in oLine := !oLine ^ (sbs iLine !lc (ns - !lc)); (* if ni = !lc then (ignore (pi 39 ni); raise (Invalid_argument "fooo")); *) lc := ns)) done with Not_found -> (output_string oF (!oLine ^ (sbs iLine !lc ((String.length iLine) - !lc))^"\n"))))) done with End_of_file -> close_out oF) in zf df ""); (* List.iter (fun x -> print_string (if 0=1 then (x.file^", "^x.ident^", "^x.tO^"\n") else ("In file "^x.file^" cat "^x.tO^" relies on cat "^x.ident^ (if x.ex then " d" else " t")^"\n"))) !ndx; *) ndx := (let sc = String.compare in (List.sort (fun x y -> let l1 = sc x.ident y.ident in if l1 = 0 then (let l2 = sc x.tO y.tO in if l2 = 0 then (if x.ex = y.ex then 0 else (if x.ex then 1 else -1)) else l2) else l1) !ndx)); let oF = open_out (ndn^"/i.html") in let p x = output_string oF x; output_string oF "\n" in p "Index of Ocaml Syntactic Categories"; p "
"; let cn = ref "" and cf = ref "" and k = ref 0 in List.iter (fun x -> if !cn <> x.ident then (p (""^"
"^x.ident^"
"); cn := x.ident; cf := ""; k := 0); if x.tO = !cf then k := !k + 1 else (p (""^x.tO^""^ (if !k>1 then (string_of_int !k) else "")^", "); k := 1; cf := x.tO)) !ndx; p "
"; close_out oF;;