1:- module(watcher, [start_watching_dirs/3,
    2                    stop_watching_dirs/1]).

filesystem watcher to automatically generate CSS

author
- James Cash */
    8:- use_module(library(apply_macros)).    9:- use_module(library(apply), [maplist/2]).   10:- use_module(library(css_write), [write_css/2, css//1]).   11:- use_module(library(filesex), [directory_member/3]).   12:- use_module(library(inotify), []).   13:- use_module(library(yall)).   14
   15:- use_module(library(tailwind_generate), [tw_from_file/2]).   16
   17:- dynamic watched_file_css/2.   18
   19not_hidden_file(Path) :-
   20    file_base_name(Path, Name),
   21    \+ ( sub_atom(Name, 0, _, _, '.') ).
 start_watching_dirs(+Dirs, +OutputFile, -Watcher) is det
Start watching the directories Dirs for file changes, outputting the combined CSS output as running tw_from_file/2 on each changed file, outputting to OutputFile. Watcher will be unified with an opaque value which can be passed to stop_watching_dirs/1 to stop the watcher running.
   30start_watching_dirs(Dirs, OutputFile, queues(WatcherQueue, BuilderQueue)) :-
   31    inotify:inotify_init(Watch, []),
   32    maplist({Watch}/[Dir]>>(
   33                inotify:inotify_add_watch(Watch, Dir, [create, delete])
   34            ), Dirs),
   35    forall(( member(Dir, Dirs),
   36             directory_member(Dir, SubDir, [recursive(true),
   37                                            exclude('.git'),
   38                                            exclude_directory('.git'),
   39                                            file_type(directory)])),
   40           inotify:inotify_add_watch(Watch, SubDir, [all])),
   41    forall(( member(Dir, Dirs),
   42             directory_member(Dir, P, [recursive(true), extensions([pl])])),
   43           ( not_hidden_file(P),
   44             inotify:inotify_add_watch(Watch, P, [all]),
   45             tw_from_file(P, Css),
   46             assertz(watched_file_css(P, Css)) )),
   47    generate_output(OutputFile),
   48    message_queue_create(WatcherQueue),
   49    message_queue_create(BuilderQueue),
   50    thread_create(build_css_output(BuilderQueue, OutputFile), _, []),
   51    thread_create(handle_file_changed(BuilderQueue, WatcherQueue, Watch), _, []).
 stop_watching_dirs(+Watcher) is det
Stop the watcher that was started with the opaque watcher Watcher.
   56stop_watching_dirs(queues(WatcherQueue, BuilderQueue)) :-
   57    thread_send_message(WatcherQueue, done),
   58    thread_send_message(BuilderQueue, done),
   59    retractall(watched_file_css(_, _)).
   60
   61handle_file_changed(BQ, WQ, Watch) :-
   62    inotify:inotify_read_event(Watch, Event, [timeout(0.5)]), !,
   63    catch(
   64        handle_event(Watch, BQ, Event),
   65        Err,
   66        debug(tailwind, "Error handling event: ~w", [Err])
   67    ),
   68    handle_file_changed(BQ, WQ, Watch).
   69handle_file_changed(BQ, WQ, Watch) :-
   70    thread_get_message(WQ, _, [timeout(0.5)])
   71    ->  inotify:inotify_close(Watch)
   72    ;  handle_file_changed(BQ, WQ, Watch).
   73
   74handle_event(Watch, BQ, create(file(File))) :-
   75    not_hidden_file(File),
   76    inotify:inotify_add_watch(Watch, File, [all]),
   77    tw_from_file(File, Css),
   78    assertz(watched_file_css(File, Css)),
   79    thread_send_message(BQ, update).
   80handle_event(Watch, _, create(directory(Dir))) :-
   81    not_hidden_file(Dir),
   82    inotify:inotify_add_watch(Watch, Dir, [all]).
   83handle_event(Watch, BQ, delete(file(File))) :-
   84    not_hidden_file(File),
   85    inotify:inotify_rm_watch(Watch, File),
   86    retractall(watched_file_css(File, _)),
   87    thread_send_message(BQ, update).
   88handle_event(_, BQ, modify(file(File))) :-
   89    tw_from_file(File, NewCss),
   90    ( watched_file_css(File, OldCss) -> true ; OldCss = [] ),
   91    ( NewCss == OldCss
   92    -> debug(tailwind, "no changes", [])
   93    ; ( transaction((retractall(watched_file_css(File, _)),
   94                     assertz(watched_file_css(File, NewCss)))),
   95        thread_send_message(BQ, update) )).
   96handle_event(W, BQ, close_write(file(F))) :-
   97    handle_event(W, BQ, modify(file(F))).
   98handle_event(_, _, Event) :-
   99    debug(yyy, "other event ~w", [Event]).
  100
  101build_css_output(Queue, Outfile) :-
  102    thread_get_message(Queue, Msg),
  103    ( Msg == done
  104    -> true
  105    ;  ( debug(tailwind, "Updating CSS", []),
  106         generate_output(Outfile),
  107         build_css_output(Queue, Outfile) )).
  108
  109generate_output(Outfile) :-
  110    setof(Style,
  111          F^Styles^(
  112              watched_file_css(F, Styles),
  113              member(Style, Styles) ),
  114          Css), !,
  115    write_css(css(Css), Txt),
  116    setup_call_cleanup(
  117        open(Outfile, write, Stream),
  118        format(Stream, "~s", [Txt]),
  119        close(Stream)
  120    ).
  121generate_output(_) :-
  122    debug(tailwind, "no css found", [])