View source with raw comments or as raw
    1/*  Part of ClioPatria SeRQL and SPARQL server
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@cs.vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (C): 2010-2011, University of Amsterdam,
    7			      VU University Amsterdam
    8
    9    This program is free software; you can redistribute it and/or
   10    modify it under the terms of the GNU General Public License
   11    as published by the Free Software Foundation; either version 2
   12    of the License, or (at your option) any later version.
   13
   14    This program is distributed in the hope that it will be useful,
   15    but WITHOUT ANY WARRANTY; without even the implied warranty of
   16    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   17    GNU General Public License for more details.
   18
   19    You should have received a copy of the GNU General Public
   20    License along with this library; if not, write to the Free Software
   21    Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
   22
   23    As a special exception, if you link this library with other files,
   24    compiled with a Free Software compiler, to produce an executable, this
   25    library does not by itself cause the resulting executable to be covered
   26    by the GNU General Public License. This exception does not however
   27    invalidate any other reasons why the executable file might be covered by
   28    the GNU General Public License.
   29*/
   30
   31:- module(cpack,
   32	  [ cpack_install/1,		% +NameOrURL
   33	    cpack_upgrade/0,
   34	    cpack_upgrade/1,		% +Name
   35	    cpack_remove/1,		% +Name
   36	    cpack_remove/2,		% +Name, +Options
   37					% For creators
   38	    cpack_create/3,		% +Name, +Title, +Options
   39	    cpack_configure/1,		% +Name
   40					% Further API
   41	    cpack_add_dir/2,		% +ConfigEnabled, +Directory
   42	    cpack_register/3,		% +Name, +Dir, +Options
   43	    current_cpack/1,		% ?Name
   44	    cpack_property/2		% ?Name, ?Property
   45	  ]).   46:- use_module(library(semweb/rdf_db)).   47:- use_module(library(semweb/rdfs)).   48:- use_module(library(semweb/rdf_library)).   49:- use_module(library(http/http_open)).   50:- use_module(library(uri)).   51:- use_module(library(lists)).   52:- use_module(library(git)).   53:- use_module(library(setup)).   54:- use_module(library(conf_d)).   55:- use_module(library(filesex)).   56:- use_module(library(settings)).   57:- use_module(library(error)).   58:- use_module(library(apply)).   59:- use_module(library(option)).

The ClioPatria package manager

*/

   65:- setting(cpack:package_directory, atom, cpack,
   66	   'Directory where packages are downloaded').   67:- setting(cpack:server, atom, 'http://cliopatria.swi-prolog.org/',
   68	   'Address of the fallback server').   69
   70:- rdf_register_ns(cpack, 'http://cliopatria.swi-prolog.org/schema/cpack#').   71:- rdf_register_ns(foaf,  'http://xmlns.com/foaf/0.1/').
 cpack_install(+Install) is semidet
Install package by name or URL. The URL of a CPACK can be found on the web-page of the package. If a name is given, cpack_install/1 queries the configured servers for the package. For example:
?- cpack_install('EDM').
% Trying CPACK server at http://cliopatria.swi-prolog.org/cpack/EDM ...
% Installing package EDM:
%    EDM -- View Europeana Data Model
% Initialized empty Git repository in /home/jan/tmp/test/cpack/EDM/.git/
%     Installing EDM.pl ...
% /home/jan/tmp/test/config-enabled/010-packs.pl compiled into conf_packs 0.00 sec, 1,480 bytes
% Added the following config files:
%     /home/jan/tmp/test/config-enabled/010-packs.pl
%     /home/jan/tmp/test/config-enabled/EDM.pl
%   library(count) compiled into count 0.02 sec, 13,280 bytes
%  skin(EDM) compiled into edm 0.02 sec, 52,984 bytes
% /home/jan/tmp/test/config-enabled/EDM.pl compiled into conf_EDM 0.02 sec, 56,112 bytes
true.
Arguments:
Install- is either a URL on the server that returns the installation parameter (this is shown in the info box of the package), or the name of a package or a list of package names.
See also
- http://cliopatria.swi-prolog.org is the central package repository.
  104cpack_install(URL) :-
  105	\+ is_list(URL),
  106	uri_is_global(URL), !,
  107	cpack_package_data(URL, Terms),
  108	cpack_install_terms(Terms).
  109cpack_install(Name) :-
  110	pack_data_url(Name, URL),
  111	print_message(informational, cpack(probe(URL))),
  112	catch(cpack_package_data(URL, Terms), E, true),
  113	(   var(E)
  114	->  !, cpack_install_terms(Terms)
  115	;   print_message(error, E),
  116	    fail
  117	).
 pack_data_url(+NameOrNames, -URL) is nondet
