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) 2008-2025, University of Amsterdam 7 VU University Amsterdam 8 CWI, Amsterdam 9 SWI-Prolog Solutions b.v. 10 All rights reserved. 11 12 Redistribution and use in source and binary forms, with or without 13 modification, are permitted provided that the following conditions 14 are met: 15 16 1. Redistributions of source code must retain the above copyright 17 notice, this list of conditions and the following disclaimer. 18 19 2. Redistributions in binary form must reproduce the above copyright 20 notice, this list of conditions and the following disclaimer in 21 the documentation and/or other materials provided with the 22 distribution. 23 24 THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS 25 "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT 26 LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS 27 FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE 28 COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, 29 INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, 30 BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; 31 LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER 32 CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT 33 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN 34 ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE 35 POSSIBILITY OF SUCH DAMAGE. 36*/ 37 38:- module(http_log, 39 [ http_log_stream/1, % -Stream 40 http_log/2, % +Format, +Args 41 http_log_close/1, % +Reason 42 post_data_encoded/2, % ?Bytes, ?Encoded 43 http_logrotate/1, % +Options 44 http_schedule_logrotate/2 % +When, +Options 45 ]). 46:- use_module(library(http/http_header)). 47:- use_module(library(settings)). 48:- use_module(library(option)). 49:- use_module(library(error)). 50:- use_module(library(debug)). 51:- use_module(library(broadcast)). 52 53:- setting(http:logfile, callable, 'httpd.log', 54 'File in which to log HTTP requests'). 55:- setting(http:log_post_data, integer, 0, 56 'Log POST data up to N bytes long'). 57:- setting(http:on_log_error, any, retry, 58 'Action if logging fails').
73:- multifile 74 nolog/1, 75 password_field/1, 76 nolog_post_content_type/1. 77 78% If the log settings change, simply close the log and it will be 79% reopened with the new settings. 80 81:- listen(settings(changed(http:logfile, _, New)), 82 http_log_close(changed(New))). 83:- listen(http(Message), 84 http_message(Message)). 85:- listen(logrotate, 86 http_log_close(logrotate)). 87 88http_message(Message) :- 89 log_message(Message), 90 http_log_stream(Stream), 91 E = error(_,_), 92 catch(http_message(Message, Stream), E, 93 log_error(E)). 94 95log_message(request_start(_Id, _Request)). 96log_message(request_finished(_Id, _Code, _Status, _CPU, _Bytes)). 97 98http_message(request_start(Id, Request), Stream) :- 99 log_started(Request, Id, Stream). 100http_message(request_finished(Id, Code, Status, CPU, Bytes), Stream) :- 101 log_completed(Code, Status, Bytes, Id, CPU, Stream).
http:on_log_error
, which is one of:
halt(Code)
. The exit
variant is
equivalent to exit(1)
.
The best choice depends on your priorities. Using retry
gives
priority to keep the server running. Using exit
guarantees proper
log files and thus the ability to examine these for security
reasons. An attacker may try to flood the disc, causing a successful
DoS attack if exit
is used and the ability to interact without
being logged if retry
is used.
125log_error(E) :- 126 print_message(warning, E), 127 log_error_continue. 128 129log_error_continue :- 130 setting(http:on_log_error, Action), 131 log_error_continue(Action). 132 133log_error_continue(retry) :- 134 http_log_close(error). 135log_error_continue(exit) :- 136 log_error_continue(exit(1)). 137log_error_continue(exit(Code)) :- 138 halt(Code). 139 140 141 142 /******************************* 143 * LOG ACTIVITY * 144 *******************************/ 145 146:- dynamic 147 log_stream/2, % Stream, TimeTried 148 halt_registered/0.
append
mode if the file is not yet open. The log file
is determined from the setting http:logfile
. If this setting is
set to the empty atom (''), this predicate fails.
If a file error is encountered, this is reported using print_message/2, after which this predicate silently fails. Opening is retried every minute when a new message arrives.
Before opening the log file, the message http_log_open(Term)
is
broadcasted. This message allows for creating the directory,
renaming, deleting or truncating an existing log file.
165http_log_stream(Stream) :- 166 log_stream(Stream, _Opened), 167 !, 168 Stream \== []. 169http_log_stream([]) :- 170 setting(http:logfile, ''), 171 !, 172 get_time(Now), 173 assert(log_stream([], Now)), 174 fail. 175http_log_stream(Stream) :- 176 setting(http:logfile, Term), 177 broadcast(http_log_open(Term)), 178 catch(absolute_file_name(Term, File, 179 [ access(append) 180 ]), 181 E, open_error(E)), 182 with_mutex(http_log, open_log(File, Stream0)), 183 Stream = Stream0. 184 185open_log(_File, Stream) :- 186 log_stream(Stream, Opened), 187 ( Stream == [] 188 -> ( get_time(Now), 189 Now - Opened > 60 190 -> retractall(log_stream(_,_)), 191 fail 192 ; !, fail 193 ) 194 ; true 195 ), !. 196open_log(File, Stream) :- 197 catch(open(File, append, Stream, 198 [ close_on_abort(false), 199 encoding(utf8), 200 buffer(line) 201 ]), E, open_error(E)), 202 get_time(Time), 203 register_close_log, 204 Error = error(_,_), 205 catch(format(Stream, 206 'server(started, ~0f).~n', 207 [ Time ]), 208 Error, 209 open_error(Stream, Error)), 210 assert(log_stream(Stream, Time)). 211 212open_error(Stream, E) :- 213 close(Stream, [force(true)]), 214 open_error(E). 215 216open_error(E) :- 217 print_message(error, E), 218 log_open_error_continue. 219 220log_open_error_continue :- 221 setting(http:on_log_error, Action), 222 log_open_error_continue(Action). 223 224log_open_error_continue(retry) :- 225 !, 226 get_time(Now), 227 assert(log_stream([], Now)), 228 fail. 229log_open_error_continue(Action) :- 230 log_error_continue(Action). 231 232register_close_log :- 233 halt_registered, 234 !. 235register_close_log :- 236 at_halt(close_log(stopped)), 237 asserta(halt_registered).
server(Reason, Time)
. to the logfile. This call is
intended for cooperation with the Unix logrotate facility
using the following schema:
254http_log_close(Reason) :- 255 with_mutex(http_log, close_log(Reason)). 256 257close_log(Reason) :- 258 retract(log_stream(Stream, _Opened)), 259 !, 260 ( is_stream(Stream) 261 -> get_time(Time), 262 catch(( format(Stream, 'server(~q, ~0f).~n', [ Reason, Time ]), 263 close(Stream) 264 ), E, print_message(warning, E)) 265 ; true 266 ). 267close_log(_).
275http_log(Format, Args) :-
276 ( http_log_stream(Stream)
277 -> Error = error(_,_),
278 catch(system:format(Stream, Format, Args), % use operators from `system`
279 Error,
280 log_error(Error))
281 ; true
282 ).
291log_started(Request, Id, Stream) :- 292 is_stream(Stream), 293 !, 294 get_time(Now), 295 add_post_data(Request, Request1), 296 log_request(Request1, LogRequest), 297 format_time(string(HDate), '%+', Now), 298 format(Stream, 299 '/*~s*/ request(~q, ~3f, ~q).~n', 300 [HDate, Id, Now, LogRequest]). 301log_started(_, _, _).
308log_request([], []). 309log_request([search(Search0)|T0], [search(Search)|T]) :- 310 !, 311 mask_passwords(Search0, Search), 312 log_request(T0, T). 313log_request([H|T0], T) :- 314 nolog(H), 315 !, 316 log_request(T0, T). 317log_request([H|T0], [H|T]) :- 318 log_request(T0, T). 319 320mask_passwords([], []). 321mask_passwords([Name=_|T0], [Name=xxx|T]) :- 322 password_field(Name), 323 !, 324 mask_passwords(T0, T). 325mask_passwords([H|T0], [H|T]) :- 326 mask_passwords(T0, T).
333password_field(password). 334password_field(pwd0). 335password_field(pwd1). 336password_field(pwd2).
344nolog(input(_)). 345nolog(accept(_)). 346nolog(accept_language(_)). 347nolog(accept_encoding(_)). 348nolog(accept_charset(_)). 349nolog(pool(_)). 350nolog(protocol(_)). 351nolog(referer(R)) :- 352 sub_atom(R, _, _, _, password), 353 !.
Content-type
header. If the
hook succeeds, the POST data is not logged. For example, to stop
logging anything but application/json messages:
:- multifile http_log:nolog_post_content_type/1. http_log:nolog_post_content_type(Type) :- Type \= (application/json).
post_data(Data)
if the setting
http:log_post_data is an integer > 0, the content length < this
setting and nolog_post_content_type/1 does not succeed on the
provided content type.377add_post_data(Request0, Request) :- 378 setting(http:log_post_data, MaxLen), 379 integer(MaxLen), MaxLen > 0, 380 memberchk(input(In), Request0), 381 memberchk(content_length(CLen), Request0), 382 CLen =< MaxLen, 383 memberchk(content_type(Type), Request0), 384 http_parse_header_value(content_type, Type, media(MType/MSubType, _)), 385 \+ nolog_post_content_type(MType/MSubType), 386 catch(peek_string(In, CLen, PostData), _, fail), 387 !, 388 post_data_encoded(PostData, Encoded), 389 Request = [post_data(Encoded)|Request0]. 390add_post_data(Request, Request).
399post_data_encoded(Bytes, Hex) :- 400 nonvar(Bytes), 401 !, 402 setup_call_cleanup( 403 new_memory_file(HMem), 404 ( setup_call_cleanup( 405 ( open_memory_file(HMem, write, Out, [encoding(octet)]), 406 zopen(Out, ZOut, []) 407 ), 408 format(ZOut, '~s', [Bytes]), 409 close(ZOut)), 410 memory_file_to_codes(HMem, Codes, octet) 411 ), 412 free_memory_file(HMem)), 413 phrase(base64(Codes), EncCodes), 414 string_codes(Hex, EncCodes). 415post_data_encoded(Bytes, Hex) :- 416 string_codes(Hex, EncCodes), 417 phrase(base64(Codes), EncCodes), 418 string_codes(ZBytes, Codes), 419 setup_call_cleanup( 420 open_string(ZBytes, In), 421 zopen(In, Zin, []), 422 read_string(Zin, _, Bytes)).
433log_completed(Code, Status, Bytes, Id, CPU, Stream) :- 434 is_stream(Stream), 435 log_check_deleted(Stream), 436 !, 437 log(Code, Status, Bytes, Id, CPU, Stream). 438log_completed(Code, Status, Bytes, Id, CPU0, _) :- 439 http_log_stream(Stream), % Logfile has changed! 440 !, 441 log_completed(Code, Status, Bytes, Id, CPU0, Stream). 442log_completed(_,_,_,_,_,_). 443 444 445log(Code, ok, Bytes, Id, CPU, Stream) :- 446 !, 447 format(Stream, 'completed(~q, ~q, ~q, ~q, ok).~n', 448 [ Id, CPU, Bytes, Code ]). 449log(Code, Status, Bytes, Id, CPU, Stream) :- 450 ( map_exception(Status, Term) 451 -> true 452 ; message_to_string(Status, String), 453 Term = error(String) 454 ), 455 format(Stream, 'completed(~q, ~q, ~q, ~q, ~W).~n', 456 [ Id, CPU, Bytes, Code, 457 Term, [ quoted(true), 458 ignore_ops(true), 459 blobs(portray), 460 portray_goal(write_blob) 461 ] 462 ]). 463 464:- public write_blob/2. 465write_blob(Blob, _Options) :- 466 format(string(S), '~q', [Blob]), 467 writeq(blob(S)). 468 469map_exception(http_reply(bytes(ContentType,Bytes),_), bytes(ContentType,L)) :- 470 string_length(Bytes, L). % also does lists 471map_exception(http_reply(Reply), Reply). 472map_exception(http_reply(Reply, _), Reply). 473map_exception(error(existence_error(http_location, Location), _Stack), 474 error(404, Location)). 475 476 477 /******************************* 478 * LOGROTATE SUPPORT * 479 *******************************/
491log_check_deleted(Stream) :- 492 stream_property(Stream, nlink(Links)), 493 Links == 0, 494 !, 495 http_log_close(log_file_deleted), 496 fail. 497log_check_deleted(_).
Options:
true
, rotate the log files in the background.528http_logrotate(Options) :- 529 select_option(background(true), Options, Options1), 530 !, 531 thread_create(http_logrotate(Options1), _, 532 [ alias('__logrotate'), 533 detached(true) 534 ]). 535http_logrotate(Options) :- 536 option(keep_logs(Keep), Options, 10), 537 option(compress_logs(Format), Options, gzip), 538 compress_extension(Format, ZExt), 539 log_file_and_ext(Base, Ext), 540 ( log_too_small(Base, Ext, Options) 541 -> true 542 ; rotate_logs(Base, Ext, ZExt, Keep) 543 ). 544 545rotate_logs(Base, Ext, ZExt, N1) :- 546 N1 > 0, 547 !, 548 N0 is N1 - 1, 549 old_log_file(Base, Ext, N0, ZO, Old), 550 ( exists_file(Old) 551 -> new_log_file(Base, Ext, N1, ZO, ZExt, ZN, New), 552 rename_log_file(ZO, Old, ZN, New) 553 ; true 554 ), 555 rotate_logs(Base, Ext, ZExt, N0). 556rotate_logs(_, _, _, _). 557 558rename_log_file(ZExt, Old, ZExt, New) :- 559 !, 560 debug(logrotate, 'Rename ~p --> ~p', [Old, New]), 561 rename_file(Old, New). 562rename_log_file('', Old, ZExt, New) :- 563 file_name_extension(NoExt, ZExt, New), 564 debug(logrotate, 'Rename ~p --> ~p', [Old, NoExt]), 565 rename_file(Old, NoExt), 566 debug(logrotate, 'Closing log file', []), 567 http_log_close(logrotate), 568 compress_extension(Format, ZExt), 569 debug(logrotate, 'Compressing (~w) ~p', [Format, NoExt]), 570 compress_file(NoExt, Format). 571 572old_log_file(Base, Ext, N, ZExt, File) :- 573 log_file(Base, Ext, N, File0), 574 ( compress_extension(_, ZExt), 575 file_name_extension(File0, ZExt, File1), 576 exists_file(File1) 577 -> File = File1 578 ; ZExt = '', 579 File = File0 580 ). 581 582new_log_file(Base, Ext, N, '', '', '', File) :- 583 !, 584 log_file(Base, Ext, N, File). 585new_log_file(Base, Ext, N, '', ZExt, ZExt, File) :- 586 !, 587 log_file(Base, Ext, N, File0), 588 file_name_extension(File0, ZExt, File). 589new_log_file(Base, Ext, N, ZExt, _, ZExt, File) :- 590 log_file(Base, Ext, N, File0), 591 file_name_extension(File0, ZExt, File). 592 593log_file(Base, Ext, 0, File) :- 594 !, 595 file_name_extension(Base, Ext, File). 596log_file(Base, Ext, N, File) :- 597 atomic_list_concat([Base, -, N], Base1), 598 file_name_extension(Base1, Ext, File). 599 600log_file_and_ext(Base, Ext) :- 601 setting(http:logfile, Term), 602 catch(absolute_file_name(Term, File, 603 [ access(exist) 604 ]), _, fail), 605 file_name_extension(Base, Ext, File). 606 607log_too_small(Base, Ext, Options) :- 608 DefMin is 1024*1024, 609 option(min_size(MinBytes), Options, DefMin), 610 file_name_extension(Base, Ext, File), 611 ( exists_file(File) 612 -> size_file(File, Bytes), 613 Bytes < MinBytes, 614 debug(logrotate, '~w has ~D bytes; not rotating', [File, Bytes]) 615 ; debug(logrotate, '~w does not exist; not rotating', [File]) 616 ).
623compress_file(File, Format) :- 624 ( compress_extension(Format, Ext) 625 -> true 626 ; domain_error(compress_format, Format) 627 ), 628 file_name_extension(File, Ext, ZFile), 629 catch(setup_call_cleanup( 630 gzopen(ZFile, write, Out, [type(binary)]), 631 setup_call_cleanup( 632 open(File, read, In, [type(binary)]), 633 copy_stream_data(In, Out), 634 close(In)), 635 close(Out)), 636 Error, 637 ( print_message(error, Error), 638 catch(delete_file(Out), _, true), 639 throw(Error) 640 )), 641 delete_file(File). 642 643compress_extension(gzip, gz). 644 645:- dynamic 646 scheduled_logrotate/2. % Schedule, Options
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).
667http_schedule_logrotate(When, Options) :- 668 listen(maintenance(_,_), http_consider_logrotate), 669 compile_schedule(When, Schedule), 670 retractall(scheduled_logrotate(_,_)), 671 asserta(scheduled_logrotate(Schedule, Options)). 672 673compile_schedule(Var, _) :- 674 var(Var), 675 !, 676 instantiation_error(Var). 677compile_schedule(daily(Time0), daily(Time)) :- 678 compile_time(Time0, Time). 679compile_schedule(weekly(Day0, Time0), weekly(Day, Time)) :- 680 compile_weekday(Day0, Day), 681 compile_time(Time0, Time). 682compile_schedule(monthly(Day, Time0), monthly(Day, Time)) :- 683 must_be(between(0, 31), Day), 684 compile_time(Time0, Time). 685 686compile_time(HH:MM0, HH:MM) :- 687 must_be(between(0, 23), HH), 688 must_be(between(0, 59), MM0), 689 MM is ((MM0+4)//5)*5. 690 691compile_weekday(N, _) :- 692 var(N), 693 !, 694 instantiation_error(N). 695compile_weekday(N, N) :- 696 integer(N), 697 !, 698 must_be(between(1,7), N). 699compile_weekday(Day, N) :- 700 downcase_atom(Day, Lwr), 701 ( sub_atom(Lwr, 0, 3, _, Abbr), 702 day(N, Abbr) 703 -> ! 704 ; domain_error(day, Day) 705 ).
711http_consider_logrotate :- 712 scheduled_logrotate(Schedule, Options), 713 get_time(NowF), 714 Now is round(NowF/60.0)*60, 715 scheduled(Schedule, Now), 716 !, 717 http_logrotate([background(true)|Options]). 718 719scheduled(daily(HH:MM), Now) :- 720 stamp_date_time(Now, DateTime, local), 721 date_time_value(time, DateTime, time(HH,MM,_)). 722scheduled(weekly(Day, Time), Now) :- 723 stamp_date_time(Now, DateTime, local), 724 date_time_value(date, DateTime, Date), 725 day_of_the_week(Date, Day), 726 scheduled(daily(Time), Now). 727scheduled(monthly(Day, Time), Now) :- 728 stamp_date_time(Now, DateTime, local), 729 date_time_value(day, DateTime, Day), 730 scheduled(daily(Time), Now). 731 732day(1, mon). 733day(2, tue). 734day(3, wed). 735day(4, thu). 736day(5, fri). 737day(6, sat). 738day(7, sun)
HTTP Logging module
Simple module for logging HTTP requests to a file. Logging is enabled by loading this file and ensure the setting http:logfile is not the empty atom. The default file for writing the log is
httpd.log
. See library(settings) for details.The level of logging can be modified using the multifile predicate nolog/1 to hide HTTP request fields from the logfile and password_field/1 to hide passwords from HTTP search specifications (e.g.
/topsecret?password=secret
). */