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).

Operating System interactions

*/

   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)).
 exists_program(+Program:atom) is semidet
Succeeds if the given program can be run from PATH.
   32exists_program(Program) :-
   33  os_path(Prefix),
   34  atomic_list_concat([Prefix,Program], /, Exe),
   35  access_file(Exe, execute), !.
 open_file(+File:atom) is semidet
 open_file(+MediaType:media_type, +File:atom) is det
Open the file using the first existing program that is registered with the Media Type denote by its file name extension.

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], []).
 os(+Os:oneof([mac,unix,windows])) is semidet
os(-Os:oneof([mac,unix,windows])) is det
Succeeds if Os denotes the current Operating System.
   67os(mac) :-
   68  current_prolog_flag(apple, true), !.
   69os(unix) :-
   70  current_prolog_flag(unix, true), !.
   71os(windows) :-
   72  current_prolog_flag(windows, true), !.
 os_path(+Directory:atom) is semidet
os_path(-Directory:atom) is nondet
Succeeds if Directory is on the OS PATH.
   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).
 os_path_separator(-Separator:oneof([:,;])) is det
   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, ;).
 process_create(+Exe, +Args:list) is det
  104process_create(Exe, Args) :-
  105  process_create(Exe, Args, [])