View source with raw comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2008-2018, University of Amsterdam
    7                              VU University Amsterdam
    8                              CWI, Amsterdam
    9    All rights reserved.
   10
   11    Redistribution and use in source and binary forms, with or without
   12    modification, are permitted provided that the following conditions
   13    are met:
   14
   15    1. Redistributions of source code must retain the above copyright
   16       notice, this list of conditions and the following disclaimer.
   17
   18    2. Redistributions in binary form must reproduce the above copyright
   19       notice, this list of conditions and the following disclaimer in
   20       the documentation and/or other materials provided with the
   21       distribution.
   22
   23    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   24    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   25    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   26    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   27    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   28    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   29    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   30    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   31    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   32    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   33    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   34    POSSIBILITY OF SUCH DAMAGE.
   35*/
   36
   37:- module(http_log,
   38          [ http_log_stream/1,          % -Stream
   39            http_log/2,                 % +Format, +Args
   40            http_log_close/1,           % +Reason
   41            post_data_encoded/2,        % ?Bytes, ?Encoded
   42            http_logrotate/1,           % +Options
   43            http_schedule_logrotate/2   % +When, +Options
   44          ]).   45:- use_module(library(http/http_header)).   46:- use_module(library(settings)).   47:- use_module(library(option)).   48:- use_module(library(error)).   49:- use_module(library(debug)).   50:- use_module(library(broadcast)).   51
   52:- setting(http:logfile, callable, 'httpd.log',
   53           'File in which to log HTTP requests').   54:- setting(http:log_post_data, integer, 0,
   55           'Log POST data up to N bytes long').   56:- setting(http:on_log_error, any, retry,
   57           'Action if logging fails').

HTTP Logging module

Simple module for logging HTTP requests to a file. Logging is enabled by loading this file and ensure the setting http:logfile is not the empty atom. The default file for writing the log is httpd.log. See library(settings) for details.

The level of logging can be modified using the multifile predicate http_log:nolog/1 to hide HTTP request fields from the logfile and http_log:password_field/1 to hide passwords from HTTP search specifications (e.g. /topsecret?password=secret). */

   72:- multifile
   73    nolog/1,
   74    password_field/1,
   75    nolog_post_content_type/1.   76
   77% If the log settings change,  simply  close   the  log  and  it will be
   78% reopened with the new settings.
   79
   80:- listen(settings(changed(http:logfile, _, New)),
   81          http_log_close(changed(New))).   82:- listen(http(Message),
   83          http_message(Message)).   84:- listen(logrotate,
   85          http_log_close(logrotate)).   86
   87http_message(Message) :-
   88    log_message(Message),
   89    http_log_stream(Stream),
   90    catch(http_message(Message, Stream), E,
   91          log_error(E)).
   92
   93log_message(request_start(_Id, _Request)).
   94log_message(request_finished(_Id, _Code, _Status, _CPU, _Bytes)).
   95
   96http_message(request_start(Id, Request), Stream) :-
   97    log_started(Request, Id, Stream).
   98http_message(request_finished(Id, Code, Status, CPU, Bytes), Stream) :-
   99    log_completed(Code, Status, Bytes, Id, CPU, Stream).
 log_error(+Error)
There was an error writing the log file. The message is printed using print_message/2 and execution continues according to the setting http:on_log_error, which is one of:
retry
Close the log file. The system will try to reopen it on the next log event, recovering from the error. Note that the most common case for this is probably running out of disc space.
exit
exit(Code)
Stop the server using halt(Code). The exit variant is equivalent to exit(1).

The best choice depends on your priorities. Using retry gives priority to keep the server running. Using exit guarantees proper log files and thus the ability to examine these for security reasons. An attacker may try to flood the disc, causing a successful DoS attack if exit is used and the ability to interact without being logged if retry is used.

  123log_error(E) :-
  124    print_message(warning, E),
  125    log_error_continue.
  126
  127log_error_continue :-
  128    setting(http:on_log_error, Action),
  129    log_error_continue(Action).
  130
  131log_error_continue(retry) :-
  132    http_log_close(error).
  133log_error_continue(exit) :-
  134    log_error_continue(exit(1)).
  135log_error_continue(exit(Code)) :-
  136    halt(Code).
  137
  138
  139
  140                 /*******************************
  141                 *         LOG ACTIVITY         *
  142                 *******************************/
  143
  144:- dynamic
  145    log_stream/2.                   % Stream, TimeTried
 http_log_stream(-Stream) is semidet