URL can be tried to obtain information about the requested packages.
  124pack_data_url(Name, URL) :-
  125	cpack_load_profile,
  126	(   rdf_has(_, cpack:servers, List),
  127	    rdfs_member(Server, List)
  128	;   setting(cpack:server, Server)
  129	),
  130	ensure_slash(Server, ServerDir),
  131	pack_data_url(ServerDir, Name, URL).
  132
  133pack_data_url(ServerDir, Names, URL) :-
  134	is_list(Names), !,
  135	maplist(pack_param, Names, Params),
  136	uri_query_components(Query, Params),
  137	atomic_list_concat([ServerDir, cpack, /?, Query], URL).
  138pack_data_url(ServerDir, Name, URL) :-
  139	atomic_list_concat([ServerDir, cpack, /, Name], URL).
  140
  141pack_param(Name, p(Name)).
  142
  143
  144ensure_slash(Server, ServerDir) :-
  145	(   sub_atom(Server, _, _, 0, /)
  146	->  ServerDir = Server
  147	;   atom_concat(Server, /, ServerDir)
  148	).
  149
  150cpack_package_data(URL, Terms) :-
  151	setup_call_cleanup(http_open(URL, In, []),
  152			   read_stream_to_terms(In, Terms),
  153			   close(In)).
  154
  155read_stream_to_terms(In, Terms) :-
  156	read_term(In, Term0, []),
  157	read_stream_to_terms(Term0, In, Terms).
  158
  159read_stream_to_terms(end_of_file, _, []) :- !.
  160read_stream_to_terms(Term, In, [Term|T]) :-
  161	read_term(In, Term1, []),
  162	read_stream_to_terms(Term1, In, T).
 cpack_install_terms(+Terms) is det
Install from the server reply.
  169cpack_install_terms(Terms) :-
  170	(   Terms = [cpack(Name, Packages)]
  171	->  print_message(informational, cpack(requires(Name, Packages))),
  172	    maplist(package_status, Packages, Status),
  173	    maplist(download_package, Status),
  174	    maplist(configure_package, Packages)
  175	;   Terms = [no_cpack(Name)]
  176	->  existence_error(cpack, Name)
  177	;   Terms = [error(Error)]
  178	->  throw(Error)
  179	;   domain_error(cpack_reply, Terms)
  180	).
 package_status(+CpackTerm, -Status)
Arguments:
Status- is a term cpack(Package, State), where State is one of no_change, upgrade(Old, New) or new.
  187package_status(cpack(Package, Options),
  188	       cpack(Package, Options, Status)) :-
  189	cpack_package_dir(Package, Dir, false),
  190	directory_file_path(Dir, '.git', GitRepo),
  191	(   access_file(GitRepo, read)
  192	->  option(branch(Branch), Options, master),
  193	    atom_concat('origin/', Branch, Commit),
  194	    git_describe(OldVersion, [directory(Dir)]),
  195	    git([fetch, origin], [ directory(Dir) ]),
  196	    git_describe(NewVersion, [directory(Dir),commit(Commit)]),
  197	    (	OldVersion == NewVersion
  198	    ->	Status = no_change(OldVersion)
  199	    ;	Status = upgrade(OldVersion, NewVersion)
  200	    )
  201	;   Status = new
  202	).
  203
  204download_package(cpack(Package, _, no_change(OldVersion))) :- !,
  205	print_message(informational, cpack(no_change(Package, OldVersion))).
  206download_package(cpack(Package, Options, upgrade(Old, New))) :- !,
  207	print_message(informational, cpack(upgrade(Package, Old, New))),
  208	option(branch(Branch), Options, master),
  209	cpack_package_dir(Package, Dir, false),
  210	atom_concat('origin/', Branch, Commit),
  211	git([merge, Commit],
  212	    [ directory(Dir)
  213	    ]).
  214download_package(cpack(Package, Options, new)) :-
  215	option(pack_repository(Repository), Options),
  216	print_message(informational, cpack(download(Package, Repository))),
  217	cpack_package_dir(Package, Dir, false),
  218	cpack_download(Repository, Dir).
  219
  220configure_package(cpack(Package, Options)) :-
  221	cpack_module_options(Options, ModuleOptions),
  222	cpack_configure(Package, ModuleOptions).
  223
  224cpack_module_options([], []).
  225cpack_module_options([H0|T0], [H|T]) :-
  226	cpack_module_option(H0, H), !,
  227	cpack_module_options(T0, T).
  228cpack_module_options([_|T0], T) :-
  229	cpack_module_options(T0, T).
  230
  231cpack_module_option(url(URL), home_url(URL)).
  232cpack_module_option(requires(Packages), requires(Packages)).
 cpack_download(+Repository, +TargetDir)
