1:- module(login_email,
    2          [
    3              send_activation_email/3,
    4              send_forgot_email/1
    5          ]).

Predicates related to sending out activation emails

/

    9:- use_module(library(http/http_dispatch)).   10:- use_module(library(http/http_parameters)).   11:- use_module(library(identity/login_database)).   12:- use_module(library(http/http_session)).   13
   14% TODO make the response code
   15% TODO make inclusion for email link
   16% TODO make 'resend link'
   17% TODO handle not activated, go to a not-activated page
   18% "hey, you need to answer your email (resend)"
   19%
   20
   21:- multifile login_email:activation_email_hook/3.   22
   23send_activation_email(UName, Email, Key) :-
   24    activation_link(UName, Key, Link),
   25    login_email:activation_email_hook(UName, Email, Link),
   26    !.
   27send_activation_email(UName, Email, Key) :-
   28    activation_link(UName, Key, Link),
   29    debug(identity(email), 'Activation email to ~w link ~w',
   30          [UName, Email, Link]).
   31
   32% TODO change to route variables for key
   33/*
   34 *
   35[21:36] <anniepoo> http_handler(api(user/id), api_handler(Request) , [role(user)]). and somehow one gets
   36[21:37] <anniepoo> http://example.com/api/42/678  routed and can find out user=42 and id=678?
   37[21:37] <RLa> http_handler(api(user/Id), api_handler(Id) , [role(user)]) <- like that
   38[21:37] <anniepoo> ah, cool
   39[21:37] <anniepoo> ok
   40[21:37] <RLa> it saves lots of manual parsing
   41[21:38] <anniepoo> so http://example.com/api/user/42  and Id becomes 42
   42[21:38] <anniepoo> Got it!
   43[21:38] <RLa> yes
   44*/
   45% TODO probably needs base option to not get a relative uri
   46activation_link(UName, Key, Link) :-
   47    http_link_to_id(activate, [], Base),
   48    setting(http:public_host, Host),
   49    setting(http:public_port, Port),
   50    setting(http:public_scheme, Scheme),
   51    (   Port = 80
   52    ->  format(atom(Link), '~w://~w~w~w/~w',
   53               [Scheme, Host, Base, UName, Key])
   54    ;   format(atom(Link), '~w://~w:~w~w/~w',
   55               [Scheme, Host, Port, Base, UName, Key])
   56    ).
   57
   58:- http_handler(login(activate/UName/Key), activate_user(UName, Key), [id(activate)]).   59
   60activate_user(UName, Key, Request) :-
   61    user_property(UName, activation_key(Key)),
   62    user_property(UName, role(needs_activation)),
   63    retractall_user_property(UName, role(needs_activation)),
   64    retractall_user_property(UName, activation_key(_)),
   65    assert_user_property(UName, role(user)),
   66    http_link_to_id(home, [], HREF),
   67    http_redirect(see_other, HREF, Request).
   68% TODO above should actually show an 'ok youre activated' page
   69%
   70% TODO fix to route variable and no login
   71:- http_handler(login(resend/UName), resend_activation(UName),
   72                [id(resend)]).   73
   74resend_activation(UName, Request) :-
   75    assert_user_property(UName, role(needs_activation)),
   76    uuid(Key),
   77    assert_user_property(UName, activation_key(Key)),
   78    user_property(UName, email(Email)),
   79    send_activation_email(UName, Email, Key),
   80    http_link_to_id(home, [], HREF),
   81    http_redirect(see_other, HREF, Request).
   82
   83		 /*******************************
   84		 *     Reset Password           *
   85		 *******************************/
   86
   87:- multifile login_email:forgot_email_hook/3.   88
   89send_forgot_email(EMail) :-
   90    user_property(UName, email(EMail)),
   91    uuid(UUID),
   92    get_time(Time),
   93    assert_user_property(UName, forgot_pw(UUID=Time)),
   94    send_forgot_email(UName, EMail, UUID).
   95send_forgot_email(_).
   96
   97send_forgot_email(UName, Email, Key) :-
   98    forgot_link(UName, Key, Link),
   99    login_email:forgot_email_hook(UName, Email, Link),
  100    !.
  101send_forgot_email(UName, Email, Key) :-
  102    forgot_link(UName, Key, Link),
  103    debug(identity(email), 'Forgot pw email to user ~w at email ~w link ~w',
  104          [UName, Email, Link]).
  105
  106% TODO probably needs base option to not get a relative uri
  107% % TODO refactor to get rid of duplication
  108forgot_link(UName, Key, Link) :-
  109    http_link_to_id(resetpw, [], Base),
  110    setting(http:public_host, Host),
  111    setting(http:public_port, Port),
  112    setting(http:public_scheme, Scheme),
  113    www_form_encode(UName, URIUName),
  114    www_form_encode(Key, URIKey),
  115    (   Port = 80
  116    ->  format(atom(Link), '~w://~w~w/~w/~w',
  117               [Scheme, Host, Base, URIUName, URIKey])
  118    ;   format(atom(Link), '~w://~w:~w~w/~w/~w',
  119               [Scheme, Host, Port, Base, URIUName, URIKey])
  120    )