Pass subarray by reference (not by value) in Common Lisp - arrays

Let's suppose I have an array - which I will call *my-array* - that looks like this:
#2A((1 2 3)
(4 5 6)
(7 8 9))
and I wish to apply some function f on the subarray
#2A((5 6)
(8 9))
I'd love to be able to write
(f (subarray *my-array* '(1 2) '(1 2))
where subarray takes as arguments:
the original array
a 2-element list with starting point and ending point on the 1st dimension
another 2-element list with starting point and ending point on the 2nd dimension
etc.
I am looking for some way to pass the subarray as argument to function f by reference (or by pointer?) instead of by value.
(The dumb way to address this would be to write a function that creates (in this specific case) a 2*2 array and loops over i and j copying values from the original array. However, if you are dealing relatively large arrays, this would be quite costly.)
I found there exists a cl-slice package but I do not get whether it copies values or accesses data by reference.

Common Lisp has Displaced Arrays which are exactly what you are asking about (see array-displacement &c).
However, in your case, displaces arrays are no help because:
Multidimensional arrays store their components in row-major order; that is, internally a multidimensional array is stored as a one-dimensional array, with the multidimensional index sets ordered lexicographically, last index varying fastest.
This means that your subarray is not a contiguous section of your main array, and, thus, you cannot create another array displaced to it.
PS. If you cannot figure out how cl-slice works, you can use time to see how much memory it uses and make your inference from that.
PPS. It is, in fact, not too hard to whip up something like what you want:
(defmacro slice (array &rest ranges)
"Return an accessor into ARRAY randing in RANGES."
(let ((args (loop for r in ranges collect (gensym "SLICE-ARG-")))
(arr (gensym "SLICE-ARRAY-")))
`(let ((,arr ,array))
(lambda ,args
(aref ,arr
,#(loop for arg in args and (lo hi) in ranges
for range = (- hi lo)
collect
`(progn
(unless (<= 0 ,arg ,range)
(error "~S is out of range [0;~S]" ,arg ,range))
(+ ,lo ,arg))))))))
(defparameter *my-array*
#2A((1 2 3)
(4 5 6)
(7 8 9)))
(defparameter f (slice *my-array* (1 2) (1 2)))
(loop for i from 0 to 1 do
(loop for j from 0 to 1 do
(format t " ~S" (funcall f i j)))
(terpri))
5 6
8 9

