View source with raw comments or as raw
   1:- module(conf_winpath, []).
   2
   3/** <module> Configure location of external programs on Windows
   4
   5ClioPatria relies on two external  executables   that  are  not standard
   6available on Windows: *|git.exe|* for  providing version information and
   7*|dot.exe|*, part of GraphViz for rendering graphs.
   8
   9These programs must either  be  in   %PATH%  or  made accessible through
  10user:file_search_path/2. The latter can be by  means of hard-coded paths
  11or using the dynamic approach implemented   below.  This hopefully works
  12out-of-the-box in most installations. If it   fails for you, please help
  13improving this config and/or add a  hard-coded location. See the example
  14below.
  15
  16@see http://git-scm.com/ for installing git
  17@see http://www.graphviz.org/ for installing the graphviz programs
  18*/
  19
  20:- multifile
  21	user:file_search_path/2.
  22:- dynamic
  23	user:file_search_path/2.
  24
  25% Add hardcoded locations if these programs   are  in weird places. Note
  26% that currently (May 2011), you cannot   specify UNC (//share/..) paths
  27% for GIT. Although Prolog can  find   git.exe,  git.exe cannot find its
  28% components on UNC paths.
  29
  30% user:file_search_path(path, 'E:/Git').
  31user:file_search_path(path, Dir) :-
  32	prog_in_dir('dot.exe', Dir).
  33user:file_search_path(path, Dir) :-
  34	prog_in_dir('git.exe', Dir).
  35
  36%%	candidate_prog_dir(-Dir) is nondet.
  37%
  38%	Propose candidate locations for installing   programs. The first
  39%	two are described by Windows.  The   next  takes the location of
  40%	SWI-Prolog, assuming that  other  programs   might  be  near and
  41%	finally we deal with old Windows versions.
  42
  43candidate_prog_dir(Dir) :-
  44	getenv('PROGRAMFILES', Dir).
  45candidate_prog_dir(Dir) :-
  46	getenv('ProgramFiles(x86)', Dir).
  47candidate_prog_dir(Dir) :-
  48	current_prolog_flag(executable, Exe),
  49	file_directory_name(Exe, PlBinDir),
  50	file_directory_name(PlBinDir, PlHomeDir),
  51	file_directory_name(PlHomeDir, Dir).
  52candidate_prog_dir('C:/Program Files').
  53
  54%%	prog_dir_pattern(+Prog, -Pattern) is nondet.
  55%
  56%	Pattern is a partial pattern for   expand_file_name/2 to find an
  57%	executable below a place where programs are normally installed.
  58
  59prog_dir_pattern('git.exe', 'Git/bin').
  60prog_dir_pattern('dot.exe', 'Graphviz*/bin').
  61
  62
  63%%	prog_in_dir(+Prog, -Directory) is semidet.
  64%
  65%	True if Prog  resides  in  Directory.   This  is  used  to  find
  66%	candidate directories for  the  =path=   alias  in  Windows. The
  67%	search   is   further   guided   by   candidate_prog_dir/1   and
  68%	prog_dir_pattern/2.
  69
  70:- dynamic
  71	dir_cache/2,
  72	resolving/1.
  73
  74prog_in_dir(Prog, _) :-			% Break loop
  75	resolving(Prog), !, fail.
  76prog_in_dir(Prog, Dir) :-
  77	(   dir_cache(Prog, Cached)
  78	->  Cached = dir(Dir)
  79	;   setup_call_cleanup(asserta(resolving(Prog), Ref),
  80			       absolute_file_name(path(Prog), _,
  81						  [ access(read),
  82						    file_errors(fail)
  83						  ]),
  84			       erase(Ref))
  85	->  asserta(dir_cache(Prog, nodir)),
  86	    fail
  87	;   prog_in_dir_no_cache(Prog, Computed)
  88	->  asserta(dir_cache(Prog, dir(Computed))),
  89	    Dir = Computed
  90	;   asserta(dir_cache(Prog, nodir)),
  91	    fail
  92	).
  93
  94
  95prog_in_dir_no_cache(Prog, Dir) :-
  96	candidate_prog_dir(Dir0),
  97	prog_dir_pattern(Prog, SubDirPattern),
  98	atomic_list_concat([Dir0, /, SubDirPattern, /, Prog], Pattern),
  99	expand_file_name(Pattern, Files0),
 100	reverse(Files0, Files),		% Last one might be last version
 101	member(File, Files),
 102	access_file(File, read),
 103	file_directory_name(File, Dir).