\n"; output_string ch ("@comment{{" ^ s ^ "}}\n"); if html then output_string ch "\n"; output_string ch "\n" | Preamble l -> if html then output_string ch "
\n"; output_string ch "@preamble{"; print_atom_list html ch l; output_string ch "}\n"; if html then output_string ch "\n"; output_string ch "\n" | Abbrev(s,l) -> if needs_output s keys then begin if html then begin Html.open_anchor ch s; Html.close_anchor ch end; if html then output_string ch "
\n"; output_string ch ("@string{" ^ s ^ " = "); print_atom_list html ch l; output_string ch "}\n"; if html then output_string ch "\n"; output_string ch "\n" end | Entry (entry_type,key,fields) -> if needs_output key keys then begin (*if html then Html.open_balise ch "p";*) if html then begin Html.open_anchor ch key; Html.close_anchor ch end; if html then output_string ch "
\n"; output_string ch ("@" ^ entry_type ^ "{"); begin match html_file with | Some f -> Html.open_href ch (f ^ "#" ^ key); output_string ch key; Html.close_href ch | None -> output_string ch key end; List.iter (fun (field,l) -> if not (List.mem field remove) then begin let ofield = try List.assoc field rename with Not_found -> field in output_string ch (",\n " ^ ofield ^ " = "); if html && field = "crossref" then print_crossref html ch l else if html && is_link_field field then print_link_field ch l else print_atom_list html ch l end) fields; output_string ch "\n}\n"; if html then output_string ch "\n"; (*if html then Html.close_balise ch "p";*) output_string ch "\n" end (*s PHP output *) open Printf exception Bad_input_for_php of string (* inspired from String.escaped *) let add_backslashes s = let n = String.length s in let b = Buffer.create (2 * n) in for i = 0 to n - 1 do let c = String.unsafe_get s i in begin match c with | '\'' | '\\' -> Buffer.add_char b '\\' | _ -> () end; Buffer.add_char b c done; Buffer.contents b let php_print_atom ch = function | Id s -> fprintf ch "\'%s\'" s | String s -> fprintf ch "'%s'" (add_backslashes s) let php_print_atom_list ch = function | [] -> () | [a] -> php_print_atom ch a | a::l -> php_print_atom ch a; List.iter (fun a -> fprintf ch "."; php_print_atom ch a) l let php_print_command index remove rename ch keys = function | Comment s -> raise (Bad_input_for_php "comments not supported, use option --no-comment") (* output_string ch "
\n"; output_string ch ("@comment{{" ^ s ^ "}}\n"); output_string ch "\n"; output_string ch "\n" *) | Preamble l -> raise (Bad_input_for_php "preamble not supported") (* output_string ch "
\n"; output_string ch "@preamble{"; php_print_atom_list ch l; output_string ch "}\n"; output_string ch "\n"; output_string ch "\n" *) | Abbrev(s,l) -> raise (Bad_input_for_php "string not supported, use option --expand") (* if needs_output s keys then begin Html.open_anchor ch s; Html.close_anchor ch; output_string ch "
\n"; output_string ch ("@string{" ^ s ^ " = "); php_print_atom_list ch l; output_string ch "}\n"; output_string ch "\n"; output_string ch "\n" end *) | Entry (entry_type,key,fields) -> if needs_output key keys then begin if index > 0 then fprintf ch ",\n\n"; fprintf ch "%-5d => Array (\n" index; fprintf ch " \'entrytype\' => \'%s\',\n" entry_type; fprintf ch " \'cite\' => \'%s\'" key; List.iter (fun (field,l) -> if not (List.mem field remove) then begin let ofield = try List.assoc field rename with Not_found -> field in fprintf ch ",\n \'%s\' => " ofield; php_print_atom_list ch l end) fields; fprintf ch ")"; succ index end else index let output_bib ?(remove=[]) ?(rename=[]) ?(php=false) ~html ?html_file ch bib keys = let _ = Bibtex.fold (fun entry i -> if php then php_print_command i remove rename ch keys entry else (print_command remove rename html html_file ch keys entry; succ i)) bib 0 in () bibtex2html-1.99/biboutput.mli 0000644 0002463 0000430 00000004202 13255132746 015757 0 ustar filliatr vals (**************************************************************************) (* bibtex2html - A BibTeX to HTML translator *) (* Copyright (C) 1997-2014 Jean-Christophe Filliâtre and Claude Marché *) (* *) (* This software is free software; you can redistribute it and/or *) (* modify it under the terms of the GNU General Public *) (* License version 2, as published by the Free Software Foundation. *) (* *) (* This software is distributed in the hope that it will be useful, *) (* but WITHOUT ANY WARRANTY; without even the implied warranty of *) (* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. *) (* *) (* See the GNU General Public License version 2 for more details *) (* (enclosed in the file GPL). *) (**************************************************************************) (*s [output_bib html ch bib keys] outputs to the channel [ch] the fields of the bibliography [bib] whose key belong to [keys]. [html] is a flag that tells whether html anchors must be added: if [html] is false, the output is a regular bibtex file, if [html] is true, anchors are added on crossrefs, abbreviations, and URLs in fields. Notice that to guarantee that the generated part of the bibliography is coherent, that is all needed abbreviations and cross-references are included, one as to call Bibfilter.saturate before. Notice finally that the channel [ch] is NOT closed by this function *) open Bibtex exception Bad_input_for_php of string val output_bib : ?remove:string list -> ?rename:(string * string) list -> ?php:bool -> html:bool -> ?html_file:string -> out_channel -> biblio -> KeySet.t option -> unit (*s [add_link_field f] declares a new field [f] to be displayed as a web link (when HTML option of [output_bib] is set) *) val add_link_field : string -> unit bibtex2html-1.99/bibtex.ml 0000644 0002463 0000430 00000020026 13255132746 015050 0 ustar filliatr vals (**************************************************************************) (* bibtex2html - A BibTeX to HTML translator *) (* Copyright (C) 1997-2014 Jean-Christophe Filliâtre and Claude Marché *) (* *) (* This software is free software; you can redistribute it and/or *) (* modify it under the terms of the GNU General Public *) (* License version 2, as published by the Free Software Foundation. *) (* *) (* This software is distributed in the hope that it will be useful, *) (* but WITHOUT ANY WARRANTY; without even the implied warranty of *) (* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. *) (* *) (* See the GNU General Public License version 2 for more details *) (* (enclosed in the file GPL). *) (**************************************************************************) (*s Datatype for BibTeX bibliographies. *) type entry_type = string type key = string module KeySet = Set.Make(struct type t = key let compare = compare end) type atom = | Id of string | String of string type command = | Comment of string | Preamble of atom list | Abbrev of string * atom list | Entry of entry_type * key * (string * atom list) list (*s biblio is stored as a list. Beware, this in reverse order: the first entry is at the end of the list. This is intentional! *) type biblio = command list let empty_biblio = [] let size b = List.length b (*s the natural iterator on biblio must start at the first entry, so it is the [fold_right] function on lists, NOT the [fold_left]! *) let fold = List.fold_right let find_entry key biblio = let rec find key b = match b with | [] -> raise Not_found | (Entry (_,s,_) as e) :: b -> if String.lowercase_ascii s = key then e else find key b | _ :: b -> find key b in find (String.lowercase_ascii key) biblio let add_new_entry command biblio = command :: biblio let rec remove_entry key biblio = match biblio with | [] -> raise Not_found | (Entry(_,s,_) as e) :: b -> if s = key then b else e :: (remove_entry key b) | e :: b -> e :: (remove_entry key b) (*s [add_entry k c b] adds an entry of key [k] and command [c] in biblio [b] and returns the new biblio. If an entry of key [k] already exists in [b], it is replaced by the new one. *) let add_entry command biblio = match command with | Entry(_,key,_) -> begin try let new_bib = remove_entry key biblio in command :: new_bib with Not_found -> command :: biblio end | _ -> command::biblio let merge_biblios b1 b2 = let b2keys = fold (fun entry accu -> match entry with | Entry (_,key,_) -> KeySet.add key accu | _ -> accu) b2 KeySet.empty and b1abbrevs = fold (fun entry accu -> match entry with | Abbrev (key,_) -> KeySet.add key accu | _ -> accu) b1 KeySet.empty in let new_b1 = fold (fun entry accu -> match entry with | Entry (_,key,_) -> if KeySet.mem key b2keys then begin Format.eprintf "Warning, key '%s' duplicated@." key; if !Options.warn_error then exit 2; accu end else entry :: accu | _ -> entry :: accu) b1 empty_biblio in let new_bib = fold (fun entry accu -> match entry with | Abbrev (key,_) -> if KeySet.mem key b1abbrevs then begin Format.eprintf "Warning, key '%s' duplicated@." key; if !Options.warn_error then exit 2; accu end else entry :: accu | _ -> entry :: accu) b2 new_b1 in new_bib let month_env = List.map (fun s -> (s,[Id s])) [ "jan" ; "feb" ; "mar" ; "apr" ; "may" ; "jun" ; "jul" ; "aug" ; "sep" ; "oct" ; "nov" ; "dec" ] let abbrev_is_implicit key = try let _ = int_of_string key in true with Failure _ -> try let _ = List.assoc key month_env in true with Not_found -> false (*i let rec abbrev_exists key biblio = match biblio with | [] -> false | (Abbrev (s,_)) :: b -> s = key || abbrev_exists key b | _ :: b -> abbrev_exists key b i*) let rec find_abbrev key biblio = match biblio with | [] -> raise Not_found | (Abbrev (s,_) as e) :: b -> if s = key then e else find_abbrev key b | _ :: b -> find_abbrev key b let concat_atom_lists a1 a2 = match (a1,a2) with | ([String s1], [String s2]) -> [String (s1 ^ s2)] | _ -> a1 @ a2 let abbrev_table = Hashtbl.create 97 let add_abbrev a l = Hashtbl.add abbrev_table a l let _ = List.iter (fun (a,l) -> add_abbrev a l) month_env let find_abbrev_in_table a = Hashtbl.find abbrev_table a let rec expand_list = function | [] -> [] | ((Id s) as a) :: rem -> begin try let v = find_abbrev_in_table s in concat_atom_lists v (expand_list rem) with Not_found -> concat_atom_lists [a] (expand_list rem) end | ((String _) as a) :: rem -> concat_atom_lists [a] (expand_list rem) let rec expand_fields = function | [] -> [] | (n,l) :: rem -> (n, expand_list l) :: (expand_fields rem) let rec expand_abbrevs biblio = fold (fun command accu -> match command with | Abbrev (a,l) -> let s = expand_list l in add_abbrev a s; accu | Entry (t,k,f) -> Entry (t,k,expand_fields f) :: accu | e -> e :: accu) biblio [] let add_crossref_fields = List.fold_left (fun acc ((x,_) as d) -> if List.mem_assoc x acc then acc else d::acc) let rec expand_crossrefs biblio = let crossref_table = Hashtbl.create 97 in let add_crossref a l = Hashtbl.add crossref_table (String.lowercase_ascii a) l in let find_crossref a = Hashtbl.find crossref_table (String.lowercase_ascii a) in let replace_crossref a l = Hashtbl.replace crossref_table (String.lowercase_ascii a) l in (* first phase: record needed crossrefs in table *) List.iter (fun command -> match command with | Entry (t,k,f) -> begin try match List.assoc "crossref" f with | [String(s)] -> add_crossref s [] | _ -> begin Format.eprintf "Warning: invalid cross-reference in entry '%s'.@." k; if !Options.warn_error then exit 2; end with Not_found -> (); end | _ -> ()) biblio; (* second phase: record crossrefs data in table *) List.iter (fun command -> match command with | Entry (t,k,f) -> begin try let _ = find_crossref k in if !Options.debug then Format.eprintf "recording cross-reference '%s'.@." k; replace_crossref k f with Not_found -> () end | _ -> ()) biblio; (* third phase: expand crossrefs *) fold (fun command accu -> match command with | Entry (t,k,f) -> begin try match List.assoc "crossref" f with | [String(s)] -> begin try let f = List.remove_assoc "crossref" f in let f' = find_crossref s in if f' = [] then begin Format.eprintf "Warning: cross-reference '%s' not found.@." s; if !Options.warn_error then exit 2; end; Entry (t,k,add_crossref_fields f f') :: accu with Not_found -> assert false end | _ -> command :: accu with Not_found -> command :: accu end | e -> e :: accu) biblio [] let sort comp bib = let comments,preambles,abbrevs,entries = List.fold_left (fun (c,p,a,e) command -> match command with | Comment _ -> (command::c,p,a,e) | Preamble _ -> (c,command::p,a,e) | Abbrev _ -> (c,p,command::a,e) | Entry _ -> (c,p,a,command::e)) ([],[],[],[]) bib in let sort_abbrevs = List.sort comp abbrevs and sort_entries = List.sort comp entries in List.rev_append sort_entries (List.rev_append sort_abbrevs (List.rev_append preambles (List.rev comments))) let current_key = ref "" bibtex2html-1.99/bibtex.mli 0000644 0002463 0000430 00000007727 13255132746 015236 0 ustar filliatr vals (**************************************************************************) (* bibtex2html - A BibTeX to HTML translator *) (* Copyright (C) 1997-2014 Jean-Christophe Filliâtre and Claude Marché *) (* *) (* This software is free software; you can redistribute it and/or *) (* modify it under the terms of the GNU General Public *) (* License version 2, as published by the Free Software Foundation. *) (* *) (* This software is distributed in the hope that it will be useful, *) (* but WITHOUT ANY WARRANTY; without even the implied warranty of *) (* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. *) (* *) (* See the GNU General Public License version 2 for more details *) (* (enclosed in the file GPL). *) (**************************************************************************) (*s A datatype for BibTeX bibliographies. *) type entry_type = string type key = string module KeySet : Set.S with type elt = key type atom = | Id of string | String of string type command = | Comment of string | Preamble of atom list | Abbrev of string * atom list | Entry of entry_type * key * (string * atom list) list type biblio (*s [empty_biblio] is an empty bibliography *) val empty_biblio : biblio (*s [add_new_entry k c b] adds an entry of key [k] and command [c] in biblio [b] and returns the new biblio. The entry [k] is supposed not to exists yet in [b]. *) val add_new_entry : command -> biblio -> biblio (*s [merge_biblios b1 b2] merges biblios [b1] and [b2]. Commands in the resulting biblio are the commands of b1, then the commands of b2, except for duplicates: any abbrev in [b2] that already exists in [b1] is ignored, and conversely every regular entries of [b1] which key exists also in [b2] is ignored. This behaviour is because abbrevs are supposed to be used by entries AFTER the definition of abbrevs, whereas regular entries are supposed to be used as crossrefs by entries BEFORE the definition of this entry. *) val merge_biblios : biblio -> biblio -> biblio (*s [find_entry k b] returns the first entry of key [k] in biblio [b]. Raises [Not_found] if no entry of this key exist. *) val find_entry : key -> biblio -> command (*s [size b] is the number of commands in [b] *) val size : biblio -> int (*s [fold f b accu] iterates [f] on the commands of [b], starting from [a]. If the commands of [b] are $c_1,\ldots,c_n$ in this order, then it computes $f ~ c_n ~ (f ~ c_{n-1} ~ \cdots ~ (f ~ c_1 ~ a)\cdots)$. *) val fold : (command -> 'a -> 'a) -> biblio -> 'a -> 'a (*s [abbrev_is_implicit k] is true when [k] is an integer or a month name. [abbrev_search k b] returns the first abbrev of key [k] in biblio [b], Raises [Not_found] if no abbrev of this key exist. *) val abbrev_is_implicit : key -> bool val find_abbrev : key -> biblio -> command (*s expansion of abbreviations. [expand_abbrevs bib] returns a new bibliography where all strings have been expanded *) val expand_abbrevs : biblio -> biblio val expand_crossrefs : biblio -> biblio (*s sorting bibliography As with the \texttt{bibsort} command of Nelson H. F. Beebe, comments are placed first, then preamble, then abbrevs, then regular entries. Within the last two categories, entries are sorted with respect to the comparison function given in argument. This function may be assumed called only on pairs of the form (Abbrev _,Abbrev _) or (Entry _, Entry _) Warning! it is up to you to provide a comparison function that will not place crossrefs before regular entries! *) val sort : (command -> command -> int) -> biblio -> biblio (* for parsing *) val current_key : string ref bibtex2html-1.99/bibtex_lexer.mll 0000644 0002463 0000430 00000010163 13255132746 016424 0 ustar filliatr vals (**************************************************************************) (* bibtex2html - A BibTeX to HTML translator *) (* Copyright (C) 1997-2014 Jean-Christophe Filliâtre and Claude Marché *) (* *) (* This software is free software; you can redistribute it and/or *) (* modify it under the terms of the GNU General Public *) (* License version 2, as published by the Free Software Foundation. *) (* *) (* This software is distributed in the hope that it will be useful, *) (* but WITHOUT ANY WARRANTY; without even the implied warranty of *) (* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. *) (* *) (* See the GNU General Public License version 2 for more details *) (* (enclosed in the file GPL). *) (**************************************************************************) (*i $Id: bibtex_lexer.mll,v 1.19 2010-02-22 07:38:19 filliatr Exp $ i*) (*s Lexer for BibTeX files. *) { open Lexing open Bibtex_parser let serious = ref false (* if we are inside a command or not *) let brace_depth = ref 0 (*s To buffer string literals *) let buffer = Buffer.create 8192 let reset_string_buffer () = Buffer.reset buffer let store_string_char c = Buffer.add_char buffer c let get_stored_string () = let s = Buffer.contents buffer in Buffer.reset buffer; s let start_delim = ref ' ' let check_delim d = match !start_delim, d with | '{', '}' | '(', ')' -> () | _ -> failwith "closing character does not match opening" } let space = [' ' '\t' '\r' '\n'] rule token = parse | space + { token lexbuf } | '@' space* ([^ ' ' '\t' '\n' '\r' '{' '(']+ as entry_type) space* (('{' | '(') as delim) space* { serious := true; start_delim := delim; match String.lowercase_ascii entry_type with | "string" -> Tabbrev | "comment" -> reset_string_buffer (); comment lexbuf; serious := false; Tcomment (get_stored_string ()) | "preamble" -> Tpreamble | et -> Tentry (entry_type, key lexbuf) } | '=' { if !serious then Tequal else token lexbuf } | '#' { if !serious then Tsharp else token lexbuf } | ',' { if !serious then Tcomma else token lexbuf } | '{' { if !serious then begin reset_string_buffer (); brace lexbuf; Tstring (get_stored_string ()) end else token lexbuf } | ('}' | ')') as d { if !serious then begin check_delim d; serious := false; Trbrace end else token lexbuf } | [^ ' ' '\t' '\n' '\r' '{' '}' '(' ')' '=' '#' ',' '"' '@']+ { if !serious then Tident (Lexing.lexeme lexbuf) else token lexbuf } | "\"" { if !serious then begin reset_string_buffer (); string lexbuf; Tstring (get_stored_string ()) end else token lexbuf } | eof { EOF } | _ { token lexbuf } and string = parse | '{' { store_string_char '{'; brace lexbuf; store_string_char '}'; string lexbuf } | '"' { () } | "\\\"" { store_string_char '\\'; store_string_char '"'; string lexbuf} | eof { failwith "unterminated string" } | _ { let c = Lexing.lexeme_char lexbuf 0 in store_string_char c; string lexbuf } and brace = parse | '{' { store_string_char '{'; brace lexbuf; store_string_char '}'; brace lexbuf } | '}' { () } | eof { failwith "unterminated string" } | _ { let c = Lexing.lexeme_char lexbuf 0 in store_string_char c; brace lexbuf } and key = parse | [^ ' ' '\t' '\n' '\r' ',']+ { lexeme lexbuf } | eof | _ { raise Parsing.Parse_error } and comment = parse | '{' { comment lexbuf; comment lexbuf } | [^ '}' '@'] as c { store_string_char c; comment lexbuf } | eof { () } | _ { () } bibtex2html-1.99/bibtex_parser.mly 0000644 0002463 0000430 00000006122 13255132746 016616 0 ustar filliatr vals /**************************************************************************/ /* bibtex2html - A BibTeX to HTML translator */ /* Copyright (C) 1997-2014 Jean-Christophe Filliâtre and Claude Marché */ /* */ /* This software is free software; you can redistribute it and/or */ /* modify it under the terms of the GNU General Public */ /* License version 2, as published by the Free Software Foundation. */ /* */ /* This software is distributed in the hope that it will be useful, */ /* but WITHOUT ANY WARRANTY; without even the implied warranty of */ /* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. */ /* */ /* See the GNU General Public License version 2 for more details */ /* (enclosed in the file GPL). */ /**************************************************************************/ /* * bibtex2html - A BibTeX to HTML translator * Copyright (C) 1997 Jean-Christophe FILLIATRE * * This software is free software; you can redistribute it and/or * modify it under the terms of the GNU General Public * License version 2, as published by the Free Software Foundation. * * This software is distributed in the hope that it will be useful, * but WITHOUT ANY WARRANTY; without even the implied warranty of * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. * * See the GNU General Public License version 2 for more details * (enclosed in the file GPL). */ /*i $Id: bibtex_parser.mly,v 1.15 2010-02-22 07:38:19 filliatr Exp $ i*/ /*s Parser for BibTeX files. */ %{ open Bibtex %} %token
"]; def "\\end{alltt}" [Print ""]; def "\\textbf" [Print "" ; Print_arg ; Print ""]; def "\\mathbf" [Print "" ; Print_arg ; Print ""]; def "\\texttt" [Print "" ; Print_arg ; Print ""]; def "\\mathtt" [Print "" ; Print_arg ; Print ""]; def "\\textit" [Print "" ; Print_arg ; Print ""]; def "\\mathit" [Print "" ; Print_arg ; Print ""]; def "\\textsl" [Print "" ; Print_arg ; Print ""]; def "\\textem" [Print "" ; Print_arg ; Print ""]; def "\\textrm" [Print_arg]; def "\\mathrm" [Print_arg]; def "\\textmd" [Print_arg]; def "\\textup" [Print_arg]; def "\\textnormal" [Print_arg]; def "\\mathnormal" [Print "" ; Print_arg ; Print ""]; def "\\mathcal" [Print_arg]; def "\\mathbb" [Print_arg]; def "\\mathfrak" [Print_arg]; def "\\textin" [Print ""; Print_arg; Print ""]; def "\\textsu" [Print ""; Print_arg; Print ""]; def "\\textsuperscript" [Print ""; Print_arg; Print ""]; def "\\textsi" [Print "" ; Print_arg ; Print ""]; (* Basic color support. *) def "\\textcolor" [ Parameterized (function name -> match String.lowercase_ascii name with (* At the moment, we support only the 16 named colors defined in HTML 4.01. *) | "black" | "silver" | "gray" | "white" | "maroon" | "red" | "purple" | "fuchsia" | "green" | "lime" | "olive" | "yellow" | "navy" | "blue" | "teal" | "aqua" -> [ Print (Printf.sprintf "" name); Print_arg ; Print "" ] (* Other, unknown colors have no effect. *) | _ -> [ Print_arg ] )]; (* Fonts without HTML equivalent *) def "\\textsf" [Print "" ; Print_arg ; Print ""]; def "\\mathsf" [Print "" ; Print_arg ; Print ""]; def "\\textsc" [Print_arg]; def "\\textln" [Print_arg]; def "\\textos" [Print_arg]; def "\\textdf" [Print_arg]; def "\\textsw" [Print_arg]; def "\\rm" []; def "\\cal" []; def "\\emph" [Print "" ; Print_arg ; Print ""]; def "\\mbox" [Print_arg]; def "\\footnotesize" []; def "\\etalchar" [ Print "" ; Raw_arg print_s ; Print "" ]; def "\\newblock" [Print " "]; (* Environments *) def "\\begin{itemize}" [Print "
"]; def "\\end{center}" [Print ""]; def "\\begin{htmlonly}" []; def "\\end{htmlonly}" []; def "\\begin{flushleft}" [Print "
"]; def "\\end{flushleft}" [Print ""]; (* Special characters *) def "\\ " [Print " "]; def "\\\n" [Print " "]; def "\\{" [Print "{"]; def "\\}" [Print "}"]; def "\\l" [Print "l"]; def "\\L" [Print "L"]; def "\\oe" [Print "œ"]; def "\\OE" [Print "Œ"]; def "\\o" [Print "ø"]; def "\\O" [Print "Ø"]; def "\\ae" [Print "æ"]; def "\\AE" [Print "Æ"]; def "\\aa" [Print "å"]; def "\\AA" [Print "Å"]; def "\\i" [Print "i"]; def "\\j" [Print "j"]; def "\\&" [Print "&"]; def "\\$" [Print "$"]; def "\\%" [Print "%"]; def "\\_" [Print "_"]; def "\\slash" [Print "/"]; def "\\copyright" [Print "(c)"]; def "\\th" [Print "þ"]; def "\\TH" [Print "Þ"]; def "\\dh" [Print "ð"]; def "\\DH" [Print "Ð"]; def "\\dj" [Print "đ"]; def "\\DJ" [Print "Đ"]; def "\\ss" [Print "ß"]; def "\\rq" [Print "’"]; def "\\'" [Raw_arg(function "e" -> print_s "é" | "E" -> print_s "É" | "a" -> print_s "á" | "A" -> print_s "Á" | "o" -> print_s "ó" | "O" -> print_s "Ó" | "i" -> print_s "í" | "\\i" -> print_s "í" | "I" -> print_s "Í" | "u" -> print_s "ú" | "U" -> print_s "Ú" | "'" -> print_s "”" | "c" -> print_s "ć" | "C" -> print_s "Ć" | "g" -> print_s "ǵ" | "G" -> print_s "G" | "l" -> print_s "ĺ" | "L" -> print_s "Ĺ" | "n" -> print_s "ń" | "N" -> print_s "Ń" | "r" -> print_s "ŕ" | "R" -> print_s "Ŕ" | "s" -> print_s "ś" | "S" -> print_s "Ś" | "y" -> print_s "ý" | "Y" -> print_s "Ý" | "z" -> print_s "Ź" | "Z" -> print_s "ź" | "" -> print_c '\'' | s -> print_s s)]; def "\\`" [Raw_arg(function "e" -> print_s "è" | "E" -> print_s "È" | "a" -> print_s "à" | "A" -> print_s "À" | "o" -> print_s "ò" | "O" -> print_s "Ò" | "i" -> print_s "ì" | "\\i" -> print_s "ì" | "I" -> print_s "Ì" | "u" -> print_s "ù" | "U" -> print_s "Ù" | "`" -> print_s "“" | "" -> print_s "‘" | s -> print_s s)]; def "\\~" [Raw_arg(function "n" -> print_s "ñ" | "N" -> print_s "Ñ" | "o" -> print_s "õ" | "O" -> print_s "Õ" | "i" -> print_s "ĩ" | "\\i" -> print_s "ĩ" | "I" -> print_s "Ĩ" | "a" -> print_s "ã" | "A" -> print_s "Ã" | "u" -> print_s "©" | "U" -> print_s "¨" | "" -> print_s "˜" | s -> print_s s)]; def "\\k" [Raw_arg(function "A" -> print_s "Ą" | "a" -> print_s "ą" | "i" -> print_s "Į" | "I" -> print_s "į" | s -> print_s s)]; def "\\c" [Raw_arg(function "c" -> print_s "ç" | "C" -> print_s "Ç" | s -> print_s s)]; def "\\^" [Raw_arg(function "a" -> print_s "â" | "A" -> print_s "Â" | "e" -> print_s "ê" | "E" -> print_s "Ê" | "i" -> print_s "î" | "\\i" -> print_s "î" | "I" -> print_s "Î" | "o" -> print_s "ô" | "O" -> print_s "Ô" | "u" -> print_s "û" | "U" -> print_s "Û" | "w" -> print_s "ŵ" | "W" -> print_s "Ŵ" | "y" -> print_s "ŷ" | "Y" -> print_s "Ŷ" | "" -> print_c '^' | s -> print_s s)]; def "\\hat" [Raw_arg(function "a" -> print_s "â" | "A" -> print_s "Â" | "e" -> print_s "ê" | "E" -> print_s "Ê" | "i" -> print_s "î" | "\\i" -> print_s "î" | "I" -> print_s "Î" | "o" -> print_s "ô" | "O" -> print_s "Ô" | "u" -> print_s "û" | "U" -> print_s "Û" | "" -> print_c '^' | s -> print_s s)]; def "\\\"" [Raw_arg(function "e" -> print_s "ë" | "E" -> print_s "Ë" | "a" -> print_s "ä" | "A" -> print_s "Ä" | "\\i" -> print_s "ï" | "i" -> print_s "ï" | "I" -> print_s "Ï" | "o" -> print_s "ö" | "O" -> print_s "Ö" | "u" -> print_s "ü" | "U" -> print_s "Ü" | "y" -> print_s "ÿ" | "Y" -> print_s "Ÿ" | s -> print_s s)]; def "\\d" [Raw_arg print_s ]; def "\\." [Raw_arg (function "a" -> print_s "ȧ" | "A" -> print_s "Ȧ" | "c" -> print_s "ċ" | "C" -> print_s "Ċ" | "e" -> print_s "ė" | "E" -> print_s "Ė" | "g" -> print_s "ġ" | "G" -> print_s "Ġ" | "i" -> print_s "i" | "\\i" -> print_s "i" | "I" -> print_s "İ" | "o" -> print_s "ȯ" | "O" -> print_s "Ȯ" | "z" -> print_s "ż" | "Z" -> print_s "Ż" | s -> print_s s)]; def "\\u" [Raw_arg(function "a" -> print_s "ă" | "A" -> print_s "Ă" | "e" -> print_s "ĕ" | "E" -> print_s "Ĕ" | "i" -> print_s "Ĭ" | "\\i" -> print_s "Ĭ" | "I" -> print_s "ĭ" | "g" -> print_s "ğ" | "G" -> print_s "Ğ" | "o" -> print_s "ŏ" | "O" -> print_s "Ŏ" | "u" -> print_s "ŭ" | "U" -> print_s "Ŭ" | s -> print_s s)]; def "\\v" [Raw_arg(function | "C" -> print_s "Č" | "c" -> print_s "č" | "D" -> print_s "Ď" | "d" -> print_s "ď" | "E" -> print_s "Ě" | "e" -> print_s "ě" | "N" -> print_s "Ň" | "n" -> print_s "ň" | "r" -> print_s "ř" | "R" -> print_s "Ř" | "s" -> print_s "š" (*"š"*) | "S" -> print_s "Š" (*"Š"*) | "T" -> print_s "Ť" | "t" -> print_s "ť" | "\\i" -> print_s "ĭ" | "i" -> print_s "ĭ" | "I" -> print_s "Ĭ" | "Z" -> print_s "Ž" | "z" -> print_s "ž" | s -> print_s s)]; def "\\H" [Raw_arg (function | "O" -> print_s "Ő" | "o" -> print_s "ő" | "U" -> print_s "Ű" | "u" -> print_s "ű" | s -> print_s s)]; def "\\r" [Raw_arg (function | "U" -> print_s "Ů" | "u" -> print_s "ů" | s -> print_s s)]; (* Math macros *) def "\\[" [Print "
"]; def "\\]" [Print "\n"]; def "\\le" [Print "<="]; def "\\leq" [Print "<="]; def "\\log" [Print "log"]; def "\\ge" [Print ">="]; def "\\geq" [Print ">="]; def "\\neq" [Print "<>"]; def "\\circ" [Print "o"]; def "\\bigcirc" [Print "O"]; def "\\sim" [Print "~"]; def "\\(" [Print ""]; def "\\)" [Print ""]; def "\\mapsto" [Print "|->"]; def "\\times" [Print "×"]; def "\\neg" [Print "¬"]; def "\\frac" [Print "("; Print_arg; Print ")/("; Print_arg; Print ")"]; def "\\not" [Print "not "]; (* Math symbols printed as texts (could we do better?) *) def "\\ne" [Print "=/="]; def "\\in" [Print "in"]; def "\\forall" [Print "for all"]; def "\\exists" [Print "there exists"]; def "\\vdash" [Print "|-"]; def "\\ln" [Print "ln"]; def "\\gcd" [Print "gcd"]; def "\\min" [Print "min"]; def "\\max" [Print "max"]; def "\\exp" [Print "exp"]; def "\\rightarrow" [Print "->"]; def "\\to" [Print "->"]; def "\\longrightarrow" [Print "-->"]; def "\\Rightarrow" [Print "=>"]; def "\\leftarrow" [Print "<-"]; def "\\longleftarrow" [Print "<--"]; def "\\Leftarrow" [Print "<="]; def "\\leftrightarrow" [Print "<->"]; def "\\sqrt" [Print "sqrt("; Print_arg; Print ")"]; def "\\vee" [Print "V"]; def "\\lor" [Print "V"]; def "\\wedge" [Print "/\\"]; def "\\land" [Print "/\\"]; def "\\Vert" [Print "||"]; def "\\parallel" [Print "||"]; def "\\mid" [Print "|"]; def "\\cup" [Print "U"]; def "\\inf" [Print "inf"]; (* Misc. macros. *) def "\\TeX" [Print "TEX"]; def "\\LaTeX" [Print "LATEX"]; def "\\LaTeXe" [Print "LATEX 2e"]; def "\\tm" [Print "TM"]; def "\\par" [Print "
"];
def "\\@" [Print " "];
def "\\#" [Print "#"];
def "\\/" [];
def "\\-" [];
def "\\left" [];
def "\\right" [];
def "\\smallskip" [];
def "\\medskip" [];
def "\\bigskip" [];
def "\\relax" [];
def "\\markboth" [Skip_arg; Skip_arg];
def "\\dots" [Print "..."];
def "\\dot" [Print "."];
def "\\simeq" [Print "˜="];
def "\\approx" [Print "˜"];
def "\\^circ" [Print "°"];
def "\\ldots" [Print "..."];
def "\\cdot" [Print "·"];
def "\\cdots" [Print "..."];
def "\\newpage" [];
def "\\hbox" [Print_arg];
def "\\noindent" [];
def "\\label" [Print ""];
def "\\ref" [Print "(ref)"];
def "\\index" [Skip_arg];
def "\\\\" [Print "
"];
def "\\," [];
def "\\;" [];
def "\\!" [];
def "\\hspace" [Skip_arg; Print " "];
def "\\symbol"
[Raw_arg (function s ->
try let n = int_of_string s in print_c (Char.chr n)
with _ -> ())];
def "\\html" [Raw_arg print_s];
def "\\textcopyright" [Print "©"];
def "\\textordfeminine" [Print "ª"];
def "\\textordmasculine" [Print "º"];
def "\\backslash" [Print "\"];
(* hyperref *)
def "\\href"
[Print ""; Print_arg; Print ""];
(* Bibliography *)
def "\\begin{thebibliography}" [Print "
\n"; main lexbuf } (* Font changes *) | "{\\it" " "* | "{\\itshape" " "* { print_s ""; save_state main lexbuf; print_s ""; main lexbuf } | "{\\em" " "* | "{\\sl" " "* | "{\\slshape" " "* { print_s ""; save_state main lexbuf; print_s ""; main lexbuf } | "{\\bf" " "* | "{\\sf" " "* | "{\\bfseries" " "* | "{\\sffamily" " "* { print_s ""; save_state main lexbuf; print_s ""; main lexbuf } | "{\\sc" " "* | "{\\scshape" " "* | "{\\normalfont" " "* | "{\\upshape" " "* | "{\\mdseries" " "* | "{\\rmfamily" " "* { save_state main lexbuf; main lexbuf } | "{\\tt" " "* | "{\\ttfamily" " "* { print_s ""; save_state main lexbuf; print_s ""; main lexbuf } | "{\\small" " "* { print_s ""; save_state main lexbuf; print_s ""; main lexbuf } | "{\\rm" " "* { print_s ""; save_state main lexbuf; print_s ""; main lexbuf } | "{\\cal" " "* { save_state main lexbuf; main lexbuf } | "\\cal" " "* { main lexbuf } (* Double quotes *) (*** | '"' { print_s ""; indoublequote lexbuf; print_s ""; main lexbuf } ***) (* Verb, verbatim *) | ("\\verb" | "\\path") _ { verb_delim := Lexing.lexeme_char lexbuf 5; print_s ""; inverb lexbuf; print_s ""; main lexbuf } | "\\begin{verbatim}" { print_s "
"; inverbatim lexbuf; print_s ""; main lexbuf } (* Raw html, latex only *) | "\\begin{rawhtml}" { rawhtml lexbuf; main lexbuf } | "\\begin{latexonly}" { latexonly lexbuf; main lexbuf } (* Itemize and similar environments *) | "\\item[" [^ ']']* "]" { print_s "
"; MathDisplay | MathNoDisplay -> MathNoDisplay | MathDisplay -> print_s "\n"; MathNone end; main lexbuf } (* \hkip *) | "\\hskip" space* dimension (space* "plus" space* dimension)? (space* "minus" space* dimension)? { print_s " "; main lexbuf } (* Special characters *) | "\\char" ['0'-'9']+ { let lxm = Lexing.lexeme lexbuf in let code = String.sub lxm 5 (String.length lxm - 5) in print_c(Char.chr(int_of_string code)); main lexbuf } | "<" { print_s "<"; main lexbuf } | ">" { print_s ">"; main lexbuf } | "~" { print_s " "; main lexbuf } | "``" { print_s "“"; main lexbuf } | "''" { print_s "”"; main lexbuf } | "--" { exec_macro ~main ~print_arg ~raw_arg ~skip_arg lexbuf "--"; main lexbuf } | "---" { exec_macro ~main ~print_arg ~raw_arg ~skip_arg lexbuf "---"; main lexbuf } | "^" { if is_math_mode() then begin let buf = Lexing.from_string (raw_arg lexbuf) in print_s ""; save_state main buf; print_s"" end else print_s "^"; main lexbuf } | "_" { if is_math_mode() then begin let buf = Lexing.from_string (raw_arg lexbuf) in print_s ""; save_state main buf; print_s"" end else print_s "_"; main lexbuf } (* URLs *) | "\\url" { let url = raw_arg lexbuf in if !hevea_url then let text = raw_arg lexbuf in print_hevea_url url text else print_latex_url url; main lexbuf } | "\\" " " { print_s " "; main lexbuf } (* General case for environments and commands *) | ("\\begin{" | "\\end{") ['A'-'Z' 'a'-'z' '@']+ "}" | "\\" (['A'-'Z' 'a'-'z' '@']+ '*'? " "? | [^ 'A'-'Z' 'a'-'z']) { let m = chop_last_space (Lexing.lexeme lexbuf) in exec_macro ~main ~print_arg ~raw_arg ~skip_arg lexbuf m; main lexbuf } (* Nesting of braces *) | '{' { incr brace_nesting; main lexbuf } | '}' { if !brace_nesting <= 0 then () else begin decr brace_nesting; main lexbuf end } (* Default rule for other characters *) | eof { () } | ['A'-'Z' 'a'-'z']+ { if is_math_mode() then print_s ""; print_s(Lexing.lexeme lexbuf); if is_math_mode() then print_s ""; main lexbuf } | _ { print_c(Lexing.lexeme_char lexbuf 0); main lexbuf } and indoublequote = parse '"' { () } | "<" { print_s "<"; indoublequote lexbuf } | ">" { print_s ">"; indoublequote lexbuf } | "&" { print_s "&"; indoublequote lexbuf } | "\\\"" { print_s "\""; indoublequote lexbuf } | "\\\\" { print_s "\\"; indoublequote lexbuf } | eof { () } | _ { print_c(Lexing.lexeme_char lexbuf 0); indoublequote lexbuf } and inverb = parse "<" { print_s "<"; inverb lexbuf } | ">" { print_s ">"; inverb lexbuf } | "&" { print_s "&"; inverb lexbuf } | eof { () } | _ { let c = Lexing.lexeme_char lexbuf 0 in if c == !verb_delim then () else (print_c c; inverb lexbuf) } and inverbatim = parse "<" { print_s "<"; inverbatim lexbuf } | ">" { print_s ">"; inverbatim lexbuf } | "&" { print_s "&"; inverbatim lexbuf } | "\\end{verbatim}" { () } | eof { () } | _ { print_c(Lexing.lexeme_char lexbuf 0); inverbatim lexbuf } and rawhtml = parse "\\end{rawhtml}" { () } | eof { () } | _ { print_c(Lexing.lexeme_char lexbuf 0); rawhtml lexbuf } and latexonly = parse "\\end{latexonly}" { () } | eof { () } | _ { latexonly lexbuf } and print_arg = parse "{" { save_nesting main lexbuf } | "[" { skip_optional_arg lexbuf; print_arg lexbuf } | " " { print_arg lexbuf } | eof { () } | _ { print_c(Lexing.lexeme_char lexbuf 0); main lexbuf } and skip_arg = parse "{" { incr brace_nesting; skip_arg lexbuf } | "}" { decr brace_nesting; if !brace_nesting > 0 then skip_arg lexbuf } | "[" { if !brace_nesting = 0 then skip_optional_arg lexbuf; skip_arg lexbuf } | " " { skip_arg lexbuf } | eof { () } | _ { if !brace_nesting > 0 then skip_arg lexbuf } and raw_arg = parse | " " | "\n" { raw_arg lexbuf } | '{' { nested_arg lexbuf } | "[" { skip_optional_arg lexbuf; raw_arg lexbuf } | '\\' ['A'-'Z' 'a'-'z']+ { Lexing.lexeme lexbuf } | eof { "" } | _ { Lexing.lexeme lexbuf } and nested_arg = parse '}' { "" } | '{' { let l = nested_arg lexbuf in "{" ^ l ^ "}" ^ (nested_arg lexbuf) } | eof { "" } | [^ '{' '}']+{ let x = Lexing.lexeme lexbuf in x ^ (nested_arg lexbuf) } and skip_optional_arg = parse "]" { () } | eof { () } | _ { skip_optional_arg lexbuf } (* ajout personnel: [read_macros] pour lire les macros (La)TeX *) and read_macros = parse | "\\def" ('\\' ['a'-'z' 'A'-'Z' '@']+ as s) ("#" (['0'-'9']+ as n))? { let b = raw_arg lexbuf in def_macro s n b; read_macros lexbuf } | "\\newcommand" space* "{" ("\\" ['a'-'z' 'A'-'Z']+ as s) "}" ("[" (['0'-'9']+ as n) "]")? { let b = raw_arg lexbuf in def_macro s n b; read_macros lexbuf } | "\\let" ('\\' ['a'-'z' 'A'-'Z' '@']+ as s) '=' { let b = raw_arg lexbuf in def_macro s None b; read_macros lexbuf } | eof { () } | _ { read_macros lexbuf } bibtex2html-1.99/main.ml 0000644 0002463 0000430 00000047467 13255132746 014541 0 ustar filliatr vals (**************************************************************************) (* bibtex2html - A BibTeX to HTML translator *) (* Copyright (C) 1997-2014 Jean-Christophe Filliâtre and Claude Marché *) (* *) (* This software is free software; you can redistribute it and/or *) (* modify it under the terms of the GNU General Public *) (* License version 2, as published by the Free Software Foundation. *) (* *) (* This software is distributed in the hope that it will be useful, *) (* but WITHOUT ANY WARRANTY; without even the implied warranty of *) (* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. *) (* *) (* See the GNU General Public License version 2 for more details *) (* (enclosed in the file GPL). *) (**************************************************************************) (*s Main module of bibtex2html. *) open Printf open Translate (* Options. *) let excluded = ref ([] : string list) let add_exclude k = excluded := k :: !excluded let style = ref "plain" let command = ref "bibtex -min-crossrefs=1000" type sort = Unsorted | By_date | By_author let sort = ref Unsorted let reverse_sort = ref false let ignore_bibtex_errors = ref false let expand_abbrev_in_bib_output = ref true (* Optional citation file. *) let use_cite_file = ref false let citations = ref ([] : string list) let add_citations file = try let chan = open_in file and buf = Buffer.create 1024 in try while true do Buffer.add_char buf (input_char chan) done with End_of_file -> close_in chan; citations := (Str.split (Str.regexp "[ \t\n]+") (Buffer.contents buf)) @ !citations with Sys_error msg -> prerr_endline ("Cannot open citation file (" ^ msg ^ ")"); exit 1 (*s Sorting the entries. *) module KeyMap = Map.Make(struct type t = string let compare = compare end) let keep_combine combine l1 l2 = let map = List.fold_left (fun m ((_,k,_) as e) -> KeyMap.add k e m) KeyMap.empty l2 in let rec keep_rec = function | [] -> [] | ((_,k,_) as x)::rem -> if not (List.mem k !excluded) then try let y = KeyMap.find k map in (combine x y) :: (keep_rec rem) with Not_found -> keep_rec rem else keep_rec rem in keep_rec l1 let combine_f (c,_,b) e = c,b,e let rev_combine_f x y = combine_f y x let sort_entries entries bibitems = if not !Options.quiet then begin eprintf "Sorting..."; flush stderr end; let el = if !sort = By_author then keep_combine combine_f bibitems entries else keep_combine rev_combine_f entries bibitems in let sl = if !sort = By_date then List.sort (fun (_,_,e1) (_,_,e2) -> Expand.date_compare entries e1 e2) el else el in if not !Options.quiet then begin eprintf "ok.\n"; flush stderr end; if !reverse_sort then List.rev sl else sl (* We use BibTeX itself to format the entries. Operations: \begin{enumerate} \item create an auxiliary file tmp.aux \item call bibtex on it \item read the resulting tmp.bbl file to get the formatted entries \end{enumerate} *) let create_aux_file fbib tmp = let ch = open_out (tmp ^ ".aux") in output_string ch "\\relax\n\\bibstyle{"; output_string ch !style; output_string ch "}\n"; if !use_cite_file then List.iter (fun k -> output_string ch ("\\citation{" ^ k ^ "}\n")) !citations else output_string ch "\\citation{*}\n"; output_string ch "\\bibdata{"; output_string ch (Filename.chop_suffix fbib ".bib"); output_string ch "}\n"; close_out ch let rm f = try Sys.remove f with _ -> () let clean tmp = if not !Options.debug then begin rm (tmp ^ ".aux"); rm (tmp ^ ".blg"); rm (tmp ^ ".bbl"); rm tmp end let call_bibtex tmp = if not !Options.quiet then begin eprintf "calling BibTeX..."; flush stderr end; match let redir = if !output_file = "" || !Options.quiet then match Sys.os_type with | "Win32" -> "> nul 2>&1" | _ -> "> /dev/null 2>&1" else "" in let cmd = sprintf "%s %s %s" !command tmp redir in if !Options.debug then begin eprintf "\nbibtex command: %s\n" cmd; flush stderr end; Sys.command cmd with | 0 -> if not !Options.quiet then begin eprintf "\n"; flush stderr end | n -> if !ignore_bibtex_errors then begin if not !Options.quiet then begin eprintf "error %d (ignored)\n" n; flush stderr end end else begin eprintf "error %d while running bibtex\n" n; exit n end let read_one_biblio lb = let rec read_items acc lb = try let (_,k,_) as item = Bbl_lexer.bibitem lb in if !Options.debug then begin eprintf "[%s]" k; flush stderr end; read_items (item::acc) lb with Bbl_lexer.End_of_biblio -> List.rev acc in let name = Bbl_lexer.biblio_header lb in let items = read_items [] lb in (name,items) let read_biblios lb = let rec read acc lb = try let b = read_one_biblio lb in read (b::acc) lb with End_of_file -> List.rev acc in read [] lb let read_bbl tmp = let fbbl = tmp ^ ".bbl" in if not !Options.quiet then begin eprintf "Reading %s..." fbbl; flush stderr end; let ch = open_in fbbl in let lexbuf = Lexing.from_channel ch in let biblios = read_biblios lexbuf in close_in ch; clean tmp; if not !Options.quiet then begin eprintf "ok "; List.iter (fun (_,items) -> eprintf "(%d entries)" (List.length items)) biblios; eprintf "\n"; flush stderr end; biblios (* temporary files in current directory (from OCaml's standard library) *) module Tmp = struct external open_desc: string -> open_flag list -> int -> int = "caml_sys_open" external close_desc: int -> unit = "caml_sys_close" let prng = Random.State.make_self_init () let temp_file prefix suffix = let rec try_name counter = let rnd = (Random.State.bits prng) land 0xFFFFFF in let name = Printf.sprintf "%s%06x%s" prefix rnd suffix in try close_desc (open_desc name [Open_wronly; Open_creat; Open_excl] 0o600); name with Sys_error _ as e -> if counter >= 1000 then raise e else try_name (counter + 1) in try_name 0 end let get_biblios fbib = let tmp = Tmp.temp_file "bib2html" "" in try create_aux_file fbib tmp; call_bibtex tmp; read_bbl tmp with e -> clean tmp; raise e (*i let insert_title_url bib = let rec remove_assoc x = function | [] -> raise Not_found | ((y,v) as p) :: l -> if x = y then (v,l) else let (v',l') = remove_assoc x l in (v', p :: l') in let url_value = function | [Bibtex.Id u] -> u | [Bibtex.String u] -> u | _ -> raise Not_found in let modify_entry f = try let t,f' = remove_assoc "title" f in let u,f'' = remove_assoc "url" f' in let u' = Html.normalize_url (url_value u) in let nt = (Bibtex.String (sprintf "\\begin{rawhtml}\\end{rawhtml}" u')) :: t @ [Bibtex.String "\\begin{rawhtml}\\end{rawhtml}"] in ("TITLE",nt) :: f'' with Not_found -> f in Bibtex.fold (fun com bib' -> match com with | Bibtex.Entry (ty,k,f) -> Bibtex.add_new_entry (Bibtex.Entry (ty,k,modify_entry f)) bib' | _ -> Bibtex.add_new_entry com bib') bib Bibtex.empty_biblio i*) let parse_only = ref false let print_keys = ref false let translate fullname = let input_bib = Readbib.read_entries_from_file fullname in if !parse_only then exit 0; let entries = List.rev (Expand.expand input_bib) in let biblios = if fullname = "" then begin let tmp = Tmp.temp_file "bibtex2htmlinput" ".bib" in let ch = open_out tmp in Biboutput.output_bib ~html:false ch input_bib None; close_out ch; let bbl = get_biblios tmp in Sys.remove tmp; bbl end else get_biblios fullname in let sb = List.map (fun (name,bibitems) -> (name,sort_entries entries bibitems)) biblios in if !print_keys then begin List.iter (fun (_,bibitems) -> List.iter (fun (_,_,(_,k,_)) -> printf "%s\n" k) bibitems) sb; flush stdout; exit 0 end; format_list (if !expand_abbrev_in_bib_output then Bibtex.expand_abbrevs input_bib else input_bib) sb (if !use_cite_file then let keys = List.fold_right (fun s e -> Bibtex.KeySet.add s e) !citations Bibtex.KeySet.empty in let keys = List.fold_right (fun s e -> Bibtex.KeySet.remove s e) !excluded keys in Some (Bibfilter.saturate input_bib keys) else None) (*s Reading macros in a file. *) let read_macros f = let chan = open_in f in let lb = Lexing.from_channel chan in Latexscan.read_macros lb; close_in chan (*s Command line parsing. *) let usage ?(error=true) () = if error then prerr_endline "bibtex2html: bad command line syntax"; (if error then prerr_endline else print_endline) " Usage: bibtex2html
no more enclosed in; bibtex fields now typeset in lowercase; added links back to f.html o macros \textin (), \textsu (), \textsi (), and macros \textln, \textos, \textdf, \textsw without translation o fixed bug in --quiet under Windows o option -t now sets the title of f_bib.html too (and of entries files when used with -multiple) Version 1.84, 19/10/2006 ======================== o improved support for MRNUMBER of AMS styles: only first word used in URL link Version 1.83, 13/09/2006 ======================== o support for DOI links: a field "DOI = {xxx}" will be recognized, if any, and a link to http://dx.doi.org/xxx will be displayed; option -no-doi turns it off and option -doi-prefix
sets a different prefix for the DOI urls o macro \H (Hungarian umlauts) o new option -linebreak to insert a linebreak between an entry and its links o new option -use-table to enforce the use of a table (to be used _after_ -no-keys if needed) Version 1.82, 07/06/2006 ======================== o `` and '' translated to “ and ” o aesthetic changes: - no more line break between the entry and the links; - more space between an abstract and the next entry o improving date parsing: month field such as "2~" # dec is now parsed o fixed bug: a space after a macro is now discarded Version 1.81, 12/05/2006 ======================== o new option --print-keys to display the sorted keys (and exit) o improved date sorting to handle months such as mar # "\slash " # apr o no table anymore with -nokeys (only HTML paragraphs) Version 1.80, 15/3/2006 ======================= o remove leading ./ in front of relative URLs (was introduced a long time ago to circumvent an Internet Explorer bug; see below) o no more escaping of the character & in URLs Version 1.79, 22/2/2006 ======================= o fixed bug with ISO-latin characters in bib2bib conditions o fixed bug with implicit abbrevs (jan, feb, etc.) Version 1.78, 16/12/2005 Version 1.77, 18/11/2005 ======================== o fixed bug with unbalanced brackets in bib2bib/bibtex2html output Version 1.76, 22/9/2005 ======================= o translation of \'c o replaced ISO latin 1 characters with their entity codes o support for Czech characters (both contributed by Danny Chrastina) Version 1.75, 2/2/2005 ====================== o updated manual (the manual was not reflecting the change of f-bib into f_bib in version 1.74; see below) Version 1.74, 22/10/2004 ======================== o bib2bib: special characters \n \r \t and \ddd in regular expressions o fix minor bug: when looking for cross-references, comparison of keys is now case-insensitive o footer and bibtex entries now enclosed in HTML paragraphs ( ...
) o in case of syntax error, the key of the entry where the error occurred is shown o new option -no-links to disable weblinks o fix bug in bib2bib: preamble now enclosed with a single pair of braces o bibtex entries now in f_bib.html (instead of f-bib.html) Version 1.72, 3/9/2004 ====================== o --help now prints on standard output and exits successfully o fixed bug with very long keys (when bibtex inserts % to cut lines) o arguments to macros read from a file (option -m) are discarded Version 1.71, 24/8/2004 ======================= o improved date sorting algorithm to handle days (e.g. month = "June 29") o bib2bib: crossrefs are expanded before conditions are checked o bib2bib: '_' allowed in field identifiers o added option -w (--warn-error) to stop immediately when a warning is issued. Version 1.70, 30/6/2004 ======================= o fixed bug with crossrefs not translated from LaTeX to HTML o macros for Greek letters now translated to HTML entities Version 1.69, 6/4/2004 ====================== o macros \bysame, \MR and \MRhref for AMS* stylew o modified -bib.html output to circumvent a Konqueror bug Version 1.68, 16/03/2004 ======================== o fixed bug with parentheses-enclosed entries o macros \relax, \hskip Version 1.66, 18/02/2004 ======================== o characters ( and ) in keys o New FAQ: pb with quotes under MS Windows Version 1.65, 3/10/2003 ======================== o better handling of accented letters, in particular LaTeX commands for accents are taken into account in regular expressions. o fixed bug: keywords were duplicated with -single o web links automatically inserted for -f and -nf fields in the .bib file o new option -use-keys to use the original keys from the .bib file o new option -single to put everything into a single page o HTML links inserted in the BibTeX entries page Version 1.61, 15/7/2003 ======================= o quoted & in URLS (&) o macro \href o bib2bib does not stop anymore when no matching citation is found, and in such a case an empty file is generated. Version 1.60, 19/6/2003 ======================= o new bib2bib option -s to sort the bibliography (and -r to reverse the sort) o macros \cal, \small Version 1.59, 16/6/2003 ======================= o LaTeX '~' translated into o field "postscript" treated as "ps" o fixed links when -o used with a full path o fixed behavior with -nf abstract ... o macro \$ Version 1.57, 9/4/2003 ====================== o option --note f to declare field f as an annotation (and then displayed like an "abstract" field) Version 1.56 12/11/2002 ======================= o bib2bib: fixed bug in conditions lexer o fixed parser error in @preamble o ./configure updated Version 1.54 10/7/2002 ====================== o option --no-header to suppress bibtex2html command in the HTML output o HTML output: tags in lowercase, quoted attributes,
->
o fixed bug in Makefile.in (man pages installation) Version 1.53 18/6/2002 ====================== o keywords displayed if a field "keywords" is present; option --no-keywords o aux2bib now handles multiple citations (\citation{foo,bar,gee}) (patch by Jose Ramon Alvarez Sanchez) Version 1.52 15/01/2002 ======================= o fixed bug in evaluation of <> operator in bib2bib conditions o fixed bugs in URLs display o new tool aux2bib by Ralf Treinen o removed when option -css is used o added macro \frac o added .txt and .html as recognized file extensions Version 1.51 15/10/2001 ======================= o fixed bug in links to not compressed documents; nicer names for links o fixed bug in --quiet o option -dl to format entries withinstead of