1 % (c) 2009-2019 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/5, system_call_env/6,
6 system_call_keep_open/7, system_call_keep_open_no_pipes/4,
7 get_writable_compiled_filename/3,
8 get_writable_compiled_filename/4, generate_temporary_cspm_file/2,
9 get_temporary_filename/2,
10 get_command_path/2]).
11 :- use_module(module_information).
12 :- module_info(group,tools).
13 :- module_info(description,'Tools for calling underlying system procedures.').
14
15 :- use_module(library(process)).
16 :- use_module(library(file_systems)).
17 :- use_module(error_manager).
18
19 :- use_module(tools,[ajoin/2]).
20 :- use_module(tools_meta,[safe_on_exception/3]).
21
22 system_call_keep_open(Command,Options,Process,STDIn,STDOut,STDErr,Env) :-
23 safe_on_exception(E,
24 process:process_create(Command, Options,
25 [process(Process),
26 stdout(pipe(STDOut,[encoding(utf8)])),
27 stdin(pipe(STDIn,[encoding(utf8)])),
28 stderr(pipe(STDErr,[encoding(utf8)])),
29 environment(Env)]),
30 ( ajoin(['Could not execute command "',Command,'" due to exception: '],Msg),
31 add_error(system_call,Msg,E),fail)).
32
33 system_call_keep_open_no_pipes(Command,Options,Process,Env) :-
34 safe_on_exception(E,
35 process:process_create(Command, Options,
36 [process(Process),environment(Env)]),
37 ( ajoin(['Could not execute command "',Command,'" due to exception: '],Msg),
38 add_error(system_call,Msg,E),fail)).
39
40 system_call(Command,Options,ErrorTextAsCodeList,ExitCode) :-
41 safe_on_exception(E,
42 process:process_create(Command, Options,
43 [process(Process),stderr(pipe(JStderr,[encoding(utf8)]))]),
44 (ajoin(['Could not execute command "',Command,'" due to exception: '],Msg),
45 add_error(system_call,Msg,E),fail)),
46
47 read_all(JStderr,Command,stderr,ErrorTextAsCodeList),
48 my_process_wait(Process,ExitCode).
49
50 system_call(Command,Options,OutputTextAsCodeList,ErrorTextAsCodeList,ExitCode) :-
51 system_call_env(Command,Options,[],OutputTextAsCodeList,ErrorTextAsCodeList,ExitCode).
52
53 system_call_env(Command,Options,ENV,OutputTextAsCodeList,ErrorTextAsCodeList,ExitCode) :-
54 %StreamOptions = [encoding('UTF-8')], % we could use pipe(JStdout,StreamOptions), ... below
55 safe_on_exception(E,
56 process:process_create(Command, Options,
57 [process(Process),
58 stdout(pipe(JStdout,[encoding(utf8)])),stderr(pipe(JStderr,[encoding(utf8)]))|ENV]),
59 (ajoin(['Could not execute command "',Command,'" due to exception: '],Msg),
60 add_error(system_call,Msg,E),fail)),
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 on_exception(error(_,E), read_all2(S,Lines),
80 (ajoin(['Error reading ',Pipe,' for "',Command,'" due to exception: '],Msg),
81 add_error(system_call,Msg,E),fail)), % E could be system_error('SPIO_E_ENCODING_INVALID')
82 append(Lines,Text).
83 read_all2(S,Text) :-
84 read_line(S,Line),
85 ( Line==end_of_file ->
86 Text=[""],close(S)
87 ; otherwise ->
88 Text = [Line, "\n" | Rest],
89 read_all2(S,Rest)).
90
91 :- use_module(tools,[get_tail_filename/2]).
92 generate_temporary_cspm_file(CSPFile,CSPFileNameTemp):-
93 get_writable_compiled_filename(CSPFile,'.tmp',CSPFileNameTemp).
94
95 :- use_module(debug,[debug_println/2]).
96 get_writable_compiled_filename(SourceFile,Extension,WritableFile) :-
97 get_writable_compiled_filename(SourceFile,Extension,WritableFile,_).
98 get_writable_compiled_filename(SourceFile,Extension,WritableFile,IsTemporaryFile) :-
99 atom_concat(SourceFile,Extension,WFile),
100 debug_println(9,generating_writable_file(SourceFile,Extension)),
101 ((file_exists(WFile),file_property(WFile,writable))
102 -> debug_println(9,file_writable(WFile)), IsTemporaryFile=false,
103 WritableFile=WFile
104 ; get_tail_filename(WFile,TFile),
105 safe_on_exception(_E,
106 (open(WFile,write,S1,[]),close(S1),WritableFile=WFile,
107 IsTemporaryFile=false),
108 (IsTemporaryFile=true,
109 get_temporary_filename(TFile,WritableFile)) )
110 ).
111
112 get_temporary_filename(PreferredFileName,WritableFile) :-
113 debug_println(9,trying_to_get_temporary_filename(PreferredFileName)),
114 open(temp(PreferredFileName),write,S1,[if_exists(generate_unique_name)]),
115 stream_property(S1,file_name(WritableFile)),
116 debug_println(9,temporary_file(WritableFile)),
117 close(S1).