1:- module(
2 os_ext,
3 [
4 exists_program/1, % +Program
5 open_file/1, % +File
6 open_file/2, % +MediaType, +File
7 os/1, % ?Os
8 os_path/1, % ?Directory
9 process_create/2 % +Exe, +Args
10 ]
11).
17:- use_module(library(process)). 18:- use_module(library(yall)). 19 20:- use_module(library(file_ext)). 21:- use_module(library(media_type)). 22:- use_module(library(thread_ext)).
32exists_program(Program) :-
33 os_path(Prefix),
34 atomic_list_concat([Prefix,Program], /, Exe),
35 access_file(Exe, execute), !.
Fails if there is no file name extension, or if the file name extension cannot be mapped to a Media Type, or if the Media Type cannot be mapped to a program, or if none of the mapped to programs exists.
50open_file(File) :- 51 file_media_type(File, MediaType), 52 open_file(MediaType, File). 53 54 55open_file(MediaType, File) :- 56 media_type_program(MediaType, Program, Args), 57 exists_program(Program), !, 58 process_create(path(Program), [file(File)|Args], []).
67os(mac) :- 68 current_prolog_flag(apple, true), !. 69os(unix) :- 70 current_prolog_flag(unix, true), !. 71os(windows) :- 72 current_prolog_flag(windows, true), !.
81os_path(Dir) :-
82 getenv('PATH', Path),
83 os_path_separator(Sep),
84 atomic_list_concat(Dirs0, Sep, Path),
85 member(Dir0, Dirs0),
86 prolog_to_os_filename(Dir, Dir0).
92os_path_separator(Sep) :- 93 os(Os), 94 os_path_separator(Os, Sep). 95 96os_path_separator(mac, :). 97os_path_separator(unix, :). 98os_path_separator(windows, ;).
104process_create(Exe, Args) :-
105 process_create(Exe, Args, [])
Operating System interactions
*/