19962009 Ericsson AB. All Rights Reserved. The contents of this file are subject to the Erlang Public License, Version 1.1, (the "License"); you may not use this file except in compliance with the License. You should have received a copy of the Erlang Public License along with this software. If not, it can be retrieved online at http://www.erlang.org/. Software distributed under the License is distributed on an "AS IS" basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See the License for the specific language governing rights and limitations under the License. lists Robert Virding 1 96-09-28 A
lists List Processing Functions

This module contains functions for list processing. The functions are organized in two groups: those in the first group perform a particular operation on one or more lists, whereas those in the second group are higher-order functions, using a fun as argument to perform an operation on one list.

Unless otherwise stated, all functions assume that position numbering starts at 1. That is, the first element of a list is at position 1.

Whenever an ordering function F is expected as argument, it is assumed that the following properties hold of F for all x, y and z:

if x F y and y F x then x = y (F is antisymmetric);

if x F y and and y F z then x F z (F is transitive);

x F y or y F x (F is total).

An example of a typical ordering function is less than or equal to, =</2.

all(Pred, List) -> bool() Return true if all elements in the list satisfyPred Pred = fun(Elem) -> bool()  Elem = term() List = [term()]

Returns true if Pred(Elem) returns true for all elements Elem in List, otherwise false.

any(Pred, List) -> bool() Return true if any of the elements in the list satisfiesPred Pred = fun(Elem) -> bool()  Elem = term() List = [term()]

Returns true if Pred(Elem) returns true for at least one element Elem in List.

append(ListOfLists) -> List1 Append a list of lists ListOfLists = [List] List = List1 = [term()]

Returns a list in which all the sub-lists of ListOfLists have been appended. For example:

> lists:append([[1, 2, 3], [a, b], [4, 5, 6]]).
[1,2,3,a,b,4,5,6]
append(List1, List2) -> List3 Append two lists List1 = List2 = List3 = [term()]

Returns a new list List3 which is made from the elements of List1 followed by the elements of List2. For example:

> lists:append("abc", "def").
"abcdef"

lists:append(A, B) is equivalent to A ++ B.

concat(Things) -> string() Concatenate a list of atoms Things = [Thing]  Thing = atom() | integer() | float() | string()

Concatenates the text representation of the elements of Things. The elements of Things can be atoms, integers, floats or strings.

> lists:concat([doc, '/', file, '.', 3]).
"doc/file.3"
delete(Elem, List1) -> List2 Delete an element from a list Elem = term() List1 = List2 = [term()]

Returns a copy of List1 where the first element matching Elem is deleted, if there is such an element.

dropwhile(Pred, List1) -> List2 Drop elements from a list while a predicate is true Pred = fun(Elem) -> bool()  Elem = term() List1 = List2 = [term()]

Drops elements Elem from List1 while Pred(Elem) returns true and returns the remaining list.

duplicate(N, Elem) -> List Make N copies of element N = int() Elem = term() List = [term()]

Returns a list which contains N copies of the term Elem. For example:

> lists:duplicate(5, xx).
[xx,xx,xx,xx,xx]
filter(Pred, List1) -> List2 Choose elements which satisfy a predicate Pred = fun(Elem) -> bool()  Elem = term() List1 = List2 = [term()]

List2 is a list of all elements Elem in List1 for which Pred(Elem) returns true.

flatlength(DeepList) -> int() Length of flattened deep list DeepList = [term() | DeepList]

Equivalent to length(flatten(DeepList)), but more efficient.

flatmap(Fun, List1) -> List2 Map and flatten in one pass Fun = fun(A) -> [B] List1 = [A] List2 = [B]  A = B = term()

Takes a function from As to lists of Bs, and a list of As (List1) and produces a list of Bs by applying the function to every element in List1 and appending the resulting lists.

That is, flatmap behaves as if it had been defined as follows:

flatmap(Fun, List1) -> append(map(Fun, List1))

Example:

> lists:flatmap(fun(X)->[X,X] end, [a,b,c]).
[a,a,b,b,c,c]
flatten(DeepList) -> List Flatten a deep list DeepList = [term() | DeepList] List = [term()]

Returns a flattened version of DeepList.

flatten(DeepList, Tail) -> List Flatten a deep list DeepList = [term() | DeepList] Tail = List = [term()]

Returns a flattened version of DeepList with the tail Tail appended.

