View source with raw comments or as raw
    1:- module(ag_utils,
    2	  [   mint_node_uri/3,
    3	      assert_user_provenance/2,
    4
    5	      now_xsd/1,
    6	      xsd_timestamp/2,
    7	      has_write_permission/0,
    8
    9	      save_perc/3,
   10	      list_offset/3,
   11	      list_limit/4,
   12	      sort_by_arg/3
   13	  ]).   14
   15:- use_module(library(apply)).   16:- use_module(library(gensym)).   17:- use_module(library(pairs)).   18:- use_module(library(sgml)).   19:- use_module(library(uri)).   20:- use_module(library(semweb/rdf_db)).   21
   22:- use_module(user(user_db)).
 mint_node_uri(+Strategy, +Type, -URI) is det
URI is a new URI in the publish_ns namespace of Strategy, with a Local part that is equal to gensym(Type, Local), such that URI is not already a RDF subject or RDF named graph.
   31mint_node_uri(_Strategy, _Type, URI) :-
   32	ground(URI),!.
   33mint_node_uri(Strategy, Type, URI) :-
   34	ground(Type),
   35	ground(Strategy),
   36	rdf_has(Strategy, amalgame:publish_ns, NS),
   37	atomic_concat(NS, Type, Base),
   38	reset_gensym(Base),
   39	repeat,
   40	gensym(Base, URI),
   41	\+ rdf_subject(URI),
   42	\+ rdf_graph(URI),
   43	!.
   44
   45
   46has_write_permission :-
   47	logged_on(User, anonymous),
   48	catch(check_permission(User, write(default,_)), _, fail).
 assert_user_provenance(+Resource, -NamedGraph)
Assert provenance about create process.
   55assert_user_provenance(R, Graph) :-
   56	logged_on(User),
   57	user_property(User, url(Agent)),
   58	(   user_property(User, realname(Realname))
   59	->  rdf_assert(Agent, rdfs:label, literal(Realname), Graph)
   60	),
   61	now_xsd(Time),
   62	rdf_assert(R, dcterms:creator, Agent, Graph),
   63	rdf_assert(R, dcterms:date, literal(type(xsd:dateTime, Time)), Graph).
 http:convert_parameter(+Type, +In, -URI) is semidet
HTTP parameter conversion for the following types:
uri
This conversion accepts NS:Local and absolute URIs.
   77http:convert_parameter(uri, In, URI) :-
   78	(   sub_atom(In, B, _, A, :),
   79	    sub_atom(In, _, A, 0, Local),
   80	    xml_name(Local)
   81	->  ( (sub_atom(In, 0, B, _, NS), rdf_db:ns(NS,_))
   82	    ->  rdf_global_id(NS:Local, URI)
   83	    ;   URI=In
   84	    )
   85	;   uri_is_global(In)
   86	->  URI = In
   87	).
 now_xsd(-Text:atom)
Text is the current time in xsd:dateTime format.
   94now_xsd(Text) :-
   95	get_time(TimeStamp),
   96	xsd_timestamp(TimeStamp, Text).
 xsd_timestamp(+Time:timestamp, -Text:atom) is det
Generate a description of a Time in xsd:dateTime format
  102xsd_timestamp(Time, Atom) :-
  103	stamp_date_time(Time, Date, 'UTC'),
  104        format_time(atom(Atom), '%FT%T%:z', Date, posix).
 list_offset(+List, +N, -SmallerList)
SmallerList starts at the nth element of List.
  110list_offset(L, N, []) :-
  111	length(L, Length),
  112	Length < N,
  113	!.
  114list_offset(L, N, L1) :-
  115	list_offset_(L, N, L1).
  116
  117list_offset_(L, 0, L) :- !.
  118list_offset_([_|T], N, Rest) :-
  119	N1 is N-1,
  120	list_offset_(T, N1, Rest).
 list_limit(+List, +N, -SmallerList, -Rest)
SmallerList ends at the nth element of List.
  126list_limit(L, N, L, []) :-
  127	N < 0,
  128	!.
  129list_limit(L, N, L, []) :-
  130	length(L, Length),
  131	Length < N,
  132	!.
  133list_limit(L, N, L1, Rest) :-
  134	list_limit_(L, N, L1, Rest).
  135
  136list_limit_(Rest, 0, [], Rest) :- !.
  137list_limit_([H|T], N, [H|T1], Rest) :-
  138	N1 is N-1,
  139	list_limit_(T, N1, T1, Rest).
 sort_by_arg(+ListOfTerms, +Arg, -SortedList)
SortedList contains the Terms from ListOfTerms sorted by their nth Arg.
  147sort_by_arg(List, Arg, Sorted) :-
  148	maplist(arg_key(Arg), List, Pairs),
  149	keysort(Pairs, SortedPairs),
  150	pairs_values(SortedPairs, Sorted).
  151
  152arg_key(Args, Term, Keys-Term) :-
  153	is_list(Args),
  154	!,
  155	args(Args, Term, Keys).
  156arg_key(Arg, Term, Key-Term) :-
  157	arg(Arg, Term, Key).
  158
  159args([A], Term, [Key]) :- !,
  160	arg(A, Term, Key).
  161args([A|As], Term, [Key|Ks]) :-
  162	arg(A, Term, Key),
  163	args(As, Term, Ks).
  164
  165
  166save_perc(_ ,0, 0) :- !.
  167save_perc(0, _, 0) :- !.
  168save_perc(Value, Total, Percentage) :-
  169	Percentage is (100 * Value) / Total