34
35:- module(in_make,
36 [ in_make/0,
37 in_nomake/0
38 ]). 39:- use_module(library(inotify)). 40:- use_module(library(debug)). 41:- use_module(library(make)). 42:- use_module(library(solution_sequences)).
63:- dynamic
64 in/1.
74in_make :-
75 in(_),
76 !,
77 print_message(warning, in_make(running)).
78in_make :-
79 in_monitor(IN),
80 thread_create(in_make_loop(IN), _, [alias(in_make)]).
81
82in_monitor(IN) :-
83 inotify_init(IN, []),
84 asserta(in(IN)),
85 forall(distinct(source_dir(Dir)),
86 watch_prolog_dir(IN, Dir)).
87
88watch_prolog_dir(_IN, Dir) :-
89 current_prolog_flag(home, Home),
90 sub_atom(Dir, 0, _, _, Home),
91 !.
92watch_prolog_dir(IN, Dir) :-
93 inotify_add_watch(IN, Dir, [close_write]).
94
95source_dir(Dir) :-
96 source_file(File),
97 file_directory_name(File, Dir).
98
99in_make_loop(IN) :-
100 repeat,
101 ( inotify_read_event(IN, Ev, [])
102 -> debug(in_make(event), 'Ev: ~p', [Ev]),
103 handle(Ev),
104 fail
105 ; debug(in_make, 'Timeout~n', [])
106 ).
107
108handle(close_write(file(File))) =>
109 source_file(File),
110 make.
111handle(Ev) =>
112 debug(in_make(ignored), 'Ignored: ~p', [Ev]).
118in_nomake :-
119 ( catch(thread_signal(in_make, abort), _, fail)
120 -> thread_join(in_make, _)
121 ; true
122 ),
123 retract(in(IN)),
124 inotify_close(IN).
125
126:- multifile user:message_hook/3. 127
128user:message_hook(load_file(done(_Level,
129 file(_File, Absolute),
130 _Action,
131 _LM,
132 _TimeUsed,
133 _ClausesCreated)),
134 _Kind, _Lines) :-
135 in(IN),
136 file_directory_name(Absolute, Dir),
137 ( inotify_current_watch(IN, Dir)
138 -> true
139 ; watch_prolog_dir(IN, Dir)
140 ),
141 fail.
142
143 146
147:- multifile prolog:message//1. 148
149prolog:message(in_make(running)) -->
150 [ 'in_make/0: already running'-[] ]
Automatically reload sources
This library simplifies the development cycle by reloading source files immediately when they are saved, regardless of the process that saved the file (i.e., this may be an external editor). To use it, add the following to the load file of your project or your
init.pl
file.Note that the files are reloaded by the
in_make
thread. If reloading affects thread-local properties these may not be visible in all threads. Examples are global variables, thread_local predicates and Prolog flags. */