Download Repository to Dir.
To be done
- Branches, trust
  241cpack_download(_Package, Dir) :-
  242	directory_file_path(Dir, '.git', GitRepo),
  243	exists_directory(GitRepo), !,
  244	git([pull],
  245	    [ directory(Dir)
  246	    ]).				% Too simplistic
  247cpack_download(git(GitURL, Options), Dir) :-
  248	findall(O, git_clone_option(O, Options), LOL),
  249	append([ [clone, GitURL, Dir]
  250	       | LOL
  251	       ], GitOptions),
  252	git(GitOptions, []),
  253	setup_push_for_download(Dir).
  254
  255git_clone_option(['-b', Branch], Options) :-
  256	option(branch(Branch), Options).
 setup_push_for_download(+Dir) is det
If the downloaded repository can be related to a push-location based on the current profile, we setup a remote for pushing changes. This remote has tehe symbolic name upload.
To be done
- We can (and should) also verify whether the upload and downloaded origin are at the same version.
  267setup_push_for_download(Dir) :-
  268	file_base_name(Dir, Name),
  269	default_binding(default, Name, pushrepository(PushURL)), !,
  270	print_message(informational, cpack(probe_remote(PushURL))),
  271	catch(git(['ls-remote', '--heads', PushURL],
  272		  [ output(_),
  273		    error(_)
  274		  ]),
  275	      E, true),
  276	(   var(E)
  277	->  print_message(informational, cpack(add_remote(upload, PushURL))),
  278	    git([ remote, add, upload, PushURL],
  279		[ directory(Dir)
  280		])
  281	;   E = error(process_error(git(_), exit(_)), _)
  282	->  true
  283	;   print_message(error, E)
  284	).
  285setup_push_for_download(_).
 cpack_upgrade
Upgrade all packages to the server versions.
  292cpack_upgrade :-
  293	findall(Name, current_cpack(Name), Names),
  294	cpack_install(Names).
 cpack_upgrade(Package)
Upgrade Package. This is the same as cpack_install(Package).
  300cpack_upgrade(Name) :-
  301	cpack_install(Name).
 cpack_configure(+Name) is det
Just configure a package.
  307cpack_configure(Name) :-
  308	cpack_configure(Name, []).
  309
  310cpack_configure(Name, Options) :-
  311	cpack_package_dir(Name, Dir, false),  !,
  312	exists_directory(Dir),
  313	(   conf_d_enabled(ConfigEnabled)
  314	->  cpack_add_dir(ConfigEnabled, Dir, Options)
  315	;   existence_error(directory, 'config-enabled')
  316	).
  317cpack_configure(Name, _) :-
  318	existence_error(cpack, Name).
 cpack_add_dir(+ConfigEnable, +PackageDir)
Install package located in directory PackageDir.
To be done
- Register version-tracking with register_git_module/3.
  327cpack_add_dir(ConfigEnable, Dir) :-
  328	cpack_add_dir(ConfigEnable, Dir, []).
  329
  330cpack_add_dir(ConfigEnable, Dir, Options) :-
  331	directory_file_path(ConfigEnable, '010-packs.pl', PacksFile),
  332	directory_file_path(Dir, 'config-available', ConfigAvailable),
  333	file_base_name(Dir, Pack),
  334	add_pack_to_search_path(PacksFile, Pack, Dir, Modified, Options),
  335	setup_default_config(ConfigEnable, ConfigAvailable, []),
  336	(   Modified == true		% Update paths first!
  337	->  load_files(PacksFile, [if(true)])
  338	;   true
  339	),
  340	conf_d_reload.
 add_pack_to_search_path(+PackFile, +Pack, +Dir, -Modified, +Options) is det
