1:- module(bc_mail, [
    2    bc_mail_send/4,      % +Goal, +From, +Subject, +To
    3    bc_mail_send_text/4, % +Text, +From, +Subject, +To
    4    bc_mail_test/3       % +User, +Params, -Result
    5]).

Helper module to send mail notifications */

    9:- use_module(library(smtp)).   10:- use_module(library(error)).   11:- use_module(library(debug)).   12
   13:- use_module(bc_data_config).
 bc_mail_test(+User, +Params, -Result) is det
Tries to send a test email. Result is one of: error(E), fail, ok.
   20bc_mail_test(User, Params, Result):-
   21    must_be(dict, User),
   22    must_be(dict, Params),
   23    BaseConfig = _{
   24        smtp: Params.host,
   25        from: Params.from,
   26        subject: Params.subject,
   27        auth_method: Params.auth,
   28        security: Params.security
   29    },
   30    (   Params.auth = login
   31    ->  Config = BaseConfig.put(auth, Params.user - Params.password)
   32    ;   Config = BaseConfig),
   33    wrap_smtp(User.username,
   34        text_body(Params.body), Config, Result).
   35
   36:- meta_predicate(wrap_smtp(+, 1, +, -)).   37
   38% Wrapper around smtp_send_mail to catch
   39% and report the mail error.
   40
   41wrap_smtp(To, Goal, Config, Result):-
   42    (   catch(smtp_send_mail(To, Goal, Config), E, true)
   43    ->  (   nonvar(E)
   44        ->  format(user_error, 'Mail sending error: ~w~n', [E]),
   45            Result = error(E)
   46        ;   Result = ok)
   47    ;   writeln(user_error, 'Mail sending failed.'),
   48        Result = fail).
   49
   50% Helper to write given
   51% text to output.
   52
   53text_body(Text, Out):-
   54    writeln(Out, Text).
   55
   56:- meta_predicate(bc_mail_send(1, +, +, +)).
 bc_mail_send(:Goal, +From, +Subject, +To) is det
Sends mail using the current SMTP configuration. Takes Goal argument that must produce the mail body. Goal must accept argument for output Stream.
   64bc_mail_send(Goal, From, Subject, To):-
   65    must_be(atomic, From),
   66    must_be(atomic, Subject),
   67    must_be(atomic, To),
   68    must_be(callable, Goal),
   69    (   bc_config_get(smtp_enabled, true)
   70    ->  debug(bc_mail, 'smtp is enabled', []),
   71        smtp_config(Config),
   72        put_dict(_{ from: From, subject: Subject },
   73            Config, Options),
   74        wrap_smtp(To, Goal, Options, _)
   75    ;   debug(bc_mail, 'smtp is not enabled', [])).
 bc_mail_send_text(+Text, +From, +Subject, +To) is det
Same as bc_mail_send/4 but takes prepared text instead of closure.
   82bc_mail_send_text(Text, From, Subject, To):-
   83    must_be(atomic, Text),
   84    bc_mail_send(text_body(Text), From, Subject, To).
   85
   86% Builds dict from the current
   87% SMTP config options.
   88
   89smtp_config(Config):-
   90    bc_config_get(smtp_host, Host),
   91    bc_config_get(smtp_auth, Auth),
   92    bc_config_get(smtp_security, Security),
   93    (   Auth = plain
   94    ->  Config = _{ smtp: Host, auth_method: Auth, security: Security }
   95    ;   bc_config_get(smtp_user, User),
   96        bc_config_get(smtp_password, Password),
   97        Config = _{ smtp: Host, auth_method: Auth, auth: User-Password, security: Security })