1% * -*- Mode: Prolog -*- */
    2
    3:- module(biomake,
    4          [
    5	   disable_backtrace/0,
    6	   call_without_backtrace/1,
    7	      
    8	   build_default/0,
    9           build_default/1,
   10
   11	   halt_success/0,
   12	   halt_error/0,
   13
   14	   bind_special_variables/1,
   15	   start_queue/1,
   16           build/1,
   17           build/2,
   18           build/3,
   19	   finish_queue/1,
   20
   21	   report/3,
   22	   report/4,
   23
   24	   verbose_report/3,
   25	   verbose_report/4,
   26
   27	   consult_gnu_makefile/3,
   28           consult_makeprog/3,
   29	   read_makeprog_stream/4,
   30	   
   31	   read_string_as_makeprog_term/3,
   32	   read_atom_as_makeprog_term/3,
   33	   eval_atom_as_makeprog_term/3,
   34
   35	   add_spec_clause/3,
   36	   add_spec_clause/4,
   37	   add_cmdline_assignment/1,
   38	   add_gnumake_clause/3,
   39	   
   40	   global_binding/2,
   41	   expand_global_binding/2,
   42	   
   43           target_bindrule/3,
   44           rebuild_required/4,
   45
   46	   normalize_pattern/3,
   47	   unwrap_t/2,
   48	   flatten_trim/2,
   49	   
   50           rule_target/3,
   51           rule_dependencies/3,
   52           rule_execs/3,
   53           rule_vars/6,
   54
   55	   run_execs_now/3,
   56	   report_run_exec/4,
   57	   update_hash/3,
   58
   59	   shell_var_specified/1,
   60	   
   61	   bindvar/3,
   62           bindvar_rule/4,
   63	   expand_vars/2,
   64	   expand_vars/3
   65           ]).   66
   67:- use_module(library(pcre)).   68
   69:- use_module(library(biomake/utils)).   70:- use_module(library(biomake/functions)).   71:- use_module(library(biomake/embed)).   72
   73:- user:op(1100,xfy,<--).   74:- user:op(1101,xfy,?=).   75:- user:op(1102,xfy,:=).   76:- user:op(1103,xfy,+=).   77:- user:op(1104,xfy,=*).   78
   79% Declare all debug topics defined in this module
   80:- nodebug(poolq).   81:- nodebug(biomake).   82:- nodebug(pattern).   83:- nodebug(bindrule).   84
   85% Configuration
   86max_recurse_depth(100).

Prolog implementation of Makefile-inspired build system

See the README

*/

   94% ----------------------------------------
   95% EXCEPTIONS
   96% ----------------------------------------
   97
   98% use disable_backtrace to permanently disable backtrace on exception,
   99% and call_without_backtrace to temporarily disable it.
  100:- dynamic no_backtrace/0.  101:- dynamic suppress_backtrace/0.  102
  103% Intercept a couple of exceptions that are thrown by the threadpool library
  104% This is kind of yucky, but only seems to affect our exception-handling code
  105:- dynamic user:prolog_exception_hook/4.  106
  107user:prolog_exception_hook(error(existence_error(thread,_),context(system:thread_property/2,_)),_,_,_) :- !, fail.
  108user:prolog_exception_hook('$aborted',_,_,_) :- !, fail.
  109
  110% Default exception handler: show backtrace
  111user:prolog_exception_hook(E,_,_,_) :-
  112	format("Exception: ~w~n",[E]),
  113        (no_backtrace; (suppress_backtrace; backtrace(99))),
  114        !,
  115        fail.
  116
  117call_without_backtrace(Term) :-
  118        assertz(suppress_backtrace),
  119	catch(call(Term),_,fail),
  120	retract(suppress_backtrace).
  121
  122disable_backtrace :- assertz(no_backtrace).
  123
  124
  125% ----------------------------------------
  126% TOP-LEVEL
  127% ----------------------------------------