Add a directive as below to PackFile. If PackFile already contains a declaration for Pack with different attributes, the file is rewritten using the new attributes.
:- cpack_register(Pack, Dir, Options).
  354add_pack_to_search_path(PackFile, Pack, Dir, Modified, Options) :-
  355	exists_file(PackFile), !,
  356	read_file_to_terms(PackFile, Terms, []),
  357	New = (:- cpack_register(Pack, Dir, Options)),
  358	(   memberchk(New, Terms)
  359	->  Modified = false
  360	;   Old = (:- cpack_register(Pack, _, _)),
  361	    memberchk(Old, Terms)
  362	->  selectchk(Old, Terms, New, Terms2),
  363	    write_pack_register(PackFile, Terms2)
  364	;   setup_call_cleanup(open(PackFile, append, Out),
  365			       extend_search_path(Out, Pack, Dir, Options),
  366			       close(Out)),
  367	    Modified = true
  368	).
  369add_pack_to_search_path(PackFile, Pack, Dir, true, Options) :-
  370	open(PackFile, write, Out),
  371	write_search_path_header(Out),
  372	extend_search_path(Out, Pack, Dir, Options),
  373	close(Out).
  374
  375write_pack_register(PackFile, Terms) :-
  376	setup_call_cleanup(open(PackFile, write, Out),
  377			   ( write_search_path_header(Out),
  378			     Templ = cpack_register(_, _, _),
  379			     forall(member((:-Templ), Terms),
  380				    format(Out, ':- ~q.~n', [Templ]))
  381			   ),
  382			   close(Out)).
  383
  384
  385write_search_path_header(Out) :-
  386	format(Out, '/* Generated file~n', []),
  387	format(Out, '   This file defines the search-path for added packs~n', []),
  388	format(Out, '*/~n~n', []),
  389	format(Out, ':- module(conf_packs, []).~n~n', []),
  390	format(Out, ':- multifile user:file_search_path/2.~n', []),
  391	format(Out, ':- dynamic user:file_search_path/2.~n', []),
  392	format(Out, ':- multifile cpack:registered_cpack/2.~n~n', []).
  393
  394extend_search_path(Out, Pack, Dir, Options) :-
  395	format(Out, ':- ~q.~n', [cpack_register(Pack, Dir, Options)]).
  396
  397
  398		 /*******************************
  399		 *	      REMOVAL		*
  400		 *******************************/
 cpack_remove(+Pack) is det
 cpack_remove(+Pack, +Options) is det
Remove CPACK Pack. Processed options:
force(Boolean)
If true, omit checking whether removing the package will break dependencies.
fake(true)
Print messages indicating what actions will be preformed, but do not modify anything.
To be done
- Should we also try to unload all loaded files?
  416cpack_remove(Name) :-
  417	cpack_remove(Name, []).
  418
  419cpack_remove(Name, Options) :-
  420	\+ option(force(true), Options),
  421	required_by(Name, Dependents), !,
  422	throw(error(cpack_error(cannot_remove(Name, Dependents)), _)).
  423cpack_remove(Name, Options) :-
  424	registered_cpack(Name, Dir, _Options),
  425	absolute_file_name(Dir, DirPath,
  426			   [ file_type(directory),
  427			     access(read)
  428			   ]),
  429	cpack_unregister(Name, Options),
  430	remove_config(DirPath, Options),
  431	remove_dir(DirPath, Options).
  432
  433required_by(Name, Dependents) :-
  434	setof(Dep, required_pack(Name, Dep), Dependents).
  435
  436required_pack(Name, Pack) :-
  437	registered_cpack(Pack, _, Options),
  438	(   member(requires(Packs), Options),
  439	    member(Name, Packs)
  440	->  true
  441	).
 cpack_unregister(+Pack, +Options) is det
Remove registration of the given CPACK. This is achieved by updating 010-packs.pl and reloading this file.
  449cpack_unregister(Pack, Options) :-
  450	conf_d_enabled(ConfigEnabled),
  451	directory_file_path(ConfigEnabled, '010-packs.pl', PacksFile),
  452	exists_file(PacksFile),
  453	read_file_to_terms(PacksFile, Terms, []),
  454	selectchk((:- cpack_register(Pack,_,_)), Terms, RestTerms), !,
  455	(   option(fake(true), Options)
  456	->  print_message(informational, cpack(action(update(PacksFile))))
  457	;   write_pack_register(PacksFile, RestTerms),
  458	    load_files(PacksFile, [if(true)])
  459	).
  460cpack_unregister(_, _).
 remove_config(+Dir, +Options)
