1:- module(login_page, [
    2          login_form//1,
    3          login_hidden_referer//0,
    4          login_user_name_field//0,
    5          login_password_field//0,
    6          login_remember_me_check//0,
    7          login_submit//0,
    8          login_warning//0,
    9          login_register_link//0,
   10          do_actual_login/4]).

*

   23:- use_module(library(http/http_dispatch)).   24:- use_module(library(http/html_write)).   25:- use_module(library(http/http_wrapper)).   26:- use_module(library(http/http_parameters)).   27:- use_module(library(http/http_session)).   28:- use_module(library(identity/login_database)).   29:- ensure_loaded(library(identity/login_register)).   30:- use_module(library(identity/customize)).   31
   32:- http_handler(login(.), login_form_handler,
   33                [id(login_form), priority(-100)]).   34:- http_handler(login(dologin), do_login_handler,
   35                [id(dologin)]).   36
   37login_form_handler(_Request) :-
   38      setting(identity:style, Style),
   39      reply_html_page(
   40          Style,
   41          title(\local('Login Form')),
   42          \login_form_page).
   43
   44:-html_meta login_form(html, ?, ?).
   45
   46login_form(Contents) -->
   47    html(form([class(login),
   48               method('POST'),
   49               action(location_by_id(dologin))],
   50              Contents
   51         )).
   52
   53%  TODO all the UX nits
   54%  TODO validation
   55login_hidden_referer -->
   56    {
   57        (   http_current_request(Request),
   58            memberchk(search(Search), Request),
   59            memberchk(redirect=Referer, Search)
   60        ;
   61            http_location_by_id(home, Referer)  % TODO test this line
   62        )  % TODO test that this uriencodes properly
   63    },
   64    html(input([type(hidden), name(referer), value(Referer)], [])).
   65
   66
   67login_warning -->
   68    {
   69        (   http_current_request(Request),
   70            memberchk(search(Search), Request),
   71            memberchk(warn=Warn, Search)
   72        )
   73    },
   74      html(div([id(warningarea), class([warn, active])], [Warn])).
   75login_warning --> [].
   76
   77login_user_name_field -->
   78    html(input([type(text),
   79                name(uname),
   80                placeholder('User Name'),
   81                required])).
   82
   83login_password_field -->
   84    { local('Password', Placeholder) },
   85    html(input([type(password),
   86                name(passwd),
   87                placeholder(Placeholder),
   88               required])).
   89
   90login_remember_me_check -->
   91    html(input([type(checkbox), name(rememberme)])).
   92
   93login_submit -->
   94    {  local('Log In', Submit) },
   95    html(input([type(submit),
   96                name(submit),
   97                value(Submit)])).
   98
   99login_forgot_password -->
  100      html(a(href(location_by_id(forgot)),
  101             [\local('forgot password or user name')])).
  102
  103login_form_page -->
  104    html(\login_form([
  105              \login_hidden_referer,
  106              div(\login_register_link),
  107              \login_warning,
  108              div([label(for(uname), \local('User Name:')),
  109                   \login_user_name_field]),
  110              div([label(for(passwd), \local('Password:')),
  111                   \login_password_field]),
  112              div([\login_remember_me_check, \local('Remember me')]),
  113              div(\login_forgot_password),
  114              div(\login_submit)
  115          ])).
  116
  117login_register_link -->
  118    html(a(href(location_by_id(register)),
  119                    'Register')).
  120
  121		 /*******************************
  122		 *          Do Login            *
  123		 *******************************/
  124
  125
  126do_login_handler(Request) :-
  127        http_parameters(
  128            Request,
  129            [ referer(SuccessURL, [default(root(.))]), % is this default ok?
  130              uname(UserName, []),
  131              passwd(Password, [])
  132            ]),
  133        authenticate_user(UserName, Password, Status),
  134        do_actual_login(Status, SuccessURL, UserName, Request).
  135do_login_handler(_Request) :-
  136      setting(identity:sytle, Style),
  137      reply_html_page(
  138          Style,
  139          title(\local('improper login')),
  140          \improper_login).
  141
  142% TODO this is public, pldoc it
  143% TODO Let Jan know - throwing is awkward for making links that
  144% are disabled/invisible if the user can't access them.
  145%
  146%  TODO check that this can be overridden
  147%
  148% TODO move ERROR section to it's own module and update README.md
  149%
  150% TODO make rest endpoints work, or at least test that they do
  151% make sure pengines work
  152
  153do_actual_login(ok, SuccessURL, UserName, Request) :-
  154      http_open_session(_SessionId, []),
  155      http_session_assert(user(UserName)),
  156      http_redirect(see_other, SuccessURL, Request).
  157        /*  TODO - make the 'remember me' cookie if remember me checked
  158            make_login_cookie(UserName, Cookie), % TODO now only send cookie if
  159            format('Status: 302 Found~n'),       %
  160            format('Location: ~w~n', [SuccessURL]),
  161            % session cookie, lives until browser exits
  162            % however the cookie itself contains an expiry
  163            % as well
  164            format('Set-Cookie: login=~w; Path=/~n', [Cookie]),
  165            format('Content-type: text/plain~n~n')
  166        */
  167do_actual_login(Status, SuccessURL, _UserName, Request) :-
  168      Status \= ok,
  169      http_link_to_id(login_form,
  170                      [
  171                          warn(Status),
  172                          referer(SuccessURL)
  173                      ],
  174                      HREF),
  175      http_redirect(see_other, HREF, Request).
  176
  177improper_login -->
  178      html(
  179          div(class('improper-login'),
  180              [
  181                  h1(\local('Sorry, login request ill formed')),
  182                  a(href(location_by_id(home), \local('Return to home')))
  183              ]))