View source with raw comments or as raw
    1/*  Part of SWISH
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2014-2015, VU University Amsterdam
    7    All rights reserved.
    8
    9    Redistribution and use in source and binary forms, with or without
   10    modification, are permitted provided that the following conditions
   11    are met:
   12
   13    1. Redistributions of source code must retain the above copyright
   14       notice, this list of conditions and the following disclaimer.
   15
   16    2. Redistributions in binary form must reproduce the above copyright
   17       notice, this list of conditions and the following disclaimer in
   18       the documentation and/or other materials provided with the
   19       distribution.
   20
   21    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   22    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   23    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   24    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   25    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   26    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   27    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   28    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   29    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   30    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   31    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   32    POSSIBILITY OF SUCH DAMAGE.
   33*/
   34
   35:- module(gitty,
   36	  [ gitty_open/2,		% +Store, +Options
   37	    gitty_close/1,		% +Store
   38
   39	    gitty_file/3,		% +Store, ?Name, ?Hash
   40	    gitty_create/5,		% +Store, +Name, +Data, +Meta, -Commit
   41	    gitty_update/5,		% +Store, +Name, +Data, +Meta, -Commit
   42	    gitty_commit/3,		% +Store, +Name, -Meta
   43	    gitty_data/4,		% +Store, +Name, -Data, -Meta
   44	    gitty_history/4,		% +Store, +Name, -History, +Options
   45	    gitty_hash/2,		% +Store, ?Hash
   46
   47	    gitty_reserved_meta/1,	% ?Key
   48	    is_gitty_hash/1,		% @Term
   49
   50	    gitty_diff/4,		% +Store, ?Start, +End, -Diff
   51
   52	    data_diff/3,		% +String1, +String2, -Diff
   53	    udiff_string/2		% +Diff, -String
   54	  ]).   55:- use_module(library(sha)).   56:- use_module(library(lists)).   57:- use_module(library(apply)).   58:- use_module(library(option)).   59:- use_module(library(process)).   60:- use_module(library(debug)).   61:- use_module(library(error)).   62:- use_module(library(filesex)).   63
   64:- if(exists_source(library(bdb))).   65:- use_module(gitty_driver_bdb, []).   66:- endif.   67:- use_module(gitty_driver_files, []).

Single-file GIT like version system

This library provides a first implementation of a lightweight versioned file store with dynamic meta-data. The store is partly modelled after GIT. Like GIT, it uses a content-based store. In fact, the stored objects are compatible with GIT. Unlike GIT though, there are no trees. Each entry (file) has its own history. Each commit is associated with a dict that can carry aribitrary meta-data. The following fields are reserved for gitties bookkeeping:

name:Name
Name of the entry (file)
time:TimeStamp
Float representing when the object was added to the store
data:Hash
Object hash of the contents
previous:Hash
Hash of the previous commit.

The key commit is reserved and returned as part of the meta-data of the newly created (gitty_create/5) or updated object (gitty_update/5). */

   93:- dynamic
   94	gitty_store_type/2.		% +Store, -Module
 gitty_open(+Store, +Options) is det
Open a gitty store according to Options. Defined options are:
driver(+Driver)
Backend driver to use. One of files or bdb. When omitted and the store exists, the current store is examined. If the store does not exist, the default is files.
  107gitty_open(Store, Options) :-
  108	(   exists_directory(Store)
  109	->  true
  110	;   existence_error(directory, Store)
  111	),
  112	(   option(driver(Driver), Options)
  113	->  true
  114	;   default_driver(Store, Driver)
  115	),
  116	set_driver(Store, Driver).
  117
  118default_driver(Store, Driver) :-
  119	directory_file_path(Store, ref, RefDir),
  120	exists_directory(RefDir), !,
  121	Driver = files.
  122default_driver(Store, Driver) :-
  123	directory_file_path(Store, heads, RefDir),
  124	exists_file(RefDir), !,
  125	Driver = bdb.
  126default_driver(_, files).
  127
  128set_driver(Store, Driver) :-
  129	must_be(atom, Store),
  130	(   driver_module(Driver, Module)
  131	->  retractall(gitty_store_type(Store, _)),
  132	    asserta(gitty_store_type(Store, Module))
  133	;   domain_error(gitty_driver, Driver)
  134	).
  135
  136driver_module(files, gitty_driver_files).
  137driver_module(bdb,   gitty_driver_bdb).
  138
  139store_driver_module(Store, Module) :-
  140	atom(Store), !,
  141	gitty_store_type(Store, Module).
 gitty_close(+Store) is det
