1/*  Part of SWI-Prolog
2
3    Author:        Jan Wielemaker
4    E-mail:        J.Wielemaker@uva.nl
5    WWW:           http://www.swi-prolog.org
6    Copyright (C): 2009, University of Amsterdam
7
8    This program is free software; you can redistribute it and/or
9    modify it under the terms of the GNU General Public License
10    as published by the Free Software Foundation; either version 2
11    of the License, or (at your option) any later version.
12
13    This program is distributed in the hope that it will be useful,
14    but WITHOUT ANY WARRANTY; without even the implied warranty of
15    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
16    GNU General Public License for more details.
17
18    You should have received a copy of the GNU General Public
19    License along with this library; if not, write to the Free Software
20    Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
21
22    As a special exception, if you link this library with other files,
23    compiled with a Free Software compiler, to produce an executable, this
24    library does not by itself cause the resulting executable to be covered
25    by the GNU General Public License. This exception does not however
26    invalidate any other reasons why the executable file might be covered by
27    the GNU General Public License.
28*/
29
30:- module(http_log,
31	  [ http_log_stream/1,		% -Stream
32	    http_log/2,			% +Format, +Args
33	    http_log_close/1		% +Reason
34	  ]).
35:- use_module(library(settings)).
36:- use_module(library(broadcast)).
37
38:- setting(http:logfile, atom, 'httpd.log',
39	   'File in which to log HTTP requests').
40
41/** <module> HTTP Logging module
42
43Simple module for logging HTTP requests to a file. Logging is enabled by
44loading this file and ensure the setting   http:logfile is not the empty
45atom. The default  file  for  writing   the  log  is  =|httpd.log|=. See
46library(settings) for details.
47
48The  level  of  logging  can  modified  using  the  multifile  predicate
49http_log:nolog/1 to hide HTTP  request  fields   from  the  logfile  and
50http_log:password_field/1   to   hide   passwords   from   HTTP   search
51specifications (e.g. =|/topsecret?password=secret|=).
52*/
53
54:- multifile
55	nolog/1,
56	password_field/1.
57
58% If the log settings change,  simply  close   the  log  and  it will be
59% reopened with the new settings.
60
61:- listen(settings(changed(http:logfile, _, New)),
62	  http_log_close(changed(New))).
63:- listen(http(Message),
64	  http_message(Message)).
65
66
67http_message(request_start(Id, Request)) :- !,
68	http_log_stream(Stream),
69	log_started(Request, Id, Stream).
70http_message(request_finished(Id, Code, Status, CPU, Bytes)) :- !,
71	http_log_stream(Stream),
72	log_completed(Code, Status, Bytes, Id, CPU, Stream).
73
74
75		 /*******************************
76		 *	   LOG ACTIVITY		*
77		 *******************************/
78
79:- dynamic
80	log_stream/1.
81
82%%	http_log_stream(-Stream) is semidet.
83%
84%	Returns handle to open logfile. Fails if no logfile is open and
85%	none is defined.
86
87http_log_stream(Stream) :-
88	log_stream(Stream), !,
89	Stream \== [].
90http_log_stream(Stream) :-
91	setting(http:logfile, File),
92	File \== '', !,
93	with_mutex(http_log,
94		   (   open(File, append, Stream,
95			    [ close_on_abort(false),
96			      encoding(utf8),
97			      buffer(line)
98			    ]),
99		       get_time(Time),
100		       format(Stream,
101			      'server(started, ~0f).~n',
102			      [ Time ]),
103		       assert(log_stream(Stream)),
104		       at_halt(close_log(stopped))
105		   )).
106http_log_stream(_) :-
107	assert(log_stream([])).
108
109%%	http_log_close(+Reason) is det.
110%
111%	If there is a currently open HTTP logfile, close it after adding
112%	a term server(Reason, Time).  to  the   logfile.  This  call  is
113%	intended for cooperation with the Unix logrotate facility
114%	using the following schema:
115%
116%	    * Move logfile (the HTTP server keeps writing to the moved
117%	    file)
118%	    * Inform the server using an HTTP request that calls
119%	    http_log_close/1
120%	    * Compress the moved logfile
121%
122%	@author Suggested by Jacco van Ossenbruggen
123
124http_log_close(Reason) :-
125	with_mutex(http_log, close_log(Reason)).
126
127close_log(Reason) :-
128	retract(log_stream(Stream)), !,
129	(   Stream == []
130	->  true
131	;   get_time(Time),
132	    format(Stream, 'server(~q, ~0f).~n', [ Reason, Time ]),
133	    close(Stream)
134	).
135close_log(_).
136
137%%	http_log(+Format, +Args) is det.
138%
139%	Write message from Format and Args   to log-stream. See format/2
140%	for details. Succeed without side  effects   if  logging  is not
141%	enabled.
142
143http_log(Format, Args) :-
144	(   http_log_stream(Stream)
145	->  format(Stream, Format, Args)
146	;   true
147	).
148
149
150%%	log_started(+Request, +Id, +Stream) is det.
151%
152%	Write log message that Request was started to Stream.
153%
154%	@param	Filled with sequence identifier for the request
155
156log_started(Request, Id, Stream) :-
157	get_time(Now),
158	log_request(Request, LogRequest),
159	format_time(string(HDate), '%+', Now),
160	format(Stream,
161	       '/*~s*/ request(~q, ~3f, ~q).~n',
162	       [HDate, Id, Now, LogRequest]).
163
164%%	log_request(+Request, -Log)
165%
166%	Remove passwords from the request to avoid sending them to the
167%	logfiles.
168
169log_request([], []).
170log_request([search(Search0)|T0], [search(Search)|T]) :- !,
171	mask_passwords(Search0, Search),
172	log_request(T0, T).
173log_request([H|T0], T) :-
174	nolog(H), !,
175	log_request(T0, T).
176log_request([H|T0], [H|T]) :-
177	log_request(T0, T).
178
179mask_passwords([], []).
180mask_passwords([Name=_|T0], [Name=xxx|T]) :-
181	password_field(Name), !,
182	mask_passwords(T0, T).
183mask_passwords([H|T0], [H|T]) :-
184	mask_passwords(T0, T).
185
186%%	password_field(+Field) is semidet.
187%
188%	Multifile predicate that can be defined to hide passwords from
189%	the logfile.
190
191password_field(password).
192password_field(pwd0).
193password_field(pwd1).
194password_field(pwd2).
195
196
197%%	nolog(+HTTPField)
198%
199%	Multifile  predicate  that  can  be   defined  to  hide  request
200%	parameters from the request logfile.
201
202nolog(input(_)).
203nolog(accept(_)).
204nolog(accept_language(_)).
205nolog(accept_encoding(_)).
206nolog(accept_charset(_)).
207nolog(pool(_)).
208nolog(protocol(_)).
209nolog(referer(R)) :-
210	sub_atom(R, _, _, _, password), !.
211
212%%	log_completed(+Code, +Status, +Bytes, +Id, +CPU, +Stream) is det.
213%
214%	Write log message to Stream from a call_cleanup/3 call.
215%
216%	@param Status	2nd argument of call_cleanup/3
217%	@param Id	Term identifying the completed request
218%	@param CPU0	CPU time at time of entrance
219%	@param Stream	Stream to write to (normally from http_log_stream/1).
220
221log_completed(Code, Status, Bytes, Id, CPU, Stream) :-
222	is_stream(Stream),
223	log_check_deleted(Stream), !,
224	log(Code, Status, Bytes, Id, CPU, Stream).
225log_completed(Code, Status, Bytes, Id, CPU0, _) :-
226	http_log_stream(Stream), !,	% Logfile has changed!
227	log_completed(Code, Status, Bytes, Id, CPU0, Stream).
228log_completed(_,_,_,_,_,_).
229
230
231%%	log_check_deleted(+Stream) is semidet.
232%
233%	If the link-count of the stream has   dropped  to zero, the file
234%	has been deleted/moved. In this case the  log file is closed and
235%	log_check_deleted/6 will open a  new   one.  This  provides some
236%	support for cleaning up the logfile   without  shutting down the
237%	server.
238%
239%	@see logrotate(1) to manage logfiles on Unix systems.
240
241log_check_deleted(Stream) :-
242	stream_property(Stream, nlink(Links)),
243	Links == 0, !,
244	http_log_close(log_file_deleted),
245	fail.
246log_check_deleted(_).
247
248
249log(Code, ok, Bytes, Id, CPU, Stream) :- !,
250	format(Stream, 'completed(~q, ~2f, ~q, ~q, ok).~n',
251	       [ Id, CPU, Bytes, Code ]).
252log(Code, Status, Bytes, Id, CPU, Stream) :-
253	(   map_exception(Status, Term)
254	->  true
255	;   message_to_string(Status, String),
256	    Term = error(String)
257	),
258	format(Stream, 'completed(~q, ~2f, ~q, ~q, ~q).~n',
259	       [ Id, CPU, Bytes, Code, Term ]).
260
261map_exception(http_reply(Reply), Reply).
262map_exception(error(existence_error(http_location, Location), _Stack),
263	      error(404, Location)).
264