34
35:- module(build_make,
36 []). 37:- use_module(tools). 38
39:- autoload(library(apply), [maplist/3]). 40:- autoload(library(error), [existence_error/2]). 41:- autoload(library(filesex), [directory_file_path/3]). 42:- autoload(library(lists), [max_list/2]). 43:- use_module(library(debug), [debug/3]).
57:- multifile
58 prolog:build_file/2,
59 prolog:build_step/4. 60
61prolog:build_file('configure', configure).
62prolog:build_file('configure.in', autoconf).
63prolog:build_file('configure.ac', autoconf).
64prolog:build_file('Makefile', make).
65prolog:build_file('makefile', make).
66prolog:build_file('Makefile.am', automake).
67
68prolog:build_step(configure, configure, State0, State) :-
69 ensure_build_dir(., State0, State),
70 automake(State),
71 findall(Opt, configure_option(Opt), Opts),
72 debug(build(configure), 'Configuring using configure', []),
73 run_process(path(bash), [configure|Opts],
74 [ env(State.env),
75 directory(State.bin_dir)
76 ]).
77prolog:build_step(configure, autoconf, State0, State) :-
78 ensure_build_dir(., State0, State),
79 automake(State),
80 ProcessOptions = [directory(State.bin_dir), env(State.env)],
81 findall(Opt, configure_option(Opt), ConfigOpts),
82 debug(build(configure), 'Running autoheader', []),
83 run_process(path(autoheader), [], ProcessOptions),
84 debug(build(configure), 'Running autoconf', []),
85 run_process(path(autoconf), [], ProcessOptions),
86 debug(build(configure), 'Configuring using configure', []),
87 run_process(path(bash), [configure|ConfigOpts], ProcessOptions).
88prolog:build_step(build, make, State0, State) :-
89 ensure_build_dir(., State0, State),
90 debug(build(build), 'Running make', []),
91 run_make(State, []).
92prolog:build_step(install, make, State0, State) :-
93 ensure_build_dir(., State0, State),
94 debug(build(build), 'Running make', []),
95 run_make(State, [install]).
96prolog:build_step(test, make, State0, State) :-
97 ensure_build_dir(., State0, State),
98 debug(build(test), 'Running make check', []),
99 run_make(State, [check]).
100prolog:build_step(clean, make, State0, State) :-
101 ensure_build_dir(., State0, State),
102 debug(build(clean), 'Running make clean', []),
103 run_make(State, [clean]).
104prolog:build_step(distclean, make, State0, State) :-
105 ensure_build_dir(., State0, State),
106 debug(build(distclean), 'Running make distclean', []),
107 run_make(State, [distclean]).
108
109automake(State) :-
110 needs_build(State.src_dir/'Makefile.in', [State.src_dir/'Makefile.am']),
111 !,
112 debug(build(configure), 'Running automake', []),
113 run_process(path(automake), [],
114 [ env(State.env),
115 directory(State.src_dir)
116 ]).
117automake(_).
118
119run_make(State, Argv) :-
120 make_program(State.env, Prog),
121 run_process(Prog, Argv,
122 [ directory(State.bin_dir),
123 env(State.env)
124 ]).
125
126make_program(BuildEnv, Prog) :-
127 ( memberchk('MAKE'=Name, BuildEnv)
128 -> true
129 ; getenv('MAKE', Name)
130 ),
131 has_program(Name, Prog, BuildEnv),
132 !.
133make_program(BuildEnv, Prog) :-
134 make_candidate(Name),
135 has_program(Name, Prog, BuildEnv),
136 !.
137make_program(_, _) :-
138 existence_error(program, make).
139
140make_candidate(gmake).
141make_candidate(make).
142
143configure_option(Opt) :-
144 prolog_install_prefix(Prefix),
145 format(atom(Opt), '--prefix=~w', [Prefix]).
146
147needs_build(Target, Sources) :-
148 Error = error(existence_error(file, _), _),
149 maplist(to_file, Sources, SourceFiles),
150 catch(maplist(time_file, SourceFiles, SourceTimes),
151 Error,
152 fail),
153 max_list(SourceTimes, SrcTime),
154 maplist(to_file, Target, TargetFile),
155 ( catch(to_file(TargetFile, TargetTime),
156 Error, fail)
157 -> SrcTime > TargetTime
158 ; true
159 ).
160
161to_file(File, Path), atom(File) =>
162 Path = File.
163to_file(File, Path), string(File) =>
164 atom_string(Path, File).
165to_file(Dir/File, Path) =>
166 directory_file_path(Dir, File, Path)
Make plugin to deal with build steps.
This build plugin deals with GNU style packages. It knows about the following programs:
config.h.in
fromconfigure.in
configure
fromconfigure.in
configure
to create Makefilemake
for the make steps.*/