builds Target using rules Call start_queue/1 beforehand and finish_queue/1 afterwards.
  139build_default :-
  140	build_default([]).
  141
  142build_default(Opts) :-
  143        default_target(T),
  144	!,
  145	build(T,Opts).
  146
  147build_default(_) :-
  148	format("No targets. Stop.~n").
  149
  150build :-
  151	format("No targets. Stop.~n").
  152
  153build(T) :-
  154        build(T,[]).
  155build(T,Opts) :-
  156        build(T,[],Opts).
  157
  158build(T,SL,Opts) :-
  159	cyclic_dependency(T,SL,Opts),
  160	!,
  161        halt_error.
  162
  163build(_T,SL,Opts) :-
  164	recursion_too_deep(SL,Opts),
  165	!,
  166	fail.
  167
  168build(T,SL,Opts) :-
  169        debug_report(build,'Target: ~w',[T],SL),
  170        target_bindrule(T,Rule,Opts),   % match target name, test target goal
  171        debug_report(build,'Rule: ~w',[Rule],SL),
  172        rule_dependencies(Rule,DL,Opts),
  173        debug_report(build,'Dependencies: ~w',[DL],SL),
  174        can_build_deps(DL,T,SL,Opts),  % test theoretical path to dependencies
  175        debug_report(build,'Dependencies buildable: ~w',[DL],SL),
  176        verbose_report('Checking dependencies: ~w <-- ~w',[T,DL],[T|SL],Opts),
  177        build_deps(DL,[T|SL],Opts),  % build dependencies
  178        debug_report(build,'Dependencies built: ~w',[DL],SL),
  179	dep_bindrule(Rule,Opts,Rule2,Opts2),  % test dependencies goal
  180        debug_report(build,'Post-dependency rule: ~w',[Rule2],SL),
  181        (   rebuild_required(T,DL,SL,Opts2)  % test if target is stale
  182        ->  run_execs_and_update(Rule2,SL,Opts2)  % (re)build
  183        ;   verbose_report('~w is up to date',[T],SL,Opts)),
  184	!.
  185build(T,SL,Opts) :-
  186        exists_file(T),
  187	!,
  188        verbose_report('Nothing to be done for ~w',[T],SL,Opts).
  189build(T,SL,Opts) :-
  190        \+ target_bindrule(T,_,Opts),
  191	handle_error('Don\'t know how to make ~w',[T],T,SL,Opts),
  192	!.
  193build(T,SL,Opts) :-
  194        target_bindrule(T,Rule,Opts),
  195        rule_dependencies(Rule,DL,Opts),
  196	member(D,DL),
  197        \+ can_build_dep(D,[T|SL],Opts),
  198	!,
  199        handle_error('No way to build ~w, needed by ~w',[D,T],T,SL,Opts).
  200build(T,SL,Opts) :-
  201        handle_error('~w FAILED',[T],T,SL,Opts).
  202
  203% tests of pathological conditions
  204cyclic_dependency(T,SL,Opts) :-
  205	member(Dep,SL),
  206	equal_as_strings(Dep,T),
  207	reverse(SL,SLrev),
  208	concat_string_list(SLrev,Chain," <-- "),
  209	report("Cyclic dependency detected: ~w <-- ~w",[Chain,T],SL,Opts).
  210
  211recursion_too_deep(SL,Opts) :-
  212	length(SL,Depth),
  213	max_recurse_depth(D),
  214	Depth > D,
  215	report("Exceeds maximum length of dependency chain (~w)",[D],SL,Opts).
  216
  217% test whether theoretical path exists
  218can_build_deps(_,_,_,Opts) :- get_opt(no_deps,true,Opts), !.
  219can_build_deps([],_,_,_).
  220can_build_deps([D|DL],T,SL,Opts) :-
  221        can_build_dep(D,[T|SL],Opts),
  222	!,
  223        can_build_deps(DL,T,SL,Opts).
  224can_build_deps([D|_],T,SL,_) :-
  225        debug_report(build,'No way to build ~w, needed by ~w~n',[D,T],SL),
  226	fail.
  227
  228can_build_dep(T,SL,_) :-
  229        debug_report(build,'Checking theoretical build path to ~w',[T],SL),
  230	fail.
  231can_build_dep(T,SL,Opts) :-
  232	cyclic_dependency(T,SL,Opts),
  233	!,
  234        fail.
  235can_build_dep(_,SL,Opts) :-
  236	recursion_too_deep(SL,Opts),
  237	!,
  238        fail.
  239can_build_dep(T,_,_) :-
  240	\+ target_bindrule_exact(T),
  241	exists_file(T),
  242	!.
  243can_build_dep(T,SL,Opts) :-
  244        target_bindrule(T,Rule,Opts),
  245        rule_dependencies(Rule,DL,Opts),
  246        can_build_deps(DL,T,SL,Opts).
  247can_build_dep(T,SL,_) :-
  248        debug_report(build,"No theoretical build path to ~w",[T],SL),
  249        fail.
  250
  251% recursive build dependencies
  252build_deps(_,_,Opts) :- get_opt(no_deps,true,Opts), !.
  253build_deps([],_,_).
  254build_deps([T|TL],SL,Opts) :-
  255        (build_count(T,_); build(T,SL,Opts)),  % never build targets twice
  256        build_deps(TL,SL,Opts).
  257
  258% Special vars
  259bind_special_variables(Opts) :-
  260        get_opt(biomake_prog,Prog,Opts),
  261	add_spec_clause(('MAKE' = Prog),[],[]),
  262	bagof(Arg,member(biomake_args(Arg),Opts),Args),
  263	atomic_list_concat(Args,' ',ArgStr),
  264	add_spec_clause(('MAKEFLAGS' = ArgStr),[],[]).
  265
  266% Queue setup/wrapup
  267start_queue(Opts) :-
  268	get_opt(queue,Q,Opts),
  269	!,
  270	ensure_loaded(library(biomake/queue)),
  271	init_queue(Q,Opts).
  272start_queue(_).
  273
  274finish_queue(Opts) :-
  275	get_opt(queue,Q,Opts),
  276	!,
  277	release_queue(Q).
  278finish_queue(_).
  279
  280
  281% ----------------------------------------
  282% REPORTING
  283% ----------------------------------------
  284
  285report(Fmt,Args,Opts) :-
  286        report(Fmt,Args,[],Opts).
  287
  288report(Fmt,Args,SL,_) :-
  289        stack_indent(SL,Fmt,IndentedFmt),
  290        format(IndentedFmt,Args),
  291        nl.
  292
  293verbose_report(Fmt,Args,Opts) :- verbose_report(Fmt,Args,[],Opts).
  294verbose_report(Fmt,Args,[],_Opts) :-
  295        report(Fmt,Args,[]),
  296        !.
  297verbose_report(Fmt,Args,SL,_Opts) :-
  298	debug_report(verbose,Fmt,Args,SL).
  299
  300stack_indent([],Text,Text).
  301stack_indent([_|T],Text,Indented) :-
  302        string_concat(' ',Text,Tab),
  303	stack_indent(T,Tab,Indented).
  304
  305debug_report(Topic,Fmt,Args) :-
  306        debug_report(Topic,Fmt,Args,[]).
  307
  308debug_report(Topic,Fmt,Args,SL) :-
  309        stack_indent(SL,Fmt,IndentedFmt),
  310	debug(Topic,IndentedFmt,Args).
  311
  312% ----------------------------------------
  313% DEPENDENCY MANAGEMENT
  314% ----------------------------------------
  315
  316% The interactions between the various options are a little tricky...
  317% Essentially (simplifying a little): MD5 overrides timestamps, except when queues are used.
  318rebuild_required(T,_,SL,Opts) :-
  319        member(phony_targets(PT),Opts),
  320        member(T,PT),
  321        !,
  322        verbose_report('Target ~w is phony - build required',[T],SL,Opts).
  323rebuild_required(T,DL,SL,Opts) :-
  324	member(what_if(D),Opts),
  325        member(D,DL),
  326        !,
  327        verbose_report('Target ~w has dependency ~w marked as modified from the command-line - build required',[T,D],SL,Opts).
  328rebuild_required(T,_,SL,Opts) :-
  329        atom_string(T,Ts),
  330        member(old_file(Ts),Opts),
  331        !,
  332        verbose_report('Target ~w marked as old from the command-line - no rebuild required',[T],SL,Opts),
  333	fail.
  334rebuild_required(T,_,SL,Opts) :-
  335        \+ exists_target(T,Opts),
  336        !,
  337        verbose_report('Target ~w not materialized - build required',[T],SL,Opts).
  338rebuild_required(T,DL,SL,Opts) :-
  339        (get_opt(dry_run,true,Opts)
  340         ; \+ get_opt(md5,true,Opts)),
  341	has_rebuilt_dependency(T,DL,D,Opts),
  342	!,
  343        verbose_report('Target ~w has rebuilt dependency ~w - rebuild required',[T,D],SL,Opts).
  344rebuild_required(T,DL,SL,Opts) :-
  345	building_asynchronously(Opts),
  346	has_rebuilt_dependency(T,DL,D,Opts),
  347	!,
  348        verbose_report('Target ~w has dependency ~w on rebuild queue - rebuild required',[T,D],SL,Opts).
  349rebuild_required(T,DL,SL,Opts) :-
  350        member(D,DL),
  351        \+ exists_target(D,Opts),
  352	\+ member(old_file(D),Opts),
  353        !,
  354        verbose_report('Target ~w has unbuilt dependency ~w - rebuild required',[T,D],SL,Opts).
  355rebuild_required(T,DL,SL,Opts) :-
  356        \+ get_opt(md5,true,Opts),
  357	has_newer_dependency(T,DL,D,Opts),
  358	!,
  359        verbose_report('Target ~w built before dependency ~w - rebuild required',[T,D],SL,Opts).
  360rebuild_required(T,DL,SL,Opts) :-
  361        get_opt(md5,true,Opts),
  362	\+ md5_hash_up_to_date(T,DL,Opts),
  363	!,
  364        verbose_report('Target ~w does not have an up-to-date checksum - rebuild required',[T],SL,Opts).
  365rebuild_required(T,_,SL,Opts) :-
  366        get_opt(always_make,true,Opts),
  367        !,
  368        verbose_report('Specified --always-make; rebuild required for target ~w',[T],SL,Opts).
  369
  370building_asynchronously(Opts) :-
  371	get_opt(queue,Q,Opts),
  372	Q \= 'test'.
  373
  374has_newer_dependency(T,DL,D,Opts) :-
  375        member(D,DL),
  376	\+ member(old_file(D),Opts),
  377        has_newer_timestamp(D,T,Opts).
  378
  379has_rebuilt_dependency(T,DL,D,Opts) :-
  380        member(D,DL),
  381	\+ member(old_file(D),Opts),
  382	was_built_after(D,T,Opts).
  383
  384rebuild_required_by_time_stamp(T,DL,SL,Opts) :-
  385        member(D,DL),
  386	was_built_after(D,T,Opts),
  387	!,
  388        verbose_report('Target ~w has rebuilt dependency ~w - rebuilding',[T,D],SL,Opts).
  389rebuild_required_by_time_stamp(T,DL,SL,Opts) :-
  390        \+ exists_directory(T),
  391        member(D,DL),
  392        has_newer_timestamp(D,T,Opts),
  393        !,
  394        verbose_report('Target ~w built before dependency ~w - rebuilding',[T,D],SL,Opts).
  395
  396has_newer_timestamp(A,B,_Opts) :-
  397        time_file(A,TA),
  398        time_file(B,TB),
  399        TA > TB.
  400
  401was_built_after(D,T,_Opts) :-
  402        build_count(D,Nd),
  403        (build_count(T,Nt) -> Nd > Nt; true).
  404
  405exists_target(T,_Opts) :-
  406        exists_file(T).
  407exists_target(T,_Opts) :-
  408        exists_directory(T).
  409
  410rule_target(rb(T,_,_,_,_),T,_Opts).
  411rule_dependencies(rb(_,DL,_,_,_),DL,_Opts).
  412rule_dep_goal(rb(_,_,DepGoal,_,_),DepGoal,_Opts).
  413rule_execs(rb(_,_,_,X,_),X,_Opts) :- !.
  414rule_execs(rb(_,_,_,X,_),_,_Opts) :- throw(error(no_exec(X))).
  415rule_vars(rb(_,_,_,_,v(S,T,D,BL)),S,T,D,BL,_Opts).
  416
  417% internal tracking of build order
  418% a bit hacky to use global assertions/retractions for this
  419:- dynamic build_count/2.  420:- dynamic build_counter/1.  421
  422flag_as_rebuilt(T) :-
  423    next_build_counter(N),
  424    retractall(build_count(T,_)),
  425    assertz(build_count(T,N)).
  426
  427next_build_counter(N) :-
  428    build_counter(Last),
  429    !,
  430    N is Last + 1,
  431    retract(build_counter(Last)),
  432    assertz(build_counter(N)).
  433
  434next_build_counter(1) :-
  435    assertz(build_counter(1)).
  436
  437
  438% ----------------------------------------
  439% TASK EXECUTION
  440% ----------------------------------------
  441
  442run_execs_and_update(Rule,SL,Opts) :-
  443    get_opt(dry_run,true,Opts),
  444    !,
  445    rule_target(Rule,T,Opts),
  446    rule_execs(Rule,Execs,Opts),
  447    forall(member(Exec,Execs),
  448	   (has_modifier(Exec,'@',ES)
  449	    -> report('~w',[ES],SL,Opts)
  450	    ; report('~w',[Exec],SL,Opts))),
  451    flag_as_rebuilt(T).
  452
  453run_execs_and_update(Rule,SL,Opts) :-
  454    rule_target(Rule,T,Opts),
  455    dispatch_run_execs(Rule,SL,Opts),
  456    flag_as_rebuilt(T).
  457
  458dispatch_run_execs(Rule,SL,Opts) :-
  459        get_opt(touch_only,true,Opts),
  460	!,
  461        rule_target(Rule,T,Opts),
  462        rule_dependencies(Rule,DL,Opts),
  463	format(string(Cmd),"touch ~w",[T]),
  464	shell(Cmd),
  465	(running_silent(T,Opts) -> true; report('~w',[Cmd],SL,Opts)),
  466	update_hash(T,DL,Opts).
  467dispatch_run_execs(Rule,SL,Opts) :-
  468	get_opt(queue,Q,Opts),
  469	!,
  470	rule_target(Rule,T,Opts),
  471	(get_opt(md5,true,Opts) -> ensure_md5_directory_exists(T) ; true),
  472	run_execs_in_queue(Q,Rule,SL,Opts),
  473	verbose_report('Target ~w queued for rebuild',[T],SL,Opts).
  474dispatch_run_execs(Rule,SL,Opts) :-
  475	run_execs_now(Rule,SL,Opts),
  476	rule_target(Rule,T,Opts),
  477	verbose_report('Target ~w built',[T],SL,Opts).
  478
  479run_execs_now(Rule,SL,Opts) :-
  480	get_opt(oneshell,true,Opts),
  481	!,
  482	run_execs_in_script(Rule,SL,Opts).
  483run_execs_now(Rule,SL,Opts) :-
  484        shell_var_specified(_),
  485	!,
  486	run_execs_in_script(Rule,SL,Opts).
  487run_execs_now(Rule,SL,Opts) :-
  488	rule_target(Rule,T,Opts),
  489        rule_dependencies(Rule,DL,Opts),
  490	rule_execs(Rule,Es,Opts),
  491	run_execs(Es,T,SL,Opts),
  492	update_hash(T,DL,Opts).
  493
  494run_execs_in_script(Rule,SL,Opts) :-
  495        ensure_loaded(library(biomake/queue)),
  496        rule_target(Rule,T,Opts),
  497        rule_dependencies(Rule,DL,Opts),
  498	rule_execs(Rule,Es,Opts),
  499	write_script_file(T,Es,Opts,Script),
  500	report_run_exec(Script,T,SL,Opts),
  501	update_hash(T,DL,Opts).
  502
  503update_hash(T,DL,Opts) :-
  504    get_opt(md5,true,Opts),
  505    !,
  506    update_md5_file(T,DL,Opts).
  507update_hash(_,_,_).
  508
  509run_execs([],_,_,_).
  510run_execs([E|Es],T,SL,Opts) :-
  511        run_exec(E,T,SL,Opts),
  512        run_execs(Es,T,SL,Opts).
  513
  514run_exec(Exec,T,SL,Opts) :-
  515        has_modifier(Exec,'-',RealExec),
  516	!,
  517	run_exec(RealExec,T,SL,[keep_going_on_error(true)|Opts]).
  518run_exec(Exec,T,SL,Opts) :-
  519        has_modifier(Exec,'@',Silent),
  520	!,
  521	silent_run_exec(Silent,T,SL,Opts).
  522run_exec(Exec,T,SL,Opts) :-
  523        running_silent(T,Opts),
  524        silent_run_exec(Exec,T,SL,Opts).
  525run_exec(Exec,T,SL,Opts) :-
  526	report_run_exec(Exec,T,SL,Opts).
  527
  528report_run_exec(Exec,T,SL,Opts) :-
  529        report('~w',[Exec],SL,Opts),
  530	silent_run_exec(Exec,T,SL,Opts).
  531
  532running_silent(_,Opts) :-
  533        get_opt(silent,true,Opts),
  534        \+ get_opt(dry_run,true,Opts).
  535
  536running_silent(T,Opts) :-
  537        member(silent_targets(TL),Opts),
  538	member(T,TL),
  539        \+ get_opt(dry_run,true,Opts).
  540
  541has_modifier(InStr,ModChar,StrippedStr) :-
  542        string_chars(InStr,InChars),
  543	phrase(strip_mod(ModChar,StrippedChars),InChars),
  544	string_chars(StrippedStr,StrippedChars).
  545
  546strip_mod(M,S) --> [' '], strip_mod(M,S).
  547strip_mod(M,S) --> [M], strip_mod_tail(S).
  548strip_mod_tail([C|S]) --> [C], strip_mod_tail(S).
  549strip_mod_tail([]) --> [].
  550
  551silent_run_exec(Exec,T,SL,Opts) :-
  552        get_time(T1),
  553        run_shell(Exec,Err),
  554        get_time(T2),
  555        DT is T2-T1,
  556        debug_report(build,'  Return: ~w Time: ~w',[Err,DT],SL),
  557	handle_exec_error(Exec,Err,T,SL,Opts),
  558        !.
  559
  560shell_var_specified(Sh) :-
  561    atom_string(SHELL,"SHELL"),
  562    global_binding(SHELL,Sh).
  563
  564run_shell(Exec,Err) :-
  565    !,
  566    debug_report(shell,'sh ~w',[Exec]),
  567    shell(Exec,Err).
  568    
  569handle_exec_error(_,0,_,_,_) :- !.
  570handle_exec_error(Exec,Err,T,SL,Opts) :-
  571        (   get_opt(keep_going_on_error,true,Opts)
  572        ->  IgnoreInfo=' (ignored)'
  573        ;   IgnoreInfo=''),
  574        handle_error('Error ~w executing ~w~w',[Err,Exec,IgnoreInfo],T,SL,Opts).
  575
  576handle_error(Fmt,Args,T,SL,Opts) :-
  577        format(string(WhileFmt),"While building ~w: ~w",[T,Fmt]),
  578        report(WhileFmt,Args,SL),
  579	handle_error(T,Opts).
  580
  581handle_error(_,Opts) :-
  582        get_opt(keep_going_on_error,true,Opts),
  583        !.
  584handle_error(T,Opts) :-
  585        member(ignore_errors_in_targets(TL),Opts),
  586	member(T,TL),
  587        !.
  588handle_error(T,Opts) :-
  589        get_opt(delete_on_error,true,Opts),
  590	exists_file(T),
  591        report('Deleting ~w',[T],Opts),
  592        delete_file(T),
  593        fail.
  594handle_error(_,_) :-
  595        halt_error.
  596
  597
  598% ----------------------------------------
  599% READING AND WRITING MAKEPROGS
  600% ----------------------------------------
  601
  602:- dynamic global_cmdline_binding/2.  603:- dynamic global_simple_binding/2.  604:- dynamic global_lazy_binding/2.  605
  606:- dynamic default_target/1.  607
  608is_assignment_op(=).
  609is_assignment_op(?=).
  610is_assignment_op(:=).
  611is_assignment_op(+=).
  612is_assignment_op(=*).
  613
  614consult_makeprog(F,AllOpts,Opts) :-
  615        debug(makeprog,'reading: ~w',[F]),
  616        open(F,read,IO,[]),
  617	read_makeprog_stream(IO,AllOpts,Opts,_),
  618        debug(makeprog,'read: ~w',[F]).
  619
  620consult_gnu_makefile(F,AllOpts,Opts) :-
  621        ensure_loaded(library(biomake/gnumake_parser)),
  622        parse_gnu_makefile(F,M,AllOpts,Opts),
  623	(member(translate_gnu_makefile(P),AllOpts)
  624	 -> translate_gnu_makefile(M,P); true).
  625
  626read_makeprog_stream(IO,Opts,Opts,[]) :-
  627        at_end_of_stream(IO),
  628	!,
  629	close(IO).
  630
  631read_makeprog_stream(IO,OptsOut,OptsIn,Terms) :-
  632        read_term(IO,Term,[variable_names(VNs),
  633                           syntax_errors(error),
  634                           module(embed)]),
  635	(Term = 'end_of_file'
  636	 -> (Terms = [], OptsOut = OptsIn)
  637	 ; (Terms = [(Term,VNs)|Rest],
  638	    debug(makeprog,'adding: ~w (variables: ~w)',[Term,VNs]),
  639            add_spec_clause(Term,VNs,Opts,OptsIn),
  640	    read_makeprog_stream(IO,OptsOut,Opts,Rest))).
  641
  642eval_atom_as_makeprog_term(Atom,OptsOut,OptsIn) :-
  643        read_atom_as_makeprog_term(Atom,Term,VNs),
  644        debug(makeprog,'adding: ~w (variables: ~w)',[Term,VNs]),
  645        add_spec_clause(Term,VNs,OptsOut,OptsIn).
  646
  647read_atom_as_makeprog_term(Atom,Term,VNs) :-
  648        read_term_from_atom(Atom,Term,[variable_names(VNs),
  649				       syntax_errors(error),
  650				       module(embed)]).
  651
  652read_string_as_makeprog_term(String,Term,VNs) :-
  653        atom_string(Atom,String),
  654        read_atom_as_makeprog_term(Atom,Term,VNs).
  655
  656translate_gnu_makefile(M,P) :-
  657    debug(makeprog,"Writing translated makefile to ~w",[P]),
  658    open(P,write,IO,[]),
  659    forall(member(G,M), write_clause(IO,G)),
  660    close(IO).
  661
  662add_gnumake_clause(G,OptsOut,OptsIn) :-
  663    translate_gnumake_clause(G,P,VNs),
  664    !,
  665    add_spec_clause(P,VNs,OptsOut,OptsIn).
  666
  667add_gnumake_clause(G,OptsOut,OptsIn) :-
  668    translate_gnumake_clause(G,P),
  669    add_spec_clause(P,OptsOut,OptsIn).
  670
  671translate_gnumake_clause(rule(Ts,Ds,Es,{HeadGoal},{true},VNs), (Ts,{HeadGoal} <-- Ds,Es), VNs):- !.
  672translate_gnumake_clause(rule(Ts,Ds,Es,{HeadGoal},{DepGoal},VNs), (Ts,{HeadGoal} <-- Ds,{DepGoal},Es), VNs):- !.
  673translate_gnumake_clause(rule(Ts,Ds,Es,{DepGoal},VNs), (Ts <-- Ds,{DepGoal},Es), VNs):- !.
  674translate_gnumake_clause(prolog(Term,VNs), Term, VNs):- !.
  675translate_gnumake_clause(rule(Ts,Ds,Es), (Ts <-- Ds,Es)):- !.
  676translate_gnumake_clause(assignment(Var,"=",Val), (Var = Val)):- !.
  677translate_gnumake_clause(assignment(Var,"?=",Val), (Var ?= Val)):- !.
  678translate_gnumake_clause(assignment(Var,":=",Val), (Var := Val)):- !.
  679translate_gnumake_clause(assignment(Var,"+=",Val), (Var += Val)):- !.
  680translate_gnumake_clause(assignment(Var,"!=",Val), (Var =* Val)):- !.
  681translate_gnumake_clause(export(Var), export(Var)):- !.
  682translate_gnumake_clause(C,_) :-
  683    format("Error translating ~w~n",[C]),
  684	backtrace(20),
  685    fail.
  686
  687write_clause(IO,export(Var)) :-
  688    !,
  689    format(IO,"export(~w).~n",[Var]).
  690
  691write_clause(IO,option(Opt)) :-
  692    !,
  693    format(IO,"option(~w).~n",[Opt]).
  694
  695write_clause(IO,rule(Ts,Ds,Es)) :-
  696    !,
  697    write_list(IO,Ts),
  698    write(IO,' <-- '),
  699    write_list(IO,Ds),
  700    (Es = []
  701     ; (write(IO,', '),
  702	write_list(IO,Es))),
  703    write(IO,'.\n').
  704
  705write_clause(IO,rule(Ts,Ds,Es,{DepGoal},VNs)) :-
  706    !,
  707    write_list(IO,Ts),
  708    write(IO,' <-- '),
  709    write_list(IO,Ds),
  710    write(IO,', {'),
  711    write_term(IO,DepGoal,[variable_names(VNs),quoted(true)]),
  712    write(IO,'}'),
  713    (Es = []
  714     ; (write(IO,', '),
  715	write_list(IO,Es))),
  716    write(IO,'.\n').
  717
  718write_clause(IO,rule(Ts,Ds,Es,{HeadGoal},{DepGoal},VNs)) :-
  719    !,
  720    write_list(IO,Ts),
  721    write(IO,', {'),
  722    write_term(IO,HeadGoal,[variable_names(VNs),quoted(true)]),
  723    write(IO,'}'),
  724    write(IO,' <-- '),
  725    write_list(IO,Ds),
  726    write(IO,', {'),
  727    write_term(IO,DepGoal,[variable_names(VNs),quoted(true)]),
  728    write(IO,'}'),
  729    (Es = []
  730     ; (write(IO,', '),
  731	write_list(IO,Es))),
  732    write(IO,'.\n').
  733
  734write_clause(_,assignment(Var,_,_)) :-
  735    atom_codes(Var,[V|_]),
  736    V @>= 0'a, V @=< 0'z,   % a through z
  737    format("Prolog will not recognize `~w' as a variable, as it does not begin with an upper-case letter.~nStubbornly refusing to translate unless you fix this outrageous affront!~n",[Var]),
  738    halt_error.
  739
  740write_clause(IO,assignment(Var,Op,Val)) :-
  741    format(IO,"~w ~w ~q.~n",[Var,Op,Val]).
  742
  743write_clause(IO,prolog( (Term,VNs) )) :-
  744    !,
  745    write_term(IO,Term,[variable_names(VNs),quoted(true)]),
  746    write(IO,'.\n').
  747
  748write_clause(_,X) :- format("Don't know how to write ~w~n",[X]).
  749
  750write_list(IO,[X]) :- format(IO,"~q",[X]), !.
  751write_list(IO,L) :- format(IO,"~q",[L]).
  752
  753add_cmdline_assignment((Var = X)) :-
  754        global_unbind(Var),
  755        assertz(global_cmdline_binding(Var,X)),
  756        debug(makeprog,'cmdline assign: ~w = ~w',[Var,X]).
  757
  758add_spec_clause(Ass,Opts,Opts) :-
  759	Ass =.. [Op,Var,_],
  760	is_assignment_op(Op),
  761	!,
  762	add_spec_clause(Ass, [Var=Var], Opts, Opts).
  763
  764add_spec_clause(export(Var),Opts,Opts) :-
  765	!,
  766	add_spec_clause(export(Var),[Var=Var],Opts,Opts).
  767    
  768add_spec_clause( Term, Opts, Opts ) :-
  769        add_spec_clause( Term, [], Opts, Opts ).
  770
  771add_spec_clause( option(Opts), _VNs, OptsOut, OptsIn ) :-
  772	!,
  773	append(Opts,OptsIn,OptsOut).
  774
  775add_spec_clause( (Var ?= X) , _VNs, Opts, Opts) :-
  776        global_binding(Var,Oldval),
  777        !,
  778        debug(makeprog,"Ignoring ~w = ~w since ~w is already bound to ~w",[Var,X,Var,Oldval]).
  779
  780add_spec_clause( (Var ?= X), VNs, Opts, Opts) :-
  781        add_spec_clause((Var = X),VNs,Opts,Opts).
  782
  783add_spec_clause( Ass, _VNs, Opts, Opts) :-
  784	Ass =.. [Op,Var,X],
  785	is_assignment_op(Op),
  786	\+ var(Var),
  787        global_cmdline_binding(Var,Oldval),
  788        !,
  789        debug(makeprog,"Ignoring ~w ~w ~w since ~w was bound to ~w on the command-line",[Var,Op,X,Var,Oldval]).
  790
  791add_spec_clause( Ass, [], Opts, Opts) :-
  792	Ass =.. [Op,Var,_],
  793	is_assignment_op(Op),
  794	atom_codes(Var,[V|_]),
  795	V @>= 0'a, V @=< 0'z,   % a through z
  796        debug(makeprog,"Warning: Prolog will not recognize ~w as a variable as it does not begin with an upper-case letter. Use at your own peril!~n",[Var]),
  797	fail.
  798
  799add_spec_clause( (Var = X), VNs, Opts, Opts) :-
  800	!,
  801        member(Var=Var,VNs),
  802        global_unbind(Var),
  803        assertz(global_lazy_binding(Var,X)),
  804        debug(makeprog,'assign: ~w = ~w',[Var,X]).
  805
  806add_spec_clause( (Var := X,{Goal}), VNs, Opts, Opts) :-
  807        !,
  808        member(Var=Var,VNs),
  809        normalize_pattern(X,Y,v(_,_,_,VNs)),
  810        findall(Y,Goal,Ys),
  811	unwrap_t(Ys,Yflat),  % hack; parser adds unwanted t(...) wrapper
  812	!,
  813        global_unbind(Var),
  814        assertz(global_simple_binding(Var,Yflat)),
  815        debug(makeprog,'assign: ~w := ~w',[Var,Yflat]).
  816
  817add_spec_clause( (Var := X), VNs, Opts, Opts) :-
  818        !,
  819        add_spec_clause( (Var := X,{true}), VNs, Opts, Opts).
  820
  821add_spec_clause( (Var += X), VNs, Opts, Opts) :-
  822        !,
  823        member(Var=Var,VNs),
  824        normalize_pattern(X,Y,v(_,_,_,VNs)),
  825	unwrap_t(Y,Yflat),  % hack; parser adds too many t(...)'s
  826	!,
  827	% handle slightly differently depending on whether variable was previously simply or recursively expanded
  828	((global_simple_binding(Var,Old)  % simply expanded
  829	  ; global_cmdline_binding(Var,Old))  % variables set on command line are simply expanded
  830	 -> (concat_string_list([Old," ",Yflat],New),
  831             global_unbind(Var),
  832             assertz(global_simple_binding(Var,New)),
  833             debug(makeprog,'assign: ~w := ~w',[Var,New]))
  834	 ; ((global_lazy_binding(Var,Old)  % recursively expanded
  835	     -> (concat_string_list([Old," ",Yflat],New),
  836		 global_unbind(Var))
  837	     ; New = Yflat),
  838	    assertz(global_lazy_binding(Var,New))),
  839	   debug(makeprog,'assign: ~w = ~w',[Var,New])).
  840
  841add_spec_clause( (Var =* X), VNs, Opts, Opts) :-
  842        !,
  843        member(Var=Var,VNs),
  844	shell_eval_str(X,Y),
  845	!,
  846        global_unbind(Var),
  847        assertz(global_lazy_binding(Var,Y)),
  848        debug(makeprog,'assign: ~w =* ~w  ==>  ~w',[Var,X,Y]).
  849
  850add_spec_clause( (Head,{HeadGoal} <-- Deps,{DepGoal},Exec), VNs, Opts, Opts) :-
  851        !,
  852        add_spec_clause(mkrule(Head,Deps,Exec,HeadGoal,DepGoal),VNs,Opts,Opts).
  853add_spec_clause( (Head,{HeadGoal} <-- Deps,{DepGoal}), VNs, Opts, Opts) :-
  854        !,
  855        add_spec_clause(mkrule(Head,Deps,[],HeadGoal,DepGoal),VNs,Opts,Opts).
  856add_spec_clause( (Head,{HeadGoal} <-- Deps, Exec), VNs, Opts, Opts) :-
  857        !,
  858        add_spec_clause(mkrule(Head,Deps,Exec,HeadGoal,true),VNs,Opts,Opts).
  859add_spec_clause( (Head,{HeadGoal} <-- Deps), VNs, Opts, Opts) :-
  860        !,
  861        add_spec_clause(mkrule(Head,Deps,[],HeadGoal,true),VNs,Opts,Opts).
  862
  863add_spec_clause( (Head <-- Deps,{DepGoal},Exec), VNs, Opts, Opts) :-
  864        !,
  865        add_spec_clause(mkrule(Head,Deps,Exec,DepGoal),VNs,Opts,Opts).
  866add_spec_clause( (Head <-- Deps,{DepGoal}), VNs, Opts, Opts) :-
  867        !,
  868        add_spec_clause(mkrule(Head,Deps,[],DepGoal),VNs,Opts,Opts).
  869add_spec_clause( (Head <-- Deps, Exec), VNs, Opts, Opts) :-
  870        !,
  871        add_spec_clause(mkrule(Head,Deps,Exec),VNs,Opts,Opts).
  872add_spec_clause( (Head <-- Deps), VNs, Opts, Opts) :-
  873        !,
  874        add_spec_clause(mkrule(Head,Deps,[]),VNs,Opts,Opts).
  875
  876add_spec_clause(Rule,VNs,Opts,Opts) :-
  877        Rule =.. [mkrule,T|_],
  878        !,
  879        debug(makeprog,'with: ~w ~w',[Rule,VNs]),
  880	set_default_target(T),
  881        assertz(with(Rule,VNs)).
  882
  883add_spec_clause(export(Var),[Var=Var],Opts,Opts) :-
  884        global_binding(Var,Val),
  885	!,
  886        debug(makeprog,'export ~w = ~w',[Var,Val]),
  887	setenv(Var,Val).
  888
  889add_spec_clause(Term,_,Opts,Opts) :-
  890        debug(makeprog,"assert ~w",Term),
  891	expand_term(Term,Expanded),
  892        assertz(Expanded).
  893
  894set_default_target(_) :-
  895	default_target(_),
  896	debug(makeprog,"Default target already set",[]),
  897	!.
  898set_default_target([T|_]) :-
  899	expand_vars_head(T,Tx),
  900	\+ string_chars(T,['.'|_]),
  901	equal_as_strings(T,Tx),  % only set default target if T contains no variables
  902	!,
  903	debug(makeprog,"Setting default target to ~s",[Tx]),
  904	assertz(default_target(Tx)).
  905set_default_target([_|_]) :- !.
  906set_default_target(T) :- set_default_target([T]).
  907
  908global_unbind(Var) :-
  909	retractall(global_cmdline_binding(Var,_)),
  910	retractall(global_simple_binding(Var,_)),
  911	retractall(global_lazy_binding(Var,_)).
  912
  913global_binding(Var,Val) :- global_cmdline_binding(Var,Val).
  914global_binding(Var,Val) :- global_simple_binding(Var,Val).
  915global_binding(Var,Val) :- global_lazy_binding(Var,Val).
  916
  917% ----------------------------------------
  918% RULES AND PATTERN MATCHING
  919% ----------------------------------------
  920
  921target_bindrule_exact(T) :-
  922        mkrule_default(TP1,_,_,HeadGoal,_,Bindings),
  923	bind_globals(Bindings),
  924	V=v(null,T,_,Bindings),
  925        normalize_patterns(TP1,TPs,V),
  926	member(TP,TPs),
  927	exact_match(TP,T),
  928	setauto('TARGET',T,Bindings),
  929	call_without_backtrace(HeadGoal).
  930
  931target_bindrule(T,rb(T,Ds,DepGoal,Exec1,V),_Opts) :-
  932        mkrule_default(TP1,DP1,Exec1,HeadGoal,DepGoal,Bindings),
  933	bind_globals(Bindings),
  934	debug(bindrule,"rule: T=~w TP1=~w DP1=~w E1=~w HG=~w DG=~w B=~w",[T,TP1,DP1,Exec1,HeadGoal,DepGoal,Bindings]),
  935        append(Bindings,_,Bindings_Open),
  936        V=v(_Base,T,Ds,Bindings_Open),
  937        normalize_patterns(TP1,TPs,V),
  938
  939        % we allow multiple heads;
  940        % only one of the specified targets has to match
  941        member(TP,TPs),
  942        pattern_match(TP,T),
  943
  944	% Check the HeadGoal
  945	setauto('TARGET',T,Bindings),
  946	call_without_backtrace(HeadGoal),
  947
  948	% Do a two-pass expansion of dependency list.
  949	% This is ultra-hacky but allows for variable-expanded dependency lists that contain % wildcards
  950	% (the variables are expanded on the first pass, and the %'s on the second pass).
  951	% A more rigorous solution would be a two-pass expansion of the entire GNU Makefile,
  952	% which would allow currently impossible things like variable-expanded rules, e.g.
  953	%   RULE = target: dep1 dep2
  954	%   $(RULE) dep3
  955	% which (in GNU make, but not here) expands to
  956	%   target: dep1 dep2 dep3
  957	% However, this would fragment the current homology between the Prolog syntax and GNU Make syntax,
  958	% making it harder to translate GNU Makefiles into Prolog.
  959	% Consequently, we currently sacrifice perfect GNU make compatibility for a simpler translation.
  960	expand_deps(DP1,DP2,V),
  961	expand_deps(DP2,Ds,V),
  962
  963	% Set up the DepGoal
  964	setauto('DEPS',Ds,Bindings),
  965
  966	% and, success
  967	debug(bindrule,"rule matched",[]).
  968
  969dep_bindrule(rb(T,Ds,true,Exec1,V),Opts,rb(T,Ds,true,Execs,V),Opts) :-
  970	!,
  971	expand_execs(Exec1,Execs,V).
  972
  973dep_bindrule(rb(T,Ds,_,Exec1,V),Opts,rb(T,Ds,true,Execs,V),[qsub_use_biomake(true)|Opts]) :-
  974        building_asynchronously(Opts),
  975	!,
  976	expand_execs(Exec1,Execs,V).
  977
  978dep_bindrule(rb(T,Ds,DepGoal,Exec1,V),Opts,rb(T,Ds,true,Execs,V),Opts) :-
  979        call_without_backtrace(DepGoal),
  980	expand_execs(Exec1,Execs,V).
  981
  982setauto(VarLabel,Value,Bindings) :-
  983	member((VarLabel = Value), Bindings),
  984	!.
  985setauto(_,_,_).
  986
  987bind_globals(Bindings) :-
  988    maplist(bind_global,Bindings).
  989
  990bind_global((VarLabel = Var)) :- var(Var), expand_global_binding(VarLabel,Var), !.
  991bind_global(_).
  992
  993expand_global_binding(VarLabel,Value) :- global_cmdline_binding(VarLabel,Value), !.
  994expand_global_binding(VarLabel,Value) :- global_simple_binding(VarLabel,Value), !.
  995expand_global_binding(VarLabel,Value) :- global_lazy_binding(VarLabel,V), !, expand_vars(V,Value).
  996
  997exact_match(t(TL),A) :- !, exact_match(TL,A).
  998exact_match([],'').
  999exact_match([Tok|PatternToks],Atom) :-
 1000    nonvar(Tok),
 1001    !,
 1002    atom_concat(Tok,Rest,Atom),
 1003    exact_match(PatternToks,Rest).
 1004exact_match([Tok|PatternToks],Atom) :-
 1005    var(Tok),
 1006    !,
 1007    atom_concat(Tok,Rest,Atom),
 1008    Tok\='',
 1009    exact_match(PatternToks,Rest).
 1010
 1011pattern_match(A,B) :- var(A),!,B=A.
 1012pattern_match(t(TL),A) :- !, pattern_match(TL,A).
 1013pattern_match([],'').
 1014pattern_match([Tok|PatternToks],Atom) :-
 1015    nonvar(Tok),
 1016    !,
 1017    atom_concat(Tok,Rest,Atom),
 1018    pattern_match(PatternToks,Rest).
 1019pattern_match([Tok|PatternToks],Atom) :-
 1020    var(Tok),
 1021    !,
 1022    atom_concat(Tok,Rest,Atom),
 1023    Tok\='',
 1024    pattern_match(PatternToks,Rest).
 1025
 1026pattern_match_list([],[]).
 1027pattern_match_list([P|Ps],[M|Ms]) :-
 1028        pattern_match(P,M),
 1029        pattern_match_list(Ps,Ms).
 1030
 1031expand_deps(Deps,Result,V) :-
 1032    normalize_patterns(Deps,NormDeps,V),
 1033    maplist(unwrap_t,NormDeps,ExpandedDeps),
 1034    maplist(split_spaces,ExpandedDeps,DepLists),
 1035    flatten_trim(DepLists,FlatDeps),
 1036    maplist(apply_wildcards,FlatDeps,LumpyWild),
 1037    flatten_trim(LumpyWild,Result).
 1038
 1039apply_wildcards(F,L) :-
 1040    atom_chars(F,C),
 1041    member('*',C),
 1042    !,
 1043    expand_file_name(F,All),
 1044    include(exists_file,All,L).
 1045apply_wildcards(F,F).
 1046	  
 1047expand_execs(Execs,Result,V) :-
 1048    normalize_patterns_body(Execs,NormExecs,V),
 1049    maplist(unwrap_t,NormExecs,ExpandedExecs),
 1050    maplist(split_newlines,ExpandedExecs,ExecLists),
 1051    flatten_trim(ExecLists,Result).
 1052
 1053flatten_trim(Lumpy,Trimmed) :-
 1054    flatten(Lumpy,Untrimmed),
 1055    include(not_empty,Untrimmed,Trimmed).
 1056
 1057not_empty(X) :- X \= "", X \= ''.
 1058
 1059% ----------------------------------------
 1060% PATTERN SYNTAX AND API
 1061% ----------------------------------------
 1062
 1063:- multifile
 1064        mkrule/3,
 1065        mkrule/4,
 1066        mkrule/5,
 1067        with/2. 1068:- dynamic
 1069        mkrule/3,
 1070        mkrule/4,
 1071        mkrule/5,
 1072        with/2. 1073
 1074mkrule_default(T,D,E,Ghead,Gdep,VNs) :- with(mkrule(T,D,E,Ghead,Gdep),VNs), Gdep \= true.
 1075mkrule_default(T,D,E,Ghead,true,VNs) :- with(mkrule(T,D,E,Ghead,true),VNs).
 1076mkrule_default(T,D,E,true,Gdep,VNs) :- with(mkrule(T,D,E,Gdep),VNs).
 1077mkrule_default(T,D,E,true,true,VNs) :- with(mkrule(T,D,E),VNs).
 1078
 1079expand_vars_head(X,Y) :-
 1080	expand_vars_head(X,Y,v(null,null,null,[])).
 1081
 1082expand_vars_head(X,Y,V) :-
 1083	normalize_pattern(X,Yt,V),
 1084	unwrap_t(Yt,Y).
 1085
 1086normalize_patterns(X,X,_) :- var(X),!.
 1087normalize_patterns([],[],_) :- !.
 1088normalize_patterns([P|Ps],[N|Ns],V) :-
 1089        !,
 1090        debug(pattern,'*norm: ~w',[P]),
 1091        normalize_pattern(P,N,V),
 1092        normalize_patterns(Ps,Ns,V).
 1093normalize_patterns(P,Ns,V) :-
 1094        normalize_pattern(P,N,V),
 1095	wrap_t(N,Ns).
 1096
 1097% this is a bit hacky - parsing is too eager to add t(...) wrapper (original comment by cmungall)
 1098% Comment by ihh: not entirely sure what all this wrapping evaluated patterns in t(...) is about.
 1099% It seems to be some kind of a marker for pattern evaluation.
 1100% Anyway...
 1101% wrap_t is a construct from cmungall's original code, abstracted into a separate term by me (ihh).
 1102% unwrap_t flattens a list into an atom, removing any t(...) wrappers in the process,
 1103% and evaluating any postponed functions wrapped with a call(...) compound clause.
 1104wrap_t(t([L]),L) :- member(t(_),L), !.
 1105wrap_t(X,[X]).
 1106
 1107%unwrap_t(_,_) :- backtrace(20), fail.
 1108unwrap_t(X,'') :- var(X), !.
 1109unwrap_t(Call,Flat) :- nonvar(Call), Call =.. [call,_|_], !, unwrap_t_call(Call,F), unwrap_t(F,Flat).
 1110unwrap_t(t(X),Flat) :- unwrap_t(X,Flat), !.
 1111unwrap_t([],'') :- !.
 1112unwrap_t([L|Ls],Flat) :- unwrap_t(L,F), unwrap_t(Ls,Fs), atom_concat(F,Fs,Flat), !.
 1113unwrap_t(N,A) :- number(A), atom_number(A,N), !.
 1114unwrap_t(S,A) :- string(S), atom_string(A,S), !.
 1115unwrap_t(S,S) :- ground(S), !.
 1116unwrap_t(X,_) :- type_of(X,T), format("Can't unwrap ~w ~w~n",[T,X]), fail.
 1117
 1118unwrap_t_call(call(X,Y),Result) :- !, unwrap_t_call(Y,Yret), call(X,Yret,Result).
 1119unwrap_t_call(call(X,Y,Z),Result) :- !, unwrap_t_call(Z,Zret), call(X,Y,Zret,Result).
 1120unwrap_t_call(R,R).
 1121
 1122normalize_pattern(X,X,_) :- var(X),!.
 1123normalize_pattern(t(X),t(X),_) :- !.
 1124normalize_pattern(Term,t(Args),_) :-
 1125        Term =.. [t|Args],!.
 1126normalize_pattern(X,t(Toks),V) :-
 1127        debug(pattern,'PARSING: ~w // ~w',[X,V]),
 1128        atom_chars(X,Chars),
 1129        phrase(head_toks(Toks,V),Chars),
 1130        debug(pattern,'PARSED: ~w ==> ~w',[X,Toks]),
 1131%	backtrace(20),
 1132        !.
 1133
 1134expand_vars(X,Y) :-
 1135	expand_vars(X,Y,v(null,null,null,[])).
 1136
 1137expand_vars(X,Y,V) :-
 1138	normalize_pattern_body(X,Yt,V),
 1139	unwrap_t(Yt,Y).
 1140
 1141normalize_patterns_body(X,X,_) :- var(X),!.
 1142normalize_patterns_body([],[],_) :- !.
 1143normalize_patterns_body([P|Ps],[N|Ns],V) :-
 1144        !,
 1145        debug(pattern,'*norm: ~w',[P]),
 1146        normalize_pattern_body(P,N,V),
 1147        normalize_patterns_body(Ps,Ns,V).
 1148normalize_patterns_body(P,Ns,V) :-
 1149        normalize_pattern_body(P,N,V),
 1150	wrap_t(N,Ns).
 1151
 1152normalize_pattern_body(X,X,_) :- var(X),!.
 1153normalize_pattern_body(t(X),t(X),_) :- !.
 1154normalize_pattern_body(Term,t(Args),_) :-
 1155        Term =.. [t|Args],!.
 1156normalize_pattern_body(X,t(Toks),V) :-
 1157        debug(pattern,'PARSING: ~w // ~w',[X,V]),
 1158        atom_chars(X,Chars),
 1159        phrase(body_toks(Toks,V),Chars),
 1160        debug(pattern,'PARSED: ~w ==> ~w',[X,Toks]),
 1161        !.
 1162
 1163body_toks([],_) --> [].
 1164body_toks([Tok|Toks],V) --> body_tok(Tok,V),!,body_toks(Toks,V).
 1165body_tok('%',_) --> ['%'], !.
 1166body_tok(Tok,V) --> tok(Tok,V).
 1167
 1168head_toks([],_) --> [].
 1169head_toks([Tok|Toks],V) --> head_tok(Tok,V),!,head_toks(Toks,V).
 1170head_tok(Var,V) --> ['%'],!,{bindvar_debug('%',V,Var)}.
 1171head_tok(Tok,V) --> tok(Tok,V).
 1172
 1173tok('$',_V) --> ['$','$'], !.  % escape $'s
 1174tok(Var,V) --> ['$'], varlabel(VL),{bindvar_debug(VL,V,Var)}.
 1175tok(Var,V) --> ['$'], makefile_subst_ref(Var,V), !.
 1176tok(Var,V) --> ['$'], makefile_computed_var(Var,V), !.
 1177tok(Var,V) --> ['$'], makefile_function(Var,V), !.
 1178tok("$",_V) --> ['$'], !.   % if all else fails, let the dollar through
 1179tok(Tok,_) --> tok_a(Cs),{atom_chars(Tok,Cs)}.
 1180tok_a([C|Cs]) --> [C],{C\='$',C\='%'},!,tok_a(Cs).
 1181tok_a([]) --> [].
 1182varlabel('<') --> ['<'],!.
 1183varlabel('*') --> ['*'],!.
 1184varlabel('@') --> ['@'],!.
 1185varlabel('^') --> ['^'],!.
 1186varlabel('+') --> ['^'],!.  % $+ is not quite the same as $^, but we fudge it
 1187varlabel('?') --> ['^'],!.  % $? is not quite the same as $^, but we fudge it
 1188varlabel('<') --> bracketed(['<']),!.
 1189varlabel('*') --> bracketed(['*']),!.
 1190varlabel('@') --> bracketed(['@']),!.
 1191varlabel('^') --> bracketed(['^']),!.
 1192varlabel('^') --> bracketed(['+']),!.
 1193varlabel('^') --> bracketed(['?']),!.
 1194varlabel('*F') --> bracketed(['*','F']),!.
 1195varlabel('*D') --> bracketed(['*','D']),!.
 1196varlabel('@F') --> bracketed(['@','F']),!.
 1197varlabel('@D') --> bracketed(['@','D']),!.
 1198varlabel('<F') --> bracketed(['<','F']),!.
 1199varlabel('<D') --> bracketed(['<','D']),!.
 1200varlabel('^F') --> bracketed(['^','F']),!.
 1201varlabel('^D') --> bracketed(['^','D']),!.
 1202varlabel('^F') --> bracketed(['+','F']),!.
 1203varlabel('^D') --> bracketed(['+','D']),!.
 1204varlabel('^F') --> bracketed(['?','F']),!.
 1205varlabel('^D') --> bracketed(['?','D']),!.
 1206varlabel(A) --> makefile_var_char(C), {atom_chars(A,[C])}.
 1207varlabel(A) --> ['('],makefile_var_atom_from_chars(A),[')'].
 1208varlabel(A) --> ['{'],makefile_var_atom_from_chars(A),['}'].
 1209
 1210bracketed(L) --> ['('],L,[')'].
 1211bracketed(L) --> ['{'],L,['}'].
 1212
 1213bindauto('%',v(X,_,_,_),X) :- !.
 1214bindauto('*',v(X,_,_,_),X) :- !.
 1215bindauto('@',v(_,X,_,_),X) :- !.
 1216bindauto('<',v(_,_,[X|_],_),X) :- !.
 1217bindauto('^',v(_,_,X,_),call(concat_string_list_spaced,X)) :- !.
 1218bindauto('*F',v(X,_,_,_),call(file_base_name,X)) :- !.
 1219bindauto('*D',v(X,_,_,_),call(file_directory_name,X)) :- !.
 1220bindauto('@F',v(_,X,_,_),call(file_base_name,X)) :- !.
 1221bindauto('@D',v(_,X,_,_),call(file_directory_name,X)) :- !.
 1222bindauto('<F',v(_,_,[X|_],_),call(file_base_name,X)) :- !.
 1223bindauto('<D',v(_,_,[X|_],_),call(file_directory_name,X)) :- !.
 1224bindauto('^F',v(_,_,X,_),call(concat_string_list_spaced,call(maplist,file_base_name,X))) :- !.
 1225bindauto('^D',v(_,_,X,_),call(concat_string_list_spaced,call(maplist,file_directory_name,X))) :- !.
 1226
 1227% bind variables, creating new variable if doesn't exist yet
 1228bindvar(VL,v(S,T,D,BL),X) :- bindauto(VL,v(S,T,D,BL),X), !.
 1229bindvar(VL,v(_,_,_,_),X) :- global_cmdline_binding(VL,X),!.
 1230bindvar(VL,v(_,_,_,_),X) :- global_simple_binding(VL,X),!.
 1231bindvar(VL,v(_,_,_,_),X) :- getenv(VL,X).
 1232bindvar(VL,v(V1,V2,V3,BL),X) :-
 1233	global_lazy_binding(VL,Y),
 1234	append(BL,[VL=VL],BL2),
 1235	normalize_pattern(Y,Z,v(V1,V2,V3,BL2)),
 1236	unwrap_t(Z,X),
 1237	!.
 1238bindvar(VL,v(_,_,_,BL),X) :- member(VL=X,BL),!.
 1239bindvar(_,v(_,_,_,_),'') :- !.  % default: bind to empty string
 1240
 1241% bind variables WITHOUT adding anything new
 1242bindvar_rule(VL,_Rule,_Opts,X) :- global_cmdline_binding(VL,X), !.
 1243bindvar_rule(VL,_Rule,_Opts,X) :- global_simple_binding(VL,X), !.
 1244bindvar_rule(VL,_Rule,_Opts,X) :- getenv(VL,X), !.
 1245bindvar_rule(VL,Rule,Opts,X) :-
 1246	rule_vars(Rule,V1,V2,V3,BL,Opts),
 1247	global_lazy_binding(VL,Y),
 1248	append(BL,[VL=VL],BL2),
 1249	normalize_pattern(Y,Z,v(V1,V2,V3,BL2)),
 1250	unwrap_t(Z,X),
 1251	!.
 1252bindvar_rule(VL,Rule,Opts,X) :-
 1253	rule_vars(Rule,_,_,_,BL,Opts),
 1254        member(VL=X,BL),
 1255        (var(X) -> X = ''; true),
 1256	!.
 1257bindvar_rule(_,_,_,'').
 1258
 1259% debugging variable binding
 1260bindvar_debug(VL,V,Var) :-
 1261    debug(pattern,"binding ~w",[VL]),
 1262    %show_global_bindings,
 1263    bindvar(VL,V,Var),
 1264    debug(pattern,"bound ~w= ~w",[VL,Var]).
 1265
 1266show_global_bindings :-
 1267    forall(global_binding(Var,Val),
 1268	   (type_of(Var,T), format("global binding: ~w (~w) = ~w\n",[Var,T,Val])))