Close access to the Store.
  147gitty_close(Store) :-
  148	store_driver_module(Store, M),
  149	M:gitty_close(Store).
 gitty_file(+Store, ?File, ?Head) is nondet
True when File entry in the gitty store and Head is the HEAD revision.
  156gitty_file(Store, Head, Hash) :-
  157	store_driver_module(Store, M),
  158	M:gitty_file(Store, Head, Hash).
 gitty_create(+Store, +Name, +Data, +Meta, -Commit) is det
Create a new object Name from Data and meta information.
Arguments:
Commit- is a dit describing the new Commit
  166gitty_create(Store, Name, _Data, _Meta, _) :-
  167	gitty_file(Store, Name, _Hash), !,
  168	throw(error(gitty(file_exists(Name)),_)).
  169gitty_create(Store, Name, Data, Meta, CommitRet) :-
  170	save_object(Store, Data, blob, Hash),
  171	get_time(Now),
  172	Commit = gitty{time:Now}.put(Meta)
  173		                .put(_{ name:Name,
  174					data:Hash
  175				      }),
  176	format(string(CommitString), '~q.~n', [Commit]),
  177	save_object(Store, CommitString, commit, CommitHash),
  178	CommitRet = Commit.put(commit, CommitHash),
  179	catch(gitty_update_head(Store, Name, -, CommitHash),
  180	      E,
  181	      ( delete_object(Store, CommitHash),
  182		throw(E))).
 gitty_update(+Store, +Name, +Data, +Meta, -Commit) is det
Update document Name using Data and the given meta information
  188gitty_update(Store, Name, Data, Meta, CommitRet) :-
  189	gitty_file(Store, Name, OldHead),
  190	(   _{previous:OldHead} >:< Meta
  191	->  true
  192	;   throw(error(gitty(commit_version(Name, OldHead, Meta.previous)), _))
  193	),
  194	load_plain_commit(Store, OldHead, OldMeta0),
  195	filter_identity(OldMeta0, OldMeta),
  196	get_time(Now),
  197	save_object(Store, Data, blob, Hash),
  198	Commit = gitty{}.put(OldMeta)
  199			.put(_{time:Now})
  200		        .put(Meta)
  201		        .put(_{ name:Name,
  202				data:Hash,
  203				previous:OldHead
  204			      }),
  205	format(string(CommitString), '~q.~n', [Commit]),
  206	save_object(Store, CommitString, commit, CommitHash),
  207	CommitRet = Commit.put(commit, CommitHash),
  208	catch(gitty_update_head(Store, Name, OldHead, CommitHash),
  209	      E,
  210	      ( delete_object(Store, CommitHash),
  211		throw(E))).
 filter_identity(+Meta0, -Meta)
Remove identification information from the previous commit.
To be done
- : the identity properties should not be hardcoded here.
  219filter_identity(Meta0, Meta) :-
  220	delete_keys([ author,user,avatar,identity,peer,
  221		      external_identity, identity_provider, profile_id,
  222		      commit_message
  223		    ], Meta0, Meta).
  224
  225delete_keys([], Dict, Dict).
  226delete_keys([H|T], Dict0, Dict) :-
  227	del_dict(H, Dict0, _, Dict1), !,
  228	delete_keys(T, Dict1, Dict).
  229delete_keys([_|T], Dict0, Dict) :-
  230	delete_keys(T, Dict0, Dict).
 gitty_update_head(+Store, +Name, +OldCommit, +NewCommit) is det