foldl(Fun, Acc0, List) -> Acc1 Fold a function over a list Fun = fun(Elem, AccIn) -> AccOut  Elem = term() Acc0 = Acc1 = AccIn = AccOut = term() List = [term()]

Calls Fun(Elem, AccIn) on successive elements A of List, starting with AccIn == Acc0. Fun/2 must return a new accumulator which is passed to the next call. The function returns the final value of the accumulator. Acc0 is returned if the list is empty. For example:

> lists:foldl(fun(X, Sum) -> X + Sum end, 0, [1,2,3,4,5]).
15
> lists:foldl(fun(X, Prod) -> X * Prod end, 1, [1,2,3,4,5]).
120
foldr(Fun, Acc0, List) -> Acc1 Fold a function over a list Fun = fun(Elem, AccIn) -> AccOut  Elem = term() Acc0 = Acc1 = AccIn = AccOut = term() List = [term()]

Like foldl/3, but the list is traversed from right to left. For example:

> P = fun(A, AccIn) -> io:format("~p ", [A]), AccIn end.
#Fun<erl_eval.12.2225172>
> lists:foldl(P, void, [1,2,3]).
1 2 3 void
> lists:foldr(P, void, [1,2,3]).
3 2 1 void

foldl/3 is tail recursive and would usually be preferred to foldr/3.

foreach(Fun, List) -> void() Apply a function to each element of a list Fun = fun(Elem) -> void()  Elem = term() List = [term()]

Calls Fun(Elem) for each element Elem in List. This function is used for its side effects and the evaluation order is defined to be the same as the order of the elements in the list.

keydelete(Key, N, TupleList1) -> TupleList2 Delete an element from a list of tuples Key = term() N = 1..tuple_size(Tuple) TupleList1 = TupleList2 = [Tuple]  Tuple = tuple()

Returns a copy of TupleList1 where the first occurrence of a tuple whose Nth element compares equal to Key is deleted, if there is such a tuple.

keyfind(Key, N, TupleList) -> Tuple | false Search for an element in a list of tuples Key = term() N = 1..tuple_size(Tuple) TupleList = [Tuple] Tuple = tuple()

Searches the list of tuples TupleList for a tuple whose Nth element compares equal to Key. Returns Tuple if such a tuple is found, otherwise false.

keymap(Fun, N, TupleList1) -> TupleList2 Map a function over a list of tuples Fun = fun(Term1) -> Term2  Term1 = Term2 = term() N = 1..tuple_size(Tuple) TupleList1 = TupleList2 = [tuple()]

Returns a list of tuples where, for each tuple in TupleList1, the Nth element Term1 of the tuple has been replaced with the result of calling Fun(Term1).

Examples:

> Fun = fun(Atom) -> atom_to_list(Atom) end.
#Fun<erl_eval.6.10732646>
2> lists:keymap(Fun, 2, [{name,jane,22},{name,lizzie,20},{name,lydia,15}]).
[{name,"jane",22},{name,"lizzie",20},{name,"lydia",15}]
keymember(Key, N, TupleList) -> bool() Test for membership of a list of tuples Key = term() N = 1..tuple_size(Tuple) TupleList = [Tuple]  Tuple = tuple()

Returns true if there is a tuple in TupleList whose Nth element compares equal to Key, otherwise false.

keymerge(N, TupleList1, TupleList2) -> TupleList3 Merge two key-sorted lists of tuples N = 1..tuple_size(Tuple) TupleList1 = TupleList2 = TupleList3 = [Tuple]  Tuple = tuple()

Returns the sorted list formed by merging TupleList1 and TupleList2. The merge is performed on the Nth element of each tuple. Both TupleList1 and TupleList2 must be key-sorted prior to evaluating this function. When two tuples compare equal, the tuple from TupleList1 is picked before the tuple from TupleList2.

keyreplace(Key, N, TupleList1, NewTuple) -> TupleList2 Replace an element in a list of tuples Key = term() N = 1..tuple_size(Tuple) TupleList1 = TupleList2 = [Tuple] NewTuple = Tuple = tuple()

Returns a copy of TupleList1 where the first occurrence of a T tuple whose Nth element compares equal to Key is replaced with NewTuple, if there is such a tuple T.

