Bumped version for release.
[cocanwiki.git] / scripts / page.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: page.ml,v 1.38 2004/11/03 13:36:45 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 Printf
26
27 open ExtString
28 open ExtList
29
30 open Cocanwiki
31 open Cocanwiki_template
32 open Cocanwiki_ok
33 open Cocanwiki_date
34 open Cocanwiki_server_settings
35 open Cocanwiki_links
36
37 type fp_status = FPOK of int * string * string * Dbi.datetime * bool
38                | FPRedirect of string
39                | FPNotFound
40
41 (* Referer strings which help us decide if the user came from
42  * a search engine and highlight terms in the page appropriately.
43  *)
44 let search_engines = [
45   Pcre.regexp "^http://.*google\\.", [ "q"; "as_q"; "as_epq"; "as_oq" ];
46   Pcre.regexp "^http://.*yahoo\\.", [ "p" ];
47   Pcre.regexp "^http://.*msn\\.", [ "q"; "MT" ]
48 ]
49 let split_words = Pcre.regexp "\\W+"
50
51 let split_qs_re = Pcre.regexp "\\?"
52
53 let xhtml_re = Pcre.regexp "<.*?>|[^<>]+"
54
55 let run r (q : cgi) (dbh : Dbi.connection) hostid
56     ({ edit_anon = edit_anon;
57        view_anon = view_anon } as host)
58     user =
59   let page = q#param "page" in
60   let page = if page = "" then "index" else page in
61
62   let template_page = get_template ~page dbh hostid "page.html" in
63   let template_404  = get_template dbh hostid "page_404.html" in
64
65   (* Host-specific fields. *)
66   let sth = dbh#prepare_cached "select css is not null,
67                                        feedback_email is not null,
68                                        mailing_list, navigation
69                                   from hosts where id = ?" in
70   sth#execute [`Int hostid];
71   let has_host_css, has_feedback_email, mailing_list, navigation =
72     match sth#fetch1 () with
73       | [ `Bool has_host_css; `Bool has_feedback_email; `Bool mailing_list;
74           `Bool navigation ] ->
75           has_host_css, has_feedback_email, mailing_list, navigation
76       | _ -> assert false in
77
78   (* User permissions. *)
79   let can_edit = can_edit host user in
80   let can_manage_users = can_manage_users host user in
81
82   (* Do we have a stats page set up? *)
83   let has_stats = server_settings_stats_page dbh <> None in
84
85   (* Given the referer string, return the list of search terms.  If none
86    * can be found, then throws Not_found.
87    *)
88   let search_terms_from_referer referer =
89     let _, argnames =
90       List.find (fun (rex, _) -> Pcre.pmatch ~rex referer) search_engines in
91     let url, qs =
92       match Pcre.split ~rex:split_qs_re ~max:2 referer with
93         | [url] | [url;""] -> url, ""
94         | [url;qs] -> url, qs
95         | _ -> assert false in
96     let args = Cgi_args.parse qs in
97     let argname =
98       List.find (fun argname -> List.mem_assoc argname args) argnames in
99     let search_string = List.assoc argname args in
100     Pcre.split ~rex:split_words search_string
101   in
102
103   (* Given a full page of XHTML, highlight search terms found in the
104    * <body> part of the page.
105    *)
106   let highlight_search_terms xhtml search_terms span_class =
107     (* Split the original XHTML into strings and tags.  For example if
108      * the original string is: "This is some <b>bold</b> text.<br/>", then
109      * after this step we will have the following list:
110      * [ "This is some "; "<b>"; "bold"; "</b>"; " text."; "<br/>" ]
111      *)
112     let xhtml = Pcre.extract_all ~rex:xhtml_re xhtml in
113     let xhtml = Array.to_list xhtml in
114     let xhtml = List.map (fun matches -> matches.(0)) xhtml in
115
116     (* Find the <body> ... </body> tags.  We only want to apply
117      * highlighting to tags within this area.
118      *)
119     let rec list_split f acc = function
120       | [] -> List.rev acc, []
121       | ((x :: _) as xs) when f x -> List.rev acc, xs
122       | x :: xs ->
123           let acc = x :: acc in
124           list_split f acc xs
125     in
126     let head, body =
127       list_split (fun str -> String.starts_with str "<body") [] xhtml in
128     let body, tail =
129       list_split ((=) "</body>") [] body in
130     (* NB: Hopefully, xhtml = head @ body @ tail. *)
131
132     (* The search terms are a list of simple words.  Turn into a big
133      * regular expression, because we want to substitute for each.  We
134      * end up with a regexp like '(word1|word2|word3)'.
135      *)
136     let rex =
137       Pcre.regexp ~flags:[`CASELESS]
138         ("(" ^ String.concat "|" search_terms ^ ")") in
139
140     (* Do the substitution, but only on text, not elements! *)
141     let body =
142       let subst text =
143         "<span class=\"" ^ span_class ^ "\">" ^ text ^ "</span>"
144       in
145       List.map (fun str ->
146                   if String.length str > 0 && str.[0] != '<' then
147                     Pcre.substitute ~rex ~subst str
148                   else
149                     str) body in
150
151     (* Join the XHTML fragments back together again. *)
152     String.concat "" (List.concat [ head ; body ; tail ])
153   in
154
155   (* Check the templates table for extensions. *)
156   let get_extension url =
157     let sth = dbh#prepare_cached "select extension from templates
158                                    where ? ~ url_regexp
159                                    order by ordering
160                                    limit 1" in
161     sth#execute [`String url];
162
163     try
164       let name = sth#fetch1string () in
165       Some (List.assoc name !extensions)
166     with
167         Not_found -> None
168   in
169
170   (* This code generates ordinary pages. *)
171   let make_page title description pageid last_modified_date has_page_css
172       version page page' extension =
173     let t = template_page in
174     t#set "title" title;
175     t#set "last_modified_date" last_modified_date;
176
177     (match description with
178          None -> t#conditional "has_description" false
179        | Some description ->
180            t#conditional "has_description" true;
181            t#set "description" description);
182
183     if page <> page' then (* redirection *) (
184       t#set "page" page';
185       t#set "original_page" page; (* XXX title - get it from database *)
186       t#conditional "redirected" true
187     ) else (
188       t#set "page" page;
189       t#conditional "redirected" false
190     );
191
192     t#conditional "has_host_css" has_host_css;
193     t#conditional "has_page_css" has_page_css;
194
195     t#conditional "has_feedback_email" has_feedback_email;
196     t#conditional "mailing_list" mailing_list;
197     t#conditional "navigation" navigation;
198
199     t#conditional "can_edit" can_edit;
200     t#conditional "can_manage_users" can_manage_users;
201     t#conditional "has_stats" has_stats;
202
203     (* Pull out the sections in this page. *)
204     let sections =
205       match pageid with
206           None -> []
207         | Some pageid ->
208             let sth = dbh#prepare_cached
209                         "select ordering, sectionname, content, divname
210                            from contents where pageid = ? order by ordering" in
211             sth#execute [`Int pageid];
212
213             sth#map
214               (function [`Int ordering;
215                          (`Null | `String _) as sectionname;
216                          `String content;
217                          (`Null | `String _) as divname] ->
218                  let divname, has_divname =
219                    match divname with
220                        `Null -> "", false
221                      | `String divname -> divname, true in
222                  let sectionname, has_sectionname =
223                    match sectionname with
224                        `Null -> "", false
225                      | `String sectionname -> sectionname, true in
226                  let linkname = linkname_of_sectionname sectionname in
227                  [ "ordering", Template.VarString (string_of_int ordering);
228                    "has_sectionname",
229                      Template.VarConditional has_sectionname;
230                    "sectionname", Template.VarString sectionname;
231                    "linkname", Template.VarString linkname;
232                    "content",
233                      Template.VarString
234                        (Wikilib.xhtml_of_content dbh hostid content);
235                    "has_divname", Template.VarConditional has_divname;
236                    "divname", Template.VarString divname ]
237                  | _ -> assert false) in
238
239     (* Call an extension to generate the first section in this page? *)
240     let sections =
241       match extension with
242           None -> sections
243         | Some extension ->
244             let content = extension dbh hostid page' in
245             let section = [
246               "ordering", Template.VarString "0";
247               "has_sectionname", Template.VarConditional false;
248               "linkname", Template.VarString "";
249               "content", Template.VarString content;
250               "has_divname", Template.VarConditional true;
251               "divname", Template.VarString "form_div";
252             ] in
253             section :: sections in
254
255     t#table "sections" sections;
256
257     (* Are we showing an old version of the page?  If so, warn. *)
258     (match version with
259          None ->
260            t#conditional "is_old_version" false
261        | Some pageid ->
262            t#conditional "is_old_version" true;
263            t#set "old_version" (string_of_int pageid));
264
265     (* Login status. *)
266     (match user with
267          Anonymous ->
268            t#conditional "user_logged_in" false
269        | User (_, username, _, _) ->
270            t#conditional "user_logged_in" true;
271            t#set "username" username);
272
273     (* If logged in, we want to update the recently_visited table. *)
274     if pageid <> None then (
275       match user with
276         | User (userid, _, _, _) ->
277             let sth = dbh#prepare_cached "delete from recently_visited
278                                            where hostid = ? and userid = ?
279                                              and url = ?" in
280             sth#execute [`Int hostid; `Int userid; `String page'];
281             let sth = dbh#prepare_cached
282                         "insert into recently_visited (hostid, userid, url)
283                          values (?, ?, ?)" in
284             sth#execute [`Int hostid; `Int userid; `String page'];
285             dbh#commit ()
286         | _ -> ()
287     );
288
289     (* Navigation links. *)
290     if navigation then (
291       let max_links = 18 in             (* Show no more links than this. *)
292
293       (* What links here. *)
294       let wlh = what_links_here dbh hostid page' in
295       let wlh = List.take max_links wlh in
296       let wlh_urls = List.map fst wlh in (* Just the URLs ... *)
297
298       let rv =
299         match user with
300           | User (userid, _, _, _) ->
301               (* Recently visited URLs, but don't repeat any from the 'what
302                * links here' section, and don't link to self.
303                *)
304               let not_urls = page' :: wlh_urls in
305               let limit = max_links - List.length wlh_urls in
306               let qs = Dbi.placeholders (List.length not_urls) in
307               let sth =
308                 dbh#prepare_cached
309                   ("select rv.url, p.title, rv.visit_time
310                       from recently_visited rv, pages p
311                      where rv.hostid = ? and rv.userid = ?
312                        and rv.url not in " ^ qs ^ "
313                        and rv.hostid = p.hostid and rv.url = p.url
314                      order by 3 desc
315                      limit ?") in
316               let args = List.map (fun s -> `String s) not_urls in
317               sth#execute
318                 ([`Int hostid; `Int userid] @ args @ [`Int limit]);
319               sth#map
320                 (function [`String url; `String title; _] ->
321                    url, title
322                    | _ -> assert false)
323           | _ -> [] in
324
325       (* Links to page. *)
326       let f (page, title) = [ "page", Template.VarString page;
327                               "title", Template.VarString title ] in
328       let table = List.map f wlh in
329       t#table "what_links_here" table;
330       t#conditional "has_what_links_here" (wlh <> []);
331
332       let table = List.map f rv in
333       t#table "recently_visited" table;
334       t#conditional "has_recently_visited" (rv <> []);
335
336       (* If both lists are empty (ie. an empty navigation box would
337        * appear), then disable navigation altogether.
338        *)
339       if wlh = [] && rv = [] then t#conditional "navigation" false
340     );
341
342     (* If we are coming from a search engine then we want to highlight
343      * search terms throughout the whole page ...
344      *)
345     try
346       let referer = Table.get (Request.headers_in r) "Referer" in
347       let search_terms = search_terms_from_referer referer in
348
349       (* Highlight the search terms. *)
350       let xhtml = t#to_string in
351       let xhtml = highlight_search_terms xhtml search_terms "search_term" in
352
353       (* Deliver the page. *)
354       q#header ();
355       ignore (print_string r xhtml)
356     with
357         Not_found ->
358           (* No referer / no search terms / not a search engine referer. *)
359           q#template t
360   in
361
362   (* This code generates 404 pages. *)
363   let make_404 () =
364     Request.set_status r 404;           (* Return a 404 error code. *)
365
366     let t = template_404 in
367     t#set "page" page;
368
369     let search_terms =
370       String.map
371         (function
372              ('a'..'z' | 'A'..'Z' | '0'..'9') as c -> c
373            | _ -> ' ') page in
374
375     t#set "search_terms" search_terms;
376
377     t#conditional "has_host_css" has_host_css;
378     t#conditional "can_edit" can_edit;
379     t#conditional "can_manage_users" can_manage_users;
380     t#conditional "has_stats" has_stats;
381
382     q#template t
383   in
384
385   (* Fetch a page by name.  This function can give three answers:
386    * (1) Page fetched OK (fetches some details of the page).
387    * (2) Page is a redirect (fetches the name of the redirect page).
388    * (3) Page not found in database, could be template or 404 error.
389    *)
390   (* XXX Should do a case-insensitive matching of URLs, and if the URL differs
391    * in case only should redirect to the lowercase version.
392    *)
393   let fetch_page page version allow_redirect =
394     match version with
395       | None ->
396           if allow_redirect then (
397             let sth =
398               dbh#prepare_cached
399                 "select redirect, id, title, description, last_modified_date,
400                         css is not null
401                    from pages where hostid = ? and url = ?" in
402             sth#execute [`Int hostid; `String page];
403             (try
404                (match sth#fetch1 () with
405                   | [ `Null; `Int id; `String title; `String description;
406                       `Timestamp last_modified_date; `Bool has_page_css ] ->
407                       FPOK (id, title, description, last_modified_date,
408                             has_page_css)
409                   | `String redirect :: _ ->
410                       FPRedirect redirect
411                   | _ -> assert false)
412              with
413                  Not_found -> FPNotFound)
414           ) else (* redirects not allowed ... *) (
415             let sth =
416               dbh#prepare_cached
417                 "select id, title, description, last_modified_date,
418                         css is not null
419                    from pages where hostid = ? and url = ?" in
420             sth#execute [`Int hostid; `String page];
421             (try
422                (match sth#fetch1 () with
423                   | [ `Int id; `String title; `String description;
424                       `Timestamp last_modified_date; `Bool has_page_css ] ->
425                       FPOK (id, title, description, last_modified_date,
426                             has_page_css)
427                   | _ -> assert false)
428              with
429                  Not_found -> FPNotFound)
430           )
431       | Some version ->
432             let sth =
433               dbh#prepare_cached
434                 "select id, title, description, last_modified_date,
435                         css is not null
436                    from pages
437                   where hostid = ? and id = ? and
438                         (url = ? or url_deleted = ?)" in
439             sth#execute [`Int hostid; `Int version;
440                          `String page; `String page];
441             (try
442                (match sth#fetch1 () with
443                   | [ `Int id; `String title; `String description;
444                       `Timestamp last_modified_date; `Bool has_page_css ] ->
445                       FPOK (id, title, description, last_modified_date,
446                             has_page_css)
447                   | _ -> assert false)
448              with
449                  Not_found -> FPNotFound)
450   in
451
452   (* Here we deal with the complex business of redirects and versions. *)
453   (* Only allow the no_redirect and version syntax for editors. *)
454   let allow_redirect, version =
455     if can_edit then (
456       not (q#param_true "no_redirect"),
457       try Some (int_of_string (q#param "version")) with Not_found -> None
458     ) else
459       (true, None) in
460
461   let rec loop page' i =
462     if i > max_redirect then (
463       error ~title:"Too many redirections" ~back_button:true
464         q ("Too many redirects between pages.  This may happen because " ^
465            "of a cycle of redirections.");
466       return ()
467     ) else
468       match fetch_page page' version allow_redirect with
469         | FPOK (pageid, title, description, last_modified_date, has_page_css)->
470             (* Check if the page is also a template. *)
471             let extension = get_extension page' in
472             make_page title (Some description) (Some pageid)
473               (printable_date last_modified_date) has_page_css
474               version page page' extension
475         | FPRedirect page' ->
476             loop page' (i+1)
477         | FPNotFound ->
478             (* Might be a templated page with no content in it. *)
479             let extension = get_extension page' in
480             (match extension with
481                | (Some _) as extension ->
482                    let title = page' in
483                    make_page title None None
484                      "Now" false None page page'
485                      extension
486                | None ->
487                    make_404 ())
488   in
489   loop page 0
490
491 let () =
492   register_script ~restrict:[CanView] run