The Ciao Make Package

Author(s): Manuel Hermenegildo.

This package is used mainly in two main ways:

In both cases, this is the package that defines the syntax and meaning of the dependency rules used.


Usage and interface

  • Library usage:

    • When writing Makefiles for lpmake, such makefiles start with:

      :- module(_,_,[make]).
      

      or

      :- make(_,_).
      

      (The latter uses the feature that an undefined declaration at the beginning of a file is interpreted by Ciao as a use_module/3 including as third argument a package with the same name, in this case make.)

    • When writing applications which use the make package, then it is loaded as any other package within the application.

    Note: It is often useful to use the fsyntax package inside a Makefile (or when when using the make library in other applications). If both make and fsyntax are used, then make should appear before fsyntax in the list of packages.

  • New operators defined:
    ::/2 [978,xfy], <-/2 [977,xfy], <=/2 [975,xfy], <-/1 [977,yf].
  • Imports:

Other information

The Dependency Rules

The package allows defining the following types of rules:

TargetSuffix <= SourceSuffix :: SourceRoot :- BodyLiterals.

A rule of this form declares that in order to produce the file with suffix TargetSuffix from a source file with the suffix SourceSuffix and root name SourceRoot the commands in BodyLiterals must be executed. BodyLiterals is a standard Ciao Prolog clause body, i.e., a comma-separated conjunction of literals. When writing the script, SourceRoot is typically left as a variable, to be instantiated by lpmake when the script is run to the root of name of the file to be processed. This allows using the value of SourceRoot in BodyLiterals. For example, the following rule:

:- use_module(library(terms), [atom_concat/2]).

dvi <= tex :: FileRoot :-
        atom_concat(['latex ',FileRoot,'.tex'],Command),
        system(Command).

states that we can generate a file File.dvi if we have a file named File.tex and that the command to do so is latex File.tex. Thus, if this rule appears in file Makefile.pl and we issue the command lpmake paper.dvi the following occurs:

  • If paper.dvi does not exist and paper.tex exists, then paper.dvi is generated from paper.tex by issuing the system command latex paper.tex.

  • If paper.dvi already exists, nothing is done.

  • If paper.tex does not exist, an error is reported.

Target <- :- BodyLiterals.

A rule of this form declares that in order to produce the file Target the commands in BodyLiterals must be executed. Target need not be a real file: it can also be simply the name of the rule, which is used to invoke it (as a procedure name). For example, the following rule, when the command lpmake realclean is issued, deletes temporary files in the LaTeX application:

:- use_module(library(source_tree), [delete_glob/2]).

clean <- :-
        delete_glob('.', '*.aux|*.log|*~').

Target <- Deps :- BodyLiterals.

A rule of this form declares that in order to produce the file Target, first targets Deps will be called (i.e., the elements of Deps are either other targets with rules defined for them, or a file or files which are already present or which can --and will be-- generated from other available files using other rules). Then, the commands in BodyLiterals will be executed. Deps may be one target or a list of targets. For example, the following rule, when the command lpmake realclean is issued, cleans all the temporary files in the LaTeX application (including .dvi and .ps files). It requires that clean be executed first:

:- use_module(library(source_tree), [delete_glob/2]).

realclean <- clean :-
        delete_glob('.', '*.dvi|*.ps').

The following rule states that in order to meet the target view, target paper.ps must be available or generated. For example, lpmake view can be used to call the ghostview visualizer on paper.ps. Note the use of a globally defined predicate main which is called in two places in the rule, and could be used in other rules in the same file (main := paper. is equivalent to the fact main(paper). --see the fsyntax library):

:- use_package(fsyntax).
:- use_module(library(system)).
:- use_module(library(system_extra)).
:- use_module(library(terms), [atom_concat/2]).

main := paper.

view <- ~atom_concat([~main,'.ps']) :-
        system(~atom_concat(['ghostview ',~main,'.ps'])).

In addition to these rules, the configuration file can define normal predicates in the usual way, or import predicates from other modules, all of which can be called from the bodies of the dependency rules. For example, the system_extra library (an extension of the system library) defines many system predicates in a form which makes them very useful inside Makefiles, specially if the fsyntax package is used (see the examples below).

If lpmake is called without an explicit target as argument, then the first target rule in the Makefile is used. This is useful in that the first rule can be seen as the default rule.

Specifying Paths

Using the vpath/1 predicate it is possible in configuration files to define several paths in which files related to the rules can be located. In this way, not all files need to be in the same directory as the configuration file. For example:

:- use_package(fsyntax).

vpath := '/home/clip/Systems/ciao/lib'.
vpath := '/home/clip/Systems/ciao/library'.
vpath := '/home/clip/Systems/lpdoc/lib'.

Documenting Rules

It is also possible to define documentation for the rules:

