View source with raw comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@cs.vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (C): 2013, VU University Amsterdam
    7
    8    This program is free software; you can redistribute it and/or
    9    modify it under the terms of the GNU General Public License
   10    as published by the Free Software Foundation; either version 2
   11    of the License, or (at your option) any later version.
   12
   13    This program is distributed in the hope that it will be useful,
   14    but WITHOUT ANY WARRANTY; without even the implied warranty of
   15    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   16    GNU General Public License for more details.
   17
   18    You should have received a copy of the GNU General Public
   19    License along with this library; if not, write to the Free Software
   20    Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
   21
   22    As a special exception, if you link this library with other files,
   23    compiled with a Free Software compiler, to produce an executable, this
   24    library does not by itself cause the resulting executable to be covered
   25    by the GNU General Public License. This exception does not however
   26    invalidate any other reasons why the executable file might be covered by
   27    the GNU General Public License.
   28*/
   29
   30:- module(pack_review,
   31	  [ pack_rating_votes/3,	% +Pack, -Rating, -Votes
   32	    pack_comment_count/2,	% +Pack, -CommentCount
   33	    pack_reviews//1,		% +Pack
   34	    show_pack_rating//1,	% +Pack
   35	    show_pack_rating//5,	% +Pack, +Rating, +Votes, +Comment, +Opts
   36	    profile_reviews//1,		% +UUID
   37	    user_review_count/2		% +UUID, -Count
   38	  ]).   39:- use_module(library(http/http_dispatch)).   40:- use_module(library(http/http_parameters)).   41:- use_module(library(http/html_write)).   42:- use_module(library(http/html_head)).   43:- use_module(library(persistency)).   44:- use_module(library(aggregate)).   45:- use_module(library(record)).   46
   47:- use_module(markitup).   48:- use_module(rating).   49:- use_module(openid).   50:- use_module(wiki).   51
   52:- http_handler(root(pack/review),        pack_review,        []).   53:- http_handler(root(pack/review/submit), pack_submit_review, []).   54:- http_handler(root(pack/review/rating), pack_rating,        []).

Handle rating and reviewing of packages

*/

   59		 /*******************************
   60		 *	       DATA		*
   61		 *******************************/
   62
   63:- persistent
   64	review(pack:atom,
   65	       user:atom,		% UUID of the user
   66	       time:number,
   67	       rating:integer,
   68	       comment:atom).   69
   70:- db_attach('reviews.db', []).   71
   72
   73		 /*******************************
   74		 *	     INTERFACE		*
   75		 *******************************/
 pack_review(+Request)
HTTP handler to review a pack.
   81pack_review(Request) :-
   82	site_user(Request, UUID),
   83	http_parameters(Request,
   84			[ p(Pack, [])
   85			]),
   86	http_link_to_id(pack_submit_review, [], Action),
   87	reply_html_page(
   88	    wiki(review(Pack)),
   89	    title('Review pack ~w'-[Pack]),
   90	    [ h1('Review pack ~w'-[Pack]),
   91	      \explain(Pack, UUID),
   92	      \html_requires(css('pack.css')),
   93	      form([ class(review), action(Action), method('POST') ],
   94		   [ input([type(hidden), name(p), value(Pack)]),
   95		     table([ \reviewer(Request, UUID),
   96			     \rating(Pack, UUID),
   97			     \comment(Pack, UUID),
   98			     tr(td([colspan(2), align(right)],
   99				   input([ type(submit),
  100					   value('Submit review')
  101					 ])))
  102			   ])
  103		   ])
  104	    ]).
  105
  106
  107explain(Pack, UUID) -->
  108	{ site_user_property(UUID, name(Name))
  109	},
  110	html([ p([ 'Dear ', Name, ', you requested to review pack ', b(Pack), '. ',
  111		   'The text field uses PlDoc wiki format, which is a ',
  112		   'superset of Markdown.  You can use the two ',
  113		   'left-most icons to open and close a preview window.'
  114		 ]),
  115	       p([ 'Any user can have at most one review per pack.  Trying ',
  116		   'to submit a new review will return the old review and ',
  117		   'allow you to update your opinion.'
  118		 ])
  119	     ]).
 reviewer(+Request, +UUID)// is det