True when Stream is a stream to the opened HTTP log file. Opens the log file in append mode if the file is not yet open. The log file is determined from the setting http:logfile. If this setting is set to the empty atom (''), this predicate fails.

If a file error is encountered, this is reported using print_message/2, after which this predicate silently fails. Opening is retried every minute when a new message arrives.

Before opening the log file, the message http_log_open(Term) is broadcasted. This message allows for creating the directory, renaming, deleting or truncating an existing log file.

  162http_log_stream(Stream) :-
  163    log_stream(Stream, _Opened),
  164    !,
  165    Stream \== [].
  166http_log_stream([]) :-
  167    setting(http:logfile, ''),
  168    !,
  169    get_time(Now),
  170    assert(log_stream([], Now)).
  171http_log_stream(Stream) :-
  172    setting(http:logfile, Term),
  173    broadcast(http_log_open(Term)),
  174    catch(absolute_file_name(Term, File,
  175                             [ access(append)
  176                             ]),
  177          E, open_error(E)),
  178    with_mutex(http_log, open_log(File, Stream0)),
  179    Stream = Stream0.
  180
  181open_log(_File, Stream) :-
  182    log_stream(Stream, Opened),
  183    (   Stream == []
  184    ->  (   get_time(Now),
  185            Now - Opened > 60
  186        ->  retractall(log_stream(_,_)),
  187            fail
  188        ;   !, fail
  189        )
  190    ;   true
  191    ), !.
  192open_log(File, Stream) :-
  193    catch(open(File, append, Stream,
  194               [ close_on_abort(false),
  195                 encoding(utf8),
  196                 buffer(line)
  197               ]), E, open_error(E)),
  198    get_time(Time),
  199    format(Stream,
  200           'server(started, ~0f).~n',
  201           [ Time ]),
  202    assert(log_stream(Stream, Time)),
  203    at_halt(close_log(stopped)).
  204
  205open_error(E) :-
  206    print_message(error, E),
  207    log_open_error_continue.
  208
  209log_open_error_continue :-
  210    setting(http:on_log_error, Action),
  211    log_open_error_continue(Action).
  212
  213log_open_error_continue(retry) :-
  214    !,
  215    get_time(Now),
  216    assert(log_stream([], Now)),
  217    fail.
  218log_open_error_continue(Action) :-
  219    log_error_continue(Action).
 http_log_close(+Reason) is det
If there is a currently open HTTP logfile, close it after adding a term server(Reason, Time). to the logfile. This call is intended for cooperation with the Unix logrotate facility using the following schema:
author
- Suggested by Jacco van Ossenbruggen
  237http_log_close(Reason) :-
  238    with_mutex(http_log, close_log(Reason)).
  239
  240close_log(Reason) :-
  241    retract(log_stream(Stream, _Opened)),
  242    !,
  243    (   is_stream(Stream)
  244    ->  get_time(Time),
  245        catch(( format(Stream, 'server(~q, ~0f).~n', [ Reason, Time ]),
  246                close(Stream)
  247              ), E, print_message(warning, E))
  248    ;   true
  249    ).
  250close_log(_).
 http_log(+Format, +Args) is det
Write message from Format and Args to log-stream. See format/2 for details. Succeed without side effects if logging is not enabled.
  258http_log(Format, Args) :-
  259    (   http_log_stream(Stream)
  260    ->  system:format(Stream, Format, Args) % use operators from `system`
  261    ;   true
  262    ).
 log_started(+Request, +Id, +Stream) is det