keysearch(Key, N, TupleList) -> {value, Tuple} | false Search for an element in a list of tuples Key = term() N = 1..tuple_size(Tuple) TupleList = [Tuple] Tuple = tuple()

Searches the list of tuples TupleList for a tuple whose Nth element compares equal to Key. Returns {value, Tuple} if such a tuple is found, otherwise false.

This function is retained for backward compatibility. The function lists:keyfind/3 (introduced in R13A) is in most cases more convenient.

keysort(N, TupleList1) -> TupleList2 Sort a list of tuples N = 1..tuple_size(Tuple) TupleList1 = TupleList2 = [Tuple]  Tuple = tuple()

Returns a list containing the sorted elements of the list TupleList1. Sorting is performed on the Nth element of the tuples.

keystore(Key, N, TupleList1, NewTuple) -> TupleList2 Store an element in a list of tuples Key = term() N = 1..tuple_size(Tuple) TupleList1 = TupleList2 = [Tuple] NewTuple = Tuple = tuple()

Returns a copy of TupleList1 where the first occurrence of a tuple T whose Nth element compares equal to Key is replaced with NewTuple, if there is such a tuple T. If there is no such tuple T a copy of TupleList1 where [NewTuple] has been appended to the end is returned.

keytake(Key, N, TupleList1) -> {value, Tuple, TupleList2} | false Extract an element from a list of tuples Key = term() N = 1..tuple_size(Tuple) TupleList1 = TupleList2 = [Tuple] Tuple = tuple()

Searches the list of tuples TupleList1 for a tuple whose Nth element compares equal to Key. Returns {value, Tuple, TupleList2} if such a tuple is found, otherwise false. TupleList2 is a copy of TupleList1 where the first occurrence of Tuple has been removed.

last(List) -> Last Return last element in a list List = [term()], length(List) > 0 Last = term()

Returns the last element in List.

map(Fun, List1) -> List2 Map a function over a list Fun = fun(A) -> B List1 = [A] List2 = [B]  A = B = term()

Takes a function from As to Bs, and a list of As and produces a list of Bs by applying the function to every element in the list. This function is used to obtain the return values. The evaluation order is implementation dependent.

mapfoldl(Fun, Acc0, List1) -> {List2, Acc1} Map and fold in one pass Fun = fun(A, AccIn) -> {B, AccOut} Acc0 = Acc1 = AccIn = AccOut = term() List1 = [A] List2 = [B]  A = B = term()

mapfold combines the operations of map/2 and foldl/3 into one pass. An example, summing the elements in a list and double them at the same time:

> lists:mapfoldl(fun(X, Sum) -> {2*X, X+Sum} end,
0, [1,2,3,4,5]).
{[2,4,6,8,10],15}
mapfoldr(Fun, Acc0, List1) -> {List2, Acc1} Map and fold in one pass Fun = fun(A, AccIn) -> {B, AccOut} Acc0 = Acc1 = AccIn = AccOut = term() List1 = [A] List2 = [B]  A = B = term()

mapfold combines the operations of map/2 and foldr/3 into one pass.

max(List) -> Max Return maximum element of a list List = [term()], length(List) > 0 Max = term()

Returns the first element of List that compares greater than or equal to all other elements of List.

member(Elem, List) -> bool() Test for membership of a list Elem = term() List = [term()]

Returns true if Elem matches some element of List, otherwise false.

merge(ListOfLists) -> List1 Merge a list of sorted lists ListOfLists = [List] List = List1 = [term()]

Returns the sorted list formed by merging all the sub-lists of ListOfLists. All sub-lists must be sorted prior to evaluating this function. When two elements compare equal, the element from the sub-list with the lowest position in ListOfLists is picked before the other element.

merge(List1, List2) -> List3 Merge two sorted lists List1 = List2 = List3 = [term()]

Returns the sorted list formed by merging List1 and List2. Both List1 and List2 must be sorted prior to evaluating this function. When two elements compare equal, the element from List1 is picked before the element from List2.

merge(Fun, List1, List2) -> List3 Merge two sorted list Fun = fun(A, B) -> bool() List1 = [A] List2 = [B] List3 = [A | B]  A = B = term()

Returns the sorted list formed by merging List1 and List2. Both List1 and List2 must be sorted according to the ordering function Fun prior to evaluating this function. Fun(A, B) should return true if A compares less than or equal to B in the ordering, false otherwise. When two elements compare equal, the element from List1 is picked before the element from List2.