Present details about the reviewer
  125reviewer(Request, UUID) -->
  126	{ site_user_property(UUID, name(Name)),
  127	  option(request_uri(RequestURI), Request),
  128	  http_link_to_id(create_profile, [return(RequestURI)], UpdateURL),
  129	  Update = a([class(update), href(UpdateURL)], 'Update profile')
  130	}, !,
  131	html([ tr([th('User:'),   td([ input([ name(name),
  132					       value(Name),
  133					       disabled(disabled)
  134					     ]),
  135				       Update
  136				     ])])
  137	     ]).
  138
  139
  140rating(Pack, UUID) -->
  141	{ http_link_to_id(pack_rating, [], HREF),
  142	  (   review(Pack, UUID, _, Rating0, _),
  143	      Rating0 > 0
  144	  ->  Extra = [data_average(Rating0)]
  145	  ;   Extra = [data_average(0)],
  146	      Rating0 = 0
  147	  )
  148	},
  149	html(tr([ th('Your rating for ~w:'-[Pack]),
  150		  td( [ input([type(hidden), name(rating), value(Rating0)]),
  151			\rate([ on_rating(HREF),
  152				data_id(Pack),
  153				set_field(rating),
  154				rate_max(5),
  155				step(true),
  156				type(big),
  157				can_rate_again(true)
  158			      | Extra
  159			      ])
  160		      ])
  161		])).
 pack_rating(+Request)
Handle the actual rating
  168pack_rating(Request) :-
  169	http_parameters(Request,
  170			[ idBox(IdBox, []),
  171			  rate(Rate, [number])
  172			], []),
  173	debug(rating, 'Got idBox = ~q, Rate = ~q', [IdBox,Rate]),
  174	format('Content-type: text/plain\n\n'),
  175	format('true\n').
  176
  177
  178comment(Pack, UUID) -->
  179	{ (   review(Pack, UUID, _, _, Comment)
  180	  ->  Extra = [value(Comment)]
  181	  ;   Extra = []
  182	  )
  183	},
  184	html(tr(td(colspan(2),
  185		   \markitup([ id(comment),
  186			       markup(pldoc),
  187			       cold(60),
  188			       rows(10)
  189			     | Extra
  190			     ])))).
 pack_submit_review(+Request)
Handle a pack review submission
  197pack_submit_review(Request) :-
  198	site_user(Request, UUID),
  199	http_parameters(Request,
  200			[ p(Pack, []),
  201			  rating(Rating, [number]),
  202			  comment(Comment, [optional(true), default('')])
  203			]),
  204	reply_html_page(
  205	    wiki(review(Pack)),
  206	    title('Thanks for your review of ~w'-[Pack]),
  207	    [ \update_review(Pack, UUID, Rating, Comment)
  208	    ]).
 update_review(+Pack, +UUID, +Rating, +Comment)// is det
Assert/update a review about a pack.
  215update_review(Pack, UUID, Rating, Comment) -->
  216	{ review(Pack, UUID, _Time, Rating, Comment) }, !,
  217	html(h4(class(wiki), 'No changes, showing your existing comment')),
  218	show_review(Pack, UUID),
  219	refresh(Pack).
  220update_review(Pack, UUID, Rating, Comment) -->
  221	{ review(Pack, UUID, _Time, _Rating, _Comment), !,
  222	  retractall_review(Pack, UUID, _, _, _),
  223	  get_time(TimeF),
  224	  Time is round(TimeF),
  225	  assert_review(Pack, UUID, Time, Rating, Comment)
  226	},
  227	html(h4(class(wiki), 'Updated your comments for pack ~w'-[Pack])),
  228	show_review(Pack, UUID),
  229	refresh(Pack).
  230update_review(Pack, UUID, Rating, Comment) -->
  231	{ get_time(Time),
  232	  assert_review(Pack, UUID, Time, Rating, Comment)
  233	},
  234	html(h4(class(wiki), 'Added comment for pack ~w'-[Pack])),
  235	show_review(Pack, UUID),
  236	refresh(Pack).
  237
  238refresh(Pack) -->
  239       { http_link_to_id(pack_list,   [p(Pack)], ListPack),
  240	 Delay = 3
  241       },
  242       html([ 'Redirecting to pack ', a(href(ListPack), Pack),
  243	      ' in ~w seconds'-[Delay]
  244	    ]),
  245       html_post(head,
  246		 meta([ 'http-equiv'(refresh),
  247			content(Delay+';'+ListPack)
  248		      ])).
  249
  250
  251		 /*******************************
  252		 *	   SHOW RESULTS		*
  253		 *******************************/
 pack_reviews(Pack)// is det