Write log message that Request was started to Stream.
Arguments:
Filled- with sequence identifier for the request
  271log_started(Request, Id, Stream) :-
  272    get_time(Now),
  273    add_post_data(Request, Request1),
  274    log_request(Request1, LogRequest),
  275    format_time(string(HDate), '%+', Now),
  276    format(Stream,
  277           '/*~s*/ request(~q, ~3f, ~q).~n',
  278           [HDate, Id, Now, LogRequest]).
 log_request(+Request, -Log)
Remove passwords from the request to avoid sending them to the logfiles.
  285log_request([], []).
  286log_request([search(Search0)|T0], [search(Search)|T]) :-
  287    !,
  288    mask_passwords(Search0, Search),
  289    log_request(T0, T).
  290log_request([H|T0], T) :-
  291    nolog(H),
  292    !,
  293    log_request(T0, T).
  294log_request([H|T0], [H|T]) :-
  295    log_request(T0, T).
  296
  297mask_passwords([], []).
  298mask_passwords([Name=_|T0], [Name=xxx|T]) :-
  299    password_field(Name),
  300    !,
  301    mask_passwords(T0, T).
  302mask_passwords([H|T0], [H|T]) :-
  303    mask_passwords(T0, T).
 password_field(+Field) is semidet
Multifile predicate that can be defined to hide passwords from the logfile.
  310password_field(password).
  311password_field(pwd0).
  312password_field(pwd1).
  313password_field(pwd2).
 nolog(+HTTPField)
Multifile predicate that can be defined to hide request parameters from the request logfile.
  321nolog(input(_)).
  322nolog(accept(_)).
  323nolog(accept_language(_)).
  324nolog(accept_encoding(_)).
  325nolog(accept_charset(_)).
  326nolog(pool(_)).
  327nolog(protocol(_)).
  328nolog(referer(R)) :-
  329    sub_atom(R, _, _, _, password),
  330    !.
 nolog_post_content_type(+Type) is semidet
Multifile hook called with the Content-type header. If the hook succeeds, the POST data is not logged. For example, to stop logging anything but application/json messages:
:- multifile http_log:nolog_post_content_type/1.

http_log:nolog_post_content_type(Type) :-
   Type \= (application/json).
Arguments:
Type- is a term MainType/SubType
 add_post_data(+Request0, -Request) is det
Add a request field post_data(Data) if the setting http:log_post_data is an integer > 0, the content length < this setting and nolog_post_content_type/1 does not succeed on the provided content type.
  354add_post_data(Request0, Request) :-
  355    setting(http:log_post_data, MaxLen),
  356    integer(MaxLen), MaxLen > 0,
  357    memberchk(input(In), Request0),
  358    memberchk(content_length(CLen), Request0),
  359    CLen =< MaxLen,
  360    memberchk(content_type(Type), Request0),
  361    http_parse_header_value(content_type, Type, media(MType/MSubType, _)),
  362    \+ nolog_post_content_type(MType/MSubType),
  363    catch(peek_string(In, CLen, PostData), _, fail),
  364    !,
  365    post_data_encoded(PostData, Encoded),
  366    Request = [post_data(Encoded)|Request0].
  367add_post_data(Request, Request).
 post_data_encoded(?Bytes:string, ?Encoded:string) is det
Encode the POST body for inclusion into the HTTP log file. The POST data is (in/de)flated using zopen/3 and base64 encoded using base64//1. The encoding makes long text messages shorter and keeps readable logfiles if binary data is posted.
  376post_data_encoded(Bytes, Hex) :-
  377    nonvar(Bytes),
  378    !,
  379    setup_call_cleanup(
  380        new_memory_file(HMem),
  381        ( setup_call_cleanup(
  382              ( open_memory_file(HMem, write, Out, [encoding(octet)]),
  383                zopen(Out, ZOut, [])
  384              ),
  385              format(ZOut, '~s', [Bytes]),
  386              close(ZOut)),
  387          memory_file_to_codes(HMem, Codes, octet)
  388        ),
  389        free_memory_file(HMem)),
  390    phrase(base64(Codes), EncCodes),
  391    string_codes(Hex, EncCodes).
  392post_data_encoded(Bytes, Hex) :-
  393    string_codes(Hex, EncCodes),
  394    phrase(base64(Codes), EncCodes),
  395    string_codes(ZBytes, Codes),
  396    setup_call_cleanup(
  397        open_string(ZBytes, In),
  398        zopen(In, Zin, []),
  399        read_string(Zin, _, Bytes)).
 log_completed(+Code, +Status, +Bytes, +Id, +CPU, +Stream) is det
