summaryrefslogtreecommitdiff
path: root/prolog/runner/daemon.pl
diff options
context:
space:
mode:
authorMarko Pušnik <marko.pusnik@guru.si>2015-10-06 00:41:37 +0200
committerMarko Pušnik <marko.pusnik@guru.si>2015-10-06 00:41:37 +0200
commit0f65272cd8f456a3e1d88d983590f47462b77e72 (patch)
tree021394bae27d500a907366bf5819759ad46ae9ec /prolog/runner/daemon.pl
parent17b999c2739006c2ec3b37ed64f119c9ad0b3338 (diff)
parente61c812f5f652c87cae76bdd155249cda14dcdff (diff)
Merge branch 'master' of ssh://212.235.189.51:22122/codeq-server
Diffstat (limited to 'prolog/runner/daemon.pl')
-rwxr-xr-xprolog/runner/daemon.pl25
1 files changed, 25 insertions, 0 deletions
diff --git a/prolog/runner/daemon.pl b/prolog/runner/daemon.pl
new file mode 100755
index 0000000..b079d94
--- /dev/null
+++ b/prolog/runner/daemon.pl
@@ -0,0 +1,25 @@
+#!/usr/bin/swipl -q --nosignals -tty -s
+
+% Pengine and HTTP server modules.
+:- use_module(library(http/http_dispatch)).
+:- use_module(library(http/http_error)).
+:- use_module(library(http/thread_httpd)).
+:- use_module(library(http/http_unix_daemon)).
+:- use_module(library(pengines)).
+:- use_module(library(pengines_io)).
+
+:- use_module(library(clpfd)).
+:- use_module(library(clpr)).
+
+:- consult(sandbox).
+
+:- multifile prolog:error_message/3.
+prolog:error_message(time_limit_exceeded) -->
+ [ 'time limit exceeded' ].
+
+:- set_setting(pengine_sandbox:time_limit, 5.0).
+:- set_setting(pengine_sandbox:thread_pool_size, 50).
+
+% Start the server. Set fork(true) if you desire for the process to fork into background. You may also want pidfile(filename).
+% See /usr/lib/swi-prolog/library/http/http_unix_daemon.pl and thread_httpd.pl for all options.
+:- http_daemon([port(3030), ip(localhost), fork(false), workers(10), timeout(30), keep_alive_timeout(30), user(nobody), group(nogroup)]).