Removed dependency on imported merjislib.
[cocanwiki.git] / scripts / wikilib.ml
1 (* Library of functions useful for people implementing a Wiki.
2  * Written by Richard W.M. Jones <rich@merjis.com>.
3  * Copyright (C) 2004 Merjis Ltd.
4  * $Id: wikilib.ml,v 1.2 2004/09/07 14:58:34 rich Exp $
5  *)
6
7 open Apache
8 open Registry
9 open Cgi
10 open Cgi_escape
11 open Printf
12
13 open ExtString
14
15 (* Generate a URL for a new page with the given title.  This code checks
16  * if the URL already exists in the database and can return one of several
17  * errors.
18  *)
19 type genurl_error_t = GenURL_OK of string
20                     | GenURL_TooShort
21                     | GenURL_BadURL
22                     | GenURL_Duplicate of string
23
24 let nontrivial_re = Pcre.regexp ~flags:[`CASELESS] "[a-z0-9]"
25
26 let generate_url_of_title (dbh : Dbi.connection) hostid title =
27   (* Create a suitable URL from this title. *)
28   let url = String.map (function '\000' .. ' ' | '<' | '>' | '&' | '"' -> '_'
29                           | c -> Char.lowercase c) title in
30
31   (* Check URL is not too trivial. *)
32   if not (Pcre.pmatch ~rex:nontrivial_re url) then
33     GenURL_TooShort
34   (* URL cannot begin with '_'. *)
35   else if url.[0] = '_' then
36     GenURL_BadURL
37   else (
38     (* Check that the URL doesn't already exist in the database.  If it does
39      * then it probably means that another page exists with similar enough
40      * content, so we should redirect to there instead.
41      *)
42     let sth = dbh#prepare_cached "select 1 from pages
43                                    where hostid = ? and url = ?" in
44     sth#execute [`Int hostid; `String url];
45
46     try
47       sth#fetch1int ();
48       GenURL_Duplicate url
49     with
50         Not_found ->
51           GenURL_OK url
52   )
53
54 (* Obscure a mailto: URL against spammers. *)
55 let obscure_mailto url =
56   if String.length url > 8 then (
57     let c7 = Char.code url.[7] in
58     let c8 = Char.code url.[8] in
59     let start = String.sub url 0 7 in
60     let rest = escape_html_tag (String.sub url 9 (String.length url - 9)) in
61     sprintf "%s&#x%02x;&#x%02x;%s" start c7 c8 rest
62   )
63   else
64     url
65
66 (* Convert Wiki markup to XHTML 1.0.
67  *
68  * Shortcomings:
69  * Doesn't support multi-level bullet points. (XXX)
70  * Intra-page links. (XXX)
71  *)
72
73 (* This matches any markup. *)
74 let markup_re =
75   let link = "\\[\\[\\s*(?:.+?)\\s*(?:\\|.+?\\s*)?\\]\\]" in
76   let tag = "</?(?:b|i|strong|em|code|sup|sub|nowiki)>" in
77   Pcre.regexp ("(.*?)((?:" ^ link ^ ")|(?:" ^ tag ^ "))(.*)")
78
79 (* This matches links only, and should be compatible with the link contained
80  * in the above regexp.
81  *)
82 let link_re = Pcre.regexp "\\[\\[\\s*(.+?)\\s*(?:\\|(.+?)\\s*)?\\]\\]"
83
84 let image_re =
85   Pcre.regexp "^(image|thumb(?:nail)?):\\s*([a-z0-9][_a-z0-9]*\\.(?:jpg|jpeg|gif|ico|png))$"
86 let file_re =
87   Pcre.regexp "^file:\\s*([a-z0-9][-._a-z0-9]*)$"
88
89 let url_re = Pcre.regexp "^[a-z]+://"
90 let mailto_re = Pcre.regexp "^mailto:"
91
92 (* Links. *)
93 let markup_link dbh hostid link =
94   let subs = Pcre.exec ~rex:link_re link in
95   let url = Pcre.get_substring subs 1 in
96
97   let tag name = function
98       `Null -> ""
99     | `String v -> " " ^ name ^ "=\"" ^ escape_html_tag v ^ "\""
100   in
101
102   if Pcre.pmatch ~rex:image_re url then (
103     (* It may be an image. *)
104     let subs = Pcre.exec ~rex:image_re url in
105     let is_thumb = (Pcre.get_substring subs 1).[0] = 't' in
106     let name = Pcre.get_substring subs 2 in
107
108     let sql = "select id, " ^
109               (if is_thumb then "tn_width, tn_height"
110                else "width, height") ^
111               ", alt, title, longdesc, class
112                from images
113               where hostid = ? and name = ?" in
114     let sth = dbh#prepare_cached sql in
115     sth#execute [`Int hostid; `String name];
116
117     try
118       let imageid, width, height, alt, title, longdesc, clasz =
119         match sth#fetch1 () with
120             [`Int imageid; `Int width; `Int height; `String alt;
121              (`Null | `String _) as title;
122              (`Null | `String _) as longdesc;
123              (`Null | `String _) as clasz] ->
124               imageid, width, height, alt, title, longdesc, clasz
125           | _ -> assert false in
126
127       let link = "/_image/" ^ escape_url name in
128
129       (if is_thumb then "<a href=\"" ^ link ^ "\">" else "") ^
130       "<img src=\"" ^ link ^ "?version=" ^ string_of_int imageid ^
131       (if is_thumb then "&thumbnail=1" else "") ^
132       "\" width=\"" ^
133       string_of_int width ^
134       "\" height=\"" ^
135       string_of_int height ^
136       "\" alt=\"" ^
137       escape_html_tag alt ^
138       "\"" ^
139       tag "title" title ^
140       tag "longdesc" longdesc ^
141       tag "class" clasz ^
142       "/>" ^
143       (if is_thumb then "</a>" else "")
144     with
145         Not_found ->
146           (* Image not found. *)
147           "<a class=\"image_not_found\" " ^
148           "href=\"/_bin/upload_image_form.cmo?name=" ^
149           escape_url name ^
150           "\">" ^
151           escape_html name ^
152           "</a>"
153   ) else if Pcre.pmatch ~rex:file_re url then (
154     (* It may be a file. *)
155     let subs = Pcre.exec ~rex:file_re url in
156     let name = Pcre.get_substring subs 1 in
157
158     let sth = dbh#prepare_cached "select title
159                                     from files
160                                    where hostid = ? and name = ?" in
161     sth#execute [`Int hostid; `String name];
162
163     try
164       let title =
165         match sth#fetch1 () with
166             [(`Null | `String _) as title] -> title
167           | _ -> assert false in
168
169       "<a href=\"/_file/" ^
170       escape_url name ^
171       "\"" ^
172       tag "title" title ^
173       ">" ^
174       escape_html name ^
175       "</a>"
176     with
177         Not_found ->
178           (* File not found. *)
179           "<a class=\"file_not_found\" " ^
180           "href=\"/_bin/upload_file_form.cmo?name=" ^
181           escape_url name ^
182           "\">" ^
183           escape_html name ^
184           "</a>"
185   ) else (
186     (* Pcre changed behaviour between versions.  Previously a non-capture
187      * would return "".  Now it throws 'Not_found'.
188      *)
189     let text =
190       try Pcre.get_substring subs 2
191       with Not_found -> "" in
192     let text = if text = "" then url else text in
193
194     (* XXX Escaping here is very hairy indeed.  (See also the obscure_mailto
195      * function which performs some escaping ...)
196      *)
197
198     let url, clasz, title =
199       if Pcre.pmatch ~rex:url_re url then
200         escape_html_tag url, "external", url (* http://.... *)
201       else if Pcre.pmatch ~rex:mailto_re url then (
202         obscure_mailto url, "mailto", url
203       ) else (
204         let title = url in
205         (* Look up the 'URL' against the titles in the database and
206          * obtain the real URL.  If none is found then it's a link to
207          * create a new page.
208          *)
209         let sth = dbh#prepare_cached "select url from pages
210                                        where hostid = ? and url is not null
211                                          and lower (title) = lower (?)" in
212         sth#execute [`Int hostid; `String url];
213
214         try
215           let url = sth#fetch1string () in
216           "/" ^ url, "internal", title
217         with
218             Not_found ->
219               "/_bin/create_form.cmo?title=" ^ escape_url url, "newpage", title
220       ) in
221
222     "<a href=\"" ^ url ^
223     "\" class=\"" ^ clasz ^
224     "\" title=\"" ^ escape_html_tag title ^ "\">" ^
225     escape_html text ^ "</a>"
226   )
227
228 type find_t = FoundNothing
229             | FoundOpen of string * string * string
230             | FoundClose of string * string * string * string
231             | FoundLink of string * string * string
232
233 let _markup_paragraph dbh hostid text =
234   let find_earliest_markup text =
235     let convert_b_and_i elem =
236       if elem = "b" then "strong"
237       else if elem = "i" then "em"
238       else elem
239     in
240
241     try
242       let subs = Pcre.exec ~rex:markup_re text in
243       let first = Pcre.get_substring subs 1 in
244       let markup = Pcre.get_substring subs 2 in
245       let rest = Pcre.get_substring subs 3 in
246       if String.length markup > 2 &&
247         markup.[0] = '[' && markup.[1] = '[' then (
248           let link = markup_link dbh hostid markup in
249           FoundLink (first, link, rest)
250         )
251       else if String.length markup > 2 &&
252         markup.[0] = '<' && markup.[1] = '/' then (
253           let elem = String.sub markup 2 (String.length markup - 3) in
254           let elem = convert_b_and_i elem in
255           FoundClose (first, elem, rest, markup ^ rest)
256         )
257       else if String.length markup > 1 && markup.[0] = '<' then (
258         let elem = String.sub markup 1 (String.length markup - 2) in
259         let elem = convert_b_and_i elem in
260         FoundOpen (first, elem, rest)
261       )
262       else
263         failwith ("bad regexp: markup is '" ^ markup ^ "'");
264     with
265         Not_found -> FoundNothing
266   in
267
268   (* This code performs markup for a "paragraph" unit.  The strategy
269    * is to look for the next matching markup or link, process that, and
270    * then continue recursively with the remainder of the string.  We also
271    * maintain a stack which is our current level of nesting of <b>-like
272    * operators.
273    *)
274   let rec loop = function
275     | "", [] -> [""]                    (* base case *)
276
277     | text, ("nowiki" :: stack) ->
278         (*prerr_endline ("nowiki case: text = " ^ text);*)
279
280         (* If the top of the stack is <nowiki> then we're just looking for
281          * the closing </nowiki>, and nothing else matters. *)
282         (match Pcre.split ~pat:"</nowiki>" ~max:2 text with
283            | [] -> loop ("", stack)
284            | [x] -> escape_html x :: loop ("", stack)
285            | [x;y] -> escape_html x :: loop (y, stack)
286            | _ -> assert false)
287
288     | "", (x :: xs) ->                  (* base case, popping the stack *)
289         "</" :: x :: ">" :: loop ("", xs)
290
291     | text, [] ->
292         (*prerr_endline ("text = " ^ text ^ ", stack empty");*)
293
294         (* Look for the earliest possible matching markup.  Because the
295          * stack is empty, we're not looking for closing tags.
296          *)
297         (match find_earliest_markup text with
298            | FoundNothing -> escape_html text :: []
299            | FoundClose (first, elem, rest, _) ->
300                (* close tags ignored *)
301                escape_html first :: "&lt;/" :: escape_html elem :: "&gt;" ::
302                  loop (rest, [])
303            | FoundOpen (first, elem, rest) when elem = "nowiki" ->
304                (* handle <nowiki> specially ... *)
305                escape_html first :: loop (rest, elem :: [])
306            | FoundOpen (first, elem, rest) ->
307                (* open tag - push it onto the stack *)
308                escape_html first :: "<" :: elem :: ">" :: loop (rest, [elem])
309            | FoundLink (first, link, rest) ->
310                escape_html first :: link :: loop (rest, [])
311         )
312
313     | text, ((x :: xs) as stack) ->
314         (*prerr_endline ("text = " ^ text ^ ", top of stack = " ^ x ^
315           ", stack size = " ^ string_of_int (List.length stack));*)
316
317         (* Look for the earliest possible matching markup. *)
318         (match find_earliest_markup text with
319            | FoundNothing -> escape_html text :: loop ("", stack)
320            | FoundClose (first, elem, rest, _) when x = elem ->
321                (* matching close tag *)
322                escape_html first :: "</" :: elem :: ">" :: loop (rest, xs)
323            | FoundClose (first, elem, rest, elem_rest) ->
324                (* non-matching close tag *)
325                escape_html first :: "</" :: x :: ">" :: loop (elem_rest, xs)
326            | FoundOpen (first, elem, rest) when elem = "nowiki" ->
327                (* handle <nowiki> specially ... *)
328                escape_html first :: loop (rest, elem :: stack)
329            | FoundOpen (first, elem, rest) ->
330                (* open tag - push it onto the stack *)
331                escape_html first :: "<" :: elem :: ">" ::
332                  loop (rest, elem :: stack)
333            | FoundLink (first, link, rest) ->
334                (* pop everything off the stack first *)
335                escape_html first :: loop ("", stack) @ link :: loop (rest, [])
336         )
337   in
338
339   (*prerr_endline ("original markup = " ^ text);*)
340   let text = loop (text, []) in
341   let text = String.concat "" text in
342   (*prerr_endline ("after loop = " ^ text);*)
343   text
344
345 let markup_paragraph dbh hostid text =
346   "<p>" ^ _markup_paragraph dbh hostid text ^ "</p>"
347
348 let markup_heading dbh hostid level text =
349   let text = _markup_paragraph dbh hostid text in
350   sprintf "<h%d>%s</h%d>" level text level
351
352 let markup_ul dbh hostid lines =
353   "<ul><li>" ^
354   String.concat "</li>\n<li>"
355     (List.map (fun t -> _markup_paragraph dbh hostid t) lines) ^
356   "</li></ul>"
357
358 let markup_ol dbh hostid lines =
359   "<ol><li>" ^
360   String.concat "</li>\n<li>"
361     (List.map (fun t -> _markup_paragraph dbh hostid t) lines) ^
362   "</li></ol>"
363
364 let markup_pre lines =
365   "<pre>\n" ^
366   String.concat "\n" (List.map Cgi_escape.escape_html lines) ^
367   "\n</pre>\n"
368
369
370 type line_t = STBlank
371             | STHeading of int * string (* <h3>, <h4>, ... *)
372             | STUnnumbered of string list (* <ul> *)
373             | STNumbered of string list (* <ol> *)
374             | STPreformatted of string list (* <pre> *)
375             | STParagraph of string     (* Ordinary <p> *)
376
377 let split_lines_re = Pcre.regexp "\\r?\\n"
378 let blank_re = Pcre.regexp "^\\s*$"
379 let heading_re = Pcre.regexp "^(=+)\\s+(.*)"
380 let unnumbered_re = Pcre.regexp "^(\\*)\\s+(.*)"
381 let numbered_re = Pcre.regexp "^(\\#)\\s+(.*)"
382 let preformatted_re = Pcre.regexp "^ (.*)"
383
384 let xhtml_of_content (dbh : Dbi.connection) hostid text =
385   (* Split the text into lines. *)
386   let lines = Pcre.split ~rex:split_lines_re text in
387   (* Iterate over the lines to isolate headers and paragraphs. *)
388   let lines =
389     List.map
390       (fun line ->
391          if Pcre.pmatch ~rex:preformatted_re line then (
392            let subs = Pcre.exec ~rex:preformatted_re line in
393            let line = Pcre.get_substring subs 1 in
394            STPreformatted [line]
395          )
396          else if Pcre.pmatch ~rex:blank_re line then
397            STBlank
398          else if Pcre.pmatch ~rex:heading_re line then (
399            let subs = Pcre.exec ~rex:heading_re line in
400            let count = String.length (Pcre.get_substring subs 1) + 2 in
401            let line = Pcre.get_substring subs 2 in
402            STHeading (count, line)
403          )
404          else if Pcre.pmatch ~rex:unnumbered_re line then (
405            let subs = Pcre.exec ~rex:unnumbered_re line in
406            let line = Pcre.get_substring subs 2 in
407            STUnnumbered [line]
408          )
409          else if Pcre.pmatch ~rex:numbered_re line then (
410            let subs = Pcre.exec ~rex:numbered_re line in
411            let line = Pcre.get_substring subs 2 in
412            STNumbered [line]
413          ) else
414            STParagraph line) lines in
415
416   (* Aggregate paragraphs and lists. *)
417   let rec loop = function
418       [] -> []
419     | STHeading (_, _) as h :: xs ->
420         h :: loop xs
421     | STUnnumbered lines1 :: STUnnumbered lines2 :: xs ->
422         loop (STUnnumbered (lines1 @ lines2) :: xs)
423     | STUnnumbered lines :: xs ->
424         STUnnumbered lines :: loop xs
425     | STNumbered lines1 :: STNumbered lines2 :: xs ->
426         loop (STNumbered (lines1 @ lines2) :: xs)
427     | STNumbered lines :: xs ->
428         STNumbered lines :: loop xs
429     | STPreformatted lines1 :: STPreformatted lines2 :: xs ->
430         loop (STPreformatted (lines1 @ lines2) :: xs)
431     | STPreformatted lines :: xs ->
432         STPreformatted lines :: loop xs
433     | STParagraph line1 :: STParagraph line2 :: xs ->
434         loop (STParagraph (line1 ^ " " ^ line2) :: xs)
435     | STParagraph line :: xs ->
436         STParagraph line :: loop xs
437     | STBlank :: xs ->
438         loop xs
439   in
440   let lines = loop lines in
441
442   (* Convert lines to XHTML. *)
443   let lines =
444     List.map
445       (function
446            STBlank -> assert false    (* Should never happen. *)
447          | STParagraph para ->
448              markup_paragraph dbh hostid para
449          | STHeading (level, text) ->
450              markup_heading dbh hostid level text
451          | STUnnumbered lines ->
452              markup_ul dbh hostid lines
453          | STNumbered lines ->
454              markup_ol dbh hostid lines
455          | STPreformatted lines ->
456              markup_pre lines
457       ) lines in
458
459   (* Return the lines. *)
460   String.concat "\n" lines
461
462 (* Convert valid XHTML to plain text. *)
463 let text_re = Pcre.regexp "<[^>]+>"
464 let text_itempl = Pcre.subst " "
465
466 let text_of_xhtml xhtml =
467   Pcre.replace ~rex:text_re ~itempl:text_itempl xhtml