Write log message to Stream from a call_cleanup/3 call.
Arguments:
Status- 2nd argument of call_cleanup/3
Id- Term identifying the completed request
CPU0- CPU time at time of entrance
Stream- Stream to write to (normally from http_log_stream/1).
  410log_completed(Code, Status, Bytes, Id, CPU, Stream) :-
  411    is_stream(Stream),
  412    log_check_deleted(Stream),
  413    !,
  414    log(Code, Status, Bytes, Id, CPU, Stream).
  415log_completed(Code, Status, Bytes, Id, CPU0, _) :-
  416    http_log_stream(Stream),       % Logfile has changed!
  417    !,
  418    log_completed(Code, Status, Bytes, Id, CPU0, Stream).
  419log_completed(_,_,_,_,_,_).
  420
  421
  422log(Code, ok, Bytes, Id, CPU, Stream) :-
  423    !,
  424    format(Stream, 'completed(~q, ~q, ~q, ~q, ok).~n',
  425           [ Id, CPU, Bytes, Code ]).
  426log(Code, Status, Bytes, Id, CPU, Stream) :-
  427    (   map_exception(Status, Term)
  428    ->  true
  429    ;   message_to_string(Status, String),
  430        Term = error(String)
  431    ),
  432    format(Stream, 'completed(~q, ~q, ~q, ~q, ~W).~n',
  433           [ Id, CPU, Bytes, Code,
  434             Term, [ quoted(true),
  435                     ignore_ops(true),
  436                     blobs(portray),
  437                     portray_goal(write_blob)
  438                   ]
  439           ]).
  440
  441:- public write_blob/2.  442write_blob(Blob, _Options) :-
  443    format(string(S), '~q', [Blob]),
  444    writeq(blob(S)).
  445
  446map_exception(http_reply(bytes(ContentType,Bytes),_), bytes(ContentType,L)) :-
  447    string_length(Bytes, L).        % also does lists
  448map_exception(http_reply(Reply), Reply).
  449map_exception(http_reply(Reply, _), Reply).
  450map_exception(error(existence_error(http_location, Location), _Stack),
  451              error(404, Location)).
  452
  453
  454                 /*******************************
  455                 *      LOGROTATE SUPPORT       *
  456                 *******************************/
 log_check_deleted(+Stream) is semidet
If the link-count of the stream has dropped to zero, the file has been deleted/moved. In this case the log file is closed and log_check_deleted/6 will open a new one. This provides some support for cleaning up the logfile without shutting down the server.
See also
- logrotate(1) to manage logfiles on Unix systems.
  468log_check_deleted(Stream) :-
  469    stream_property(Stream, nlink(Links)),
  470    Links == 0,
  471    !,
  472    http_log_close(log_file_deleted),
  473    fail.
  474log_check_deleted(_).
 http_logrotate(+Options) is det
Rotate the available log files. Note that there are two ways to deal with the rotation of log files:
  1. Use the OS log rotation facility. In that case the OS must (1) move the logfile and (2) have something calling http_log_close/1 to close the (moved) file and make this server create a new one on the next log message. If library(http/http_unix_daemon) is used, closing is achieved by sending SIGHUP or SIGUSR1 to the process.
  2. Call this predicate at scheduled intervals. This can be achieved by calling http_schedule_logrotate/2 in the context of library(http/http_unix_daemon) which schedules the maintenance actions.

Options:

