1:- module(ninja, [variable//1, variable//2, rule//2, rule//3, build//3, build//4,
    2                  deps//1]).    3
    4:- use_module(library(dcg/basics)).    5:- use_module(library(dcg/high_order)).    6:- use_module(library(option)).    7:- use_module(library(error)).

Ninja build system generator

This module contains helper dcg predicates to generate ninja build files akin to the ninja_syntax.py python module distributed by ninja. You can use these predicates if you want to generate your own build.ninja build file.

Example usage:

build_graph -->
  rule(cp, "cp $in $out"),
  build(["input.txt"], cp, ["output.txt"]).

main -->
  phrase(build_graph, L),
  open("build.ninja", write, Stream),
  string_codes(S, L),
  write(Stream, S),
  close(Stream).

Then build.ninja contains the following build specification:

rule cp
  command = cp $in $out

build input.txt: cp output.txt

See the ninja build format documentation for generating more complex build files.

author
- Kwon-Young Choi
license
- GPL */
   40maybe_atom(NameAtom, Name) :-
   41  (  atom(NameAtom)
   42  -> Name = atom(NameAtom)
   43  ;  Name = NameAtom
   44  ).
   45
   46identity(X) -->
   47  X.
   48
   49indents(List) -->
   50  indents(identity, List).
   51
   52:- meta_predicate indents(3, ?, ?, ?).   53indents(Goal, List) -->
   54  indents_(List, Goal).
   55indents_([], _) --> [].
   56indents_([H | T], Goal) -->
   57  sequence(indent(Goal), [H | T]).
   58indent(Goal, X) -->
   59  "  ", call(Goal, X).
   60
   61ws(List) -->
   62  sequence(identity, " ", List).
   63ws(Start, List) -->
   64  ws_(List, Start).
   65ws_([], _) -->
   66  [].
   67ws_([H | T], Start) -->
   68  sequence(Start, identity, " ", "", [H | T]).
 variable(+Pair:pair)// is semidet
Generate a variable declaration from a pair Pair. The key can be an atom or a dcg, value should be a dcg. A variable definition always end with a new line.
?- phrase(variable(name-"Value"), L), format("~s", [L]).
name = Value
L = [110, 97, 109, 101, 32, 61, 32, 86, 97|...].
   80variable(Pair) -->
   81  { must_be(pair, Pair), Pair = Name-Value },
   82  variable(Name, Value).
 variable(+Name:atom;dcg, +Value:dcg)// is semidet
Generate a variable declaration as a variable Name with value Value. The variable name can be an atom or a dcg, value should be a dcg. A variable definition always end with a new line.
?- phrase(variable(name, "Value"), L), format("~s", [L]).
name = Value
L = [110, 97, 109, 101, 32, 61, 32, 86, 97|...].
   94variable(NameAtom, Value) -->
   95  { maybe_atom(NameAtom, Name) },
   96  ws([Name, "=", Value]), eol.
 rule(+Name:atom;dcg, +Command:dcg)// is semidet
Generate a rule declaration with no additional variables. The name can be an atom or a dcg, the command should be dcg.
?- phrase(rule(cp, "cp $in $out"), L), format("~s", [L]).
rule cp
  command = cp $in $out
L = [114, 117, 108, 101, 32, 99, 112, 10, 32|...].
  108rule(Name, Command) -->
  109  rule(Name, Command, []).
 rule(+Name:atom;dcg, +Command:dcg, +Variables:list(pair))// is semidet
Generate a rule declaration with no additional variables. The name can be an atom or a dcg. The command should be dcg and describe the command to run. Variables is a list and will be generate using the variable//1 rule.
?- phrase(rule(cp, "cp $in $out"), L), format("~s", [L]).
rule cp
  command = cp $in $out
L = [114, 117, 108, 101, 32, 99, 112, 10, 32|...].
  123rule(NameAtom, Command, Variables) -->
  124  { maybe_atom(NameAtom, Name) },
  125  "rule ", Name, eol,
  126  indents(variable, [command-Command | Variables]).
 build(+Outs:list(dcg), +Rule:atom;dcg, +Ins:list(dcg))// is semidet
Generate a build statement between input Ins and Output Outs with the rule Rule.
?- phrase(build(["input.txt"], cp, ["output.txt"]), L), format("~s", [L]).
build input.txt: cp output.txt
L = [98, 117, 105, 108, 100, 32, 105, 110, 112|...].
  136build(Outs, Rule, Ins) -->
  137  build(Outs, Rule, Ins, []).
 build(+Outs:list(dcg), +Rule:atom;dcg, +Ins:list(dcg), +Options:list)// is semidet
Generate a build statement between input Ins and Output Outs with the rule Rule. Optional arguments can be specify in the option list Options. Valid options are:
implicit_ins(ImplicitIns:list(dcg))
List of implicit dependencies, as list of dcgs.
implicit_outs(ImplicitOuts:list(dcg))
List of implicit outputs, as list of dcgs.
orderonly_ins(OrderonlyIns:list(dcg))
List of order only dependencies, as list of dcgs.
validations(Validations:list(dcg))
List of validation targets, as list of dcgs.
variables(Variables:list(pair))
List of variables as pairs.
?- phrase(build(["input.txt"], cp, ["output.txt"],
     [implicit_outs(["implicit_out.txt"]),
      implicit_ins(["implicit_in.txt"]),
      orderonly_ins(["orderonly_in.txt"]),
      validations(["validation.txt"]),
      variables([name-"value"])]), L), format("~s", [L]).
build input.txt | implicit_out.txt: cp output.txt | implicit_in.txt || orderonly_in.txt |@ validation.txt
  name = value
L = `build input.txt | implici...alue\n`.
  166build(Outs, RuleAtom, Ins, Options) -->
  167  {
  168    must_be(list, Outs),
  169    (  Outs = []
  170    -> domain_error(nonempty_list, Outs)
  171    ;  true
  172    ),
  173    maybe_atom(RuleAtom, Rule)
  174  },
  175  ws("build ", Outs),
  176  { option(implicit_outs(ImplicitOuts), Options, []) },
  177  ws(" | ", ImplicitOuts),
  178  ws((": ", Rule, " "), Ins),
  179  { option(implicit_ins(ImplicitIns), Options, []) },
  180  ws(" | ", ImplicitIns),
  181  { option(orderonly_ins(OrderonlyIns), Options, []) },
  182  ws(" || ", OrderonlyIns),
  183  { option(validations(Validations), Options, []) },
  184  ws(" |@ ", Validations),
  185  eol,
  186  { option(variables(Variables), Options, []) },
  187  indents(variable, Variables).
 deps(++Source:string)// is semidet
Generate a whitespace separated list of dependencies from prolog source file Source. It also include Source as a dependency.
?- phrase(deps("ninja.pl"), L), format("~s", [L]).
ninja.pl /usr/lib64/swipl-9.0.4/library/dcg/basics.pl /usr/lib64/swipl-9.0.4/library/dcg/high_order.pl /usr/lib64/swipl-9.0.4/library/option.pl /usr/lib64/swipl-9.0.4/library/error.pl
L = `ninja.pl /usr/lib64/swipl...or.pl`.
  198deps(Source) -->
  199  Source, " ",
  200  { xref_source(Source) },
  201  foreach(xref_uses_file(Source, _, Path), atom(Path), " ").
  202
  203:- begin_tests(ninja).  204
  205test(maybe_atom, [true(Name == atom(name))]) :-
  206  maybe_atom(name, Name).
  207
  208test(maybe_atom, [true(Name == NewName)]) :-
  209  maybe_atom(Name, NewName).
  210
  211test(indents, [true(S == "  toto  tata")]) :-
  212  phrase(indents(["toto", "tata"]), L),
  213  string_codes(S, L).
  214
  215test(ws, [true(S == "a b")]) :-
  216  phrase(ws(["a", "b"]), L),
  217  string_codes(S, L).
  218
  219test(ws, [true(S == "start: a b")]) :-
  220  phrase(ws("start: ", ["a", "b"]), L),
  221  string_codes(S, L).
  222
  223test(ws, [true(S == "")]) :-
  224  phrase(ws("start: ", []), L),
  225  string_codes(S, L).
  226
  227test(variable, [true(S == "name = value\n")]) :-
  228  phrase(variable(name-"value"), L),
  229  string_codes(S, L).
  230
  231test(variable, [true(S == "name = value\n")]) :-
  232  phrase(variable(name, "value"), L),
  233  string_codes(S, L).
  234
  235test(variable, [true(S == "name = value\n")]) :-
  236  phrase(variable("name", "value"), L),
  237  string_codes(S, L).
  238
  239test(rule, [true(S == "rule cp\n  command = cp $in $out\n")]) :-
  240  phrase(rule(cp, "cp $in $out"), L),
  241  string_codes(S, L).
  242
  243test(rule, [true(S == "rule cp\n  command = cp $in $out\n")]) :-
  244  phrase(rule("cp", "cp $in $out"), L),
  245  string_codes(S, L).
  246
  247test(rule, [true(S == "rule cp\n  command = cp $in $out\n  a = b\n")]) :-
  248  phrase(rule("cp", "cp $in $out", [a-"b"]), L),
  249  string_codes(S, L).
  250
  251test(build, [true(S == "build input.txt: cp output.txt\n")]) :-
  252  phrase(build(["input.txt"], cp, ["output.txt"]), L),
  253  string_codes(S, L).
  254
  255test(build, [true(S == "build input.txt | implicit_out.txt: cp output.txt | implicit_in.txt || orderonly_in.txt |@ validation.txt\n  name = value\n")]) :-
  256  phrase(build(["input.txt"], cp, ["output.txt"], [
  257    implicit_outs(["implicit_out.txt"]),
  258    implicit_ins(["implicit_in.txt"]),
  259    orderonly_ins(["orderonly_in.txt"]),
  260    validations(["validation.txt"]),
  261    variables([name-"value"])]), L),
  262  string_codes(S, L).
  263
  264test(deps, [true(S == "ninja.pl /usr/lib64/swipl-9.0.4/library/dcg/basics.pl /usr/lib64/swipl-9.0.4/library/dcg/high_order.pl /usr/lib64/swipl-9.0.4/library/option.pl /usr/lib64/swipl-9.0.4/library/error.pl")]) :-
  265  phrase(deps("ninja.pl"), L),
  266  string_codes(S, L).
  267
  268:- end_tests(ninja).