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	   bindvar/3,
   60           bindvar_rule/4,
   61	   expand_vars/2,
   62	   expand_vars/3
   63           ]).   64
   65:- use_module(library(biomake/utils)).   66:- use_module(library(biomake/functions)).   67:- use_module(library(biomake/embed)).   68
   69:- user:op(1100,xfy,<--).   70:- user:op(1101,xfy,?=).   71:- user:op(1102,xfy,:=).   72:- user:op(1103,xfy,+=).   73:- user:op(1104,xfy,=*).   74
   75% Declare all debug topics defined in this module
   76:- nodebug(poolq).   77:- nodebug(biomake).   78:- nodebug(pattern).   79:- nodebug(bindrule).   80
   81% Configuration
   82max_recurse_depth(100).

Prolog implementation of Makefile-inspired build system

See the README

*/

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