merge3(List1, List2, List3) -> List4 Merge three sorted lists List1 = List2 = List3 = List4 = [term()]

Returns the sorted list formed by merging List1, List2 and List3. All of List1, List2 and List3 must be sorted prior to evaluating this function. When two elements compare equal, the element from List1, if there is such an element, is picked before the other element, otherwise the element from List2 is picked before the element from List3.

min(List) -> Min Return minimum element of a list List = [term()], length(List) > 0 Min = term()

Returns the first element of List that compares less than or equal to all other elements of List.

nth(N, List) -> Elem Return the Nth element of a list N = 1..length(List) List = [term()] Elem = term()

Returns the Nth element of List. For example:

> lists:nth(3, [a, b, c, d, e]).
c
nthtail(N, List1) -> Tail Return the Nth tail of a list N = 0..length(List1) List1 = Tail = [term()]

Returns the Nth tail of List, that is, the sublist of List starting at N+1 and continuing up to the end of the list. For example:

> lists:nthtail(3, [a, b, c, d, e]).
[d,e]
> tl(tl(tl([a, b, c, d, e]))).
[d,e]
> lists:nthtail(0, [a, b, c, d, e]).
[a,b,c,d,e]
> lists:nthtail(5, [a, b, c, d, e]).
[]
partition(Pred, List) -> {Satisfying, NonSatisfying} Partition a list into two lists based on a predicate Pred = fun(Elem) -> bool()  Elem = term() List = Satisfying = NonSatisfying = [term()]

Partitions List into two lists, where the first list contains all elements for which Pred(Elem) returns true, and the second list contains all elements for which Pred(Elem) returns false.

Examples:

> lists:partition(fun(A) -> A rem 2 == 1 end, [1,2,3,4,5,6,7]).
{[1,3,5,7],[2,4,6]}
> lists:partition(fun(A) -> is_atom(A) end, [a,b,1,c,d,2,3,4,e]).
{[a,b,c,d,e],[1,2,3,4]}

See also splitwith/2 for a different way to partition a list.

prefix(List1, List2) -> bool() Test for list prefix List1 = List2 = [term()]

Returns true if List1 is a prefix of List2, otherwise false.

reverse(List1) -> List2 Reverse a list List1 = List2 = [term()]

Returns a list with the top level elements in List1 in reverse order.

reverse(List1, Tail) -> List2 Reverse a list appending a tail List1 = Tail = List2 = [term()]

Returns a list with the top level elements in List1 in reverse order, with the tail Tail appended. For example:

> lists:reverse([1, 2, 3, 4], [a, b, c]).
[4,3,2,1,a,b,c]
seq(From, To) -> Seq seq(From, To, Incr) -> Seq Generate a sequence of integers From = To = Incr = int() Seq = [int()]

Returns a sequence of integers which starts with From and contains the successive results of adding Incr to the previous element, until To has been reached or passed (in the latter case, To is not an element of the sequence). Incr defaults to 1.

Failure: If and Incr is positive, or if To>From-Incr and Incr is negative, or if Incr==0 and From/=To.

The following equalities hold for all sequences:

length(lists:seq(From, To)) == To-From+1 length(lists:seq(From, To, Incr)) == (To-From+Incr) div Incr

Examples:

> lists:seq(1, 10).
[1,2,3,4,5,6,7,8,9,10]
> lists:seq(1, 20, 3).
[1,4,7,10,13,16,19]
> lists:seq(1, 0, 1).
[]
> lists:seq(10, 6, 4).
[]
> lists:seq(1, 1, 0).
[1]
sort(List1) -> List2 Sort a list List1 = List2 = [term()]

Returns a list containing the sorted elements of List1.

sort(Fun, List1) -> List2 Sort a list Fun = fun(Elem1, Elem2) -> bool()  Elem1 = Elem2 = term() List1 = List2 = [term()]

Returns a list containing the sorted elements of List1, according to the ordering function Fun. Fun(A, B) should return true if A compares less than or equal to B in the ordering, false otherwise.

split(N, List1) -> {List2, List3} Split a list into two lists N = 0..length(List1) List1 = List2 = List3 = [term()]

Splits List1 into List2 and List3. List2 contains the first N elements and List3 the rest of the elements (the Nth tail).