Show reviews for Pack
  259pack_reviews(Pack) -->
  260	html(h2(class(wiki), 'Reviews')),
  261	show_reviews(Pack).
  262
  263show_reviews(Pack) -->
  264	{ \+ review(Pack, _, _, _, _), !,
  265	  http_link_to_id(pack_review, [p(Pack)], HREF)
  266	},
  267	html([ p([ 'No reviews.  ',
  268		   a(href(HREF), 'Create'), ' the first review!.'
  269		 ])
  270	     ]).
  271show_reviews(Pack) -->
  272	{ findall(review(Pack, UUID, Time, Rating, Comment),
  273		  ( review(Pack, UUID, Time, Rating, Comment),
  274		    Comment \== ''
  275		  ),
  276		  Reviews),
  277	  length(Reviews, Count),
  278	  sort_reviews(time, Reviews, Sorted)
  279	},
  280	html([ div(\review_action(Pack)),
  281	       div(class(smallprint), \showing_reviews(Count))
  282	     ]),
  283	list_reviews(Sorted, []).
  284
  285review_action(Pack) -->
  286	{ site_user_logged_in(User),
  287	  review(Pack, User, Time, _Rating, _Comment),
  288	  http_link_to_id(pack_review, [p(Pack)], HREF)
  289	}, !,
  290	html([ a(href(HREF), 'Update'), ' your rating or review from ',
  291	       \show_time(Time), '.'
  292	     ]).
  293review_action(Pack) -->
  294	{ http_link_to_id(pack_review, [p(Pack)], HREF)
  295	},
  296	html([ a(href(HREF), 'Write'), ' a review or add a rating.' ]).
  297
  298showing_reviews(Count) -->
  299	{ Count >= 2 },
  300	html([ 'Showing ~D reviews, '-[Count],
  301	       'sorted by date entered, last review first. '
  302	     ]).
  303showing_reviews(_) --> [].
  304
  305
  306list_reviews([], _) --> [].
  307list_reviews([H|T], Options) --> list_review(H, Options), list_reviews(T, Options).
  308
  309list_review(Review, Options) -->
  310	{ review_name(Review, Pack),
  311	  review_user(Review, UUID),
  312	  review_time(Review, Time),
  313	  review_rating(Review, Rating),
  314	  review_comment(Review, Comment)
  315	},
  316	html([ div(class(review),
  317		   [ div(class(rating),
  318			 [ \show_pack(Pack, Options),
  319			   \show_rating_value(Pack, Rating, [])
  320			 ]),
  321		     div(class(comment),  \show_comment(Comment)),
  322		     div(class(reviewer), \show_reviewer(UUID, Time))
  323		   ])
  324	     ]).
  325
  326:- record
  327	  review(name:atom,
  328		 user:atom,
  329		 time:number,
  330		 rating:integer,
  331		 comment:atom).  332
  333sort_reviews(By, Reviews, Sorted) :-
  334	map_list_to_pairs(review_data(By), Reviews, Keyed),
  335	keysort(Keyed, KeySorted),
  336	pairs_values(KeySorted, Sorted0),
  337	reverse(Sorted0, Sorted).
 show_review(+Pack, +UUID)// is det
Show an individual review about Pack
  343show_review(Pack, UUID) -->
  344	{ review(Pack, UUID, _Time, Rating, Comment),
  345	  http_link_to_id(pack_review, [p(Pack)], Update),
  346	  http_link_to_id(pack_list,   [p(Pack)], ListPack)
  347	},
  348	html_requires(css('pack.css')),
  349	html([ div(class(review),
  350		   [ b('Reviewer: '),    \show_reviewer(UUID), ', ',
  351		     b('Your rating: '), \show_rating_value(Pack, Rating, []),
  352		     b('Average rating: '), \show_rating(Pack),
  353		     div(class(comment), \show_comment(Comment)),
  354		     ul([ li([a(href(Update), 'Update'), ' my review']),
  355			  li([a(href(ListPack), 'View'), ' pack ', Pack])
  356			])
  357		   ])
  358	     ]).
 show_pack(Pack, +Options)// is det
  363show_pack(Pack, Options) -->
  364	{ option(show_pack(true), Options), !,
  365	  http_link_to_id(pack_list, [p(Pack)], HREF)
  366	},
  367	html(span(['Pack: ', a(href(HREF), Pack)])).
  368show_pack(_, _) --> [].
 show_reviewer(+UUID)
  373show_reviewer(UUID) -->
  374	{ site_user_property(UUID, name(Name)),
  375	  http_link_to_id(view_profile, [user(UUID)], HREF),
  376	  Name \== '',
  377	  aggregate_all(count,
  378			( review(_, UUID, _, _, Comment), Comment \== '' ),
  379			Comments),
  380	  aggregate_all(count-sum(Rating),
  381			( review(_, UUID, _, Rating, _), Rating > 0 ),
  382			Ratings-Sum),
  383	  (   Ratings > 0
  384	  ->  Avg is Sum/Ratings,
  385	      format(atom(Title), '~D comments, ~D ratings (avg ~1f)',
  386		     [Comments, Ratings, Avg])
  387	  ;   format(atom(Title), '~D comments', [Comments])
  388	  )
  389	}, !,
  390	html(a([class(user), href(HREF), title(Title)], Name)).
  391show_reviewer(_UUID) -->
  392	html(i(anonymous)).
 show_reviewer(+UUID, +Time)
  396show_reviewer(UUID, Time) -->
  397	show_time(Time),
  398	html(', '),
  399	show_reviewer(UUID).
  400
  401show_time(Time) -->
  402	{ format_time(atom(Date), '%A %d %B %Y', Time)
  403	},
  404	html(Date).
  405
  406show_rating(Pack) -->
  407	{ pack_rating_votes(Pack, Rating, Votes),
  408	  pack_comment_count(Pack, Count)
  409	},
  410	show_pack_rating(Pack, Rating, Votes, Count, []).
 show_pack_rating(+Pack)// is det
