1:- module(login_forgot, [
    2          forgot_password_link//0]).

*

   11:- use_module(library(http/http_dispatch)).   12:- use_module(library(http/html_write)).   13:- use_module(library(http/http_parameters)).   14:- ensure_loaded(library(identity/login_register)).   15:- use_module(library(identity/login_email), [send_forgot_email/1]).   16:- use_module(library(identity/customize)).   17:- use_module(library(identity/login_crypto), [password_hash/2]).   18:- use_module(library(identity/login_database), [user_property/2, set_user_property/2]).   19:- use_module(library(http/http_client)).   20
   21:- setting(identity:reset_email_life, integer, 86400,
   22           "Time a password reset email is valid").   23
   24% where the 'forgot my pw' link goes
   25:- http_handler(login(forgot), forgot_form_handler, [priority(-100), id(forgot)]).   26% where user goes after entering email at form on above page
   27:- http_handler(login(doforgot), doforgot_form_handler, [priority(-100), id(doforgot)]).   28% Where the emailed link takes the user
   29:- http_handler(login(resetpw), resetpw_form_handler, [prefix, priority(-100), id(resetpw)]).   30% Where the form presented in resetpw takes the user
   31:- http_handler(login(doactualpwreset), do_actual_reset_handler, [priority(-100),
   32                                                               id(doactualpwreset)]).   33
   34forgot_password_link -->
   35      html([
   36          a(href(location_by_id(forgot)), \local('Forgot my password'))
   37      ]).
   38
   39% Where the 'Forgot password' link goes
   40forgot_form_handler(_Request) :-
   41      setting(identity:style, Style),
   42      reply_html_page(
   43          Style,
   44          title(\local('Gather Email')),
   45          \forgot_form_page).
   46
   47% todo client side validation of this.
   48forgot_form_page -->
   49    html([
   50        form([method('POST'), action(location_by_id(doforgot))],
   51             [
   52                 h1(class('forgotheader'), \local('Password reset')),
   53                 p(
   54\local('Enter your email address. An email with a password reset link will be sent')),
   55                 p([input([name(email), type(email), required]),
   56                 input([name(submit), type(submit), value('Send')])])
   57             ])
   58    ]).
   59
   60% doforget landing page, Where you go after entering your
   61% email
   62doforgot_form_handler(Request) :-
   63      setting(identity:style, Style),
   64      member(method(post), Request), !,
   65      http_read_data(Request, Data, []),
   66      member(email=Email, Data),
   67      send_forgot_email(Email),
   68      reply_html_page(
   69          Style,
   70          title(\local('Email Sent')),
   71          \doforgot_page).
   72
   73doforgot_page -->
   74      html([h1(\local('Email Sent')),
   75            p(\local('An email has been sent to this address if that email has an account.'))
   76            % TODO should there be a back button? needs to go not 'back', but back 2
   77           ]).
   78
   79% last two segments are /username/key
   80resetpw_form_handler(Request) :-
   81      setting(identity:style, Style),
   82      member(path(P), Request),
   83      atom_string(P, PS),
   84      split_string(PS, "/", "/", PL),
   85      reverse(PL, [URIKey, URIUName | _]),
   86      reply_html_page(
   87          Style,
   88          title(\local('Reset Password')),
   89          \resetpw_form_page(URIUName, URIKey)).
   90
   91resetpw_form_page(URIUName, URIKey) -->
   92      { local('New Password', NewPasswordPlaceholder),
   93        local('Repeat New Password', NewPasswordPlaceholder2),
   94        local('Change', CH),
   95        www_form_encode(UName, URIUName)
   96      },
   97      html([h1(\local('Reset Password')),
   98           div(p(\local('Reset password for ~w'-[UName]))),
   99           form([method('POST'), action(location_by_id(doactualpwreset))],
  100               [
  101                input([type(hidden), name(uname), value(URIUName)]),
  102                input([type(hidden), name(resetkey), value(URIKey)]),
  103                input([type(password), name(passwd), placeholder(NewPasswordPlaceholder)]),
  104                input([type(password), name(passwd2), placeholder(NewPasswordPlaceholder2)]),
  105                input([type(submit), name(submit), value(CH)])
  106                ])]).
  107
  108do_actual_reset_handler(Request) :-
  109      setting(identity:style, Style),
  110      http_parameters(Request,
  111                      [
  112                          uname(UName, []),
  113                          resetkey(Key, []),
  114                          passwd(PassWD, []),
  115                          passwd2(PassWD2, [])
  116                      ]),
  117      (   PassWD = PassWD2,
  118          change_password(UName, Key, PassWD)
  119      ->
  120          http_location_by_id(login_form, SuccessURL),
  121          http_redirect(see_other, SuccessURL, Request)
  122      ;
  123          reply_html_page(
  124              Style,
  125              title(\local('Cannot Reset Password')),
  126              \bad_reset_page)
  127      ).
  128
  129bad_reset_page -->
  130      html([
  131          h1(\local('Cannot Reset Password')),
  132          p('We cannot reset your password. Either you entered two unmatched passwords, or your password reset link has expired')
  133      ]).
  134
  135% succeeds if we changed the pw
  136change_password(UName, Key, PassWD) :-
  137      user_property(UName, forgot_pw(Key=Time)), % also checks user exists
  138      get_time(Now),
  139      setting(identity:reset_email_life, Delta),
  140      Delta > Now - Time,
  141      password_hash(PassWD, Hash),
  142      set_user_property(UName, password_hash(Hash))