As others pointed out, you cannot use displaced arrays for matrices (maybe you could with non-standard functions). But all you need is to change how you interact with the original array. Here are some possibilities.
Sequences of displaced arrays
(defun area (matrix tlx tly brx bry)
;; you may also want to check that all coordinates are valid
;; inside current matrix. You could generalize this function for
;; more dimensions.
(assert (<= tlx tly))
(assert (<= brx bry))
(loop
for y from tly upto bry
collect (make-array (1+ (- brx tlx))
:displaced-to matrix
:displaced-index-offset
(array-row-major-index matrix y tlx))))
(tl means top-left, br means bottom-right).
Then, assuming you define your matrix as follows:
(defparameter *matrix* #2A((1 2 3)
(4 5 6)
(7 8 9)))
... the sub-matrix is obtained as follows:
(area *matrix* 1 1 2 2)
=> (#(5 6) #(8 9))
... and accessed like this:
(aref (nth ROW *) COL)
Any changes to *matrix* is reflected in one of the two displaced arrays, and inversely.
But if you coerce the resulting list as a vector, then you'll have a vector of arrays. This is different from multi-dimensional arrays, but gives you constant time access for rows:
(aref (aref area ROW) COL)
Wrapper closure
Another way to provide a restricted view of the original matrix is to create an accessor function that works only for the ranges of interest:
(defun sub-matrix (matrix tlx tly brx bry)
;; again, you should do more checks
(assert (<= tlx tly))
(assert (<= brx bry))
(lambda (x y &optional (value nil valuep))
(incf x tlx)
(incf y tly)
(assert (<= tlx x brx))
(assert (<= tly y bry))
(if valuep
(setf (aref matrix y x) value)
(aref matrix y x))))
This returns a closure which takes 2 or 3 arguments. The first two arguments are x and y coordinates relative to the inner matrix. When given a third argument, the closure sets the value. Otherwise, it gets the value.
This can be made more generic. I was partly inspired by sds's answer but tried to do things a little differently; here I can generate either a setter or a getter function. I also add some checks before creating the function and during the execution of the created function:
(defun slice-accessor (array ranges mode)
(let* ((dimensions (array-dimensions array))
(max-length (length dimensions)))
(check-type array array)
(loop
with r = (copy-list ranges)
for range = (pop r)
for (lo hi) = range
for d in dimensions
for x from 0
for $index = (gensym x)
collect $index into $indices
when range
do (assert (<= 0 lo hi d))
and collect `(check-type ,$index (integer 0 ,(- hi lo))) into checks
and collect `(incf ,$index ,lo) into increments
finally (let ((body `(apply #'aref ,array ,#$indices ())))
(return
(compile nil
(ecase mode
(:read `(lambda ,$indices
,#checks
,#increments
,body))
(:write (let (($v (make-symbol "VALUE")))
`(lambda (,$v ,#$indices)
(check-type ,$v ,(array-element-type array))
,#checks
,#increments
(setf ,body ,$v)))))))))))
CLOS
Once you have the above, you can provide a nice interface through objects. The setter and getter functions are updated whenever we change the ranges or the array being sliced:
(defclass array-slice ()
((array :initarg :array :accessor reference-array)
(ranges :initarg :ranges :accessor slice-ranges :initform nil)
(%fast-getter :accessor %fast-getter)
(%fast-setter :accessor %fast-setter)))
(flet ((update-fast-calls (o)
(setf (%fast-setter o)
(slice-accessor (reference-array o) (slice-ranges o) :write)
(%fast-getter o)
(slice-accessor (reference-array o) (slice-ranges o) :read))))
(defmethod initialize-instance :after ((o array-slice) &rest k)
(declare (ignore k))
(update-fast-calls o))
(defmethod (setf reference-array) :after (new-array (o array-slice))
(declare (ignore new-array))
(update-fast-calls o))
(defmethod (setf slice-ranges) :after (new-ranges (o array-slice))
(declare (ignore new-ranges))
(update-fast-calls o)))
(defgeneric slice-aref (slice &rest indices)
(:method ((o array-slice) &rest indices)
(apply (%fast-getter o) indices)))
(defgeneric (setf slice-aref) (new-value slice &rest indices)
(:method (new-value (o array-slice) &rest indices)
(apply (%fast-setter o) new-value indices)))
Examples
(defparameter *slice*
(make-instance 'array-slice :array *matrix*))
;; no range by default
(slice-aref *slice* 0 0)
=> 1
;; update ranges
(setf (slice-ranges *slice*) '((1 2) (1 2)))
(slice-aref *slice* 0 0)
=> 5
(incf (slice-aref *slice* 0 0) 10)
=> 15
*matrix*
=> #2A((1 2 3) (4 15 6) (7 8 9))
;; change array
(setf (reference-array *slice*) (make-array '(3 3) :initial-element -1))
(slice-aref *slice* 0 0)
=> -1

I don't think it is possible to do exactly what you want to do. In memory, multidimensional arrays are implemented as a single flat array with some metadata which is used to convert from the multidimensional interface to the flat one. In your case *my-array* would look like this:
#(1 2 3 4 5 6 7 8 9)
If you had the subarray you desired as a reference to the original array, it would look like this:
#(5 6 _ 8 9)
Which is impossible since you are trying to skip the 7 of the original array. If all of the desired elements were part of a contiguous sub-sequence, you would be able to use the :displaced-to argument of make-array in order to copy the sub-sequence by reference, but unfortunately, that is not the case.

Related

Defining a macro for iterate

I wanted to define a new clause for the iterate macro. Something similar to Python's range where you have a start, stop, step. Here's a first try:
(defmacro-clause (for var start start stop stop step step)
(if (minusp step)
`(for ,var from ,start downto ,stop by (- ,step))
`(for ,var from ,start to ,stop by ,step)))
It deals with increasing and decreasing ranges using the to and downto keywords of iterate. (Note that, unlike Python, these include the stop value.)
This works as desired for
(iter (for x start 5 stop 3 step -1)
(collect x))
;; => (5 4 3)
(iter (for x start 2 stop 5 step 1)
(collect x))
;; => (3,4,5)
However it fails for anything like
(let ((a 9)
(b 3)
(c -1))
(iter (for x start a stop b step c)
(collect x)))
Is it a quirk of iterate that it requires explicit numbers in these places? It has no problem with things like
(iter (for x below (+ 3 3) by (+ 1 1))
(collect x))
Concretely my question is, how can I define a new iterate clause that accepts variables which are bound to numbers in these places?
The problem is that you are trying to decide things at macro-expansion time which can't be known then, such as the sign of a variable. In particular you can't write a macro which expands into (part of) another macro depending on anything which is only known at run time, or you can, but that necessarily means you have to call the moral equivalent of eval at run-time, and ... don't do that.
Instead you have to make the decision about which way to count at run-time. This means you can't use any of the (for var from ...) or related clauses because there don't seem to be any which are agnostic about direction (why (for i from 1 to -5 by -1) doesn't work is beyond me but ... well).
So whatever clause you end up with needs to expand into a (for var next ...) clause, I think.
Here is an attempt at such. Disclaimer: not tested very much, I don't use iterate, may explode on contact, poisonous to fish.
(defmacro-driver (for v in-range a to b &optional by s)
(let ((firstp (make-symbol "FIRSTP"))
(value (make-symbol "VALUE"))
(limit (make-symbol "LIMIT"))
(step (make-symbol "STEP")))
`(progn
(with ,firstp = t)
(with ,value = (let ((v ,a))
(unless (numberp v)
(warn "doomed"))
(when (null v)
(warn "extremely doomed"))
v))
(with ,limit = (let ((v ,b))
(unless (numberp v)
(warn "also doomed"))
v))
(with ,step = (let ((v (or ,s (signum (- ,limit ,value)))))
(when (not (numberp v))
(warn "doomed again"))
(when (zerop v)
(warn "zero step"))
(when (not (= (signum v) (signum (- ,limit ,value))))
(warn "likely doomed"))
v))
(,(if generate 'generate 'for)
,v
next (if ,firstp
(progn
(setf ,firstp nil)
,value)
(progn
(incf ,value ,step)
(when (if (> ,step 0)
(>= ,value ,limit)
(<= ,value ,limit))
(terminate))
,value))))))
And now
> (iter (for i in-range 1 to 5 by 2)
(print i))
1
3
nil
> (iter (for i in-range 1 to -1)
(print i))
1
0
nil
> (iter (for i in-range 1 to 5 by -2)
(when (< i -20)
(terminate)))
Warning: likely doomed
nil
Obviously some of the checks could be better.

Using loop inside defmacro

I'm learning (common) Lisp, and as exercise, I want to implement 'xond', a cond macro, that transform this silly example:
(xond (= n 1) (setq x 2) (= n 2) (setq x 1))
into a if-else chain:
(if (= n 1) (setq x 2) (if (= n 2) (setq x 1)))
Currently, I have this macro:
(defmacro xond (&rest x) (if x (list 'progn (list 'if (pop x) (pop x)))))
that just expand the first two items in x:
(macroexpand '(xond (= x 1) (setq y 2)))
produce
(PROGN (IF (= X 1) (SETQ Y 2))) ;
Now I want to process all items in x, so I add a loop to produce a if-serie (a step toward if-else-version):
(defmacro xond (&rest x)
(loop (if x
(list 'progn (list 'if (pop x) (pop x)))
(return t))))
but then macro seems to stop working:
(macroexpand '(xond (= x 1) (setq y 2)))
T ;
What I'm missing here?
Edition
verdammelt's answer put me in the right track, and coredump's made me change my approach to an iterative one.
Now I'll implement (xond test1 exp1 test2 exp2) as:
(block nil
test1 (return exp1)
test2 (return exp2)
)
which can be done by iteration.
I'm writing this for my minimal Lisp interpreter; I have only implemented the most basic functions.
This is what I wrote. I'm using la to accumulate the parts of the output.
(defmacro xond (&rest x)
(let ((la '()))
(loop
(if x (push (list 'if (pop x) (list 'return (pop x))) la)
(progn (push 'nil la)
(push 'block la)
(return la)
)))))
with
(macroexpand '(xond (= x 1) (setq y 2) (= X 2) (setq y 1)))
result:
(BLOCK NIL
(IF (= X 2) (RETURN (SETQ Y 1)))
(IF (= X 1) (RETURN (SETQ Y 2)))
) ;
Second edition
Add a label to block and change return to return-from, to avoid conflict with other return inside arguments. Also changed push for append to generate code in the same orden as the parameters.
(defmacro xond (&rest x)
(let ((label (gensym)) (la '()) (condition nil) (expresion nil))
(setq la (append la (list 'block label)))
(loop
(if x
(setq la (append la (list
(list 'if (pop x) (list 'return-from label (pop x))))))
(return la)))))
So
(macroexpand '(xond (= x 1) (setq y 2) (= X 2) (setq y 1)))
now gives
(BLOCK #:G3187 (IF (= X 1) (RETURN-FROM #:G3187 (SETQ Y 2))) (IF (= X 2) (RETURN-FROM #:G3187 (SETQ Y 1))))
Some remarks
You do not need a progn when you only expand into a single if
The use of pop might be confusing for the reader (and the programmer too) since it mutates a place, maybe you want to start with a less imperative approach
Also, in that case I don't think a loop approach is helpful, because you need to nest the expressions that come after in the body inside a previously built form, and even though it can be done, it is a bit more complex to do that simply a recursive function or a "recursive" macro.
Here I explain both approach, starting with "recursive" macro (the quote here is because the macro does not call itself, but expands as call to itself).
Macro expansion fixpoint
If I had to implement xond, I would write a macro that expands into other calls to xond, until macroexpansion reaches a base case where there are no more xond:
(defmacro xond (&rest body)
(if (rest body)
(destructuring-bind (test if-action . rest) body
`(if ,test ,if-action (xond ,#rest)))
(first body)))
For example, this expression:
(xond (= n 1) (setq x 2) (= n 2) (setq x 1))
First macroexpands into:
(if (= n 1)
(setq x 2)
(xond (= n 2) (setq x 1)))
And eventually reaches a fixpoint with:
(if (= n 1)
(setq x 2)
(if (= n 2)
(setq x 1)
nil))
Be careful, you cannot directly use xond inside the definition of xond, what happens is that the macro expands as a call to xond, which Lisp then expands again. If you are not careful, you may end up with an infinite macroexpansion, that's why you need a base case where the macro does not expand into xond.
Macro calling a recursive function
Alternatively, you can call a recursive function inside your macro, and expand all the inner forms at once.
With LABELS, you bind xond-expand to a recursive function. Here this is an actual recursive approach:
(labels ((xond-expand (body)
(if body
(list 'if
(pop body)
(pop body)
(xond-expand body))
nil)))
(xond-expand '((= n 1) (setq x 2) (= n 2) (setq x 1))))
; => (IF (= N 1)
; (SETQ X 2)
; (IF (= N 2)
; (SETQ X 1)
; NIL))
Your xond macro ends with (return t) so it evaluates to t rather than your accumulated if expressions.
You could use loop's collect clause to accumulate the code you wish to return. For example: (loop for x in '(1 2 3) collect (* 2 x)) would evaluate to (2 4 6).
How about
(ql:quickload :alexandria)
(defun as-last (l1 l2)
`(,#l1 ,l2))
(defmacro xond (&rest args)
(reduce #'as-last
(loop for (condition . branch) in (alexandria:plist-alist args)
collect `(if ,condition ,branch))
:from-end t))
(macroexpand-1 '(xond c1 b1 c2 b2 c3 b3))
;; (IF C1 B1 (IF C2 B2 (IF C3 B3))) ;
;; T
alexandria's plist-alist was used to pair the arguments,
the intrinsic destructuring in loop used to extract conditions and branches.
The helper function as-last stacks lists together in the kind of
(a b c) (d e f) => (a b c (d e f)).
(reduce ... :from-end t) right-folds the sequence of the collected (if condition branch) clauses stacking them into each other using #'as-last.
Without any dependencies
('though, does alexandria even count as a dependency? ;) )
(defun pairs (l &key (acc '()) (fill-with-nil-p nil))
(cond ((null l) (nreverse acc))
((null (cdr l)) (pairs (cdr l)
:acc (cons (if fill-with-nil-p
(list (car l) nil)
l)
acc)
:fill-with-nil-p fill-with-nil-p))
(t (pairs (cdr (cdr l))
:acc (cons (list (car l) (cadr l)) acc)
:fill-with-nil-p fill-with-nil-p))))
(defun as-last (l1 l2)
`(,#l1 ,l2))
(defmacro xond (&rest args)
(reduce #'as-last
(loop for (condition branch) in (pairs args)
collect `(if ,condition ,branch))
:from-end t))
(macroexpand-1 '(xond c1 b1 c2 b2 c3 b3))
;; (IF C1 B1 (IF C2 B2 (IF C3 B3))) ;
;; T
The helper function pairs makes out of (a b c d e f) => ((a b) (c d) (e f)).
(:fill-with-nil-p determines in case of odd number of list elements, whether the last element would be listed (last-el) or (last-el nil) - in the latter case filled with nil).

cannot modify specific element in array of objects

(defclass schedule ()
((day :accessor schedule-day :initarg :day)))
(setf october
(make-array '(31)
:element-type 'schedule
:initial-element
(make-instance 'schedule :day 0)))
(setq searcher (read))
(setf (schedule-day (aref october (- searcher 1))) searcher)
(dotimes (i 31)
(format t "-month:10 day:~S~%" (schedule-day (aref october i))))
This is part of my october scheduling program.
This part should get the day I typed and change that day's day element, and print every october schedule.
however,
(setq searcher (read))
(setf (schedule-day (aref october (- searcher 1))) searcher)
I have trouble in this. if I type 17, then only 17th day of october should affected and printed like this,
-month:10 day:0
-month:10 day:0
...
-month:10 day:17
-month:10 day:0
...
but what I really got is
-month:10 day:17
-month:10 day:17
-month:10 day:17
...
why I can't change only one element? I managed to do this in c++ like,
october[searcher - 1].setDay(searcher);
It seems setf affects the class itself, not class object. can you help me? Thanks.
Your problem is that your array contains 31 pointers, each pointing to the same object.
Thus (setf (schedule-day (aref october a)) b) modifies that unique object.
You can achieve what you want by either encapsulating october so that the ith element is created only as necessary, or by initializing the array with something like
(apply #'vector (loop repeat 31 collect (make-instance 'schedule)))
or
(make-array 31 :initial-contents (loop repeat 31 collect (make-instance 'schedule)))
The root cause of your confusion is that you specified the array element-type and assumed that you created a "specialized" array.
Thus, despite the fact that you actually call (make-instance 'schedule) just once, you will have 31 objects in contiguous memory.
However, your implementation is not obligated to honor the
element-type specification in that way (it will create an array which
can hold the objects of the type you specified, but not necessarily
only those objects),
and what you actually got is a simple-vector.
PS. You should
use defvar or defparameter
instead of setq
or setf to define global
variables (like october), and you should name them
using
"earmuffs",
like *october*.
You can easily see that the array elements are pointing to just one CLOS object.
CL-USER 28 > (defclass foo () ())
#<STANDARD-CLASS FOO 4020002613>
CL-USER 29 > (make-array 3 :initial-element (make-instance 'foo))
#(#<FOO 402000AE9B> #<FOO 402000AE9B> #<FOO 402000AE9B>)
All objects have the same ID 402000AE9B.
In the next example the objects are different:
CL-USER 30 > (make-array 3 :initial-contents (list (make-instance 'foo)
(make-instance 'foo)
(make-instance 'foo)))
#(#<FOO 4020000B43> #<FOO 4020000B63> #<FOO 4020000B83>)
All have different IDs.

Common Lisp vector printing: Vector axis is not zero: 1

This is the first time I have ever seen this compiler error does anyone know what it is? and why my function can't print my nested vectors.
(defvar *col-lookup* #.(let ((ht (make-hash-table)))
(loop for (key . value) in
'(
(A . 0) (B . 1) (C . 2)
(D . 3) (E . 4) (F . 5) (G . 6))
do (setf (gethash key ht) value))
ht))
;; vector of vectors
(defparameter *game-board*
(make-array 7 :initial-element (make-array 0 :initial-element 0)))
;;make move lookup character in table then push X onto vector of value of key
(defun move (c)
(let ((place (gethash c *col-lookup*)))
(cond ((oddp *turn-count*)
(push "X" (aref *game-board* place))
(incf *turn-count*))
((push "O" (aref *game-board* place))
(incf *turn-count*)))))
You are creating a very peculiar vector of vectors with the code:
(make-array 7 :initial-element (make-array 0 :initial-element 0)))
This code will create a vector of 7 elements, each of them a vector with 0 elements (i.e. an empty vector) (and note that giving the initial-element to 0 is useless because there are no elements to assign). If you print it you should see:
#(#() #() #() #() #() #() #())
which means exactly this, a vector with seven empty vectors. So if you try to access the internal vector with something like (aref (aref *game-board*) 1) 2) you get an error.
Finally note that in the code of the function move you use:
(push "X" (aref *game-board* place))
whose effect is not of modifying the internal vector at place place, but of replace the old value of (aref *game-board* place) with a cons of the string "X" and the old value of (aref *game-board* place), the empty vector.
I was able to print my vector of vectors by simply looping over it once. I still do not know what that error was but I haven't ran into it since.
(defun print-game ()
(loop for i from 0 to 6 do
(print (aref *game-board* i))))

Variadic Functions in Scheme (using nested maps)

I have to define a variadic function in Scheme that takes the following form: (define (n-loop procedure [a list of pairs (x,y)]) where the list of pairs can be any length.
Each pair specifies a lower (inclusive) and upper bound (exclusive). That is, the following function call: (n-loop (lambda (x y) (inspect (list x y))) (0 2) (0 3)) produces:
(list x y) is (0 0)
(list x y) is (0 1)
(list x y) is (0 2)
(list x y) is (1 0)
(list x y) is (1 1)
(list x y) is (1 2)
Now, I had posted on this topic one previous time and was helped wonderfully. However, I have been given new guidelines to adhere to. The solution is to be found using nested maps only.
The way I've been going about this is as follows: find all of the values specified by the first set of bounds (in the example, (0 1 2)). This can be done by a function called (enumerate lowBound highBound). Then, I need to take each of those numbers, and cons each number in the next set of bounds (0 1 2 3), resulting in ((0 0) (0 1) (0 2) (0 3) (1 0)...).
What I've written to this point is the following:
(define (n-loop op . pairs)
(apply op (generate pairs))
)
(define (generate pairs)
(map (lambda (x) (cons x (generate (cdr pairs))))
(map (lambda (x) (enumerate (car x) (cadr x))) pairs))
)
But for the given numbers, this outputs (0 1 0 1 2 0 1 2 0 1 2) when I need ((0 0) (0 1) (0 2) (0 3) (1 0)...). This is a nasty problem. Does anyone have any insight?
This problem is more complex than you seem to realize. In particular, generating the cartesian product of an arbitrary list of ranges needs far more work - have you tried your procedure with more than two ranges? It piqued my interest, this time I'll give my shot to a complete solution, using only procedures defined for the solution, simple operations over lists (cons, car, cdr, append), lambda, apply and map.
First, the helper procedures from simplest to hardest. We need a way to generate a range of numbers. If available, use build-list or for-list, but if you need to implement it from scratch:
(define (enumerate low high)
(if (>= low high)
'()
(cons low
(enumerate (add1 low) high))))
Now we need a mechanism for folding (reducing, accumulating) the values in a list. If available use foldr, otherwise implement it like this:
(define (reduce proc lst init)
(if (null? lst)
init
(proc (car lst)
(reduce proc (cdr lst) init))))
To avoid unnecessary nesting in lists, use a flatmap - a procedure that both maps and flattens a list of values:
(define (flatmap proc lst)
(reduce (lambda (e acc)
(append (proc e) acc))
lst '()))
This is the core of the solution - a procedure that generates the cartesian product of an arbitrarily long list of lists of values denoting ranges:
(define (product . args)
(reduce (lambda (pool result)
(flatmap (lambda (x)
(map (lambda (y)
(cons x y))
result))
pool))
args
'(())))
Finally, the procedure in the question. It uses the helper procedures defined above, noticing that the op received can have an arbitrary number of parameters (depending on the number of ranges specified), so we need to use apply on each generated tuple of values:
(define (n-loop op . pairs)
(map (lambda (tuple) (apply op tuple))
(apply product
(map (lambda (pair)
(enumerate (car pair) (cadr pair)))
pairs))))
Test it like this:
(n-loop (lambda (x y z) (list x y z))
'(0 2) '(0 3) '(4 6))
> '((0 0 4) (0 0 5) (0 1 4) (0 1 5) (0 2 4) (0 2 5)
(1 0 4) (1 0 5) (1 1 4) (1 1 5) (1 2 4) (1 2 5))

Resources