1:- module(notes800, [caller_id/3]).    2:- use_module(library(dcg/basics), [integer//1,string//1,string_without//2]).    3:- use_module(library(delay)).    4:- use_module(library(rbtrees)).    5:- use_module(library(pairs)).    6:- use_module(library(solution_sequences)).    7:- use_module(library(web), []).    8:- use_module(library(xpath)).    9
   10% Naming conventions:
   11%
   12% `Phone` - a phone number
   13% `PageN` - the number of an HTML page of results
 caller_id(+Phone:string, -Caller:string, -Type:atom) is det
Determine the Caller and call Type for a given Phone number. If 800notes.com lacks information for Caller, a default value of "Unknown" is used; for Type, a default of unknown.
   20caller_id(Phone,Caller,Type) :-
   21    rb_empty(EmptyCallers),
   22    rb_empty(EmptyTypes),
   23    A0 = x(EmptyCallers,EmptyTypes),
   24    fold_solutions(accum(Name,Value),limit(10,attribute(Phone,Name,Value)),A0,A),
   25    A= x(Callers,Types),
   26    once( rb_popular(Callers,Caller); Caller="Unknown" ),
   27    once( rb_popular(Types,Type); Type=unknown ),
   28    !.
   29caller_id(_,"Unknown",unknown).
   30
   31accum(caller,Caller,x(T0,X),x(T,X)) :-
   32    !,
   33    rb_increment(T0,Caller,T).
   34accum(type,Value,x(X,T0),x(X,T)) :-
   35    !,
   36    rb_increment(T0,Value,T).
   37accum(_,_,Accum,Accum).
   38
   39rb_increment(T0,Key,T) :-
   40    ( rb_update(T0,Key,Old,New,T) ->
   41        succ(Old,New)
   42    ; otherwise ->
   43        rb_insert(T0,Key,1,T)
   44    ).
   45
   46rb_popular(T,Key) :-
   47    rb_visit(T,Pairs),
   48    transpose_pairs(Pairs,LeastToGreatest),
   49    reverse(LeastToGreatest,[_-Key|_]).
   50
   51
   52fold_solutions(F,Goal,Accum0,Accum) :-
   53    Ref = ref(Accum0),
   54    ( call(Goal),
   55      Ref = ref(A0),
   56      call(F,A0,A1),
   57      nb_setarg(1,Ref,A1),
   58      fail
   59    ; Ref = ref(Accum)
   60    ).
 attribute(+Phone, -Name, -Value) is multi
   64attribute(Phone,Name,Value) :-
   65    page(Phone,Page),
   66    comment(Page,Comment),
   67    detail(Comment,Name,Value).
   68
   69url(Phone,Url) :-
   70    url(Phone,1,Url).
   71
   72url(Phone,PageN,Url) :-
   73    once(phrase(url(Phone,PageN),Url)).
   74
   75url(Phone,PageN) -->
   76    "http://800notes.com",
   77    path(Phone,PageN).
   78url(Phone,PageN) -->
   79    path(Phone,PageN).
 pager_specific(+Dom, -PageN:integer, -Url:codes)
Iterates each distinct link pointing to a specific page of results.
   84pager_specific(Dom,PageN,Url) :-
   85    distinct([PageN],pager_link_(Dom,PageN,Url)).
   86
   87pager_link_(Dom,PageN,Url) :-
   88    xpath(Dom,//div(@id='treeThread')/div(contains(@class,oos_pager))/a(@href=Href),_),
   89    atom_codes(Href,RelativeUrl),
   90    url(Phone,PageN,RelativeUrl),
   91    url(Phone,PageN,Url).
   92
   93path(Phone,PageN) -->
   94    { delay(string_codes(Phone,PhoneCodes)) },
   95    "/Phone.aspx/",
   96    string_without(`/`,PhoneCodes),
   97    page_n(PageN).
   98
   99page_n(1) -->
  100    "".
  101page_n(N) -->
  102    "/",
  103    integer(N).
 page(+Phone, -Page)
Iterates each Page of results for a given Phone from youngest to oldest.
  110page(Phone,Page) :-
  111    url(Phone,1,Url),
  112    web:get(Url,[html5(FirstPage)]),
  113    once( aggregate(max(N),U^pager_specific(FirstPage,N,U),MaxPageN)
  114        ; MaxPageN = 1
  115        ),
  116    ( page_(Phone,MaxPageN,Page)
  117    ; Page=FirstPage
  118    ).
  119
  120page_(Phone,PageN,Page) :-
  121    PageN > 1,
  122    url(Phone,PageN,Url),
  123    web:get(Url,[html5(Dom)]),
  124    ( Page=Dom
  125    ; succ(PrevPageN,PageN),
  126      page_(Phone,PrevPageN,Page)
  127    ).
 comment(+Page, -Comment)
Iterates each Comment on a Page.
  133comment(Page,Comment) :-
  134    xpath(Page,//div(contains(@class,oos_init))/ul/li, Comment).
 detail(+Comment, -Type, -Value)
Iterates each Detail within a Comment.
  140detail(Comment,Type,Value) :-
  141    xpath(Comment,//div(contains(@class,callDetails))/div(text),Text),
  142    atom_codes(Text,Codes),
  143    phrase(detail(Type,Value),Codes).
  144
  145detail(caller,Value) -->
  146    "Caller: ",
  147    string(Codes),
  148    { string_codes(Value,Codes) }.
  149detail(type,Value) -->
  150    "Call Type: ",
  151    string(Raw),
  152    { maplist(transform_type,Raw,Transformed) },
  153    { atom_codes(Value,Transformed) }.
  154
  155transform_type(0' ,0'_) :- !.
  156transform_type(U,L) :-
  157    code_type(U,upper(L)),
  158    !.
  159transform_type(C,C)