splitwith(Pred, List) -> {List1, List2} Split a list into two lists based on a predicate Pred = fun(Elem) -> bool()  Elem = term() List = List1 = List2 = [term()]

Partitions List into two lists according to Pred. splitwith/2 behaves as if it is defined as follows:

splitwith(Pred, List) -> {takewhile(Pred, List), dropwhile(Pred, List)}.

Examples:

> lists:splitwith(fun(A) -> A rem 2 == 1 end, [1,2,3,4,5,6,7]).
{[1],[2,3,4,5,6,7]}
> lists:splitwith(fun(A) -> is_atom(A) end, [a,b,1,c,d,2,3,4,e]).
{[a,b],[1,c,d,2,3,4,e]}

See also partition/2 for a different way to partition a list.

sublist(List1, Len) -> List2 Return a sub-list of a certain length, starting at the first position List1 = List2 = [term()] Len = int()

Returns the sub-list of List1 starting at position 1 and with (max) Len elements. It is not an error for Len to exceed the length of the list -- in that case the whole list is returned.

sublist(List1, Start, Len) -> List2 Return a sub-list starting at a given position and with a given number of elements List1 = List2 = [term()] Start = 1..(length(List1)+1) Len = int()

Returns the sub-list of List1 starting at Start and with (max) Len elements. It is not an error for Start+Len to exceed the length of the list.

> lists:sublist([1,2,3,4], 2, 2).
[2,3]
> lists:sublist([1,2,3,4], 2, 5).
[2,3,4]
> lists:sublist([1,2,3,4], 5, 2).
[]
subtract(List1, List2) -> List3 Subtract the element in one list from another list List1 = List2 = List3 = [term()]

Returns a new list List3 which is a copy of List1, subjected to the following procedure: for each element in List2, its first occurrence in List1 is deleted. For example:

> lists:subtract("123212", "212").
"312".

lists:subtract(A, B) is equivalent to A -- B.

The complexity of lists:subtract(A, B) is proportional to length(A)*length(B), meaning that it will be very slow if both A and B are long lists. (Using ordered lists and ordsets:subtract/2 is a much better choice if both lists are long.)

suffix(List1, List2) -> bool() Test for list suffix

Returns true if List1 is a suffix of List2, otherwise false.

sum(List) -> number() Return sum of elements in a list List = [number()]

Returns the sum of the elements in List.

takewhile(Pred, List1) -> List2 Take elements from a list while a predicate is true Pred = fun(Elem) -> bool()  Elem = term() List1 = List2 = [term()]

Takes elements Elem from List1 while Pred(Elem) returns true, that is, the function returns the longest prefix of the list for which all elements satisfy the predicate.

ukeymerge(N, TupleList1, TupleList2) -> TupleList3 Merge two key-sorted lists of tuples, removing duplicates N = 1..tuple_size(Tuple) TupleList1 = TupleList2 = TupleList3 = [Tuple]  Tuple = tuple()

Returns the sorted list formed by merging TupleList1 and TupleList2. The merge is performed on the Nth element of each tuple. Both TupleList1 and TupleList2 must be key-sorted without duplicates prior to evaluating this function. When two tuples compare equal, the tuple from TupleList1 is picked and the one from TupleList2 deleted.

ukeysort(N, TupleList1) -> TupleList2 Sort a list of tuples, removing duplicates N = 1..tuple_size(Tuple) TupleList1 = TupleList2 = [Tuple]  Tuple = tuple()

Returns a list containing the sorted elements of the list TupleList1 where all but the first tuple of the tuples comparing equal have been deleted. Sorting is performed on the Nth element of the tuples.

umerge(ListOfLists) -> List1 Merge a list of sorted lists, removing duplicates ListOfLists = [List] List = List1 = [term()]

Returns the sorted list formed by merging all the sub-lists of ListOfLists. All sub-lists must be sorted and contain no duplicates prior to evaluating this function. When two elements compare equal, the element from the sub-list with the lowest position in ListOfLists is picked and the other one deleted.

umerge(List1, List2) -> List3 Merge two sorted lists, removing duplicates List1 = List2 = List3 = [term()]

Returns the sorted list formed by merging List1 and List2. Both List1 and List2 must be sorted and contain no duplicates prior to evaluating this function. When two elements compare equal, the element from List1 is picked and the one from List2 deleted.