min_size(+Bytes)
Do not rotate if the log file is smaller than Bytes. The default is 1Mbytes.
keep_logs(+Count)
Number of rotated log files to keep (default 10)
compress_logs(+Format)
Compress the log files to the given format.
background(+Boolean)
If true, rotate the log files in the background.
  505http_logrotate(Options) :-
  506    select_option(background(true), Options, Options1),
  507    !,
  508    thread_create(http_logrotate(Options1), _,
  509                  [ alias('__logrotate'),
  510                    detached(true)
  511                  ]).
  512http_logrotate(Options) :-
  513    option(keep_logs(Keep), Options, 10),
  514    option(compress_logs(Format), Options, gzip),
  515    compress_extension(Format, ZExt),
  516    log_file_and_ext(Base, Ext),
  517    (   log_too_small(Base, Ext, Options)
  518    ->  true
  519    ;   rotate_logs(Base, Ext, ZExt, Keep)
  520    ).
  521
  522rotate_logs(Base, Ext, ZExt, N1) :-
  523    N1 > 0,
  524    !,
  525    N0 is N1 - 1,
  526    old_log_file(Base, Ext, N0, ZO, Old),
  527    (   exists_file(Old)
  528    ->  new_log_file(Base, Ext, N1, ZO, ZExt, ZN, New),
  529        rename_log_file(ZO, Old, ZN, New)
  530    ;   true
  531    ),
  532    rotate_logs(Base, Ext, ZExt, N0).
  533rotate_logs(_, _, _, _).
  534
  535rename_log_file(ZExt, Old, ZExt, New) :-
  536    !,
  537    debug(logrotate, 'Rename ~p --> ~p', [Old, New]),
  538    rename_file(Old, New).
  539rename_log_file('', Old, ZExt, New) :-
  540    file_name_extension(NoExt, ZExt, New),
  541    debug(logrotate, 'Rename ~p --> ~p', [Old, NoExt]),
  542    rename_file(Old, NoExt),
  543    debug(logrotate, 'Closing log file', []),
  544    http_log_close(logrotate),
  545    compress_extension(Format, ZExt),
  546    debug(logrotate, 'Compressing (~w) ~p', [Format, NoExt]),
  547    compress_file(NoExt, Format).
  548
  549old_log_file(Base, Ext, N, ZExt, File) :-
  550    log_file(Base, Ext, N, File0),
  551    (   compress_extension(_, ZExt),
  552        file_name_extension(File0, ZExt, File1),
  553        exists_file(File1)
  554    ->  File = File1
  555    ;   ZExt = '',
  556        File = File0
  557    ).
  558
  559new_log_file(Base, Ext, N, '', '', '', File) :-
  560    !,
  561    log_file(Base, Ext, N, File).
  562new_log_file(Base, Ext, N, '', ZExt, ZExt, File) :-
  563    !,
  564    log_file(Base, Ext, N, File0),
  565    file_name_extension(File0, ZExt, File).
  566new_log_file(Base, Ext, N, ZExt, _, ZExt, File) :-
  567    log_file(Base, Ext, N, File0),
  568    file_name_extension(File0, ZExt, File).
  569
  570log_file(Base, Ext, 0, File) :-
  571    !,
  572    file_name_extension(Base, Ext, File).
  573log_file(Base, Ext, N, File) :-
  574    atomic_list_concat([Base, -, N], Base1),
  575    file_name_extension(Base1, Ext, File).
  576
  577log_file_and_ext(Base, Ext) :-
  578    setting(http:logfile, Term),
  579    catch(absolute_file_name(Term, File,
  580                             [ access(exist)
  581                             ]), _, fail),
  582    file_name_extension(Base, Ext, File).
  583
  584log_too_small(Base, Ext, Options) :-
  585    DefMin is 1024*1024,
  586    option(min_size(MinBytes), Options, DefMin),
  587    file_name_extension(Base, Ext, File),
  588    (   exists_file(File)
  589    ->  size_file(File, Bytes),
  590        Bytes < MinBytes,
  591        debug(logrotate, '~w has ~D bytes; not rotating', [File, Bytes])
  592    ;   debug(logrotate, '~w does not exist; not rotating', [File])
  593    ).
 compress_file(+File, +Format)
