1 % (c) 2009-2025 Lehrstuhl fuer Softwaretechnik und Programmiersprachen,
2 % Heinrich Heine Universitaet Duesseldorf
3 % This software is licenced under EPL 1.0 (http://www.eclipse.org/org/documents/epl-v10.html)
4
5 :- module(system_call,[system_call/4, system_call_with_options/5,
6 system_call/5, system_call_with_options/6,
7 system_call_keep_open/7, system_call_keep_open_no_pipes/4,
8 get_writable_compiled_filename/3,
9 get_writable_compiled_filename/4, generate_temporary_cspm_file/2,
10 get_temporary_filename/2,
11 get_command_path/2,
12 safe_process_create/3]).
13 :- use_module(module_information).
14 :- module_info(group,tools).
15 :- module_info(description,'Tools for calling underlying system procedures or binaries (java, dot, krt,...).').
16
17 :- use_module(library(process)).
18 :- use_module(library(file_systems)).
19 :- use_module(error_manager).
20
21 :- use_module(tools,[ajoin/2]).
22 :- use_module(tools_meta,[safe_on_exception/3]).
23
24 safe_process_create(Command,Args,ProcessCreateOptions) :-
25 safe_on_exception(E,
26 process:process_create(Command, Args, ProcessCreateOptions),
27 ( ajoin(['Could not execute command "',Command,'" due to exception: '],Msg),
28 add_error(system_call,Msg,E),fail)).
29 % for existence error we could check if Command has .exe extension on Windows
30
31 system_call_keep_open(Command,Args,Process,STDIn,STDOut,STDErr,Env) :-
32 safe_process_create(Command,Args,
33 [process(Process),
34 stdout(pipe(STDOut,[encoding(utf8)])),
35 stdin(pipe(STDIn,[encoding(utf8)])),
36 stderr(pipe(STDErr,[encoding(utf8)])),
37 environment(Env)]).
38
39 system_call_keep_open_no_pipes(Command,Args,Process,Env) :-
40 safe_process_create(Command, Args,
41 [process(Process),environment(Env)]).
42
43 system_call(Command,Args,ErrorTextAsCodeList,ExitCode) :-
44 system_call_with_options(Command,Args,[],ErrorTextAsCodeList,ExitCode).
45
46 system_call_with_options(Command,Args,Options,ErrorTextAsCodeList,ExitCode) :-
47 safe_process_create(Command, Args,
48 [process(Process),stderr(pipe(JStderr,[encoding(utf8)]))|Options]),
49
50 read_all(JStderr,Command,stderr,ErrorTextAsCodeList),
51 my_process_wait(Process,ExitCode).
52
53 system_call(Command,Args,OutputTextAsCodeList,ErrorTextAsCodeList,ExitCode) :-
54 system_call_with_options(Command,Args,[],OutputTextAsCodeList,ErrorTextAsCodeList,ExitCode).
55
56 system_call_with_options(Command,Args,Options,OutputTextAsCodeList,ErrorTextAsCodeList,ExitCode) :-
57 %StreamOptions = [encoding('UTF-8')], % we could use pipe(JStdout,StreamOptions), ... below
58 safe_process_create(Command, Args,
59 [process(Process),
60 stdout(pipe(JStdout,[encoding(utf8)])),stderr(pipe(JStderr,[encoding(utf8)]))|Options]),
61 read_all(JStdout,Command,stdout,OutputTextAsCodeList),
62 read_all(JStderr,Command,stderr,ErrorTextAsCodeList),
63 my_process_wait(Process,ExitCode).
64
65 my_process_wait(Process,ExitCode) :- (ExitCode == no_process_wait -> true ; process_wait(Process,ExitCode)).
66
67 get_command_path(CmdName,CmdPath) :-
68 ? absolute_file_name(path(CmdName),
69 CmdPath,
70 [access(exist),extensions(['.exe','']),solutions(all),file_errors(fail)]),!.
71 get_command_path(CmdName,_) :-
72 add_error_fail(get_command_path,'Could not get path to command: ',CmdName).
73
74
75 :- use_module(library(lists)).
76
77 % read all characters from a stream
78 read_all(S,Command,Pipe,Text) :-
79 call_cleanup(read_all1(S,Command,Pipe,Text),
80 close(S)).
81 read_all1(S,Command,Pipe,Text) :-
82 catch(read_all2(S,Lines), error(_,E), ( % E could be system_error('SPIO_E_ENCODING_INVALID')
83 ajoin(['Error reading ',Pipe,' for "',Command,'" due to exception: '],Msg),
84 add_error(system_call,Msg,E),
85 fail
86 )),
87 append(Lines,Text).
88 read_all2(S,Text) :-
89 read_line(S,Line),
90 ( Line==end_of_file ->
91 Text=[[]]
92 ;
93 Text = [Line, [0'\n] | Rest],
94 read_all2(S,Rest)).
95
96 :- use_module(tools,[get_tail_filename/2]).
97 generate_temporary_cspm_file(CSPFile,CSPFileNameTemp):-
98 get_writable_compiled_filename(CSPFile,'.tmp',CSPFileNameTemp).
99
100 :- use_module(debug,[debug_println/2]).
101 get_writable_compiled_filename(SourceFile,Extension,WritableFile) :-
102 get_writable_compiled_filename(SourceFile,Extension,WritableFile,_).
103 get_writable_compiled_filename(SourceFile,Extension,WritableFile,IsTemporaryFile) :-
104 atom_concat(SourceFile,Extension,WFile),
105 debug_println(9,generating_writable_file(SourceFile,Extension)),
106 (file_exists(WFile),
107 file_property(WFile,writable)
108 -> debug_println(9,file_writable(WFile)), IsTemporaryFile=false,
109 WritableFile=WFile
110 ; get_tail_filename(WFile,TFile),
111 safe_on_exception(_E,
112 (open(WFile,write,S1,[]),close(S1),WritableFile=WFile,
113 IsTemporaryFile=false),
114 (IsTemporaryFile=true,
115 get_temporary_filename(TFile,WritableFile)) )
116 ).
117
118 :- use_module(tools, [open_temp_file/3]).
119 get_temporary_filename(PreferredFileName,WritableFile) :-
120 debug_println(9,trying_to_get_temporary_filename(PreferredFileName)),
121 open_temp_file(PreferredFileName, WritableFile, S1),
122 debug_println(9,temporary_file(WritableFile)),
123 close(S1).