Update the head of a gitty store for Name. OldCommit is the current head and NewCommit is the new head. If Name is created, and thus there is no head, OldCommit must be -.

This operation can fail because another writer has updated the head. This can both be in-process or another process.

Errors
- gitty(file_exists(Name) if the file already exists
- gitty(not_at_head(Name, OldCommit) if the head was moved by someone else.
  246gitty_update_head(Store, Name, OldCommit, NewCommit) :-
  247	store_driver_module(Store, Module),
  248	Module:gitty_update_head(Store, Name, OldCommit, NewCommit).
 gitty_data(+Store, +NameOrHash, -Data, -Meta) is semidet
Get the data in object Name and its meta-data
  254gitty_data(Store, Name, Data, Meta) :-
  255	gitty_commit(Store, Name, Meta),
  256	load_object(Store, Meta.data, Data).
 gitty_commit(+Store, +NameOrHash, -Meta) is semidet
True if Meta holds the commit data of NameOrHash. A key commit is added to the meta-data to specify the commit hash.
  263gitty_commit(Store, Name, Meta) :-
  264	must_be(atom, Name),
  265	gitty_file(Store, Name, Head), !,
  266	load_commit(Store, Head, Meta).
  267gitty_commit(Store, Hash, Meta) :-
  268	load_commit(Store, Hash, Meta).
  269
  270load_commit(Store, Hash, Meta) :-
  271	load_plain_commit(Store, Hash, Meta0),
  272	Meta1 = Meta0.put(commit, Hash),
  273	(   gitty_file(Store, Meta0.name, Hash)
  274	->  Meta = Meta1.put(symbolic, "HEAD")
  275	;   Meta = Meta1
  276	).
  277
  278load_plain_commit(Store, Hash, Meta) :-
  279	store_driver_module(Store, Module),
  280	Module:load_plain_commit(Store, Hash, Meta).
 gitty_history(+Store, +NameOrHash, -History, +Options) is det
History is a list of dicts representating the history of Name in Store. Options:
depth(+Depth)
Number of entries in the history. If not present, defaults to 5.
includes(+HASH)
Ensure Hash is included in the history. This means that the history includes the entry with HASH an (depth+1)//2 entries after the requested HASH.
  295gitty_history(Store, Name, History, Options) :-
  296	history_hash_start(Store, Name, Hash0),
  297	option(depth(Depth), Options, 5),
  298	(   option(includes(Hash), Options)
  299	->  read_history_to_hash(Store, Hash0, Hash, History0),
  300	    length(History0, Before),
  301	    After is max(Depth-Before, (Depth+1)//2),
  302	    read_history_depth(Store, Hash, After, History1),
  303	    append(History0, History1, History2),
  304	    list_prefix(Depth, History2, History)
  305	;   read_history_depth(Store, Hash0, Depth, History)
  306	).
  307
  308history_hash_start(Store, Name, Hash) :-
  309	gitty_file(Store, Name, Head), !,
  310	Hash = Head.
  311history_hash_start(_, Hash, Hash).
  312
  313
  314read_history_depth(_, _, 0, []) :- !.
  315read_history_depth(Store, Hash, Left, [H|T]) :-
  316	load_commit(Store, Hash, H), !,
  317	Left1 is Left-1,
  318	(   read_history_depth(Store, H.get(previous), Left1, T)
  319	->  true
  320	;   T = []
  321	).
  322read_history_depth(_, _, _, []).
 read_history_to_hash(+Store, +Start, +Upto, -History)
Read the history upto, but NOT including Upto.
  328read_history_to_hash(Store, Hash, Upto, [H|T]) :-
  329	Upto \== Hash,
  330	load_commit(Store, Hash, H),
  331	(   read_history_to_hash(Store, H.get(previous), Upto, T)
  332	->  true
  333	;   T = []
  334	).
  335read_history_to_hash(_, _, _, []).
  336
  337list_prefix(0, _, []) :- !.
  338list_prefix(_, [], []) :- !.
  339list_prefix(N, [H|T0], [H|T]) :-
  340	N2 is N - 1,
  341	list_prefix(N2, T0, T).
 save_object(+Store, +Data:string, +Type, -Hash) is det
Save an object in a git compatible way. Data provides the data as a string.
See also
- http://www.gitguys.com/topics/what-is-the-format-of-a-git-blob/
bug
- We currently delete objects if the head cannot be moved. This can lead to a race condition. We need to leave that to GC.
  354save_object(Store, Data, Type, Hash) :-
  355	size_in_bytes(Data, Size),
  356	format(string(Hdr), '~w ~d\u0000', [Type, Size]),
  357	sha_new_ctx(Ctx0, []),
  358	sha_hash_ctx(Ctx0, Hdr, Ctx1, _),
  359	sha_hash_ctx(Ctx1, Data, _, HashBin),
  360	hash_atom(HashBin, Hash),
  361	store_object(Store, Hash, Hdr, Data).
  362
  363store_object(Store, Hash, Hdr, Data) :-
  364	store_driver_module(Store, Module),
  365	Module:store_object(Store, Hash, Hdr, Data).
  366
  367size_in_bytes(Data, Size) :-
  368	setup_call_cleanup(
  369	    open_null_stream(Out),
  370	    ( format(Out, '~s', [Data]),
  371	      byte_count(Out, Size)
  372	    ),
  373	    close(Out)).
 fsck_object(+Store, +Hash) is semidet
Test the integrity of object Hash in Store.
  380:- public fsck_object/2.  381fsck_object(Store, Hash) :-
  382	load_object(Store, Hash, Data, Type, Size),
  383	format(string(Hdr), '~w ~d\u0000', [Type, Size]),
  384	sha_new_ctx(Ctx0, []),
  385	sha_hash_ctx(Ctx0, Hdr, Ctx1, _),
  386	sha_hash_ctx(Ctx1, Data, _, HashBin),
  387	hash_atom(HashBin, Hash).
 load_object(+Store, +Hash, -Data) is det
 load_object(+Store, +Hash, -Data, -Type, -Size) is det
Load the given object.
  395load_object(Store, Hash, Data) :-
  396	load_object(Store, Hash, Data, _, _).
  397load_object(Store, Hash, Data, Type, Size) :-
  398	store_driver_module(Store, Module),
  399	Module:load_object(Store, Hash, Data, Type, Size).
 gitty_hash(+Store, ?Hash) is nondet
True when Hash is an object in the store.
  405gitty_hash(Store, Hash) :-
  406	store_driver_module(Store, Module),
  407	Module:gitty_hash(Store, Hash).
 delete_object(+Store, +Hash)
Delete an existing object
  413delete_object(Store, Hash) :-
  414	store_driver_module(Store, Module),
  415	Module:delete_object(Store, Hash).
 gitty_reserved_meta(?Key) is nondet
True when Key is a gitty reserved key for the commit meta-data
  421gitty_reserved_meta(name).
  422gitty_reserved_meta(time).
  423gitty_reserved_meta(data).
  424gitty_reserved_meta(previous).
 is_gitty_hash(@Term) is semidet
True if Term is a possible gitty (SHA1) hash
  431is_gitty_hash(SHA1) :-
  432	atom(SHA1),
  433	atom_length(SHA1, 40),
  434	atom_codes(SHA1, Codes),
  435	maplist(hex_digit, Codes).
  436
  437hex_digit(C) :- between(0'0, 0'9, C), !.
  438hex_digit(C) :- between(0'a, 0'f, C).
  439
  440
  441		 /*******************************
  442		 *	    FSCK SUPPORT	*
  443		 *******************************/
  444
  445:- public
  446	delete_object/2,
  447	delete_head/2,
  448	set_head/3.
 delete_head(+Store, +Head) is det
Delete Head from the administration. Used if the head is inconsistent.
  455delete_head(Store, Head) :-
  456	store_driver_module(Store, Module),
  457	Module:delete_head(Store, Head).
 set_head(+Store, +File, +Head) is det
Register Head as the Head hash for File, removing possible old head.
  464set_head(Store, File, Head) :-
  465	store_driver_module(Store, Module),
  466	Module:set_head(Store, File, Head).
  467
  468
  469		 /*******************************
  470		 *	       DIFF		*
  471		 *******************************/
 gitty_diff(+Store, ?Hash1, +FileOrHash2OrData, -Dict) is det
True if Dict representeds the changes in Hash1 to FileOrHash2. If Hash1 is unbound, it is unified with the previous of FileOrHash2. Returns _{initial:true} if Hash1 is unbound and FileOrHash2 is the initial commit. Dict contains:
from:Meta1
to:Meta2
Meta-data for the two diffed versions
data:UDiff
String holding unified diff representation of changes to the data. Only present of data has changed
tags:_94988{added:AddedTags, deleted:DeletedTags}
If tags have changed, the added and deleted ones.
Arguments:
FileOrHash2OrData- is a file name, hash or a term data(String) to compare a given string with a gitty version.
  493gitty_diff(Store, C1, data(Data2), Dict) :- !,
  494	must_be(atom, C1),
  495	gitty_data(Store, C1, Data1, _Meta1),
  496	(   Data1 \== Data2
  497	->  udiff_string(Data1, Data2, UDIFF),
  498	    Dict = json{data:UDIFF}
  499	;   Dict = json{}
  500	).
  501gitty_diff(Store, C1, C2, Dict) :-
  502	gitty_data(Store, C2, Data2, Meta2),
  503	(   var(C1)
  504	->  C1 = Meta2.get(previous)
  505	;   true
  506	), !,
  507	gitty_data(Store, C1, Data1, Meta1),
  508	Pairs = [ from-Meta1, to-Meta2|_],
  509	(   Data1 \== Data2
  510	->  udiff_string(Data1, Data2, UDIFF),
  511	    memberchk(data-UDIFF, Pairs)
  512	;   true
  513	),
  514	meta_tag_set(Meta1, Tags1),
  515	meta_tag_set(Meta2, Tags2),
  516	(   Tags1 \== Tags2
  517	->  ord_subtract(Tags1, Tags2, Deleted),
  518	    ord_subtract(Tags2, Tags1, Added),
  519	    memberchk(tags-_{added:Added, deleted:Deleted}, Pairs)
  520	;   true
  521	),
  522	once(length(Pairs,_)),			% close list
  523	dict_pairs(Dict, json, Pairs).
  524gitty_diff(_Store, '0000000000000000000000000000000000000000', _C2,
  525	   json{initial:true}).
  526
  527
  528meta_tag_set(Meta, Tags) :-
  529	sort(Meta.get(tags), Tags), !.
  530meta_tag_set(_, []).
 udiff_string(+Data1, +Data2, -UDIFF) is det
Produce a unified difference between two strings. Note that we can avoid one temporary file using diff's - arg and the second by passing =/dev/fd/NNN= on Linux systems. See http://stackoverflow.com/questions/3800202
  539:- if(true).  540
  541udiff_string(Data1, Data2, UDIFF) :-
  542	setup_call_cleanup(
  543	    save_string(Data1, File1),
  544	    setup_call_cleanup(
  545		save_string(Data2, File2),
  546		process_diff(File1, File2, UDIFF),
  547		delete_file(File2)),
  548	    delete_file(File1)).
  549
  550save_string(String, File) :-
  551	tmp_file_stream(utf8, File, TmpOut),
  552	format(TmpOut, '~s', [String]),
  553	close(TmpOut).
  554
  555process_diff(File1, File2, String) :-
  556	setup_call_cleanup(
  557	    process_create(path(diff),
  558			   ['-u', file(File1), file(File2)],
  559			   [ stdout(pipe(Out)),
  560			     process(PID)
  561			   ]),
  562	    read_string(Out, _, String),
  563	    ( close(Out),
  564	      process_wait(PID, Status)
  565	    )),
  566	assertion(normal_diff_exit(Status)).
  567
  568normal_diff_exit(exit(0)).		% equal
  569normal_diff_exit(exit(1)).		% different
  570
  571:- else.  572
  573udiff_string(Data1, Data2, UDIFF) :-
  574	data_diff(Data1, Data2, Diffs),
  575	maplist(udiff_string, Diffs, Strings),
  576	atomics_to_string(Strings, UDIFF).
  577
  578:- endif.  579
  580
  581		 /*******************************
  582		 *	   PROLOG DIFF		*
  583		 *******************************/
  584
  585/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
  586Attempt at a built-in diff utility. Doing   it in Prolog may seem weird,
  587but is good for tasting  ones  own   dog  food.  In  addition, it avoids
  588temporary files and relatively expensive fork()  calls. As it turns out,
  589implementing an efficient LCS (Longest  Common   Sequence)  in Prolog is
  590rather hard. We'll leave the  code  for   reference,  but  might  seek a
  591different solution for the real thing.  Options are:
  592
  593  - Use external diff after all
  594  - Add a proper Prolog implementation of LCS
  595  - Add LCS in C.
  596- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
 data_diff(+Data1, +Data2, -UDiff) is det
Diff two data strings line-by-line. UDiff is a list of terms of the form below, where L1 and L2 provide the starting line in Data1 and Data2 and S1 and S2 provide the number of affected lines.
udiff(L1,S1,L2,S2,Diff)

Diff is a list holding

+ Line
Line was added to Data1 to get Data2
- Line
Line was deleted from Data1 to get Data2
Line1 - Line2
Line was replaced
=(Line)
Line is identical (context line).
  621data_diff(Data, Data, UDiff) :- !,
  622	UDiff = [].
  623data_diff(Data1, Data2, Diff) :-
  624	split_string(Data1, "\n", "", List1),
  625	split_string(Data2, "\n", "", List2),
  626	list_diff(List1, List2, Diff).
  627
  628list_diff(List1, List2, UDiff) :-
  629	list_lcs(List1, List2, Lcs),
  630	make_diff(List1, List2, Lcs, c(), 1, 1, Diff),
  631	join_diff(Diff, UDiff).
 make_diff(+List1, +List2, +Lcs, +Context0, +Line1, +Line2, -Diff)
  635make_diff([], [], [], _, _, _, []) :- !.
  636make_diff([H|T1], [H|T2], [H|C], c(_,C0,C1), L1, L2, Diff) :- !,
  637	L11 is L1+1,
  638	L21 is L2+1,
  639	make_diff(T1, T2, C, c(C0,C1,H), L11, L21, Diff).
  640make_diff([H|T1], [H|T2], [H|C], C0, L1, L2, Diff) :- !,
  641	L11 is L1+1,
  642	L21 is L2+1,
  643	add_context(C0, H, C1),
  644	(   compound_name_arity(C1, _, L1)
  645	->  Diff = Diff1
  646	;   Diff = [=(H)|Diff1]
  647	),
  648	make_diff(T1, T2, C, C1, L11, L21, Diff1).
  649make_diff([H|T1], [H2|T2], [H|C], C0, L1, L2, [d(L1,L2,C0,+H2)|Diff]) :- !,
  650	L21 is L2+1,
  651	make_diff([H|T1], T2, [H|C], c(), L1, L21, Diff).
  652make_diff([], [H2|T2], [], C0, L1, L2, [d(L1,L2,C0,+H2)|Diff]) :- !,
  653	L21 is L2+1,
  654	make_diff([], T2, [], c(), L1, L21, Diff).
  655make_diff([H1|T1], [H|T2], [H|C], C0, L1, L2, [d(L1,L2,C0,-H1)|Diff]) :- !,
  656	L11 is L1+1,
  657	make_diff(T1, [H|T2], [H|C], c(), L11, L2, Diff).
  658make_diff([H1|T1], [], [], C0, L1, L2, [d(L1,L2,C0,-H1)|Diff]) :- !,
  659	L11 is L1+1,
  660	make_diff(T1, [], [], c(), L11, L2, Diff).
  661make_diff([H1|T1], [H2|T2], C, C0, L1, L2, [d(L1,L2,C0,H1-H2)|Diff]) :- !,
  662	L11 is L1+1,
  663	L21 is L2+1,
  664	make_diff(T1, T2, C, c(), L11, L21, Diff).
  665
  666add_context(c(_,B,C),N,c(B,C,N)).
  667add_context(c(A,B),  N,c(A,B,N)).
  668add_context(c(A),    N,c(A,N)).
  669add_context(c(),     N,c(N)).
 join_diff(+Diff, -UDiff) is det
  673join_diff([], []).
  674join_diff([d(L10,L20,C,L)|T0], [udiff(L1,S1,L2,S2,Diff)|T]) :-
  675	pre_context(C, S0, Diff, [L|DiffT]),
  676	L1 is L10-S0,
  677	L2 is L20-S0,
  678	diff_affected(L,S10,S20),
  679	S11 is S10+S0,
  680	S21 is S20+S0,
  681	collect_diff(T0,S11,S21,S1,S2,0,DiffT,T1),
  682	join_diff(T1, T).
  683
  684pre_context(c(),      0, L, L).
  685pre_context(c(A),     1, [=(A)|L], L).
  686pre_context(c(A,B),   2, [=(A),=(B)|L], L).
  687pre_context(c(A,B,C), 3, [=(A),=(B),=(C)|L], L).
  688
  689collect_diff([d(_,_,_,L)|T0], S10,S20,S1,S2,C,[L|Diff],T) :-
  690	C < 3, !,
  691	diff_affected(L,S1x,S2x),
  692	S11 is S10+S1x,
  693	S21 is S20+S2x,
  694	collect_diff(T0,S11,S21,S1,S2,0,Diff,T).
  695collect_diff([=(L)|T0], S10,S20,S1,S2,C0,[=(L)|Diff],T) :- !,
  696	S11 is S10+1,
  697	S21 is S20+1,
  698	C1 is C0+1,
  699	collect_diff(T0,S11,S21,S1,S2,C1,Diff,T).
  700collect_diff(T,S1,S2,S1,S2,_,[],T).
  701
  702diff_affected(+(_),   0, 1).
  703diff_affected(-(_),   0, 1).
  704diff_affected(-(_,_), 1, 1).
 udiff_string(+UDiff, -String) is det
True when String is the string representation of UDiff.
  710udiff_string(udiff(L1,S1,L2,S2,Diff), Final) :-
  711	format(string(Hdr), '@@ -~d,~d +~d,~d @@', [L1,S1,L2,S2]),
  712	udiff_blocks(Diff, Blocks),
  713	maplist(block_lines, Blocks, LineSets),
  714	append(LineSets, Lines),
  715	atomics_to_string([Hdr|Lines], "\n", Final).
  716
  717block_lines(=(U), Lines) :- maplist(string_concat(' '), U, Lines).
  718block_lines(+(U), Lines) :- maplist(string_concat('+'), U, Lines).
  719block_lines(-(U), Lines) :- maplist(string_concat('-'), U, Lines).
  720
  721udiff_blocks([], []) :- !.
  722udiff_blocks([=(H)|T0], [=([H|E])|T]) :- !,
  723	udiff_cp(T0, E, T1),
  724	udiff_blocks(T1, T).
  725udiff_blocks(U, List) :-
  726	udiff_block(U, D, A, T1),
  727	udiff_add(D,A,List,ListT),
  728	udiff_blocks(T1, ListT).
  729
  730udiff_add([],A,[+A|T],T) :- !.
  731udiff_add(D,[],[-D|T],T) :- !.
  732udiff_add(D,A,[-D,+A|T],T).
  733
  734udiff_cp([=(H)|T0], [H|E], T) :- !,
  735	udiff_cp(T0, E, T).
  736udiff_cp(L, [], L).
  737
  738udiff_block([-L|T], [L|D], A, Rest) :- !,
  739	udiff_block(T, D, A, Rest).
  740udiff_block([+L|T], D, [L|A], Rest) :- !,
  741	udiff_block(T, D, A, Rest).
  742udiff_block([L1-L2|T], [L1|D], [L2|A], Rest) :- !,
  743	udiff_block(T, D, A, Rest).
  744udiff_block(T, [], [], T).
 list_lcs(+List1, +List2, -Lcs) is det
To be done
- Too slow. See http://wordaligned.org/articles/longest-common-subsequence
  750:- thread_local lcs_db/2.  751
  752list_lcs([], [], []) :- !.
  753list_lcs([H|L1], [H|L2], [H|Lcs]) :- !,
  754	list_lcs(L1, L2, Lcs).
  755list_lcs(List1, List2, Lcs) :-
  756	reverse(List1, Rev1),
  757	reverse(List2, Rev2),
  758	copy_prefix(Rev1, Rev2, RevDiff1, RevDiff2, RevLcs, RevT),
  759	list_lcs2(RevDiff1, RevDiff2, RevT),
  760	reverse(RevLcs, Lcs).
  761
  762list_lcs2(List1, List2, Lcs) :-
  763	variant_sha1(List1+List2, Hash),
  764	call_cleanup(
  765	    lcs(List1, List2, Hash, Lcs),
  766	    retractall(lcs_db(_,_))).
  767
  768copy_prefix([H|T1], [H|T2], L1, L2, [H|L], LT) :- !,
  769	copy_prefix(T1, T2, L1, L2, L, LT).
  770copy_prefix(R1, R2, R1, R2, L, L).
  771
  772
  773lcs(_,_,Hash,Lcs) :-
  774	lcs_db(Hash,Lcs), !.
  775lcs([H|L1], [H|L2], _, [H|Lcs]) :- !,
  776	variant_sha1(L1+L2,Hash),
  777	lcs(L1, L2, Hash, Lcs).
  778lcs(List1, List2, Hash, Lcs) :-
  779	List1 = [H1|L1],
  780	List2 = [H2|L2],
  781	variant_sha1(L1+[H2|L2],Hash1),
  782	variant_sha1([H1|L1]+L2,Hash2),
  783	lcs(    L1 , [H2|L2], Hash1, Lcs1),
  784	lcs([H1|L1],     L2 , Hash2, Lcs2),
  785	longest(Lcs1, Lcs2, Lcs),!,
  786	asserta(lcs_db(Hash, Lcs)).
  787lcs(_,_,_,[]).
  788
  789longest(L1, L2, Longest) :-
  790	length(L1, Length1),
  791	length(L2, Length2),
  792	(   Length1 > Length2
  793	->  Longest = L1
  794	;   Longest = L2
  795	).
  796
  797		 /*******************************
  798		 *	      MESSAGES		*
  799		 *******************************/
  800:- multifile
  801	prolog:error_message//1.  802
  803prolog:error_message(gitty(not_at_head(Name, _OldCommit))) -->
  804	[ 'Gitty: cannot update head for "~w" because it was \c
  805	   updated by someone else'-[Name] ].
  806prolog:error_message(gitty(file_exists(Name))) -->
  807	[ 'Gitty: File exists: ~p'-[Name] ].
  808prolog:error_message(gitty(commit_version(Name, _Head, _Previous))) -->
  809	[ 'Gitty: ~p: cannot update (modified by someone else)'-[Name] ]