"copy constructors" -- when are terms copied and when linked

Hello,

I am wondering about space need and implicit copying of terms in my code. What are the rules in swi-prolog that help me determine when terms are copied and when linked.

For example, I have a dictionary (assoc) that holds as value a list, to add an item to the list i first lookup the (Key, List), and the create a new list as so:

NewList = [New Item | List] and then update the assoc with the New List (via add_key).

I am now wondering – do i actually create a brand new copy of the list – if yes, should i use difference lists instead, or something else.?

Also, when i pass a composite term as argument – is this by “reference”, or is some copying happening as well.

thanks,

Dan

The nodes are “copied” (actually, new ones are created), but the contents remain the same. So, if you start with [a,b,c] and append d, then a new node is created for each item, but the contents (a, b, c) aren’t “copied”; the new nodes just point to them. The old nodes can often be garbage collected.

You might want to use library(assoc) or library(rbtrees) – for them, a typical insert would copy log N nodes…

That sounds very wasteful – suppose I have a very large list – i really only want to have one node added – just the delta …

Would difference lists help ?

Is this possible ?

If you append at the front, there’s no extra cost. Difference lists can be used to add at the end, but require a bit of care in setting up and using (DCGs can help with this).

If you have keys, then I suggest using association lists; the cost is O(log N) rather than O(N). And, the “copied” nodes can be reclaimed if you’re not creating choicepoints.

I have some code that does lots of inserting and lookup; when I last looked at the performance profile, the cost of insertions was ~5%. YMMV. (And my code uses SWI-Prolog’s “dicts”; if I switched to red-black trees, it would be considerably faster.)

Yes, that is what i tried to do with the code:

NewList = [Item | OldList ]

Dan

p.s. since i am only pre-prending one item i thought append/3 is not needed.

That is correct – only one node is created. Although append/3 won’t be expensive in that situation either: append([Item], OldList, NewList) becomes NewList = [Item|OldList].
And when your computation is finished, you can use reverse/2 to put the list in insertion order, if that’s what you want.
append(OldList, [Item], NewList) will create N new nodes when creating NewList from OldList (but the contents of the nodes won’t be copied).
put_assoc(Key, OldAssoc, Value, NewAssoc) or rb_insert(OldTree, Key, Value, NewTree) will create O(log N) new nodes.

Note that the typical Prolog idiom of generating a new list from an old one, is an O(N) algorithm; but if you use append/3 it becomes O(N). The following code illustrates some of the options (I haven’t tested any of this, so there could be typos):

% O(N) algorithm:
transform([], []).
transform([X|Xs], [Y|Ys]) :-
    pred(X, Y),
    transform(Xs, Ys). 

% O(N):
transform(Xs, Ys) :- maplist(pred, Xs, Ys).

% O(N^2) algorithm:
transform(Xs, Ys) :- transform(Xs, [], Ys).
transform([], Result, Result).
transform([X|Xs], SoFar, Ys) :-
    pred(X, Y),
    append(SoFar, [X], SoFar2),
    transform(Xs, SoFar2, Ys).

% O(N) algorithm:
transform(Xs, Ys) :- 
    transform(Xs, [], YsReverse),
    reverse(YsReverse, Ys).
