1:- module(customize, [
    2 %             localized//1,
    3 %             localized/2,
    4              local//1,
    5              local/2
    6          ]).

User settings and config for identity

/

   11:- use_module(library(http/html_write)).   12:- use_module(library(settings)).   13
   14		 /*******************************
   15		 *       Localization		*
   16		 *******************************/
   17
   18:- html_meta local(+, ?, ?).
   19local(English) -->
   20    { local(English, Local) },
   21    html(Local).
   22
   23:- multifile customize:local_hook/2.   24
   25local(X, Y) :-
   26    customize:local_hook(X,Y),
   27    !.
   28local(X, X).
   29
   30
   31		 /*******************************
   32		 *           SETTINGS           *
   33		 *******************************/
   34:- setting(identity:style, atom, default,
   35           "Name of the style to apply to identity pages").   36:- setting(identity:require_activation_email, boolean, false,
   37           "true = require activation email, false = not required").