Compress a file according to Format. Currently only supports gzip.
  600compress_file(File, Format) :-
  601    (   compress_extension(Format, Ext)
  602    ->  true
  603    ;   domain_error(compress_format, Format)
  604    ),
  605    file_name_extension(File, Ext, ZFile),
  606    catch(setup_call_cleanup(
  607              gzopen(ZFile, write, Out, [type(binary)]),
  608              setup_call_cleanup(
  609                  open(File, read, In, [type(binary)]),
  610                  copy_stream_data(In, Out),
  611                  close(In)),
  612              close(Out)),
  613          Error,
  614          ( print_message(error, Error),
  615            catch(delete_file(Out), _, true),
  616            throw(Error)
  617          )),
  618    delete_file(File).
  619
  620compress_extension(gzip, gz).
  621
  622:- dynamic
  623    scheduled_logrotate/2.  % Schedule, Options
 http_schedule_logrotate(When, Options)
Schedule log rotation based on maintenance broadcasts. When is one of:
daily(Hour:Min)
Run each day at Hour:Min. Min is rounded to a multitude of 5.
weekly(Day, Hour:Min)
Run at the given Day and Time each week. Day is either a number 1..7 (1 is Monday) or a weekday name or abbreviation.
monthly(DayOfTheMonth, Hour:Min)
Run each month at the given Day (1..31). Note that not all months have all days.

This must be used with a timer that broadcasts a maintenance(_,_) message (see broadcast/1). Such a timer is part of library(http/http_unix_daemon).

  644http_schedule_logrotate(When, Options) :-
  645    listen(maintenance(_,_), http_consider_logrotate),
  646    compile_schedule(When, Schedule),
  647    retractall(scheduled_logrotate(_,_)),
  648    asserta(scheduled_logrotate(Schedule, Options)).
  649
  650compile_schedule(Var, _) :-
  651    var(Var),
  652    !,
  653    instantiation_error(Var).
  654compile_schedule(daily(Time0), daily(Time)) :-
  655    compile_time(Time0, Time).
  656compile_schedule(weekly(Day0, Time0), weekly(Day, Time)) :-
  657    compile_weekday(Day0, Day),
  658    compile_time(Time0, Time).
  659compile_schedule(monthly(Day, Time0), monthly(Day, Time)) :-
  660    must_be(between(0, 31), Day),
  661    compile_time(Time0, Time).
  662
  663compile_time(HH:MM0, HH:MM) :-
  664    must_be(between(0, 23), HH),
  665    must_be(between(0, 59), MM0),
  666    MM is ((MM0+4)//5)*5.
  667
  668compile_weekday(N, _) :-
  669    var(N),
  670    !,
  671    instantiation_error(N).
  672compile_weekday(N, N) :-
  673    integer(N),
  674    !,
  675    must_be(between(1,7), N).
  676compile_weekday(Day, N) :-
  677    downcase_atom(Day, Lwr),
  678    (   sub_atom(Lwr, 0, 3, _, Abbr),
  679        day(N, Abbr)
  680    ->  !
  681    ;   domain_error(day, Day)
  682    ).
 http_consider_logrotate
Perform a log rotation if the schedule is met
  688http_consider_logrotate :-
  689    scheduled_logrotate(Schedule, Options),
  690    get_time(NowF),
  691    Now is round(NowF/60.0)*60,
  692    scheduled(Schedule, Now),
  693    !,
  694    http_logrotate([background(true)|Options]).
  695
  696scheduled(daily(HH:MM), Now) :-
  697    stamp_date_time(Now, DateTime, local),
  698    date_time_value(time, DateTime, time(HH,MM,_)).
  699scheduled(weekly(Day, Time), Now) :-
  700    stamp_date_time(Now, DateTime, local),
  701    date_time_value(date, DateTime, Date),
  702    day_of_the_week(Date, Day),
  703    scheduled(daily(Time), Now).
  704scheduled(monthly(Day, Time), Now) :-
  705    stamp_date_time(Now, DateTime, local),
  706    date_time_value(day, DateTime, Day),
  707    scheduled(daily(Time), Now).
  708
  709day(1, mon).
  710day(2, tue).
  711day(3, wed).
  712day(4, thu).
  713day(5, fri).
  714day(6, sat).
  715day(7, sun)