View source with raw comments or as raw
    1/*  Part of SWISH
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@cs.vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (C): 2017, VU University Amsterdam
    7			 CWI 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_cron,
   37          [ http_schedule_maintenance/2         % +When, :Goal
   38          ]).   39:- use_module(library(broadcast)).   40:- use_module(library(error)).   41
   42:- meta_predicate
   43    http_schedule_maintenance(+, 0).   44
   45:- dynamic
   46    cron_schedule/2.                            % Schedule, Goal

Schedule HTTP server maintenance tasks

This module deals with scheduling low frequency maintenance tasks to run at specified time stamps. The jobs are scheduled on the wall clock and thus the interval is kept over server restarts. */

 http_schedule_maintenance(+When, :Goal) is det
Schedule running Goal 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.
clear
Clear the schedule for the given goal.

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).

Arguments:
Goal- is the goal called. This is executed in the thread that broadcasts the maintenance(_,_) event, i.e., by default in the main thread. If a considerable amount of work is to be done it is adviced to start a detached thread to do the real work.
   81http_schedule_maintenance(When, Goal) :-
   82    listen(maintenance(_,_), http_consider_cronstart),
   83    (   compile_schedule(When, Schedule)
   84    ->  clear_schedule(Goal),
   85        (   Schedule == clear
   86        ->  true
   87        ;   asserta(cron_schedule(Schedule, Goal))
   88        )
   89    ;   domain_error(schedule, When)
   90    ).
   91
   92clear_schedule(Goal) :-
   93    (   clause(cron_schedule(_, Goal0), true, Ref),
   94        Goal =@= Goal0,
   95        erase(Ref),
   96        fail
   97    ;   true
   98    ).
   99
  100compile_schedule(Var, _) :-
  101    var(Var),
  102    !,
  103    instantiation_error(Var).
  104compile_schedule(clear, clear).
  105compile_schedule(daily(Time0), daily(Time)) :-
  106    compile_time(Time0, Time).
  107compile_schedule(weekly(Day0, Time0), weekly(Day, Time)) :-
  108    compile_weekday(Day0, Day),
  109    compile_time(Time0, Time).
  110compile_schedule(monthly(Day, Time0), monthly(Day, Time)) :-
  111    must_be(between(0, 31), Day),
  112    compile_time(Time0, Time).
  113
  114compile_time(HH:MM0, HH:MM) :-
  115    must_be(between(0, 23), HH),
  116    must_be(between(0, 59), MM0),
  117    MM is ((MM0+4)//5)*5.
  118
  119compile_weekday(N, _) :-
  120    var(N),
  121    !,
  122    instantiation_error(N).
  123compile_weekday(N, N) :-
  124    integer(N),
  125    !,
  126    must_be(between(1,7), N).
  127compile_weekday(Day, N) :-
  128    downcase_atom(Day, Lwr),
  129    (   sub_atom(Lwr, 0, 3, _, Abbr),
  130        day(N, Abbr)
  131    ->  !
  132    ;   domain_error(day, Day)
  133    ).
 http_consider_cronstart
Run scheduled tasks.
  139http_consider_cronstart :-
  140    get_time(NowF),
  141    Now is round(NowF/60.0)*60,
  142    (   cron_schedule(Schedule, Goal),
  143        scheduled(Schedule, Now),
  144        catch(Goal, E, print_message(warning, E)),
  145        fail
  146    ;   true
  147    ).
  148
  149scheduled(daily(HH:MM), Now) :-
  150    stamp_date_time(Now, DateTime, local),
  151    date_time_value(time, DateTime, time(HH,MM,_)).
  152scheduled(weekly(Day, Time), Now) :-
  153    stamp_date_time(Now, DateTime, local),
  154    date_time_value(date, DateTime, Date),
  155    day_of_the_week(Date, Day),
  156    scheduled(daily(Time), Now).
  157scheduled(monthly(Day, Time), Now) :-
  158    stamp_date_time(Now, DateTime, local),
  159    date_time_value(day, DateTime, Day),
  160    scheduled(daily(Time), Now).
  161
  162day(1, mon).
  163day(2, tue).
  164day(3, wed).
  165day(4, thu).
  166day(5, fri).
  167day(6, sat).
  168day(7, sun)