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) 2017, VU University Amsterdam 7 All rights reserved. 8 9 Redistribution and use in source and binary forms, with or without 10 modification, are permitted provided that the following conditions 11 are met: 12 13 1. Redistributions of source code must retain the above copyright 14 notice, this list of conditions and the following disclaimer. 15 16 2. Redistributions in binary form must reproduce the above copyright 17 notice, this list of conditions and the following disclaimer in 18 the documentation and/or other materials provided with the 19 distribution. 20 21 THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS 22 "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT 23 LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS 24 FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE 25 COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, 26 INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, 27 BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; 28 LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER 29 CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT 30 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN 31 ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE 32 POSSIBILITY OF SUCH DAMAGE. 33*/ 34 35:- module(inotify, 36 [ inotify_init/2, % -INotify, +Options 37 inotify_close/1, % +INotify 38 inotify_add_watch/3, % +INotify, +Path, +Options 39 inotify_rm_watch/2, % +INotify, +Path 40 inotify_read_event/3, % +INotify, -Event, +Options 41 inotify_current_watch/2 % ?INotify, ?Watch 42 ]). 43 44:- use_foreign_library(foreign(inotify4pl)).
56:- dynamic inotify/4. % INotify, Path, WatchID, Type 57:- volatile inotify/4.
67inotify_close(INotify) :-
68 inotify_close_(INotify),
69 retractall(inotify(INotify, _, _, _)).
inotify(7)
. The Prolog version is derived from the C
macro name (e.g., IN_CLOSE_WRITE) by dropping IN_ and turning the
remainder to lower case (e.g., close_write
). Using all
watches
for all events.81inotify_add_watch(INotify, Spec, Options) :- 82 spec_path(Spec, Path, Type), 83 inotify_add_watch(INotify, Path, Watch, Options), 84 assertz(inotify(INotify, Watch, Path, Type)). 85 86spec_path(Spec, Path, directory) :- 87 absolute_file_name(Spec, Path0, [file_errors(fail), file_type(directory)]), 88 !, 89 Path = Path0. 90spec_path(Spec, Path, file) :- 91 absolute_file_name(Spec, Path, [access(exist)]).
inotify(7)
. The Prolog version is
derived from the C macro name (e.g., IN_CLOSE_WRITE) by dropping IN_
and turning the remainder to lower case (e.g., close_write
).108inotify_rm_watch(INotify, Watch) :- 109 integer(Watch), !, 110 inotify_rm_watch_(INotify, Watch), 111 retractall(inotify(INotify, Watch, _, _)). 112inotify_rm_watch(INotify, Path) :- 113 atom(Path), 114 retract(inotify(INotify, Watch, Path, _Type)), 115 !, 116 inotify_rm_watch_(INotify, Watch). 117inotify_rm_watch(INotify, Spec) :- 118 spec_path(Spec, Path, Type), 119 retract(inotify(INotify, Watch, Path, Type)), 120 !, 121 inotify_rm_watch_(INotify, Watch).
127inotify_current_watch(INotify, Path) :-
128 inotify(INotify, _Watch, Path, _Type).
member(File)
, directory
or file
ignored
,
q_overflow
or unmount
. Note that the isdir
flag
defines the value for Object.Options defined are:
poll()
API, which implies a 1 millisecond
granularity and a max time of (2^31)/1000 seconds.file(File)
or
directory(Directory)
and action is one of:
write(2)
, truncate(2)
).189inotify_read_event(INotify, Event, Options) :- 190 inotify_read_event_(INotify, 191 inotify(Watch, Action, Cookie, On0, Flags), 192 Options), 193 on_object(On0, Watch, INotify, On), 194 map_event(Action, Watch, Cookie, On, Flags, INotify, Event0), 195 ( Event0 == again 196 -> inotify_read_event(INotify, Event, Options) 197 ; Event = Event0 198 ). 199 200on_object(file, Watch, INotify, file(File)) :- 201 inotify(INotify, Watch, File, _Type). 202on_object(directory, Watch, INotify, directory(Directory)) :- 203 inotify(INotify, Watch, Directory, _Type). 204on_object(unknown, Watch, INotify, Obj) :- 205 inotify(INotify, Watch, Path, Type), 206 Obj =.. [Type,Path]. 207on_object(member(File), Watch, INotify, file(Path)) :- 208 inotify(INotify, Watch, Directory, _Type), 209 atomic_list_concat([Directory, File], /, Path).
213map_event(null, Watch, _Cookie, _Obj, Flags, INotify, again) :- 214 memberchk(ignored, Flags), 215 !, 216 retractall(inotify(INotify, Watch, _, _)). 217map_event(Action, _Watch, _Cookie, Obj, _Flags, _INotify, Event) :- 218 Event =.. [Action,Obj]
Monitor file system changes
This library provides an interface to the Linux inotify API that generates events for changes to the file system. The interface exposes a high level interface that is built on top of a complete encapsulation of the low-level Linux inotify API. The high level interface maintains an admin of watched locations and translates the events to the physical file locations. */