Show overall rating. If there is no rating, offer to create one.
  416show_pack_rating(Pack) -->
  417	{ pack_rating_votes(Pack, Rating, Votes) },
  418	(   { Votes =:= 0 }
  419	->  { http_link_to_id(pack_review, [p(Pack)], HREF) },
  420	    html(span(class(not_rated),
  421		      [ 'Not rated.  ', a(href(HREF), 'Create'),
  422			' the first rating!'
  423		      ]))
  424	;   { pack_comment_count(Pack, Count) },
  425	    show_pack_rating(Pack, Rating, Votes, Count, [])
  426	).
 pack_rating_votes(+Pack, -Rating, -Votes) is det
Rating is the current rating for Pack, based on Votes.
  433pack_rating_votes(Pack, Rating, Votes) :-
  434	aggregate_all(count-sum(R), pack_rating(Pack, R), Votes-Sum),
  435	Votes > 0, !,
  436	Rating is Sum/Votes.
  437pack_rating_votes(_Pack, 0, 0).
  438
  439pack_rating(Pack, Rating) :-
  440	review(Pack, _, _, Rating, _),
  441	Rating > 0.
 pack_comment_count(Pack, Count)
True when Count is the number of comments for Pack.
  447pack_comment_count(Pack, Count) :-
  448	aggregate_all(count,
  449		      ( review(Pack, _, _, _, Comment),
  450			Comment \== ''
  451		      ),
  452		      Count).
  453
  454
  455show_rating_value(Pack, Value, Options) -->
  456	rate([ rate_max(5),
  457	       data_id(Pack),
  458	       type(small),
  459	       disabled(true),
  460	       class(rated),
  461	       post(script),
  462	       data_average(Value)
  463	     | Options
  464	     ]).
 show_pack_rating(+Pack, +Rating, +Votes, +CommentCount, +Options)// is det
Show rating for Pack.
  471show_pack_rating(Pack, Rating, 0, 0, Options) --> !,
  472	show_rating_value(Pack, Rating, Options).
  473show_pack_rating(Pack, Rating, Votes, Count, Options) -->
  474	html(span(class(rating),
  475		  [ \show_rating_value(Pack, Rating, Options),
  476		    span(class(votes), ' (~D/~D)'-[Votes, Count])
  477		  ])).
 show_comment(+Comment)// is det
Display Comment. Comment is an atom holding Wiki text.
  483show_comment('') --> !,
  484	html(i('No comment')).
  485show_comment(Text) -->
  486	{ atom_codes(Text, Codes),
  487	  wiki_file_codes_to_dom(Codes, /, DOM0),
  488	  clean_dom(DOM0, DOM)
  489	},
  490	html(DOM).
  491
  492clean_dom([p(X)], X) :- !.
  493clean_dom(X, X).
  494
  495
  496		 /*******************************
  497		 *	 PROFILE COMPONENTS	*
  498		 *******************************/
 profile_reviews(+UUID)// is det
Create a h2 section with all reviews by a given OpenID.
  504profile_reviews(UUID) -->
  505	{ findall(review(Pack, UUID, Time, Rating, Comment),
  506		  review(Pack, UUID, Time, Rating, Comment),
  507		  Reviews),
  508	  Reviews \== [], !,
  509	  length(Reviews, Count),
  510	  sort_reviews(time, Reviews, Sorted),
  511	  site_user_property(UUID, name(Name))
  512	},
  513	html_requires(css('pack.css')),
  514	html([ h2(class(wiki), 'Reviews by ~w'-[Name]),
  515	       p([ \showing_reviews(Count)
  516		 ])
  517	     ]),
  518	list_reviews(Sorted, [show_pack(true)]).
  519profile_reviews(_) -->
  520	[].
 user_review_count(+UUID, -Count) is det
True when Count is the number of reviews by UUID.
  527user_review_count(UUID, Count) :-
  528	aggregate_all(count, review(_, UUID, _, _, _), Count)