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