umerge(Fun, List1, List2) -> List3 Merge two sorted lists, removing duplicates Fun = fun(A, B) -> bool() List1 = [A] List2 = [B] List3 = [A | B]  A = B = term()

Returns the sorted list formed by merging List1 and List2. Both List1 and List2 must be sorted according to the ordering function Fun and contain no duplicates prior to evaluating this function. Fun(A, B) should return true if A compares less than or equal to B in the ordering, false otherwise. When two elements compare equal, the element from List1 is picked and the one from List2 deleted.

umerge3(List1, List2, List3) -> List4 Merge three sorted lists, removing duplicates List1 = List2 = List3 = List4 = [term()]

Returns the sorted list formed by merging List1, List2 and List3. All of List1, List2 and List3 must be sorted and contain no duplicates prior to evaluating this function. When two elements compare equal, the element from List1 is picked if there is such an element, otherwise the element from List2 is picked, and the other one deleted.

unzip(List1) -> {List2, List3} Unzip a list of two-tuples into two lists List1 = [{X, Y}] List2 = [X] List3 = [Y]  X = Y = term()

"Unzips" a list of two-tuples into two lists, where the first list contains the first element of each tuple, and the second list contains the second element of each tuple.

unzip3(List1) -> {List2, List3, List4} Unzip a list of three-tuples into three lists List1 = [{X, Y, Z}] List2 = [X] List3 = [Y] List4 = [Z]  X = Y = Z = term()

"Unzips" a list of three-tuples into three lists, where the first list contains the first element of each tuple, the second list contains the second element of each tuple, and the third list contains the third element of each tuple.

usort(List1) -> List2 Sort a list, removing duplicates List1 = List2 = [term()]

Returns a list containing the sorted elements of List1 where all but the first element of the elements comparing equal have been deleted.

usort(Fun, List1) -> List2 Sort a list, removing duplicates Fun = fun(Elem1, Elem2) -> bool()  Elem1 = Elem2 = term() List1 = List2 = [term()]

Returns a list which contains the sorted elements of List1 where all but the first element of the elements comparing equal according to the ordering function Fun have been deleted. Fun(A, B) should return true if A compares less than or equal to B in the ordering, false otherwise.

zip(List1, List2) -> List3 Zip two lists into a list of two-tuples List1 = [X] List2 = [Y] List3 = [{X, Y}]  X = Y = term()

"Zips" two lists of equal length into one list of two-tuples, where the first element of each tuple is taken from the first list and the second element is taken from corresponding element in the second list.

zip3(List1, List2, List3) -> List4 Zip three lists into a list of three-tuples List1 = [X] List2 = [Y] List3 = [Z] List3 = [{X, Y, Z}]  X = Y = Z = term()

"Zips" three lists of equal length into one list of three-tuples, where the first element of each tuple is taken from the first list, the second element is taken from corresponding element in the second list, and the third element is taken from the corresponding element in the third list.

zipwith(Combine, List1, List2) -> List3 Zip two lists into one list according to a fun Combine = fun(X, Y) -> T List1 = [X] List2 = [Y] List3 = [T]  X = Y = T = term()

Combine the elements of two lists of equal length into one list. For each pair X, Y of list elements from the two lists, the element in the result list will be Combine(X, Y).

zipwith(fun(X, Y) -> {X,Y} end, List1, List2) is equivalent to zip(List1, List2).

Example:

> lists:zipwith(fun(X, Y) -> X+Y end, [1,2,3], [4,5,6]).
[5,7,9]
zipwith3(Combine, List1, List2, List3) -> List4 Zip three lists into one list according to a fun Combine = fun(X, Y, Z) -> T List1 = [X] List2 = [Y] List3 = [Z] List4 = [T]  X = Y = Z = T = term()

Combine the elements of three lists of equal length into one list. For each triple X, Y, Z of list elements from the three lists, the element in the result list will be Combine(X, Y, Z).

zipwith3(fun(X, Y, Z) -> {X,Y,Z} end, List1, List2, List3) is equivalent to zip3(List1, List2, List3).

Examples:

> lists:zipwith3(fun(X, Y, Z) -> X+Y+Z end, [1,2,3], [4,5,6], [7,8,9]).
[12,15,18]
> lists:zipwith3(fun(X, Y, Z) -> [X,Y,Z] end, [a,b,c], [x,y,z], [1,2,3]).
[[a,x,1],[b,y,2],[c,z,3]]