transform([], Result, Result).
transform([X|Xs], SoFar, Ys) :-
    pred(X, Y),
    transform(Xs, [Y|SoFar, Ys).

% O(N) algorithm:
transform(Xs, Ys) :- phrase(transform(Xs), Ys).
transform([]) --> [].
transform([X|Xs]) -->
    { pred(X, Y) },
    [Y],
    transform(Xs).

% O(M + log N) algorithm for K-V pairs (see also `map_assoc/3):
transform([], Assoc, Assoc).
transform([K|Ks], Assoc0, Assoc) :-
    get_assoc(K, Assoc0, V0)
    pred(K, V0, V1),
    put_assoc(K, Assoc0, V1, Assoc1),
    transform(KVs, Assoc1, Assoc).

and

isnt this a contradiction …

I am also unclear what the distinction between contents and node – the contents is an atom which essentially is a symbol - presumably in a symbol table pointed at – so adding an atom to a list should create another pointer (cons?) to the atom in the symbol table, and link it to the list.

There would also be some need to handle the choice point and that the append could be removed during backtracking. But, for all this, is there a need to actually copy nodes?

[a, b, c] is represented like this:

+----+----+    +----+----+    +----+----+    +------+
|    |   ----->|    |   ----->|    |   ----->|  nil |
+--|-+----+    +--|-+----+    +--|-+----+    +------+
   |              |              |
   |              |              |
   V              V              V
+------+       +------+       +------+
+ atom |       + atom |       + atom |
+ 'a'  |       + 'b'  |       + 'c'  |
+------+       +------+       +------+

If you make a copy of the list with d at the end, you get this:

+----+----+    +----+----+    +----+----+    +------+
|    |   ----->|    |   ----->|    |   ----->|  nil |
+--|-+----+    +--|-+----+    +--|-+----+    +------+
   |              |              |
   |              |              |
   V              V              V
+------+       +------+       +------+       +------+
+ atom |       + atom |       + atom |       + atom |
+ 'a'  |       + 'b'  |       + 'c'  |       + 'd'  |
+------+       +------+       +------+       +------+
   A              A              A              A
   |              |              |              |
   |              |              |              |
+--|-+----+    +--|-+----+    +--|-+----+    +--|-+----+   +------+
|    |   ----->|    |   ----->|    |   ----->|    |  ----->|  nil |
+----+----+    +----+----+    +----+----+    +----+----+   +------+

There are N new nodes created during the copying; each node can point at arbitrarily complex things, but there’s no need to copy any of what they point to. This is similar to “shallow copy” in imperative programming languages like C++ or Python. There’s no need for “deep copy” in Prolog because everything is immutable; in C++ or Python, deep copy is often used in case the original values are changed.

After copying the list, if you garbage collect the first list, the atoms remain the same but they’re only pointed at by the second list of nodes.

1 Like

If you put d at the head of the list (OldList=[a,b,c], NewList = [d|OldList]), you end up with this:

NewList        OldList
   |              |
   |              |
   V              V
+----+----+    +----+----+    +----+----+    +--|-+----+   +------+
|    |   ----->|    |   ----->|    |   ----->|    |   ---->|  nil |
+--|-+----+    +--|-+----+    +--|-+----+    +--|-+----+   +------+
   |              |              |              |
   |              |              |              |
   V              V              V              V
+------+       +------+       +------+       +------+
+ atom |       + atom |       + atom |       + atom |
+ 'd'  |       + 'a'  |       + 'b'  |       + 'c'  |
+------+       +------+       +------+       +------+

The [a,b,c] part is “shared” between the new list and the old list. Because it’s immutable, nothing more needs to be done.

You don’t have to think about whether something is shared or copied; in fact, there are so-called “structure-sharing” and “structure-copying” implementations of Prolog that are identical from the programming point of view but that do different things when unifying. (There are no logical variables in the diagrams I’ve drawn, so I haven’t shown this distinction.)

1 Like

Hi Peter,

Many thanks for the helpful visualization and explanation

I am very concerned about the runtime cost and whether its shared or copied would mean different runtime costs for an append operation (either via append or via the list construction i used).

To make the point in the extreme, if for example I have a list of 100K items and add an item, I surely don’t want an internal copying of 100K pointer cells (cons cells in lisp jargon) happening just because i am adding another item.

At the level I am currently working, I am appending a list – so, i am not deciding to copy or to share – I am “at the mercy” of the append implementation …

But, if the append implementation is copying the current list’s cons cells just to add another item to a list, then I better look for an implementation that does not copy but merely adds a one of those “cons” cells.

Edit: I would also not understand why cons cells would be copied in an append – what is the rationale for that – if merely adding a cons cell seems to suffice.

This is what @peter.ludemann has explained: cons cells are only copied if necessary. Consing to the front of a list will not copy the list.

ok. good.

thanks for clarifying further.

Dan

If you’re dealing with 100K items, then lists are probably not an appropriate data structure for you – they have O(N) behaviour for almost all operations (prepending on the front is one exception, as is splitting the list into the first element and the rest – both of these are O(1) but are not for languages such as Python).

Without understanding your problem and your software design background, it’s difficult for me to give more advice than I’ve already done. If you could provide some more details (DM if you want it to remain private), then perhaps I can be more helpful.

HI Peter,

Thank you for your comment and offer to PM.

I said 100K just to give an extreme example – i don’t expect that many, but, the number of items could end up being large.

Right now, the purpose of the list is to collect, during a search, items for which a condition holds – no additional processing is done on “my” side of the system.

But, with your comment in mind, perhaps it could be useful to provide the list of items embodied in a more convenient data structure that could support a client in doing some additional processing – the cost from “my” side would be minimal, while the convenience provided to client code could be significant.

Perhaps, in the future I could provide an option for a client to choose which data structure to use for providing the list.

Dan

Have you seen:

Does SWI-Prolog have N+K-trees?

Take a look at this post by Jan W.

If all you’re doing is collecting results, then I would suggest simply prepending each new result onto the list. If you need to get this in order of results, then use reverse/2 before outputting; to remove duplicates, use sort/2. This is probably the simplest way and uses the least memory.

The choice of any other data structure depends on how you want to access the contents. If by index, then something like N+K trees could be good; if by a key, then perhaps library(assoc) or library(rbtrees) (SWI-Prolog’s dicts, while convenient, are probably not appropriate for large amounts of data). In some cases, using assertz/1 makes sense (with some appropriate provisos). Etc., etc.