target_comment(Target) :- BodyLiterals.

A rule of this form allows documenting the actions related to the target. The body (BodyLiterals) will be called in two circumstances:

  • If Target is called during execution of 'lpmake commands'.

  • When calling 'lpmake -h'.

Using noun forms (generation of foo instead of generating foo) in comments helps this dual purpose. For example, the following rule:

target_comment(realclean) :- 
        display('Cleanup of all generated files.').

will produce output in the two cases pointed out above.

dependency_comment(SourceSuffix, TargetSuffix, SourceRoot) :- BodyLiterals.

Same as the previous rule, but for suffix rules. See, for example, the following generic rule:

:- use_module(library(terms), [atom_concat/2]).

dependency_comment(SSuffix,TSuffix,FileBase) :- 
        display(~atom_concat(['Generation of ',FileBase,'.',
	        TSuffix, ' from ',FileBase,'.',SSuffix])).

An Example of a Makefile

The following is a simple example of a Makefile showing some basic functionality (this is MakefileExample.pl in the example_simple directory in the make library.):

:- module(_,_,[make,fsyntax]).

:- use_module(library(system)).
:- use_module(library(file_utils), [file_to_string/2, string_to_file/2]).
:- use_module(library(lists), [append/3]).
:- use_module(library(terms), [atom_concat/2]).

:- discontiguous(comment/2).

%% -------------------------------------------------------------------------
%% A simple target. Defines how to produce file 'hw'.

hw <-  []    :-
 	string_to_file("Hello world", hw).

%% A comment describing this target (see below):
comment(hw,['Generation of file hw']).

%% -------------------------------------------------------------------------
%% A target with a dependency. 'hwhw' requires 'hw'.

hwhw <- [hw] :-
	file_to_string(hw,Content),
	append(Content,[0'\n|Content],DoubleContent),
	string_to_file(DoubleContent,hwhw).

comment(hwhw,['Generation of file hwhw']).

%% -------------------------------------------------------------------------
%% A simple target. Defines how to produce file 'datafile.simple'.

'datafile.simple' <-  :-
	string_to_file("Hello world", 'datafile.simple').

comment('datafile.simple',['Generation of file datafile.simple']).

%% -------------------------------------------------------------------------
%% A dependency based on suffixes: 
%% <file>.double is generated always from <file>.simple

double <= simple :: Name :-
	file_to_string(~atom_concat([Name,'.simple']),Content),
	append(Content,[0'\n|Content],DoubleContent),
	string_to_file(DoubleContent,~atom_concat([Name,'.double'])).

%% -------------------------------------------------------------------------
%% A dependency based on suffixes with a precondition.
%% <file>.double is generated always from <file>.simple, once 
%% precond is done

boo <- :-
	display((double <= simple :: name <- precond :- body1, body2)).

%% -------------------------------------------------------------------------
%% Example using library predicates

:- use_module(library(source_tree), [delete_glob/2]).

clean <- [] # "Cleanup of temporary files " :-
	delete_glob('.', '*~|*.asr|*.itf|*.po').

realclean <- clean :-
	delete_glob('.', 'hw|hwhw|*simple|*double').

comment(realclean,['Cleanup of all generated files']).

%% -------------------------------------------------------------------------
%% Reporting progress and documenting commands: 
%% If target_comment/1 is defined it can be used to produce user-defined 
%% output when targets are processed and/or documentation on what each 
%% target does (used for example when lpmake is called with -h). Using 
%% 'generation of foo' instead of 'generating foo' in comments helps in this 
%% dual purpose.
%% -------------------------------------------------------------------------

:- push_prolog_flag(multi_arity_warnings,off).
%% Make calls target_comment/1 for simple targets:
target_comment(Target) :- 
	comment(Target,Comment),
	display(~atom_concat([~atom_concat(Comment), '\n'])).
:- pop_prolog_flag(multi_arity_warnings).

%% Similarly, make calls dependency_comment/3 for dependencies (only 
%% during execution, not when documenting -h).
dependency_comment(SSuffix,TSuffix,FileBase) :- 
	display(~atom_concat(['Generation of ',FileBase,TSuffix,
                              ' from ',FileBase,SSuffix,'\nl'])).

The following are a few commands that can be used on the previous file (see file CommandsToTry in the example_simple directory in the make library):

lpmake -m MakefileExample.pl hwhw
(Generate file hwhw --needs to generate file hw first)

lpmake -m MakefileExample.pl datafile.double
(Generate file datafile.double --needs to generate file
datafile.simple first)

lpmake -m MakefileExample.pl realclean
(Cleanup)

lpmake -h -m MakefileExample.pl
(Help on general use of lpmake and commands available in MakefileExample.pl)

See also the LaTeX example in the example_latex directory in the make library.