Note small bug in cocanwiki_links.
[cocanwiki.git] / scripts / wikilib.ml
1 (* COCANWIKI - a wiki written in Objective CAML.
2  * Written by Richard W.M. Jones <rich@merjis.com>.
3  * Copyright (C) 2004 Merjis Ltd.
4  * $Id: wikilib.ml,v 1.15 2004/10/17 17:29:48 rich Exp $
5  *
6  * This program is free software; you can redistribute it and/or modify
7  * it under the terms of the GNU General Public License as published by
8  * the Free Software Foundation; either version 2 of the License, or
9  * (at your option) any later version.
10  *
11  * This program is distributed in the hope that it will be useful,
12  * but WITHOUT ANY WARRANTY; without even the implied warranty of
13  * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
14  * GNU General Public License for more details.
15  *
16  * You should have received a copy of the GNU General Public License
17  * along with this program; see the file COPYING.  If not, write to
18  * the Free Software Foundation, Inc., 59 Temple Place - Suite 330,
19  * Boston, MA 02111-1307, USA.
20  *)
21
22 open Apache
23 open Registry
24 open Cgi
25 open Cgi_escape
26 open Printf
27
28 open ExtString
29
30 open Cocanwiki_strings
31
32 (* Generate a URL for a new page with the given title.  This code checks
33  * if the URL already exists in the database and can return one of several
34  * errors.
35  *)
36 type genurl_error_t = GenURL_OK of string
37                     | GenURL_TooShort
38                     | GenURL_BadURL
39                     | GenURL_Duplicate of string
40
41 let nontrivial_re = Pcre.regexp ~flags:[`CASELESS] "[a-z0-9]"
42
43 let generate_url_of_title (dbh : Dbi.connection) hostid title =
44   (* Create a suitable URL from this title. *)
45   let url =
46     String.map (function
47                     '\000' .. ' ' | '<' | '>' | '&' | '"' | '+' | '#' | '%'
48                       -> '_'
49                   | c -> Char.lowercase c) title in
50
51   (* Check URL is not too trivial. *)
52   if not (Pcre.pmatch ~rex:nontrivial_re url) then
53     GenURL_TooShort
54   (* URL cannot begin with '_'. *)
55   else if url.[0] = '_' then
56     GenURL_BadURL
57   else (
58     (* Check that the URL doesn't already exist in the database.  If it does
59      * then it probably means that another page exists with similar enough
60      * content, so we should redirect to there instead.
61      *)
62     let sth = dbh#prepare_cached "select 1 from pages
63                                    where hostid = ? and url = ?" in
64     sth#execute [`Int hostid; `String url];
65
66     try
67       sth#fetch1int ();
68       GenURL_Duplicate url
69     with
70         Not_found ->
71           GenURL_OK url
72   )
73
74 (* Obscure a mailto: URL against spammers. *)
75 let obscure_mailto url =
76   if String.length url > 8 then (
77     let c7 = Char.code url.[7] in
78     let c8 = Char.code url.[8] in
79     let start = String.sub url 0 7 in
80     let rest = escape_html_tag (String.sub url 9 (String.length url - 9)) in
81     sprintf "%s&#x%02x;&#x%02x;%s" start c7 c8 rest
82   )
83   else
84     url
85
86 (* Convert Wiki markup to XHTML 1.0.
87  *
88  * Shortcomings:
89  * Doesn't support multi-level bullet points. (XXX)
90  * Intra-page links. (XXX)
91  *)
92
93 (* This matches any markup. *)
94 let markup_re =
95   let link = "\\[\\[\\s*(?:.+?)\\s*(?:\\|.+?\\s*)?\\]\\]" in
96   let tag = "</?(?:b|i|strong|em|code|tt|sup|sub|nowiki|big|small|strike|s|br)>" in
97   Pcre.regexp ("(.*?)((?:" ^ link ^ ")|(?:" ^ tag ^ "))(.*)")
98
99 (* This matches links only, and should be compatible with the link contained
100  * in the above regexp.
101  *)
102 let link_re = Pcre.regexp "\\[\\[\\s*(.+?)\\s*(?:\\|(.+?)\\s*)?\\]\\]"
103
104 let image_re =
105   Pcre.regexp "^(image|thumb(?:nail)?):\\s*([a-z0-9][_a-z0-9]*\\.(?:jpg|jpeg|gif|ico|png))$"
106 let file_re =
107   Pcre.regexp "^file:\\s*([a-z0-9][-._a-z0-9]*)$"
108
109 let url_re = Pcre.regexp "^[a-z]+://"
110 let mailto_re = Pcre.regexp "^mailto:"
111
112 (* Links. *)
113 let markup_link dbh hostid link =
114   let subs = Pcre.exec ~rex:link_re link in
115   let url = Pcre.get_substring subs 1 in
116
117   let tag name = function
118       `Null -> ""
119     | `String v -> " " ^ name ^ "=\"" ^ escape_html_tag v ^ "\""
120   in
121
122   if Pcre.pmatch ~rex:image_re url then (
123     (* It may be an image. *)
124     let subs = Pcre.exec ~rex:image_re url in
125     let is_thumb = (Pcre.get_substring subs 1).[0] = 't' in
126     let name = Pcre.get_substring subs 2 in
127
128     let sql = "select id, " ^
129               (if is_thumb then "tn_width, tn_height"
130                else "width, height") ^
131               ", alt, title, longdesc, class
132                from images
133               where hostid = ? and name = ?" in
134     let sth = dbh#prepare_cached sql in
135     sth#execute [`Int hostid; `String name];
136
137     try
138       let imageid, width, height, alt, title, longdesc, clasz =
139         match sth#fetch1 () with
140             [`Int imageid; `Int width; `Int height; `String alt;
141              (`Null | `String _) as title;
142              (`Null | `String _) as longdesc;
143              (`Null | `String _) as clasz] ->
144               imageid, width, height, alt, title, longdesc, clasz
145           | _ -> assert false in
146
147       let link = "/_image/" ^ escape_url name in
148
149       (if is_thumb then "<a href=\"" ^ link ^ "\">" else "") ^
150       "<img src=\"" ^ link ^ "?version=" ^ string_of_int imageid ^
151       (if is_thumb then "&thumbnail=1" else "") ^
152       "\" width=\"" ^
153       string_of_int width ^
154       "\" height=\"" ^
155       string_of_int height ^
156       "\" alt=\"" ^
157       escape_html_tag alt ^
158       "\"" ^
159       tag "title" title ^
160       tag "longdesc" longdesc ^
161       tag "class" clasz ^
162       "/>" ^
163       (if is_thumb then "</a>" else "")
164     with
165         Not_found ->
166           (* Image not found. *)
167           "<a class=\"image_not_found\" " ^
168           "href=\"/_bin/upload_image_form.cmo?name=" ^
169           escape_url name ^
170           "\">" ^
171           escape_html name ^
172           "</a>"
173   ) else if Pcre.pmatch ~rex:file_re url then (
174     (* It may be a file. *)
175     let subs = Pcre.exec ~rex:file_re url in
176     let name = Pcre.get_substring subs 1 in
177
178     let sth = dbh#prepare_cached "select title
179                                     from files
180                                    where hostid = ? and name = ?" in
181     sth#execute [`Int hostid; `String name];
182
183     try
184       let title =
185         match sth#fetch1 () with
186             [(`Null | `String _) as title] -> title
187           | _ -> assert false in
188
189       "<a href=\"/_file/" ^
190       escape_url name ^
191       "\"" ^
192       tag "title" title ^
193       ">" ^
194       escape_html name ^
195       "</a>"
196     with
197         Not_found ->
198           (* File not found. *)
199           "<a class=\"file_not_found\" " ^
200           "href=\"/_bin/upload_file_form.cmo?name=" ^
201           escape_url name ^
202           "\">" ^
203           escape_html name ^
204           "</a>"
205   ) else (
206     (* Pcre changed behaviour between versions.  Previously a non-capture
207      * would return "".  Now it throws 'Not_found'.
208      *)
209     let text =
210       try Pcre.get_substring subs 2
211       with Not_found -> "" in
212     let text = if text = "" then url else text in
213
214     (* XXX Escaping here is very hairy indeed.  (See also the obscure_mailto
215      * function which performs some escaping ...)
216      *)
217
218     let url, clasz, title =
219       if Pcre.pmatch ~rex:url_re url then
220         escape_html_tag url, "external", url (* http://.... *)
221       else if Pcre.pmatch ~rex:mailto_re url then
222         obscure_mailto url, "mailto", url
223       else if String.length url >= 1 && url.[0] = '/' then (* /index etc. *)
224         escape_html_tag url, "internal", url
225       else (
226         let title = url in
227         (* Look up the 'URL' against the titles in the database and
228          * obtain the real URL.
229          *)
230         let sth = dbh#prepare_cached "select url from pages
231                                        where hostid = ? and url is not null
232                                          and lower (title) = lower (?)" in
233         sth#execute [`Int hostid; `String url];
234
235         try
236           let url = sth#fetch1string () in
237           "/" ^ url, "internal", title
238         with
239             Not_found ->
240               (* It might be a template page ...  These pages don't
241                * exist in the template, but can be synthesized on the
242                * fly by page.ml.
243                *)
244               let is_template_page url =
245                 let sth = dbh#prepare_cached "select 1 from templates
246                                                where ? ~ url_regexp
247                                                order by ordering
248                                                limit 1" in
249                 sth#execute [`String url];
250
251                 try sth#fetch1int () = 1 with Not_found -> false
252               in
253
254               if is_template_page url then
255                 "/" ^ url, "internal", title
256               else
257                 (* No, it really doesn't exist, so make it a link to
258                  * a new page.
259                  *)
260               "/_bin/edit.cmo?title=" ^ escape_url url, "newpage", title
261       ) in
262
263     "<a href=\"" ^ url ^
264     "\" class=\"" ^ clasz ^
265     "\" title=\"" ^ escape_html_tag title ^ "\">" ^
266     escape_html text ^ "</a>"
267   )
268
269 type find_t = FoundNothing
270             | FoundOpen of string * string * string
271             | FoundClose of string * string * string * string
272             | FoundLink of string * string * string
273
274 let _markup_paragraph dbh hostid text =
275   let find_earliest_markup text =
276     let convert_b_and_i elem =
277       if elem = "b" then "strong"
278       else if elem = "i" then "em"
279       else elem
280     in
281
282     try
283       let subs = Pcre.exec ~rex:markup_re text in
284       let first = Pcre.get_substring subs 1 in
285       let markup = Pcre.get_substring subs 2 in
286       let rest = Pcre.get_substring subs 3 in
287       if String.length markup > 2 &&
288         markup.[0] = '[' && markup.[1] = '[' then (
289           let link = markup_link dbh hostid markup in
290           FoundLink (first, link, rest)
291         )
292       else if String.length markup > 2 &&
293         markup.[0] = '<' && markup.[1] = '/' then (
294           let elem = String.sub markup 2 (String.length markup - 3) in
295           let elem = convert_b_and_i elem in
296           FoundClose (first, elem, rest, markup ^ rest)
297         )
298       else if String.length markup > 1 && markup.[0] = '<' then (
299         let elem = String.sub markup 1 (String.length markup - 2) in
300         let elem = convert_b_and_i elem in
301         FoundOpen (first, elem, rest)
302       )
303       else
304         failwith ("bad regexp: markup is '" ^ markup ^ "'");
305     with
306         Not_found -> FoundNothing
307   in
308
309   (* This code performs markup for a "paragraph" unit.  The strategy
310    * is to look for the next matching markup or link, process that, and
311    * then continue recursively with the remainder of the string.  We also
312    * maintain a stack which is our current level of nesting of <b>-like
313    * operators.
314    *)
315   let rec loop = function
316     | "", [] -> [""]                    (* base case *)
317
318     | text, ("nowiki" :: stack) ->
319         (*prerr_endline ("nowiki case: text = " ^ text);*)
320
321         (* If the top of the stack is <nowiki> then we're just looking for
322          * the closing </nowiki>, and nothing else matters. *)
323         (match Pcre.split ~pat:"</nowiki>" ~max:2 text with
324            | [] -> loop ("", stack)
325            | [x] -> escape_html x :: loop ("", stack)
326            | [x;y] -> escape_html x :: loop (y, stack)
327            | _ -> assert false)
328
329     | "", (x :: xs) ->                  (* base case, popping the stack *)
330         "</" :: x :: ">" :: loop ("", xs)
331
332     | text, [] ->
333         (*prerr_endline ("text = " ^ text ^ ", stack empty");*)
334
335         (* Look for the earliest possible matching markup.  Because the
336          * stack is empty, we're not looking for closing tags.
337          *)
338         (match find_earliest_markup text with
339            | FoundNothing -> escape_html text :: []
340            | FoundClose (first, elem, rest, _) ->
341                (* close tags ignored *)
342                escape_html first :: "&lt;/" :: escape_html elem :: "&gt;" ::
343                  loop (rest, [])
344            | FoundOpen (first, elem, rest) when elem = "nowiki" ->
345                (* handle <nowiki> specially ... *)
346                escape_html first :: loop (rest, elem :: [])
347            | FoundOpen (first, elem, rest) when elem = "br" ->
348                (* handle <br> specially ... *)
349                escape_html first :: "<br/>" :: loop (rest, [])
350            | FoundOpen (first, elem, rest) ->
351                (* open tag - push it onto the stack *)
352                escape_html first :: "<" :: elem :: ">" :: loop (rest, [elem])
353            | FoundLink (first, link, rest) ->
354                escape_html first :: link :: loop (rest, [])
355         )
356
357     | text, ((x :: xs) as stack) ->
358         (*prerr_endline ("text = " ^ text ^ ", top of stack = " ^ x ^
359           ", stack size = " ^ string_of_int (List.length stack));*)
360
361         (* Look for the earliest possible matching markup. *)
362         (match find_earliest_markup text with
363            | FoundNothing -> escape_html text :: loop ("", stack)
364            | FoundClose (first, elem, rest, _) when x = elem ->
365                (* matching close tag *)
366                escape_html first :: "</" :: elem :: ">" :: loop (rest, xs)
367            | FoundClose (first, elem, rest, elem_rest) ->
368                (* non-matching close tag *)
369                escape_html first :: "</" :: x :: ">" :: loop (elem_rest, xs)
370            | FoundOpen (first, elem, rest) when elem = "nowiki" ->
371                (* handle <nowiki> specially ... *)
372                escape_html first :: loop (rest, elem :: stack)
373            | FoundOpen (first, elem, rest) when elem = "br" ->
374                (* handle <br> specially ... *)
375                escape_html first :: "<br/>" :: loop (rest, stack)
376            | FoundOpen (first, elem, rest) ->
377                (* open tag - push it onto the stack *)
378                escape_html first :: "<" :: elem :: ">" ::
379                  loop (rest, elem :: stack)
380            | FoundLink (first, link, rest) ->
381                (* link *)
382                escape_html first :: link :: loop (rest, stack)
383         )
384   in
385
386   (*prerr_endline ("original markup = " ^ text);*)
387   let text = loop (text, []) in
388   let text = String.concat "" text in
389   (*prerr_endline ("after loop = " ^ text);*)
390   text
391
392 let markup_paragraph ~first_para dbh hostid text =
393   let p = if first_para then "<p class=\"first_para\">" else "<p>" in
394   p ^ _markup_paragraph dbh hostid text ^ "</p>"
395
396 let markup_heading dbh hostid level text =
397   let text = _markup_paragraph dbh hostid text in
398   sprintf "<h%d>%s</h%d>" level text level
399
400 let markup_ul dbh hostid lines =
401   "<ul><li>" ^
402   String.concat "</li>\n<li>"
403     (List.map (fun t -> _markup_paragraph dbh hostid t) lines) ^
404   "</li></ul>"
405
406 let markup_ol dbh hostid lines =
407   "<ol><li>" ^
408   String.concat "</li>\n<li>"
409     (List.map (fun t -> _markup_paragraph dbh hostid t) lines) ^
410   "</li></ol>"
411
412 let markup_pre lines =
413   "<pre>\n" ^
414   String.concat "\n" (List.map Cgi_escape.escape_html lines) ^
415   "\n</pre>\n"
416
417 (* Validate HTML permitted in between <html> ... </html> markers.
418  * Note that what we support is a very limited but strict subset of XHTML
419  * 1.0.  Actually, that's not true.  We should really use an XML parser
420  * and a proper DTD here to ensure elements only appear in the correct
421  * context ...
422  *)
423 let split_tags_re = Pcre.regexp ~flags:[`DOTALL] "<.*?>|[^<]+"
424
425 let open_attr_re = Pcre.regexp "^<([a-z]+)\\s*([^>]*?)(/?)>$"
426 let close_attr_re = Pcre.regexp "^</([a-z]+)>$"
427
428 let allowed_elements =
429   let basic = [
430     "p", [];
431     "ul", []; "ol", []; "li", [];
432     "pre", []; "blockquote", ["cite"];
433     "strong", []; "em", []; "dfn", []; "code", []; "tt", [];
434     "samp", []; "kbd", []; "var", []; "cite", [];
435     "sup", []; "sub", []; "q", [];
436     "abbr", []; "acronym", [];
437     "b", []; "i", [];
438     "big", []; "small", []; "strike", []; "s", [];
439     "div", []; "span", [];
440     "br", [];
441   ] in
442   let headers = [ "h3", []; "h4", []; "h5", []; "h6", [] ] in
443   let links = [ "a", ["href"; "name"] ] in
444   let images = [ "img", ["src"; "alt"; "width"; "height"; "longdesc"] ] in
445
446   let forms = [
447     "form", [ "method"; "action"; "enctype" ];
448     "input", [ "name"; "value"; "type"; "size"; "maxlength"; "src"; "alt" ];
449     "textarea", [ "name"; "rows"; "cols" ];
450   ] in
451
452   let tables = [
453     "table", []; "tr", [];
454     "th", [ "colspan"; "rowspan" ]; "td", [ "colspan"; "rowspan" ];
455     "thead", []; "tbody", []
456   ] in
457
458   basic @ headers @ links @ images @ forms @ tables
459
460 let standard_tags = [ "title"; "lang"; "class"; "id" ]
461
462 (* Parse a list of tags like:
463  * name="value" name="value with space"
464  * into an assoc list.  The tricky bit is that there may be
465  * spaces within the quoted strings.
466  *)
467 let parse_tags str =
468   if str = "" then []                   (* Very common case. *)
469   else (
470     let len = String.length str in
471
472     let fail () = invalid_arg ("bad tags near: " ^ truncate 20 str) in
473     let get_alphas i =
474       let b = Buffer.create 100 in
475       let rec loop i =
476         if i < len && isalpha str.[i] then (
477           Buffer.add_char b str.[i];
478           loop (i+1)
479         ) else
480           Buffer.contents b, i
481       in
482       loop i
483     in
484     let get_to_next_quote i =
485       let b = Buffer.create 100 in
486       let rec loop i =
487         if i < len && str.[i] <> '"' then (
488           Buffer.add_char b str.[i];
489           loop (i+1)
490         ) else
491           Buffer.contents b, (i+1)
492       in
493       loop i
494     in
495
496     let r = ref [] in
497     let rec loop i =
498       if i >= len then !r
499       else (
500         let c = str.[i] in
501         if isspace c then loop (i+1)
502         else if isalpha c then (
503           let name, i = get_alphas i in
504           if String.length str > i && str.[i] = '=' && str.[i+1] = '"' then (
505             let value, i = get_to_next_quote (i+2) in
506             r := (name, value) :: !r;
507             loop i
508           )
509           else fail ()
510         )
511         else fail ()
512       )
513     in
514     loop 0
515   )
516
517 type valid_t = VText of string
518              | VOpen of string * (string * string) list
519              | VClose of string
520
521 let validate html =
522   (* Split into attrs and non-attrs.  We end up with a list like this:
523    * [ "<ul>"; "<li>"; "Some text"; "</li>"; ... ]
524    *)
525   let html =
526     try
527       let html = Pcre.extract_all ~rex:split_tags_re html in
528       let html = Array.to_list html in
529       List.map (function [| a |] -> a | _ -> assert false) html
530     with
531         Not_found -> [] in
532
533   (* Parse up each attribute to get the tags. *)
534   let html =
535     List.concat
536       (List.map
537          (fun str ->
538             if String.length str >= 2 && str.[0] = '<' then (
539               try
540                 if str.[1] <> '/' then (
541                   (* Possible open attr. *)
542                   let subs = Pcre.exec ~rex:open_attr_re str in
543                   let attr = Pcre.get_substring subs 1 in
544                   let tags = Pcre.get_substring subs 2 in
545                   let close = Pcre.get_substring subs 3 = "/" in
546                   let tags = parse_tags tags in
547                   if not close then
548                     [VOpen (attr, tags)]
549                   else
550                     [VOpen (attr, tags); VClose attr]
551                 ) else (
552                   (* Possible close attr. *)
553                   let subs = Pcre.exec ~rex:close_attr_re str in
554                   let attr = Pcre.get_substring subs 1 in
555                   [VClose attr]
556                 )
557               with
558                   Not_found ->
559                     invalid_arg ("invalid element near " ^ truncate 20 str)
560             ) else (
561               (* Ordinary text.  Check no < or > characters. *)
562               (* XXX Check for valid &quoted; entities. *)
563               if String.contains str '<' || String.contains str '>' then
564                 invalid_arg
565                   ("unquoted '<' or '>' characters near " ^ truncate 20 str);
566               [VText str]
567             )
568          ) html
569       ) in
570
571   (* Check that opening/closing tags match. *)
572   let rec loop stack html =
573     match stack, html with
574       | [], [] -> ()
575       | (attr :: _), [] ->
576           invalid_arg ("mismatched element: " ^ truncate 20 attr)
577       | stack, (VOpen (attr, _) :: xs) ->
578           loop (attr :: stack) xs
579       | (attr1 :: stack), (VClose attr2 :: xs) when attr1 = attr2 ->
580           loop stack xs
581       | (attr1 :: stack), (VClose attr2 :: xs) ->
582           invalid_arg ("open/close elements don't match: " ^
583                        truncate 20 attr1 ^ " and: " ^
584                        truncate 20 attr2)
585       | [], (VClose attr2 :: _) ->
586           invalid_arg ("close element with no matching open: " ^
587                        truncate 20 attr2)
588       | stack, (VText _ :: xs) ->
589           loop stack xs
590   in
591   loop [] html;
592
593   (* Now check that we only use the permitted elements. *)
594   let rec loop = function
595     | [] -> ()
596     | (VOpen (attr, tags)) :: xs ->
597         (try
598            let allowed_tags = List.assoc attr allowed_elements in
599            let allowed_tags = allowed_tags @ standard_tags in
600            List.iter (fun (tag, _) ->
601                         if not (List.mem tag allowed_tags) then
602                           raise Not_found) tags;
603            loop xs
604          with
605              Not_found ->
606                invalid_arg ("this HTML attr is not allowed or contains a " ^
607                             "tag which is not permitted: " ^
608                             truncate 20 attr))
609     | _ :: xs -> loop xs
610   in
611   loop html
612
613 type preline_t = STpHTML of string list (* Block of HTML. *)
614                | STpLine of string      (* A line. *)
615
616 type line_t = STBlank
617             | STHeading of int * string (* <h3>, <h4>, ... *)
618             | STUnnumbered of string list (* <ul> *)
619             | STNumbered of string list (* <ol> *)
620             | STPreformatted of string list (* <pre> *)
621             | STParagraph of string     (* Ordinary <p> *)
622             | STHTML of string list     (* Block of (unvalidated) HTML. *)
623
624 let split_lines_re = Pcre.regexp "\\r?\\n"
625 let blank_re = Pcre.regexp "^\\s*$"
626 let heading_re = Pcre.regexp "^(=+)\\s+(.*)"
627 let unnumbered_re = Pcre.regexp "^(\\*)\\s+(.*)"
628 let numbered_re = Pcre.regexp "^(\\#)\\s+(.*)"
629 let preformatted_re = Pcre.regexp "^ (.*)"
630 let html_open_re = Pcre.regexp "^<html>\\s*$"
631 let html_close_re = Pcre.regexp "^</html>\\s*$"
632
633 let xhtml_of_content (dbh : Dbi.connection) hostid text =
634   (* Split the text into lines. *)
635   let lines = Pcre.split ~rex:split_lines_re text in
636
637   (* HTML blocks span multiple lines, so isolate these out first. *)
638   let rec loop = function
639     | [] -> []
640     | line :: xs when Pcre.pmatch ~rex:html_open_re line ->
641       (* Find the closing tag.  If not found, ignore opening tag. *)
642       let rec loop' acc = function
643         | [] -> None
644         | line :: xs when Pcre.pmatch ~rex:html_close_re line ->
645           Some (List.rev acc, xs)
646         | line :: xs ->
647             let acc = line :: acc in
648             loop' acc xs
649       in
650       (match loop' [] xs with
651          | Some (html, rest) ->
652              STpHTML html :: loop rest
653          | None ->
654              STpLine line :: loop xs)
655     | line :: xs ->
656         STpLine line :: loop xs
657   in
658   let lines = loop lines in
659
660   (* Iterate over the lines to isolate headers and paragraphs. *)
661   let lines =
662     List.map
663       (function
664          | STpLine line ->
665              if Pcre.pmatch ~rex:preformatted_re line then (
666                let subs = Pcre.exec ~rex:preformatted_re line in
667                let line = Pcre.get_substring subs 1 in
668                STPreformatted [line]
669              )
670              else if Pcre.pmatch ~rex:blank_re line then
671                STBlank
672              else if Pcre.pmatch ~rex:heading_re line then (
673                let subs = Pcre.exec ~rex:heading_re line in
674                let count = String.length (Pcre.get_substring subs 1) + 2 in
675                let line = Pcre.get_substring subs 2 in
676                STHeading (count, line)
677              )
678              else if Pcre.pmatch ~rex:unnumbered_re line then (
679                let subs = Pcre.exec ~rex:unnumbered_re line in
680                let line = Pcre.get_substring subs 2 in
681                STUnnumbered [line]
682              )
683              else if Pcre.pmatch ~rex:numbered_re line then (
684                let subs = Pcre.exec ~rex:numbered_re line in
685                let line = Pcre.get_substring subs 2 in
686                STNumbered [line]
687              ) else
688                STParagraph line
689          | STpHTML html ->
690              STHTML html
691       ) lines in
692
693   (* Aggregate paragraphs and lists. *)
694   let rec loop = function
695     | [] -> []
696     | STHeading (_, _) as h :: xs ->
697         h :: loop xs
698     | STUnnumbered lines1 :: STUnnumbered lines2 :: xs ->
699         loop (STUnnumbered (lines1 @ lines2) :: xs)
700     | STUnnumbered lines :: xs ->
701         STUnnumbered lines :: loop xs
702     | STNumbered lines1 :: STNumbered lines2 :: xs ->
703         loop (STNumbered (lines1 @ lines2) :: xs)
704     | STNumbered lines :: xs ->
705         STNumbered lines :: loop xs
706     | STPreformatted lines1 :: STPreformatted lines2 :: xs ->
707         loop (STPreformatted (lines1 @ lines2) :: xs)
708     | STPreformatted lines :: xs ->
709         STPreformatted lines :: loop xs
710     | STParagraph line1 :: STParagraph line2 :: xs ->
711         loop (STParagraph (line1 ^ " " ^ line2) :: xs)
712     | STParagraph line :: xs ->
713         STParagraph line :: loop xs
714     | STHTML html as h :: xs ->
715         h :: loop xs
716     | STBlank :: xs ->
717         loop xs
718   in
719   let lines = loop lines in
720
721   (* In the following map, first_para records whether this is the
722    * first (non-indented) paragraph.  We "reset" this to true after
723    * non-paragraphs.
724    *)
725   let first_para = ref true in
726
727   (* Convert lines to XHTML. *)
728   let lines =
729     List.map
730       (fun st ->
731          let xhtml =
732            match st with
733              | STBlank -> assert false  (* Should never happen. *)
734              | STParagraph para ->
735                  markup_paragraph ~first_para:!first_para dbh hostid para
736              | STHeading (level, text) ->
737                  markup_heading dbh hostid level text
738              | STUnnumbered lines ->
739                  markup_ul dbh hostid lines
740              | STNumbered lines ->
741                  markup_ol dbh hostid lines
742              | STPreformatted lines ->
743                  markup_pre lines
744              | STHTML html ->
745                  let html' = String.concat "\n" html in
746                  try
747                    validate html';
748                    html'
749                  with
750                      Invalid_argument msg ->
751                        let msg = "Invalid HTML: " ^ msg in
752                        markup_pre (msg :: html) in
753          first_para := (match st with STParagraph _ -> false | _ -> true);
754          xhtml
755       ) lines in
756
757   (* Return the lines. *)
758   String.concat "\n" lines
759
760 (* Convert valid XHTML to plain text. *)
761 let text_re = Pcre.regexp "<[^>]+>"
762 let text_itempl = Pcre.subst " "
763
764 let text_of_xhtml xhtml =
765   Pcre.replace ~rex:text_re ~itempl:text_itempl xhtml