Remove configuration that we loaded from Dir. Currently deletes links and Prolog `link files'.
To be done
- Deal with copied config files. We can base this on config.done and maybe on the module name.
- Update config.done.
  472remove_config(Dir, Options) :-
  473	conf_d_enabled(ConfigEnabled),
  474	entry_paths(ConfigEnabled, Paths),
  475	maplist(remove_config(Dir, Options), Paths).
  476
  477remove_config(PackDir, Options, File) :-
  478	read_link(File, _, Target),
  479	absolute_file_name(Target, CanonicalTarget),
  480	sub_atom(CanonicalTarget, 0, _, _, PackDir), !,
  481	action(delete_file(File), Options).
  482remove_config(PackDir, Options, PlFile) :-
  483	file_name_extension(_, pl, PlFile),
  484	setup_call_cleanup(open(PlFile, read, In),
  485			   read(In, Term0),
  486			   close(In)),
  487	Term0 = (:- consult(Rel)),
  488	absolute_file_name(Rel, Target,
  489			   [ relative_to(PlFile) ]),
  490	sub_atom(Target, 0, _, _, PackDir), !,
  491	action(delete_file(PlFile), Options).
  492remove_config(_, _, _).
 remove_dir(+Dir, Options)
Removes a directory recursively.
  499remove_dir(Link, Options) :-
  500	read_link(Link, _, _), !,
  501	action(delete_file(Link), Options).
  502remove_dir(Dir, Options) :-
  503	exists_directory(Dir), !,
  504	entry_paths(Dir, Paths),
  505	forall(member(P, Paths),
  506	       remove_dir(P, Options)),
  507	action(delete_directory(Dir), Options).
  508remove_dir(File, Options) :-
  509	action(delete_file(File), Options).
  510
  511entry_paths(Dir, Paths) :-
  512	directory_files(Dir, Entries),
  513	entry_paths(Entries, Dir, Paths).
  514
  515entry_paths([], _, []).
  516entry_paths([H|T0], Dir, T) :-
  517	hidden(H), !,
  518	entry_paths(T0, Dir, T).
  519entry_paths([H|T0], Dir, [P|T]) :-
  520	directory_file_path(Dir, H, P),
  521	entry_paths(T0, Dir, T).
  522
  523hidden(.).
  524hidden(..).
  525
  526:- meta_predicate
  527	action(0, +).  528
  529action(G, Options) :-
  530	option(fake(true), Options), !,
  531	print_message(informational, cpack(action(G))).
  532action(G, _) :-
  533	G.
  534
  535		 /*******************************
  536		 *	   REGISTRATION		*
  537		 *******************************/
 cpack_register(+PackName, +Dir, +Options)
Attach a CPACK to the search paths
  543cpack_register(PackName, Dir, Options) :-
  544	throw(error(context_error(nodirective,
  545				  cpack_register(PackName, Dir, Options)), _)).
  546
  547
  548user:term_expansion((:-cpack_register(PackName, Dir0, Options)), Clauses) :-
  549	full_dir(Dir0, Dir),
  550	Term =.. [PackName,'.'],
  551	Clauses = [ user:file_search_path(PackName, Dir),
  552		    user:file_search_path(cpacks, Term),
  553		    cpack:registered_cpack(PackName, Dir, Options)
  554		  ].
  555
  556full_dir(Dir, Dir) :-
  557	compound(Dir), !.
  558full_dir(Dir, Dir) :-
  559	is_absolute_file_name(Dir), !.
  560full_dir(Dir, AbsDir) :-
  561	prolog_load_context(directory, ConfigEnabled),
  562	file_directory_name(ConfigEnabled, RelTo),
  563	absolute_file_name(Dir, AbsDir,
  564			   [ relative_to(RelTo),
  565			     file_type(directory),
  566			     access(exist)
  567			   ]).
  568
  569
  570
  571:- multifile
  572	registered_cpack/3.
 current_cpack(-Name) is nondet
True when Name is the name of a registered package.
  578current_cpack(Name) :-
  579	registered_cpack(Name, _, _).
 cpack_property(Name, Property) is nondet
True when Property is a property of the CPACK Name. Defined properties are:
  588cpack_property(Name, Property) :-
  589	property_cpack(Property, Name).
  590
  591property_cpack(directory(Dir), Name) :-
  592	registered_cpack(Name, LocalDir, _),
  593	absolute_file_name(LocalDir, Dir).
  594property_cpack(Option, Name) :-
  595	registered_cpack(Name, _, Options),
  596	member(Option, Options).
 prolog_version:git_module_hook(?Name, ?Directory, ?Options) is nondet
Make packages available for the version management implemented by library(version).
  604:- multifile
  605	prolog_version:git_module_hook/3.  606
  607prolog_version:git_module_hook(Name, Directory, Options) :-
  608	registered_cpack(Name, LocalDir, Options),
  609	absolute_file_name(LocalDir, Directory).
  610
  611
  612		 /*******************************
  613		 *	CREATE NEW PACKAGES	*
  614		 *******************************/
 cpack_create(+Name, +Title, +Options) is det
Create a new package. Options include
type(Type)
Label of a subclass of cpack:Package. Default is package
title(Title)
Title for the package. Should be a short line.
foafname(FoafName)
foaf:name to put into the default template
foafmbox(Email)
foaf:mbox to put into the default template

Default options are extracted from the cpack:Profile named default

To be done
- Allow selection profile, auto-loading of profile, etc.
  634cpack_create(Name, Title, Options) :-
  635	cpack_load_schema,
  636	cpack_load_profile,
  637	option(type(Type), Options, package),
  638	option(description(Descr), Options,
  639	       'Package description goes here.  You can use markdown.'),
  640	package_class_id(Type, PkgClass),
  641	default_bindings(default, Name, DefaultBindings),
  642	merge_options(Options,
  643		      [ name(Name),
  644			title(Title),
  645			pkgclass(PkgClass),
  646			description(Descr)
  647		      | DefaultBindings
  648		      ], Vars),
  649	cpack_package_dir(Name, Dir, true),
  650	forall(cpack_dir(SubDir, Type),
  651	       make_cpack_dir(Dir, SubDir)),
  652	forall(cpack_template(In, Out),
  653	       install_template_file(In, Out, Vars)),
  654	git([init], [directory(Dir)]),
  655	git([add, '.'], [directory(Dir)]),
  656	git([commit, '-m', 'Installed template'], [directory(Dir)]),
  657	git([tag, epoch], [directory(Dir)]),
  658	git_setup_push(Dir, Vars).
  659
  660package_class_id(Label, TurtleID) :-
  661	package_class(Label, Class),
  662	rdf_global_id(Prefix:Name, Class),
  663	atomic_list_concat([Prefix, :, Name], TurtleID).
  664
  665package_class(Label, Class) :-
  666	rdf_has(Class, rdfs:label, literal(Label)),
  667	rdfs_subclass_of(Class, cpack:'Package'), !.
  668package_class(Label, _) :-
  669	domain_error(package_class, Label).
  670
  671default_bindings(Profile, Name, Bindings) :-
  672	findall(B, default_binding(Profile, Name, B), Bindings).
  673
  674default_binding(ProfileName, Name, B) :-
  675	rdf_has(Profile, cpack:name, literal(ProfileName)),
  676	(   rdf_has(Profile, cpack:defaultAuthor, Author),
  677	    (   rdf_has(Author, foaf:name, literal(AuthorName)),
  678		B = foafname(AuthorName)
  679	    ;   rdf_has(Author, foaf:mbox, MBOX),
  680		B = foafmbox(MBOX)
  681	    )
  682	;   rdf_has(Profile, cpack:fetchRepositoryTemplate, literal(GitTempl)),
  683	    substitute(GitTempl, '@CPACK@', Name, GitRepo),
  684	    B = fetchrepository(GitRepo)
  685	;   rdf_has(Profile, cpack:pushRepositoryTemplate, literal(GitTempl)),
  686	    substitute(GitTempl, '@CPACK@', Name, GitRepo),
  687	    B = pushrepository(GitRepo)
  688	).
 git_setup_push(+Dir, +Vars) is det
Set an origin for the newly created repository. This also tries to setup a bare repository at the remote machine using git_create_origin/2.
  696git_setup_push(Dir, Vars) :-
  697	option(pushrepository(PushURL), Vars), !,
  698	option(title(Title), Vars, 'ClioPatria CPACK'),
  699	git([remote, add, origin, PushURL], [directory(Dir)]),
  700	directory_file_path(Dir, '.git/config', Config),
  701	setup_call_cleanup(open(Config, append, Out),
  702			   format(Out, '[branch "master"]\n\c
  703					\tremote = origin\n\c
  704					\tmerge = refs/heads/master\n', []),
  705			   close(Out)),
  706	catch(git_create_origin(Dir, PushURL, Title), E, true),
  707	(   var(E)
  708	->  true
  709	;   subsumes_term(error(existence_error(source_sink, path(Exe)), _), E)
  710	->  print_message(error, cpack(missing_program(Exe)))
  711	;   print_message(error, E)
  712	).
  713git_setup_push(_,_).
 git_create_origin(+Dir, +PushURL, +Title) is det
Try to create the repository origin. As the user has setup push, we hope he setup SSH appropriately. Note that this only works if the remote user has a real shell and not a git-shell.

When using GitHub, PushURL is

git@github.com:<user>/@CPACK@.git
https://github.com/<user>/@CPACK@.git
  728git_create_origin(Dir, PushURL, Title) :-
  729	(   atom_concat('git@github.com:', UserPath, PushURL)
  730	->  true
  731	;   atom_concat('https://github.com/', UserPath, PushURL)
  732	),
  733	atomic_list_concat([_User, RepoGit], /, UserPath),
  734	file_name_extension(Repo, git, RepoGit), !,
  735	process_create(path(hub), [create, Repo, '-d', Title],
  736		       [ cwd(Dir)
  737		       ]).
  738git_create_origin(_Dir, PushURL, Title) :-
  739	uri_components(PushURL, Components),
  740	uri_data(scheme, Components, Scheme),
  741	(   Scheme == ssh
  742	->  uri_data(authority, Components, Authority)
  743	;   Authority = Scheme
  744	),
  745	uri_data(path, Components, Path),
  746	file_directory_name(Path, Parent),
  747	file_base_name(Path, Repo),
  748	format(atom(Command),
  749	       'cd "~w" && mkdir "~w" && cd "~w" && \c
  750	       git init --bare && echo "~w" > description && \c
  751	       touch git-daemon-export-ok',
  752	       [Parent, Repo, Repo, Title]),
  753	process_create(path(ssh), [ Authority, Command ], []).
 make_cpack_dir(+BaseDir, +CPACKDir) is det
Setup th directory structure for a new package.
  760make_cpack_dir(Dir, SubDir) :-
  761	directory_file_path(Dir, SubDir, New),
  762	(   exists_directory(New)
  763	->  true
  764	;   make_directory_path(New),
  765	    print_message(informational, cpack(create_directory(New)))
  766	).
  767
  768install_template_file(In, Out, Vars) :-
  769	option(name(Name), Vars),
  770	absolute_file_name(In, InFile, [access(read)]),
  771	substitute(Out, '@NAME@', Name, OutFile),
  772	cpack_package_dir(Name, Dir, true),
  773	directory_file_path(Dir, OutFile, OutPath),
  774	copy_file_with_vars(InFile, OutPath, Vars),
  775	print_message(informational, cpack(installed_template(OutFile))).
  776
  777substitute(In, From, To, Out) :-
  778	sub_atom(In, B, _, A, From), !,
  779	sub_atom(In, 0, B, _, Start),
  780	sub_atom(In, _, A, 0, End),
  781	atomic_list_concat([Start, To, End], Out).
  782substitute(In, _, _, In).
  783
  784cpack_dir('rdf', _).
  785cpack_dir('rdf/cpack', _).
  786cpack_dir('config-available', _).
  787cpack_dir('entailment', _).
  788cpack_dir('applications', _).
  789cpack_dir('api', _).
  790cpack_dir('components', _).
  791cpack_dir('skin', _).
  792cpack_dir('lib', _).
  793cpack_dir('web', _).
  794cpack_dir('web/js', _).
  795cpack_dir('web/css', _).
  796cpack_dir('web/html', _).
  797
  798cpack_template(library('cpack/config-available.pl.in'),
  799	       'config-available/@NAME@.pl').
  800cpack_template(library('cpack/DEFAULTS.in'),
  801	       'config-available/DEFAULTS').
  802cpack_template(library('cpack/pack.ttl.in'),
  803	       'rdf/cpack/@NAME@.ttl').
  804cpack_template(library('cpack/README.md.in'),
  805	       'README.md').
  806
  807
  808		 /*******************************
  809		 *	      PROFILE		*
  810		 *******************************/
 cpack_load_profile is det
Try to load the profile from user_profile('.cpack.ttl').
To be done
- Prompt for a default profile (notably fill in the servers).
  818cpack_load_profile :-
  819	absolute_file_name(user_profile('.cpack.ttl'), Path,
  820			   [ access(read),
  821			     file_errors(fail)
  822			   ]), !,
  823	rdf_load(Path).
  824cpack_load_profile.
 cpack_load_schema
Ensure the CPACK schema data is loaded.
  831cpack_load_schema :-
  832	rdf_attach_library(rdf(cpack)),
  833	rdf_load_library(cpack).
  834
  835
  836
  837		 /*******************************
  838		 *	       UTIL		*
  839		 *******************************/
 cpack_package_dir(+PackageName, -Dir, +Create)
Installation directory for Package
  845cpack_package_dir(Name, Dir, Create) :-
  846	setting(cpack:package_directory, PackageDir),
  847	directory_file_path(PackageDir, Name, Dir),
  848	(   (   Create == false
  849	    ;	exists_directory(Dir)
  850	    )
  851	->  true
  852	;   make_directory_path(Dir)
  853	).
  854
  855:- multifile
  856	prolog:message//1,
  857	prolog:error_message//1.  858
  859prolog:message(cpack(Message)) -->
  860	message(Message).
  861
  862message(create_directory(New)) -->
  863	[ 'Created directory ~w'-[New] ].
  864message(installed_template(File)) -->
  865	[ 'Installed template ~w'-[File] ].
  866message(requires(Name, Packages)) -->
  867	(   { is_list(Name) }
  868	->  [ 'Packages ~w require the following packages:'-[Name] ]
  869	;   [ 'Package ~w requires the following packages:'-[Name] ]
  870	),
  871	sub_packages(Packages),
  872	[ nl, 'Querying package status ...'-[] ].
  873message(no_change(Name, Version)) -->
  874	[ '   ~w: ~t~30|no change (~w)'-[Name, Version] ].
  875message(upgrade(Name, Old, New)) -->
  876	[ '   ~w: ~t~30|upgrading (~w..~w) ...'-[Name, Old, New] ].
  877message(download(Name, git(Url, _))) -->
  878	[ '   ~w: ~t~30|downloading from ~w ...'-[Name, Url] ].
  879message(probe(URL)) -->
  880	[ 'Trying CPACK server at ~w ...'-[URL] ].
  881message(probe_remote(URL)) -->
  882	[ 'Checking availability of GIT repository ~w ...'-[URL] ].
  883message(add_remote(Name, URL)) -->
  884	[ 'Running "git remote add ~w ~w ..."'-[Name, URL] ].
  885message(action(G)) -->
  886	[ '~q'-[G] ].
  887message(missing_program(hub)) --> !,
  888	[ 'Cannot find the GitHub command line utility "hub".'-[], nl,
  889	  'See https://hub.github.com/ for installation instructions'-[]
  890	].
  891message(missing_program(Prog)) -->
  892	[ 'Cannot find helper program "~w".'-[Prog] ].
  893sub_packages([]) --> [].
  894sub_packages([H|T]) --> sub_package(H), sub_packages(T).
  895
  896sub_package(cpack(Name, Options)) -->
  897	{ option(title(Title), Options) }, !,
  898	[ nl, '   ~w: ~t~30|~w'-[Name, Title] ].
  899sub_package(cpack(Name, _)) -->
  900	[ nl, '   ~w: ~t~30|~w'-[Name] ].
  901
  902prolog:error_message(cpack_error(Error)) -->
  903	cpack_error(Error).
  904
  905cpack_error(not_satisfied(Pack, Reasons)) -->
  906	[ 'Package not satisfied: ~p'-[Pack] ],
  907	not_satisfied_list(Reasons).
  908cpack_error(cannot_remove(Pack, Dependents)) -->
  909	[ 'Cannot remove "~p" because the following packs depend on it'-[Pack] ],
  910	pack_list(Dependents).
  911
  912not_satisfied_list([]) --> [].
  913not_satisfied_list([H|T]) --> not_satisfied(H), not_satisfied_list(T).
  914
  915not_satisfied(no_token(Token)) -->
  916	[ nl, '   Explicit requirement not found: ~w'-[Token] ].
  917not_satisfied(file(File, Problems)) -->
  918	[ nl, '   File ~p'-[File] ],
  919	file_problems(Problems).
  920
  921file_problems([]) --> [].
  922file_problems([H|T]) --> file_problem(H), file_problems(T).
  923
  924file_problem(predicate_not_found(PI)) -->
  925	[ nl, '        Predicate not resolved: ~w'-[PI] ].
  926
  927pack_list([]) --> [].
  928pack_list([H|T]) -->
  929	[ nl, '   ~p'-[H] ],
  930	pack_list(T)