View source with formatted 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-2016, University of Amsterdam
    7                              VU University Amsterdam
    8    All rights reserved.
    9
   10    Redistribution and use in source and binary forms, with or without
   11    modification, are permitted provided that the following conditions
   12    are met:
   13
   14    1. Redistributions of source code must retain the above copyright
   15       notice, this list of conditions and the following disclaimer.
   16
   17    2. Redistributions in binary form must reproduce the above copyright
   18       notice, this list of conditions and the following disclaimer in
   19       the documentation and/or other materials provided with the
   20       distribution.
   21
   22    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   23    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   24    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   25    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   26    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   27    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   28    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   29    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   30    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   31    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   32    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   33    POSSIBILITY OF SUCH DAMAGE.
   34*/
   35
   36:- module(http_log,
   37          [ http_log_stream/1,          % -Stream
   38            http_log/2,                 % +Format, +Args
   39            http_log_close/1,           % +Reason
   40            post_data_encoded/2,        % ?Bytes, ?Encoded
   41            http_logrotate/1,           % +Options
   42            http_schedule_logrotate/2   % +When, +Options
   43          ]).   44:- use_module(library(http/http_header)).   45:- use_module(library(settings)).   46:- use_module(library(option)).   47:- use_module(library(error)).   48:- use_module(library(debug)).   49:- use_module(library(broadcast)).   50
   51:- setting(http:logfile, callable, 'httpd.log',
   52           'File in which to log HTTP requests').   53:- setting(http:log_post_data, integer, 0,
   54           'Log POST data up to N bytes long').   55
   56/** <module> HTTP Logging module
   57
   58Simple module for logging HTTP requests to a file. Logging is enabled by
   59loading this file and ensure the setting   http:logfile is not the empty
   60atom. The default  file  for  writing   the  log  is  =|httpd.log|=. See
   61library(settings) for details.
   62
   63The  level  of  logging  can  modified  using  the  multifile  predicate
   64http_log:nolog/1 to hide HTTP  request  fields   from  the  logfile  and
   65http_log:password_field/1   to   hide   passwords   from   HTTP   search
   66specifications (e.g. =|/topsecret?password=secret|=).
   67*/
   68
   69:- multifile
   70    nolog/1,
   71    password_field/1,
   72    nolog_post_content_type/1.   73
   74% If the log settings change,  simply  close   the  log  and  it will be
   75% reopened with the new settings.
   76
   77:- listen(settings(changed(http:logfile, _, New)),
   78          http_log_close(changed(New))).   79:- listen(http(Message),
   80          http_message(Message)).   81:- listen(logrotate,
   82          http_log_close(logrotate)).   83
   84
   85http_message(request_start(Id, Request)) :-
   86    !,
   87    http_log_stream(Stream),
   88    log_started(Request, Id, Stream).
   89http_message(request_finished(Id, Code, Status, CPU, Bytes)) :-
   90    !,
   91    http_log_stream(Stream),
   92    log_completed(Code, Status, Bytes, Id, CPU, Stream).
   93
   94
   95                 /*******************************
   96                 *         LOG ACTIVITY         *
   97                 *******************************/
   98
   99:- dynamic
  100    log_stream/2.                   % Stream, TimeTried
  101
  102%!  http_log_stream(-Stream) is semidet.
  103%
  104%   True when Stream is a stream to  the opened HTTP log file. Opens
  105%   the log file in =append= mode if the   file is not yet open. The
  106%   log file is determined  from   the  setting =|http:logfile|=. If
  107%   this setting is set  to  the   empty  atom  (''), this predicate
  108%   fails.
  109%
  110%   If  a  file  error  is  encountered,   this  is  reported  using
  111%   print_message/2, after which this predicate silently fails.
  112
  113http_log_stream(Stream) :-
  114    log_stream(Stream, _Opened),
  115    !,
  116    Stream \== [].
  117http_log_stream([]) :-
  118    setting(http:logfile, ''),
  119    !,
  120    get_time(Now),
  121    assert(log_stream([], Now)).
  122http_log_stream(Stream) :-
  123    setting(http:logfile, Term),
  124    catch(absolute_file_name(Term, File,
  125                             [ access(append)
  126                             ]), E, open_error(E)),
  127    with_mutex(http_log,
  128               (   catch(open(File, append, Stream,
  129                              [ close_on_abort(false),
  130                                encoding(utf8),
  131                                buffer(line)
  132                              ]), E, open_error(E)),
  133                   get_time(Time),
  134                   format(Stream,
  135                          'server(started, ~0f).~n',
  136                          [ Time ]),
  137                   assert(log_stream(Stream, Time)),
  138                   at_halt(close_log(stopped))
  139               )).
  140
  141open_error(E) :-
  142    print_message(error, E),
  143    get_time(Now),
  144    assert(log_stream([], Now)),
  145    fail.
  146
  147
  148%!  http_log_close(+Reason) is det.
  149%
  150%   If there is a currently open HTTP logfile, close it after adding
  151%   a term server(Reason, Time).  to  the   logfile.  This  call  is
  152%   intended for cooperation with the Unix logrotate facility
  153%   using the following schema:
  154%
  155%       * Move logfile (the HTTP server keeps writing to the moved
  156%       file)
  157%       * Inform the server using an HTTP request that calls
  158%       http_log_close/1
  159%       * Compress the moved logfile
  160%
  161%   @author Suggested by Jacco van Ossenbruggen
  162
  163http_log_close(Reason) :-
  164    with_mutex(http_log, close_log(Reason)).
  165
  166close_log(Reason) :-
  167    retract(log_stream(Stream, _Opened)),
  168    !,
  169    (   is_stream(Stream)
  170    ->  get_time(Time),
  171        format(Stream, 'server(~q, ~0f).~n', [ Reason, Time ]),
  172        close(Stream)
  173    ;   true
  174    ).
  175close_log(_).
  176
  177%!  http_log(+Format, +Args) is det.
  178%
  179%   Write message from Format and Args   to log-stream. See format/2
  180%   for details. Succeed without side  effects   if  logging  is not
  181%   enabled.
  182
  183http_log(Format, Args) :-
  184    (   http_log_stream(Stream)
  185    ->  system:format(Stream, Format, Args) % use operators from `system`
  186    ;   true
  187    ).
  188
  189
  190%!  log_started(+Request, +Id, +Stream) is det.
  191%
  192%   Write log message that Request was started to Stream.
  193%
  194%   @param  Filled with sequence identifier for the request
  195
  196log_started(Request, Id, Stream) :-
  197    get_time(Now),
  198    add_post_data(Request, Request1),
  199    log_request(Request1, LogRequest),
  200    format_time(string(HDate), '%+', Now),
  201    format(Stream,
  202           '/*~s*/ request(~q, ~3f, ~q).~n',
  203           [HDate, Id, Now, LogRequest]).
  204
  205%!  log_request(+Request, -Log)
  206%
  207%   Remove passwords from the request to avoid sending them to the
  208%   logfiles.
  209
  210log_request([], []).
  211log_request([search(Search0)|T0], [search(Search)|T]) :-
  212    !,
  213    mask_passwords(Search0, Search),
  214    log_request(T0, T).
  215log_request([H|T0], T) :-
  216    nolog(H),
  217    !,
  218    log_request(T0, T).
  219log_request([H|T0], [H|T]) :-
  220    log_request(T0, T).
  221
  222mask_passwords([], []).
  223mask_passwords([Name=_|T0], [Name=xxx|T]) :-
  224    password_field(Name),
  225    !,
  226    mask_passwords(T0, T).
  227mask_passwords([H|T0], [H|T]) :-
  228    mask_passwords(T0, T).
  229
  230%!  password_field(+Field) is semidet.
  231%
  232%   Multifile predicate that can be defined to hide passwords from
  233%   the logfile.
  234
  235password_field(password).
  236password_field(pwd0).
  237password_field(pwd1).
  238password_field(pwd2).
  239
  240
  241%!  nolog(+HTTPField)
  242%
  243%   Multifile  predicate  that  can  be   defined  to  hide  request
  244%   parameters from the request logfile.
  245
  246nolog(input(_)).
  247nolog(accept(_)).
  248nolog(accept_language(_)).
  249nolog(accept_encoding(_)).
  250nolog(accept_charset(_)).
  251nolog(pool(_)).
  252nolog(protocol(_)).
  253nolog(referer(R)) :-
  254    sub_atom(R, _, _, _, password),
  255    !.
  256
  257%!  nolog_post_content_type(+Type) is semidet.
  258%
  259%   Multifile hook called with the   =|Content-type|= header. If the
  260%   hook succeeds, the POST data is not logged. For example, to stop
  261%   logging  anything  but  application/json   messages:
  262%
  263%     ==
  264%     :- multifile http_log:nolog_post_content_type/1.
  265%
  266%     http_log:nolog_post_content_type(Type) :-
  267%        Type \= (application/json).
  268%     ==
  269%
  270%   @arg Type is a term MainType/SubType
  271
  272%!  add_post_data(+Request0, -Request) is det.
  273%
  274%   Add   a   request   field   post_data(Data)   if   the   setting
  275%   http:log_post_data is an integer > 0,  the content length < this
  276%   setting and nolog_post_content_type/1 does not   succeed  on the
  277%   provided content type.
  278
  279add_post_data(Request0, Request) :-
  280    setting(http:log_post_data, MaxLen),
  281    integer(MaxLen), MaxLen > 0,
  282    memberchk(input(In), Request0),
  283    memberchk(content_length(CLen), Request0),
  284    CLen =< MaxLen,
  285    memberchk(content_type(Type), Request0),
  286    http_parse_header_value(content_type, Type, media(MType/MSubType, _)),
  287    \+ nolog_post_content_type(MType/MSubType),
  288    catch(peek_string(In, CLen, PostData), _, fail),
  289    !,
  290    post_data_encoded(PostData, Encoded),
  291    Request = [post_data(Encoded)|Request0].
  292add_post_data(Request, Request).
  293
  294%!  post_data_encoded(?Bytes:string, ?Encoded:string) is det.
  295%
  296%   Encode the POST body for inclusion into   the HTTP log file. The
  297%   POST data is (in/de)flated  using   zopen/3  and  base64 encoded
  298%   using base64//1. The encoding makes   long text messages shorter
  299%   and keeps readable logfiles if binary data is posted.
  300
  301post_data_encoded(Bytes, Hex) :-
  302    nonvar(Bytes),
  303    !,
  304    setup_call_cleanup(
  305        new_memory_file(HMem),
  306        ( setup_call_cleanup(
  307              ( open_memory_file(HMem, write, Out, [encoding(octet)]),
  308                zopen(Out, ZOut, [])
  309              ),
  310              format(ZOut, '~s', [Bytes]),
  311              close(ZOut)),
  312          memory_file_to_codes(HMem, Codes, octet)
  313        ),
  314        free_memory_file(HMem)),
  315    phrase(base64(Codes), EncCodes),
  316    string_codes(Hex, EncCodes).
  317post_data_encoded(Bytes, Hex) :-
  318    string_codes(Hex, EncCodes),
  319    phrase(base64(Codes), EncCodes),
  320    string_codes(ZBytes, Codes),
  321    setup_call_cleanup(
  322        open_string(ZBytes, In),
  323        zopen(In, Zin, []),
  324        read_string(Zin, _, Bytes)).
  325
  326%!  log_completed(+Code, +Status, +Bytes, +Id, +CPU, +Stream) is det.
  327%
  328%   Write log message to Stream from a call_cleanup/3 call.
  329%
  330%   @param Status   2nd argument of call_cleanup/3
  331%   @param Id       Term identifying the completed request
  332%   @param CPU0     CPU time at time of entrance
  333%   @param Stream   Stream to write to (normally from http_log_stream/1).
  334
  335log_completed(Code, Status, Bytes, Id, CPU, Stream) :-
  336    is_stream(Stream),
  337    log_check_deleted(Stream),
  338    !,
  339    log(Code, Status, Bytes, Id, CPU, Stream).
  340log_completed(Code, Status, Bytes, Id, CPU0, _) :-
  341    http_log_stream(Stream),       % Logfile has changed!
  342    !,
  343    log_completed(Code, Status, Bytes, Id, CPU0, Stream).
  344log_completed(_,_,_,_,_,_).
  345
  346
  347log(Code, ok, Bytes, Id, CPU, Stream) :-
  348    !,
  349    format(Stream, 'completed(~q, ~q, ~q, ~q, ok).~n',
  350           [ Id, CPU, Bytes, Code ]).
  351log(Code, Status, Bytes, Id, CPU, Stream) :-
  352    (   map_exception(Status, Term)
  353    ->  true
  354    ;   message_to_string(Status, String),
  355        Term = error(String)
  356    ),
  357    format(Stream, 'completed(~q, ~q, ~q, ~q, ~W).~n',
  358           [ Id, CPU, Bytes, Code,
  359             Term, [ quoted(true),
  360                     ignore_ops(true),
  361                     blobs(portray),
  362                     portray_goal(write_blob)
  363                   ]
  364           ]).
  365
  366:- public write_blob/2.  367write_blob(Blob, _Options) :-
  368    format(string(S), '~q', [Blob]),
  369    writeq(blob(S)).
  370
  371map_exception(http_reply(bytes(ContentType,Bytes),_), bytes(ContentType,L)) :-
  372    string_length(Bytes, L).        % also does lists
  373map_exception(http_reply(Reply), Reply).
  374map_exception(http_reply(Reply, _), Reply).
  375map_exception(error(existence_error(http_location, Location), _Stack),
  376              error(404, Location)).
  377
  378
  379                 /*******************************
  380                 *      LOGROTATE SUPPORT       *
  381                 *******************************/
  382
  383%!  log_check_deleted(+Stream) is semidet.
  384%
  385%   If the link-count of the stream has   dropped  to zero, the file
  386%   has been deleted/moved. In this case the  log file is closed and
  387%   log_check_deleted/6 will open a  new   one.  This  provides some
  388%   support for cleaning up the logfile   without  shutting down the
  389%   server.
  390%
  391%   @see logrotate(1) to manage logfiles on Unix systems.
  392
  393log_check_deleted(Stream) :-
  394    stream_property(Stream, nlink(Links)),
  395    Links == 0,
  396    !,
  397    http_log_close(log_file_deleted),
  398    fail.
  399log_check_deleted(_).
  400
  401%!  http_logrotate(+Options) is det.
  402%
  403%   Rotate the available log files. Note that  there are two ways to
  404%   deal with the rotation of log files:
  405%
  406%     1. Use the OS log rotation facility. In that case the OS must
  407%     (1) move the logfile and (2) have something calling
  408%     http_log_close/1 to close the (moved) file and make this
  409%     server create a new one on the next log message.  If
  410%     library(http/http_unix_daemon) is used, closing is
  411%     achieved by sending SIGHUP or SIGUSR1 to the process.
  412%
  413%     2. Call this predicate at scheduled intervals.  This can
  414%     be achieved by calling http_schedule_logrotate/2 in the
  415%     context of library(http/http_unix_daemon) which schedules
  416%     the maintenance actions.
  417%
  418%   Options:
  419%
  420%     - min_size(+Bytes)
  421%     Do not rotate if the log file is smaller than Bytes.
  422%     The default is 1Mbytes.
  423%     - keep_logs(+Count)
  424%     Number of rotated log files to keep (default 10)
  425%     - compress_logs(+Format)
  426%     Compress the log files to the given format.
  427%     - background(+Boolean)
  428%     If `true`, rotate the log files in the background.
  429
  430http_logrotate(Options) :-
  431    select_option(background(true), Options, Options1),
  432    !,
  433    thread_create(http_logrotate(Options1), _,
  434                  [ alias('__logrotate'),
  435                    detached(true)
  436                  ]).
  437http_logrotate(Options) :-
  438    option(keep_logs(Keep), Options, 10),
  439    option(compress_logs(Format), Options, gzip),
  440    compress_extension(Format, ZExt),
  441    log_file_and_ext(Base, Ext),
  442    (   log_too_small(Base, Ext, Options)
  443    ->  true
  444    ;   rotate_logs(Base, Ext, ZExt, Keep)
  445    ).
  446
  447rotate_logs(Base, Ext, ZExt, N1) :-
  448    N1 > 0,
  449    !,
  450    N0 is N1 - 1,
  451    old_log_file(Base, Ext, N0, ZO, Old),
  452    (   exists_file(Old)
  453    ->  new_log_file(Base, Ext, N1, ZO, ZExt, ZN, New),
  454        rename_log_file(ZO, Old, ZN, New)
  455    ;   true
  456    ),
  457    rotate_logs(Base, Ext, ZExt, N0).
  458rotate_logs(_, _, _, _).
  459
  460rename_log_file(ZExt, Old, ZExt, New) :-
  461    !,
  462    debug(logrotate, 'Rename ~p --> ~p', [Old, New]),
  463    rename_file(Old, New).
  464rename_log_file('', Old, ZExt, New) :-
  465    file_name_extension(NoExt, ZExt, New),
  466    debug(logrotate, 'Rename ~p --> ~p', [Old, NoExt]),
  467    rename_file(Old, NoExt),
  468    debug(logrotate, 'Closing log file', []),
  469    http_log_close(logrotate),
  470    compress_extension(Format, ZExt),
  471    debug(logrotate, 'Compressing (~w) ~p', [Format, NoExt]),
  472    compress_file(NoExt, Format).
  473
  474old_log_file(Base, Ext, N, ZExt, File) :-
  475    log_file(Base, Ext, N, File0),
  476    (   compress_extension(_, ZExt),
  477        file_name_extension(File0, ZExt, File1),
  478        exists_file(File1)
  479    ->  File = File1
  480    ;   ZExt = '',
  481        File = File0
  482    ).
  483
  484new_log_file(Base, Ext, N, '', '', '', File) :-
  485    !,
  486    log_file(Base, Ext, N, File).
  487new_log_file(Base, Ext, N, '', ZExt, ZExt, File) :-
  488    !,
  489    log_file(Base, Ext, N, File0),
  490    file_name_extension(File0, ZExt, File).
  491new_log_file(Base, Ext, N, ZExt, _, ZExt, File) :-
  492    log_file(Base, Ext, N, File0),
  493    file_name_extension(File0, ZExt, File).
  494
  495log_file(Base, Ext, 0, File) :-
  496    !,
  497    file_name_extension(Base, Ext, File).
  498log_file(Base, Ext, N, File) :-
  499    atomic_list_concat([Base, -, N], Base1),
  500    file_name_extension(Base1, Ext, File).
  501
  502log_file_and_ext(Base, Ext) :-
  503    setting(http:logfile, Term),
  504    catch(absolute_file_name(Term, File,
  505                             [ access(exist)
  506                             ]), _, fail),
  507    file_name_extension(Base, Ext, File).
  508
  509log_too_small(Base, Ext, Options) :-
  510    DefMin is 1024*1024,
  511    option(min_size(MinBytes), Options, DefMin),
  512    file_name_extension(Base, Ext, File),
  513    (   exists_file(File)
  514    ->  size_file(File, Bytes),
  515        Bytes < MinBytes,
  516        debug(logrotate, '~w has ~D bytes; not rotating', [File, Bytes])
  517    ;   debug(logrotate, '~w does not exist; not rotating', [File])
  518    ).
  519
  520%!  compress_file(+File, +Format)
  521%
  522%   Compress a file according  to   Format.  Currently only supports
  523%   gzip.
  524
  525compress_file(File, Format) :-
  526    (   compress_extension(Format, Ext)
  527    ->  true
  528    ;   domain_error(compress_format, Format)
  529    ),
  530    file_name_extension(File, Ext, ZFile),
  531    catch(setup_call_cleanup(
  532              gzopen(ZFile, write, Out, [type(binary)]),
  533              setup_call_cleanup(
  534                  open(File, read, In, [type(binary)]),
  535                  copy_stream_data(In, Out),
  536                  close(In)),
  537              close(Out)),
  538          Error,
  539          ( print_message(error, Error),
  540            catch(delete_file(Out), _, true),
  541            throw(Error)
  542          )),
  543    delete_file(File).
  544
  545compress_extension(gzip, gz).
  546
  547:- dynamic
  548    scheduled_logrotate/2.  % Schedule, Options
  549
  550%!  http_schedule_logrotate(When, Options)
  551%
  552%   Schedule log rotation based on maintenance broadcasts.  When
  553%   is one of:
  554%
  555%     - daily(Hour:Min)
  556%     Run each day at Hour:Min.  Min is rounded to a multitude
  557%     of 5.
  558%     - weekly(Day, Hour:Min)
  559%     Run at the given Day and Time each week.  Day is either a
  560%     number 1..7 (1 is Monday) or a weekday name or abbreviation.
  561%     - monthly(DayOfTheMonth, Hour:Min)
  562%     Run each month at the given Day (1..31).  Note that not all
  563%     months have all days.
  564%
  565%   This  must  be  used   with   a    timer   that   broadcasts   a
  566%   maintenance(_,_) message (see broadcast/1). Such a timer is part
  567%   of library(http/http_unix_daemon).
  568
  569http_schedule_logrotate(When, Options) :-
  570    listen(maintenance(_,_), http_consider_logrotate),
  571    compile_schedule(When, Schedule),
  572    retractall(scheduled_logrotate(_,_)),
  573    asserta(scheduled_logrotate(Schedule, Options)).
  574
  575compile_schedule(Var, _) :-
  576    var(Var),
  577    !,
  578    instantiation_error(Var).
  579compile_schedule(daily(Time0), daily(Time)) :-
  580    compile_time(Time0, Time).
  581compile_schedule(weekly(Day0, Time0), weekly(Day, Time)) :-
  582    compile_weekday(Day0, Day),
  583    compile_time(Time0, Time).
  584compile_schedule(monthly(Day, Time0), monthly(Day, Time)) :-
  585    must_be(between(0, 31), Day),
  586    compile_time(Time0, Time).
  587
  588compile_time(HH:MM0, HH:MM) :-
  589    must_be(between(0, 23), HH),
  590    must_be(between(0, 59), MM0),
  591    MM is ((MM0+4)//5)*5.
  592
  593compile_weekday(N, _) :-
  594    var(N),
  595    !,
  596    instantiation_error(N).
  597compile_weekday(N, N) :-
  598    integer(N),
  599    !,
  600    must_be(between(1,7), N).
  601compile_weekday(Name, N) :-
  602    downcase_atom(Name, Lwr),
  603    (   day(N, Name),
  604        sub_atom(Name, 0, _, _, Lwr)
  605    ->  !
  606    ;   domain_error(day, Name)
  607    ).
  608
  609%!  http_consider_logrotate
  610%
  611%   Perform a log rotation if the schedule is met
  612
  613http_consider_logrotate :-
  614    scheduled_logrotate(Schedule, Options),
  615    get_time(NowF),
  616    Now is round(NowF/60.0)*60,
  617    scheduled(Schedule, Now),
  618    !,
  619    http_logrotate([background(true)|Options]).
  620
  621scheduled(daily(HH:MM), Now) :-
  622    stamp_date_time(Now, DateTime, local),
  623    date_time_value(time, DateTime, time(HH,MM,_)).
  624scheduled(weekly(Day, Time), Now) :-
  625    stamp_date_time(Now, DateTime, local),
  626    date_time_value(date, DateTime, Date),
  627    day_of_the_week(Date, Day),
  628    scheduled(daily(Time), Now).
  629scheduled(monthly(Day, Time), Now) :-
  630    stamp_date_time(Now, DateTime, local),
  631    date_time_value(day, DateTime, Day),
  632    scheduled(daily(Time), Now).
  633
  634day(1, mon).
  635day(2, tue).
  636day(3, wed).
  637day(4, thu).
  638day(5, fri).
  639day(6, sat).
  640day(7, sun)