(git:f56c6e3)
Loading...
Searching...
No Matches
cp_linked_list_pw.F
Go to the documentation of this file.
1!--------------------------------------------------------------------------------------------------!
2! CP2K: A general program to perform molecular dynamics simulations !
3! Copyright 2000-2025 CP2K developers group <https://cp2k.org> !
4! !
5! SPDX-License-Identifier: GPL-2.0-or-later !
6!--------------------------------------------------------------------------------------------------!
7
8
10 USE kinds, ONLY: dp
13#include "../base/base_uses.f90"
14
15
16! **************************************************************************************************
17!> \brief describes a generic linked list template.
18!> Linked list are supposed to always use pointers to the nodes for
19!> basically everything: a pointer to the node is a list, an element of
20!> the list, an iterator between the elment of the list.
21!> An empty list is represented by an unassociated pointer.
22!> \par History
23!> 1.2002 created
24!> 4.2002 changed most of the methods, by making access to the list
25!> always through pointers (identifying pointer, list and iterators)
26!> 6.2004 removed %initialized from list elements
27!> \author Fawzi Mohamed
28! **************************************************************************************************
29 IMPLICIT NONE
30 PRIVATE
31
32 LOGICAL, PRIVATE, PARAMETER :: debug_this_module = .true.
33
34
35!API type
41
42!API common methods
43 PUBLIC :: cp_create, cp_dealloc, cp_next
44!API special get
46!API special set
47 PUBLIC :: cp_set_element_at
48!API structure manipulation
50
51 !API underlying routines
52
98
99! creation of an object (from a pointer)
100 INTERFACE cp_create
101 MODULE PROCEDURE cp_sll_3d_r_create
102 MODULE PROCEDURE cp_sll_3d_c_create
103 MODULE PROCEDURE cp_sll_1d_r_create
104 MODULE PROCEDURE cp_sll_1d_c_create
105 MODULE PROCEDURE cp_sll_rs_create
106 END INTERFACE
107! destruction of an object (from a pointer)
108 INTERFACE cp_dealloc
109 MODULE PROCEDURE cp_sll_3d_r_dealloc
110 MODULE PROCEDURE cp_sll_3d_c_dealloc
111 MODULE PROCEDURE cp_sll_1d_r_dealloc
112 MODULE PROCEDURE cp_sll_1d_c_dealloc
113 MODULE PROCEDURE cp_sll_rs_dealloc
114 END INTERFACE
115! iterates to the next element
116 INTERFACE cp_next
117 MODULE PROCEDURE cp_sll_3d_r_next
118 MODULE PROCEDURE cp_sll_3d_c_next
119 MODULE PROCEDURE cp_sll_1d_r_next
120 MODULE PROCEDURE cp_sll_1d_c_next
121 MODULE PROCEDURE cp_sll_rs_next
122 END INTERFACE
123! returns the first element
125 MODULE PROCEDURE cp_sll_3d_r_get_first_el
126 MODULE PROCEDURE cp_sll_3d_c_get_first_el
127 MODULE PROCEDURE cp_sll_1d_r_get_first_el
128 MODULE PROCEDURE cp_sll_1d_c_get_first_el
129 MODULE PROCEDURE cp_sll_rs_get_first_el
130 END INTERFACE
131! returns the rest of the list
132 INTERFACE cp_get_rest
133 MODULE PROCEDURE cp_sll_3d_r_get_rest
134 MODULE PROCEDURE cp_sll_3d_c_get_rest
135 MODULE PROCEDURE cp_sll_1d_r_get_rest
136 MODULE PROCEDURE cp_sll_1d_c_get_rest
137 MODULE PROCEDURE cp_sll_rs_get_rest
138 END INTERFACE
139! returns the length of the list
141 MODULE PROCEDURE cp_sll_3d_r_get_length
142 MODULE PROCEDURE cp_sll_3d_c_get_length
143 MODULE PROCEDURE cp_sll_1d_r_get_length
144 MODULE PROCEDURE cp_sll_1d_c_get_length
145 MODULE PROCEDURE cp_sll_rs_get_length
146 END INTERFACE
147! returns the element at the given position
149 MODULE PROCEDURE cp_sll_3d_r_get_el_at
150 MODULE PROCEDURE cp_sll_3d_c_get_el_at
151 MODULE PROCEDURE cp_sll_1d_r_get_el_at
152 MODULE PROCEDURE cp_sll_1d_c_get_el_at
153 MODULE PROCEDURE cp_sll_rs_get_el_at
154 END INTERFACE
155! sets the element at the given position
157 MODULE PROCEDURE cp_sll_3d_r_set_el_at
158 MODULE PROCEDURE cp_sll_3d_c_set_el_at
159 MODULE PROCEDURE cp_sll_1d_r_set_el_at
160 MODULE PROCEDURE cp_sll_1d_c_set_el_at
161 MODULE PROCEDURE cp_sll_rs_set_el_at
162 END INTERFACE
163! inserts one element call cp_insert(list,element,...)
164 INTERFACE cp_insert
165 MODULE PROCEDURE cp_sll_3d_r_insert_el
166 MODULE PROCEDURE cp_sll_3d_c_insert_el
167 MODULE PROCEDURE cp_sll_1d_r_insert_el
168 MODULE PROCEDURE cp_sll_1d_c_insert_el
169 MODULE PROCEDURE cp_sll_rs_insert_el
170 END INTERFACE
171 INTERFACE cp_insert_at
172 MODULE PROCEDURE cp_sll_3d_r_insert_el_at
173 MODULE PROCEDURE cp_sll_3d_c_insert_el_at
174 MODULE PROCEDURE cp_sll_1d_r_insert_el_at
175 MODULE PROCEDURE cp_sll_1d_c_insert_el_at
176 MODULE PROCEDURE cp_sll_rs_insert_el_at
177 END INTERFACE
178! removes an element
179 INTERFACE cp_remove_el
180 MODULE PROCEDURE cp_sll_3d_r_rm_first_el, &
182 MODULE PROCEDURE cp_sll_3d_c_rm_first_el, &
184 MODULE PROCEDURE cp_sll_1d_r_rm_first_el, &
186 MODULE PROCEDURE cp_sll_1d_c_rm_first_el, &
188 MODULE PROCEDURE cp_sll_rs_rm_first_el, &
190 END INTERFACE
191! removes the first el
193 MODULE PROCEDURE cp_sll_3d_r_rm_first_el
194 MODULE PROCEDURE cp_sll_3d_c_rm_first_el
195 MODULE PROCEDURE cp_sll_1d_r_rm_first_el
196 MODULE PROCEDURE cp_sll_1d_c_rm_first_el
197 MODULE PROCEDURE cp_sll_rs_rm_first_el
198 END INTERFACE
199! remove all the elements
201 MODULE PROCEDURE cp_sll_3d_r_rm_all_el
202 MODULE PROCEDURE cp_sll_3d_c_rm_all_el
203 MODULE PROCEDURE cp_sll_1d_r_rm_all_el
204 MODULE PROCEDURE cp_sll_1d_c_rm_all_el
205 MODULE PROCEDURE cp_sll_rs_rm_all_el
206 END INTERFACE
207! transorms the list in array
208 INTERFACE cp_to_array
209 module procedure cp_sll_3d_r_to_array
210 module procedure cp_sll_3d_c_to_array
211 module procedure cp_sll_1d_r_to_array
212 module procedure cp_sll_1d_c_to_array
213 module procedure cp_sll_rs_to_array
214 END INTERFACE
215
216! **************************************************************************************************
217!> \brief represent a single linked list that stores pointers to the elements
218!> \param first_el the element that is stored in this node.
219!> \param rest the rest of the list
220!>
221!> \param empty true if the list pointer is not associated, if it points to
222!> to a not it is always false (as there is at least the
223!> first_el in the list)
224!> \param length the number of elements in the list
225!> \note
226!> List are alway accessed through pointers, so every node of the
227!> linked list can be seen as a list, its first element
228!> a pointer to the position before itself, in a very natural way:
229!> all the insertions take place before the actual element, and
230!> you still can insert an element at the end.
231!> This way I could identify nodes, lists and pointers between the
232!> elements of the list.
233!> Indexing is 1 based.
234!> \par History
235!> none
236!> \author Fawzi Mohamed
237! **************************************************************************************************
239 REAL(kind=dp),dimension(:,:,:),pointer,contiguous :: first_el => null()
240 TYPE(cp_sll_3d_r_type), POINTER :: rest => null()
241 END TYPE cp_sll_3d_r_type
242! **************************************************************************************************
243!> \brief represent a single linked list that stores pointers to the elements
244!> \param first_el the element that is stored in this node.
245!> \param rest the rest of the list
246!>
247!> \param empty true if the list pointer is not associated, if it points to
248!> to a not it is always false (as there is at least the
249!> first_el in the list)
250!> \param length the number of elements in the list
251!> \note
252!> List are alway accessed through pointers, so every node of the
253!> linked list can be seen as a list, its first element
254!> a pointer to the position before itself, in a very natural way:
255!> all the insertions take place before the actual element, and
256!> you still can insert an element at the end.
257!> This way I could identify nodes, lists and pointers between the
258!> elements of the list.
259!> Indexing is 1 based.
260!> \par History
261!> none
262!> \author Fawzi Mohamed
263! **************************************************************************************************
265 COMPLEX(kind=dp),dimension(:,:,:),pointer,contiguous :: first_el => null()
266 TYPE(cp_sll_3d_c_type), POINTER :: rest => null()
267 END TYPE cp_sll_3d_c_type
268! **************************************************************************************************
269!> \brief represent a single linked list that stores pointers to the elements
270!> \param first_el the element that is stored in this node.
271!> \param rest the rest of the list
272!>
273!> \param empty true if the list pointer is not associated, if it points to
274!> to a not it is always false (as there is at least the
275!> first_el in the list)
276!> \param length the number of elements in the list
277!> \note
278!> List are alway accessed through pointers, so every node of the
279!> linked list can be seen as a list, its first element
280!> a pointer to the position before itself, in a very natural way:
281!> all the insertions take place before the actual element, and
282!> you still can insert an element at the end.
283!> This way I could identify nodes, lists and pointers between the
284!> elements of the list.
285!> Indexing is 1 based.
286!> \par History
287!> none
288!> \author Fawzi Mohamed
289! **************************************************************************************************
291 REAL(kind=dp),dimension(:),pointer,contiguous :: first_el => null()
292 TYPE(cp_sll_1d_r_type), POINTER :: rest => null()
293 END TYPE cp_sll_1d_r_type
294! **************************************************************************************************
295!> \brief represent a single linked list that stores pointers to the elements
296!> \param first_el the element that is stored in this node.
297!> \param rest the rest of the list
298!>
299!> \param empty true if the list pointer is not associated, if it points to
300!> to a not it is always false (as there is at least the
301!> first_el in the list)
302!> \param length the number of elements in the list
303!> \note
304!> List are alway accessed through pointers, so every node of the
305!> linked list can be seen as a list, its first element
306!> a pointer to the position before itself, in a very natural way:
307!> all the insertions take place before the actual element, and
308!> you still can insert an element at the end.
309!> This way I could identify nodes, lists and pointers between the
310!> elements of the list.
311!> Indexing is 1 based.
312!> \par History
313!> none
314!> \author Fawzi Mohamed
315! **************************************************************************************************
317 COMPLEX(kind=dp),dimension(:),pointer,contiguous :: first_el => null()
318 TYPE(cp_sll_1d_c_type), POINTER :: rest => null()
319 END TYPE cp_sll_1d_c_type
320! **************************************************************************************************
321!> \brief represent a single linked list that stores pointers to the elements
322!> \param first_el the element that is stored in this node.
323!> \param rest the rest of the list
324!>
325!> \param empty true if the list pointer is not associated, if it points to
326!> to a not it is always false (as there is at least the
327!> first_el in the list)
328!> \param length the number of elements in the list
329!> \note
330!> List are alway accessed through pointers, so every node of the
331!> linked list can be seen as a list, its first element
332!> a pointer to the position before itself, in a very natural way:
333!> all the insertions take place before the actual element, and
334!> you still can insert an element at the end.
335!> This way I could identify nodes, lists and pointers between the
336!> elements of the list.
337!> Indexing is 1 based.
338!> \par History
339!> none
340!> \author Fawzi Mohamed
341! **************************************************************************************************
343 type(realspace_grid_type),pointer :: first_el => null()
344 TYPE(cp_sll_rs_type), POINTER :: rest => null()
345 END TYPE cp_sll_rs_type
346
347! **************************************************************************************************
348!> \brief pointer to a linked list (to make arrays of pointers)
349!> \param list the pointer to the list
350!> \par History
351!> none
352!> \author Fawzi Mohamed
353! **************************************************************************************************
355 TYPE(cp_sll_3d_r_type), POINTER :: list => null()
356 END TYPE cp_sll_3d_r_p_type
357! **************************************************************************************************
358!> \brief pointer to a linked list (to make arrays of pointers)
359!> \param list the pointer to the list
360!> \par History
361!> none
362!> \author Fawzi Mohamed
363! **************************************************************************************************
365 TYPE(cp_sll_3d_c_type), POINTER :: list => null()
366 END TYPE cp_sll_3d_c_p_type
367! **************************************************************************************************
368!> \brief pointer to a linked list (to make arrays of pointers)
369!> \param list the pointer to the list
370!> \par History
371!> none
372!> \author Fawzi Mohamed
373! **************************************************************************************************
375 TYPE(cp_sll_1d_r_type), POINTER :: list => null()
376 END TYPE cp_sll_1d_r_p_type
377! **************************************************************************************************
378!> \brief pointer to a linked list (to make arrays of pointers)
379!> \param list the pointer to the list
380!> \par History
381!> none
382!> \author Fawzi Mohamed
383! **************************************************************************************************
385 TYPE(cp_sll_1d_c_type), POINTER :: list => null()
386 END TYPE cp_sll_1d_c_p_type
387! **************************************************************************************************
388!> \brief pointer to a linked list (to make arrays of pointers)
389!> \param list the pointer to the list
390!> \par History
391!> none
392!> \author Fawzi Mohamed
393! **************************************************************************************************
395 TYPE(cp_sll_rs_type), POINTER :: list => null()
396 END TYPE cp_sll_rs_p_type
397
398 CONTAINS
399
400 ! this comment prevents trailing whitespace
401
402! =========== creation / destruction ========
403
404! **************************************************************************************************
405!> \brief allocates and initializes a single linked list
406!> \param sll the single linked list to initialize
407!> \param first_el the first element of this list
408!> \param rest the following elements (if not given: empty)
409!> \par History
410!> none
411!> \author Fawzi Mohamed
412! **************************************************************************************************
413 SUBROUTINE cp_sll_3d_r_create(sll, first_el, rest)
414 TYPE(cp_sll_3d_r_type), POINTER :: sll
415 REAL(kind=dp),dimension(:,:,:),pointer,contiguous, OPTIONAL :: first_el
416 TYPE(cp_sll_3d_r_type), POINTER, OPTIONAL :: rest
417
418 IF (.NOT. PRESENT(first_el)) THEN
419 NULLIFY (sll)
420 IF (PRESENT(rest)) sll => rest
421 ELSE
422 ALLOCATE (sll)
423 sll%first_el =>first_el
424 NULLIFY (sll%rest)
425 IF (PRESENT(rest)) sll%rest => rest
426 END IF
427 END SUBROUTINE cp_sll_3d_r_create
428! **************************************************************************************************
429!> \brief allocates and initializes a single linked list
430!> \param sll the single linked list to initialize
431!> \param first_el the first element of this list
432!> \param rest the following elements (if not given: empty)
433!> \par History
434!> none
435!> \author Fawzi Mohamed
436! **************************************************************************************************
437 SUBROUTINE cp_sll_3d_c_create(sll, first_el, rest)
438 TYPE(cp_sll_3d_c_type), POINTER :: sll
439 COMPLEX(kind=dp),dimension(:,:,:),pointer,contiguous, OPTIONAL :: first_el
440 TYPE(cp_sll_3d_c_type), POINTER, OPTIONAL :: rest
441
442 IF (.NOT. PRESENT(first_el)) THEN
443 NULLIFY (sll)
444 IF (PRESENT(rest)) sll => rest
445 ELSE
446 ALLOCATE (sll)
447 sll%first_el =>first_el
448 NULLIFY (sll%rest)
449 IF (PRESENT(rest)) sll%rest => rest
450 END IF
451 END SUBROUTINE cp_sll_3d_c_create
452! **************************************************************************************************
453!> \brief allocates and initializes a single linked list
454!> \param sll the single linked list to initialize
455!> \param first_el the first element of this list
456!> \param rest the following elements (if not given: empty)
457!> \par History
458!> none
459!> \author Fawzi Mohamed
460! **************************************************************************************************
461 SUBROUTINE cp_sll_1d_r_create(sll, first_el, rest)
462 TYPE(cp_sll_1d_r_type), POINTER :: sll
463 REAL(kind=dp),dimension(:),pointer,contiguous, OPTIONAL :: first_el
464 TYPE(cp_sll_1d_r_type), POINTER, OPTIONAL :: rest
465
466 IF (.NOT. PRESENT(first_el)) THEN
467 NULLIFY (sll)
468 IF (PRESENT(rest)) sll => rest
469 ELSE
470 ALLOCATE (sll)
471 sll%first_el =>first_el
472 NULLIFY (sll%rest)
473 IF (PRESENT(rest)) sll%rest => rest
474 END IF
475 END SUBROUTINE cp_sll_1d_r_create
476! **************************************************************************************************
477!> \brief allocates and initializes a single linked list
478!> \param sll the single linked list to initialize
479!> \param first_el the first element of this list
480!> \param rest the following elements (if not given: empty)
481!> \par History
482!> none
483!> \author Fawzi Mohamed
484! **************************************************************************************************
485 SUBROUTINE cp_sll_1d_c_create(sll, first_el, rest)
486 TYPE(cp_sll_1d_c_type), POINTER :: sll
487 COMPLEX(kind=dp),dimension(:),pointer,contiguous, OPTIONAL :: first_el
488 TYPE(cp_sll_1d_c_type), POINTER, OPTIONAL :: rest
489
490 IF (.NOT. PRESENT(first_el)) THEN
491 NULLIFY (sll)
492 IF (PRESENT(rest)) sll => rest
493 ELSE
494 ALLOCATE (sll)
495 sll%first_el =>first_el
496 NULLIFY (sll%rest)
497 IF (PRESENT(rest)) sll%rest => rest
498 END IF
499 END SUBROUTINE cp_sll_1d_c_create
500! **************************************************************************************************
501!> \brief allocates and initializes a single linked list
502!> \param sll the single linked list to initialize
503!> \param first_el the first element of this list
504!> \param rest the following elements (if not given: empty)
505!> \par History
506!> none
507!> \author Fawzi Mohamed
508! **************************************************************************************************
509 SUBROUTINE cp_sll_rs_create(sll, first_el, rest)
510 TYPE(cp_sll_rs_type), POINTER :: sll
511 type(realspace_grid_type),pointer, OPTIONAL :: first_el
512 TYPE(cp_sll_rs_type), POINTER, OPTIONAL :: rest
513
514 IF (.NOT. PRESENT(first_el)) THEN
515 NULLIFY (sll)
516 IF (PRESENT(rest)) sll => rest
517 ELSE
518 ALLOCATE (sll)
519 sll%first_el =>first_el
520 NULLIFY (sll%rest)
521 IF (PRESENT(rest)) sll%rest => rest
522 END IF
523 END SUBROUTINE cp_sll_rs_create
524
525! **************************************************************************************************
526!> \brief deallocates the singly linked list starting at sll.
527!> Does not work if loops are present!
528!> \param sll the list to be deallocated
529!> \par History
530!> none
531!> \author Fawzi Mohamed
532!> \note
533!> does not deallocate the elements that are stored in the list
534!> check more?
535! **************************************************************************************************
536 SUBROUTINE cp_sll_3d_r_dealloc(sll)
537 TYPE(cp_sll_3d_r_type), POINTER :: sll
538
539 CALL cp_sll_3d_r_rm_all_el(sll)
540 END SUBROUTINE cp_sll_3d_r_dealloc
541! **************************************************************************************************
542!> \brief deallocates the singly linked list starting at sll.
543!> Does not work if loops are present!
544!> \param sll the list to be deallocated
545!> \par History
546!> none
547!> \author Fawzi Mohamed
548!> \note
549!> does not deallocate the elements that are stored in the list
550!> check more?
551! **************************************************************************************************
552 SUBROUTINE cp_sll_3d_c_dealloc(sll)
553 TYPE(cp_sll_3d_c_type), POINTER :: sll
554
555 CALL cp_sll_3d_c_rm_all_el(sll)
556 END SUBROUTINE cp_sll_3d_c_dealloc
557! **************************************************************************************************
558!> \brief deallocates the singly linked list starting at sll.
559!> Does not work if loops are present!
560!> \param sll the list to be deallocated
561!> \par History
562!> none
563!> \author Fawzi Mohamed
564!> \note
565!> does not deallocate the elements that are stored in the list
566!> check more?
567! **************************************************************************************************
568 SUBROUTINE cp_sll_1d_r_dealloc(sll)
569 TYPE(cp_sll_1d_r_type), POINTER :: sll
570
571 CALL cp_sll_1d_r_rm_all_el(sll)
572 END SUBROUTINE cp_sll_1d_r_dealloc
573! **************************************************************************************************
574!> \brief deallocates the singly linked list starting at sll.
575!> Does not work if loops are present!
576!> \param sll the list to be deallocated
577!> \par History
578!> none
579!> \author Fawzi Mohamed
580!> \note
581!> does not deallocate the elements that are stored in the list
582!> check more?
583! **************************************************************************************************
584 SUBROUTINE cp_sll_1d_c_dealloc(sll)
585 TYPE(cp_sll_1d_c_type), POINTER :: sll
586
587 CALL cp_sll_1d_c_rm_all_el(sll)
588 END SUBROUTINE cp_sll_1d_c_dealloc
589! **************************************************************************************************
590!> \brief deallocates the singly linked list starting at sll.
591!> Does not work if loops are present!
592!> \param sll the list to be deallocated
593!> \par History
594!> none
595!> \author Fawzi Mohamed
596!> \note
597!> does not deallocate the elements that are stored in the list
598!> check more?
599! **************************************************************************************************
600 SUBROUTINE cp_sll_rs_dealloc(sll)
601 TYPE(cp_sll_rs_type), POINTER :: sll
602
603 CALL cp_sll_rs_rm_all_el(sll)
604 END SUBROUTINE cp_sll_rs_dealloc
605
606! * low-level *
607
608! **************************************************************************************************
609!> \brief deallocates a node of a singly linked list (low level)
610!> \param sll the node to be deallocated
611!> \par History
612!> none
613!> \author Fawzi Mohamed
614! **************************************************************************************************
615 SUBROUTINE cp_sll_3d_r_dealloc_node(sll)
616 TYPE(cp_sll_3d_r_type), POINTER :: sll
617
618 DEALLOCATE (sll)
619 END SUBROUTINE cp_sll_3d_r_dealloc_node
620! **************************************************************************************************
621!> \brief deallocates a node of a singly linked list (low level)
622!> \param sll the node to be deallocated
623!> \par History
624!> none
625!> \author Fawzi Mohamed
626! **************************************************************************************************
627 SUBROUTINE cp_sll_3d_c_dealloc_node(sll)
628 TYPE(cp_sll_3d_c_type), POINTER :: sll
629
630 DEALLOCATE (sll)
631 END SUBROUTINE cp_sll_3d_c_dealloc_node
632! **************************************************************************************************
633!> \brief deallocates a node of a singly linked list (low level)
634!> \param sll the node to be deallocated
635!> \par History
636!> none
637!> \author Fawzi Mohamed
638! **************************************************************************************************
639 SUBROUTINE cp_sll_1d_r_dealloc_node(sll)
640 TYPE(cp_sll_1d_r_type), POINTER :: sll
641
642 DEALLOCATE (sll)
643 END SUBROUTINE cp_sll_1d_r_dealloc_node
644! **************************************************************************************************
645!> \brief deallocates a node of a singly linked list (low level)
646!> \param sll the node to be deallocated
647!> \par History
648!> none
649!> \author Fawzi Mohamed
650! **************************************************************************************************
651 SUBROUTINE cp_sll_1d_c_dealloc_node(sll)
652 TYPE(cp_sll_1d_c_type), POINTER :: sll
653
654 DEALLOCATE (sll)
655 END SUBROUTINE cp_sll_1d_c_dealloc_node
656! **************************************************************************************************
657!> \brief deallocates a node of a singly linked list (low level)
658!> \param sll the node to be deallocated
659!> \par History
660!> none
661!> \author Fawzi Mohamed
662! **************************************************************************************************
663 SUBROUTINE cp_sll_rs_dealloc_node(sll)
664 TYPE(cp_sll_rs_type), POINTER :: sll
665
666 DEALLOCATE (sll)
667 END SUBROUTINE cp_sll_rs_dealloc_node
668
669! ============= get/set ============
670
671! **************************************************************************************************
672!> \brief returns the first element stored in the list
673!> \param sll the single linked list to get the element from
674!> \return ...
675!> \par History
676!> none
677!> \author Fawzi Mohamed
678! **************************************************************************************************
679 FUNCTION cp_sll_3d_r_get_first_el(sll) RESULT(res)
680 TYPE(cp_sll_3d_r_type), POINTER :: sll
681 REAL(kind=dp),dimension(:,:,:),pointer,contiguous :: res
682
683 res =>sll%first_el
684 END FUNCTION cp_sll_3d_r_get_first_el
685! **************************************************************************************************
686!> \brief returns the first element stored in the list
687!> \param sll the single linked list to get the element from
688!> \return ...
689!> \par History
690!> none
691!> \author Fawzi Mohamed
692! **************************************************************************************************
693 FUNCTION cp_sll_3d_c_get_first_el(sll) RESULT(res)
694 TYPE(cp_sll_3d_c_type), POINTER :: sll
695 COMPLEX(kind=dp),dimension(:,:,:),pointer,contiguous :: res
696
697 res =>sll%first_el
698 END FUNCTION cp_sll_3d_c_get_first_el
699! **************************************************************************************************
700!> \brief returns the first element stored in the list
701!> \param sll the single linked list to get the element from
702!> \return ...
703!> \par History
704!> none
705!> \author Fawzi Mohamed
706! **************************************************************************************************
707 FUNCTION cp_sll_1d_r_get_first_el(sll) RESULT(res)
708 TYPE(cp_sll_1d_r_type), POINTER :: sll
709 REAL(kind=dp),dimension(:),pointer,contiguous :: res
710
711 res =>sll%first_el
712 END FUNCTION cp_sll_1d_r_get_first_el
713! **************************************************************************************************
714!> \brief returns the first element stored in the list
715!> \param sll the single linked list to get the element from
716!> \return ...
717!> \par History
718!> none
719!> \author Fawzi Mohamed
720! **************************************************************************************************
721 FUNCTION cp_sll_1d_c_get_first_el(sll) RESULT(res)
722 TYPE(cp_sll_1d_c_type), POINTER :: sll
723 COMPLEX(kind=dp),dimension(:),pointer,contiguous :: res
724
725 res =>sll%first_el
726 END FUNCTION cp_sll_1d_c_get_first_el
727! **************************************************************************************************
728!> \brief returns the first element stored in the list
729!> \param sll the single linked list to get the element from
730!> \return ...
731!> \par History
732!> none
733!> \author Fawzi Mohamed
734! **************************************************************************************************
735 FUNCTION cp_sll_rs_get_first_el(sll) RESULT(res)
736 TYPE(cp_sll_rs_type), POINTER :: sll
737 type(realspace_grid_type),pointer :: res
738
739 res =>sll%first_el
740 END FUNCTION cp_sll_rs_get_first_el
741
742! **************************************************************************************************
743!> \brief returns the rest of the list
744!> \param sll the single linked list to get the rest from
745!> \param iter how many times the call to rest should be iterated,
746!> defaults to 1; -1 means till end of the list.
747!> \return ...
748!> \par History
749!> none
750!> \author Fawzi Mohamed
751!> \note
752!> split the case iter=1 to make it more optimized?
753! **************************************************************************************************
754 FUNCTION cp_sll_3d_r_get_rest(sll, iter) RESULT(res)
755 TYPE(cp_sll_3d_r_type), POINTER :: sll
756 INTEGER, OPTIONAL :: iter
757
758 TYPE(cp_sll_3d_r_type), POINTER :: res
759
760 INTEGER :: i
761
762 IF (.NOT. ASSOCIATED(sll)) THEN
763 NULLIFY (res)
764 ELSE
765 IF (PRESENT(iter)) THEN
766 res => sll
767 DO i = 1, iter
768 IF (ASSOCIATED(res%rest)) THEN
769 res => res%rest
770 ELSE
771 cpabort("tried to go past end")
772 END IF
773 END DO
774 IF (iter == -1) THEN
775 DO
776 IF (.NOT. ASSOCIATED(res%rest)) EXIT
777 res => res%rest
778 END DO
779 END IF
780 ELSE
781 res => sll%rest ! make the common case fast...
782 END IF
783 END IF
784 END FUNCTION cp_sll_3d_r_get_rest
785! **************************************************************************************************
786!> \brief returns the rest of the list
787!> \param sll the single linked list to get the rest from
788!> \param iter how many times the call to rest should be iterated,
789!> defaults to 1; -1 means till end of the list.
790!> \return ...
791!> \par History
792!> none
793!> \author Fawzi Mohamed
794!> \note
795!> split the case iter=1 to make it more optimized?
796! **************************************************************************************************
797 FUNCTION cp_sll_3d_c_get_rest(sll, iter) RESULT(res)
798 TYPE(cp_sll_3d_c_type), POINTER :: sll
799 INTEGER, OPTIONAL :: iter
800
801 TYPE(cp_sll_3d_c_type), POINTER :: res
802
803 INTEGER :: i
804
805 IF (.NOT. ASSOCIATED(sll)) THEN
806 NULLIFY (res)
807 ELSE
808 IF (PRESENT(iter)) THEN
809 res => sll
810 DO i = 1, iter
811 IF (ASSOCIATED(res%rest)) THEN
812 res => res%rest
813 ELSE
814 cpabort("tried to go past end")
815 END IF
816 END DO
817 IF (iter == -1) THEN
818 DO
819 IF (.NOT. ASSOCIATED(res%rest)) EXIT
820 res => res%rest
821 END DO
822 END IF
823 ELSE
824 res => sll%rest ! make the common case fast...
825 END IF
826 END IF
827 END FUNCTION cp_sll_3d_c_get_rest
828! **************************************************************************************************
829!> \brief returns the rest of the list
830!> \param sll the single linked list to get the rest from
831!> \param iter how many times the call to rest should be iterated,
832!> defaults to 1; -1 means till end of the list.
833!> \return ...
834!> \par History
835!> none
836!> \author Fawzi Mohamed
837!> \note
838!> split the case iter=1 to make it more optimized?
839! **************************************************************************************************
840 FUNCTION cp_sll_1d_r_get_rest(sll, iter) RESULT(res)
841 TYPE(cp_sll_1d_r_type), POINTER :: sll
842 INTEGER, OPTIONAL :: iter
843
844 TYPE(cp_sll_1d_r_type), POINTER :: res
845
846 INTEGER :: i
847
848 IF (.NOT. ASSOCIATED(sll)) THEN
849 NULLIFY (res)
850 ELSE
851 IF (PRESENT(iter)) THEN
852 res => sll
853 DO i = 1, iter
854 IF (ASSOCIATED(res%rest)) THEN
855 res => res%rest
856 ELSE
857 cpabort("tried to go past end")
858 END IF
859 END DO
860 IF (iter == -1) THEN
861 DO
862 IF (.NOT. ASSOCIATED(res%rest)) EXIT
863 res => res%rest
864 END DO
865 END IF
866 ELSE
867 res => sll%rest ! make the common case fast...
868 END IF
869 END IF
870 END FUNCTION cp_sll_1d_r_get_rest
871! **************************************************************************************************
872!> \brief returns the rest of the list
873!> \param sll the single linked list to get the rest from
874!> \param iter how many times the call to rest should be iterated,
875!> defaults to 1; -1 means till end of the list.
876!> \return ...
877!> \par History
878!> none
879!> \author Fawzi Mohamed
880!> \note
881!> split the case iter=1 to make it more optimized?
882! **************************************************************************************************
883 FUNCTION cp_sll_1d_c_get_rest(sll, iter) RESULT(res)
884 TYPE(cp_sll_1d_c_type), POINTER :: sll
885 INTEGER, OPTIONAL :: iter
886
887 TYPE(cp_sll_1d_c_type), POINTER :: res
888
889 INTEGER :: i
890
891 IF (.NOT. ASSOCIATED(sll)) THEN
892 NULLIFY (res)
893 ELSE
894 IF (PRESENT(iter)) THEN
895 res => sll
896 DO i = 1, iter
897 IF (ASSOCIATED(res%rest)) THEN
898 res => res%rest
899 ELSE
900 cpabort("tried to go past end")
901 END IF
902 END DO
903 IF (iter == -1) THEN
904 DO
905 IF (.NOT. ASSOCIATED(res%rest)) EXIT
906 res => res%rest
907 END DO
908 END IF
909 ELSE
910 res => sll%rest ! make the common case fast...
911 END IF
912 END IF
913 END FUNCTION cp_sll_1d_c_get_rest
914! **************************************************************************************************
915!> \brief returns the rest of the list
916!> \param sll the single linked list to get the rest from
917!> \param iter how many times the call to rest should be iterated,
918!> defaults to 1; -1 means till end of the list.
919!> \return ...
920!> \par History
921!> none
922!> \author Fawzi Mohamed
923!> \note
924!> split the case iter=1 to make it more optimized?
925! **************************************************************************************************
926 FUNCTION cp_sll_rs_get_rest(sll, iter) RESULT(res)
927 TYPE(cp_sll_rs_type), POINTER :: sll
928 INTEGER, OPTIONAL :: iter
929
930 TYPE(cp_sll_rs_type), POINTER :: res
931
932 INTEGER :: i
933
934 IF (.NOT. ASSOCIATED(sll)) THEN
935 NULLIFY (res)
936 ELSE
937 IF (PRESENT(iter)) THEN
938 res => sll
939 DO i = 1, iter
940 IF (ASSOCIATED(res%rest)) THEN
941 res => res%rest
942 ELSE
943 cpabort("tried to go past end")
944 END IF
945 END DO
946 IF (iter == -1) THEN
947 DO
948 IF (.NOT. ASSOCIATED(res%rest)) EXIT
949 res => res%rest
950 END DO
951 END IF
952 ELSE
953 res => sll%rest ! make the common case fast...
954 END IF
955 END IF
956 END FUNCTION cp_sll_rs_get_rest
957
958! **************************************************************************************************
959!> \brief returns the length of the list
960!> \param sll the list you want to know the length of
961!> \return ...
962!> \par History
963!> none
964!> \author Fawzi Mohamed
965!> \note
966!> slow (O(n))
967! **************************************************************************************************
968 FUNCTION cp_sll_3d_r_get_length(sll) RESULT(res)
969 TYPE(cp_sll_3d_r_type), pointer :: sll
970 INTEGER ::res
971
972 TYPE(cp_sll_3d_r_type), POINTER :: iterator
973
974 res = 0
975 iterator => sll
976 DO
977 IF (ASSOCIATED(iterator)) THEN
978 res = res + 1
979 iterator => iterator%rest
980 ELSE
981 EXIT
982 END IF
983 END DO
984 END FUNCTION cp_sll_3d_r_get_length
985! **************************************************************************************************
986!> \brief returns the length of the list
987!> \param sll the list you want to know the length of
988!> \return ...
989!> \par History
990!> none
991!> \author Fawzi Mohamed
992!> \note
993!> slow (O(n))
994! **************************************************************************************************
995 FUNCTION cp_sll_3d_c_get_length(sll) RESULT(res)
996 TYPE(cp_sll_3d_c_type), pointer :: sll
997 INTEGER ::res
998
999 TYPE(cp_sll_3d_c_type), POINTER :: iterator
1000
1001 res = 0
1002 iterator => sll
1003 DO
1004 IF (ASSOCIATED(iterator)) THEN
1005 res = res + 1
1006 iterator => iterator%rest
1007 ELSE
1008 EXIT
1009 END IF
1010 END DO
1011 END FUNCTION cp_sll_3d_c_get_length
1012! **************************************************************************************************
1013!> \brief returns the length of the list
1014!> \param sll the list you want to know the length of
1015!> \return ...
1016!> \par History
1017!> none
1018!> \author Fawzi Mohamed
1019!> \note
1020!> slow (O(n))
1021! **************************************************************************************************
1022 FUNCTION cp_sll_1d_r_get_length(sll) RESULT(res)
1023 TYPE(cp_sll_1d_r_type), pointer :: sll
1024 INTEGER ::res
1025
1026 TYPE(cp_sll_1d_r_type), POINTER :: iterator
1027
1028 res = 0
1029 iterator => sll
1030 DO
1031 IF (ASSOCIATED(iterator)) THEN
1032 res = res + 1
1033 iterator => iterator%rest
1034 ELSE
1035 EXIT
1036 END IF
1037 END DO
1038 END FUNCTION cp_sll_1d_r_get_length
1039! **************************************************************************************************
1040!> \brief returns the length of the list
1041!> \param sll the list you want to know the length of
1042!> \return ...
1043!> \par History
1044!> none
1045!> \author Fawzi Mohamed
1046!> \note
1047!> slow (O(n))
1048! **************************************************************************************************
1049 FUNCTION cp_sll_1d_c_get_length(sll) RESULT(res)
1050 TYPE(cp_sll_1d_c_type), pointer :: sll
1051 INTEGER ::res
1052
1053 TYPE(cp_sll_1d_c_type), POINTER :: iterator
1054
1055 res = 0
1056 iterator => sll
1057 DO
1058 IF (ASSOCIATED(iterator)) THEN
1059 res = res + 1
1060 iterator => iterator%rest
1061 ELSE
1062 EXIT
1063 END IF
1064 END DO
1065 END FUNCTION cp_sll_1d_c_get_length
1066! **************************************************************************************************
1067!> \brief returns the length of the list
1068!> \param sll the list you want to know the length of
1069!> \return ...
1070!> \par History
1071!> none
1072!> \author Fawzi Mohamed
1073!> \note
1074!> slow (O(n))
1075! **************************************************************************************************
1076 FUNCTION cp_sll_rs_get_length(sll) RESULT(res)
1077 TYPE(cp_sll_rs_type), pointer :: sll
1078 INTEGER ::res
1079
1080 TYPE(cp_sll_rs_type), POINTER :: iterator
1081
1082 res = 0
1083 iterator => sll
1084 DO
1085 IF (ASSOCIATED(iterator)) THEN
1086 res = res + 1
1087 iterator => iterator%rest
1088 ELSE
1089 EXIT
1090 END IF
1091 END DO
1092 END FUNCTION cp_sll_rs_get_length
1093
1094! **************************************************************************************************
1095!> \brief returns the element at the given index
1096!> \param sll the list you get the element from
1097!> \param index the position of the element (stating at 1)
1098!> \return ...
1099!> \par History
1100!> none
1101!> \author Fawzi Mohamed
1102!> \note
1103!> slow (O(index))
1104! **************************************************************************************************
1105 FUNCTION cp_sll_3d_r_get_el_at(sll, index) RESULT(res)
1106 REAL(kind=dp),dimension(:,:,:),pointer,contiguous :: res
1107 TYPE(cp_sll_3d_r_type), POINTER :: sll
1108 INTEGER, INTENT(in) :: index
1109
1110 TYPE(cp_sll_3d_r_type), POINTER :: pos
1111
1112 IF (index == -1) THEN
1113 pos => cp_sll_3d_r_get_rest(sll, iter=-1)
1114 ELSE
1115 pos => cp_sll_3d_r_get_rest(sll, iter=index - 1)
1116 END IF
1117 cpassert(ASSOCIATED(pos))
1118
1119 res =>pos%first_el
1120 END FUNCTION cp_sll_3d_r_get_el_at
1121! **************************************************************************************************
1122!> \brief returns the element at the given index
1123!> \param sll the list you get the element from
1124!> \param index the position of the element (stating at 1)
1125!> \return ...
1126!> \par History
1127!> none
1128!> \author Fawzi Mohamed
1129!> \note
1130!> slow (O(index))
1131! **************************************************************************************************
1132 FUNCTION cp_sll_3d_c_get_el_at(sll, index) RESULT(res)
1133 COMPLEX(kind=dp),dimension(:,:,:),pointer,contiguous :: res
1134 TYPE(cp_sll_3d_c_type), POINTER :: sll
1135 INTEGER, INTENT(in) :: index
1136
1137 TYPE(cp_sll_3d_c_type), POINTER :: pos
1138
1139 IF (index == -1) THEN
1140 pos => cp_sll_3d_c_get_rest(sll, iter=-1)
1141 ELSE
1142 pos => cp_sll_3d_c_get_rest(sll, iter=index - 1)
1143 END IF
1144 cpassert(ASSOCIATED(pos))
1145
1146 res =>pos%first_el
1147 END FUNCTION cp_sll_3d_c_get_el_at
1148! **************************************************************************************************
1149!> \brief returns the element at the given index
1150!> \param sll the list you get the element from
1151!> \param index the position of the element (stating at 1)
1152!> \return ...
1153!> \par History
1154!> none
1155!> \author Fawzi Mohamed
1156!> \note
1157!> slow (O(index))
1158! **************************************************************************************************
1159 FUNCTION cp_sll_1d_r_get_el_at(sll, index) RESULT(res)
1160 REAL(kind=dp),dimension(:),pointer,contiguous :: res
1161 TYPE(cp_sll_1d_r_type), POINTER :: sll
1162 INTEGER, INTENT(in) :: index
1163
1164 TYPE(cp_sll_1d_r_type), POINTER :: pos
1165
1166 IF (index == -1) THEN
1167 pos => cp_sll_1d_r_get_rest(sll, iter=-1)
1168 ELSE
1169 pos => cp_sll_1d_r_get_rest(sll, iter=index - 1)
1170 END IF
1171 cpassert(ASSOCIATED(pos))
1172
1173 res =>pos%first_el
1174 END FUNCTION cp_sll_1d_r_get_el_at
1175! **************************************************************************************************
1176!> \brief returns the element at the given index
1177!> \param sll the list you get the element from
1178!> \param index the position of the element (stating at 1)
1179!> \return ...
1180!> \par History
1181!> none
1182!> \author Fawzi Mohamed
1183!> \note
1184!> slow (O(index))
1185! **************************************************************************************************
1186 FUNCTION cp_sll_1d_c_get_el_at(sll, index) RESULT(res)
1187 COMPLEX(kind=dp),dimension(:),pointer,contiguous :: res
1188 TYPE(cp_sll_1d_c_type), POINTER :: sll
1189 INTEGER, INTENT(in) :: index
1190
1191 TYPE(cp_sll_1d_c_type), POINTER :: pos
1192
1193 IF (index == -1) THEN
1194 pos => cp_sll_1d_c_get_rest(sll, iter=-1)
1195 ELSE
1196 pos => cp_sll_1d_c_get_rest(sll, iter=index - 1)
1197 END IF
1198 cpassert(ASSOCIATED(pos))
1199
1200 res =>pos%first_el
1201 END FUNCTION cp_sll_1d_c_get_el_at
1202! **************************************************************************************************
1203!> \brief returns the element at the given index
1204!> \param sll the list you get the element from
1205!> \param index the position of the element (stating at 1)
1206!> \return ...
1207!> \par History
1208!> none
1209!> \author Fawzi Mohamed
1210!> \note
1211!> slow (O(index))
1212! **************************************************************************************************
1213 FUNCTION cp_sll_rs_get_el_at(sll, index) RESULT(res)
1214 type(realspace_grid_type),pointer :: res
1215 TYPE(cp_sll_rs_type), POINTER :: sll
1216 INTEGER, INTENT(in) :: index
1217
1218 TYPE(cp_sll_rs_type), POINTER :: pos
1219
1220 IF (index == -1) THEN
1221 pos => cp_sll_rs_get_rest(sll, iter=-1)
1222 ELSE
1223 pos => cp_sll_rs_get_rest(sll, iter=index - 1)
1224 END IF
1225 cpassert(ASSOCIATED(pos))
1226
1227 res =>pos%first_el
1228 END FUNCTION cp_sll_rs_get_el_at
1229
1230! **************************************************************************************************
1231!> \brief sets the element at the given index
1232!> \param sll the list you get the element from
1233!> \param index the position of the element (stating at 1)
1234!> -1 means at the end
1235!> \param value the new element
1236!> \par History
1237!> none
1238!> \author Fawzi Mohamed
1239!> \note
1240!> slow (O(index))
1241! **************************************************************************************************
1242 SUBROUTINE cp_sll_3d_r_set_el_at(sll, index, value)
1243 REAL(kind=dp),dimension(:,:,:),pointer,contiguous :: value
1244 TYPE(cp_sll_3d_r_type), POINTER :: sll
1245 INTEGER, INTENT(in) :: index
1246
1247 TYPE(cp_sll_3d_r_type), POINTER :: pos
1248
1249 IF (index == -1) THEN
1250 pos => cp_sll_3d_r_get_rest(sll, iter=-1)
1251 ELSE
1252 pos => cp_sll_3d_r_get_rest(sll, iter=index - 1)
1253 END IF
1254 cpassert(ASSOCIATED(pos))
1255
1256 pos%first_el =>value
1257 END SUBROUTINE cp_sll_3d_r_set_el_at
1258! **************************************************************************************************
1259!> \brief sets the element at the given index
1260!> \param sll the list you get the element from
1261!> \param index the position of the element (stating at 1)
1262!> -1 means at the end
1263!> \param value the new element
1264!> \par History
1265!> none
1266!> \author Fawzi Mohamed
1267!> \note
1268!> slow (O(index))
1269! **************************************************************************************************
1270 SUBROUTINE cp_sll_3d_c_set_el_at(sll, index, value)
1271 COMPLEX(kind=dp),dimension(:,:,:),pointer,contiguous :: value
1272 TYPE(cp_sll_3d_c_type), POINTER :: sll
1273 INTEGER, INTENT(in) :: index
1274
1275 TYPE(cp_sll_3d_c_type), POINTER :: pos
1276
1277 IF (index == -1) THEN
1278 pos => cp_sll_3d_c_get_rest(sll, iter=-1)
1279 ELSE
1280 pos => cp_sll_3d_c_get_rest(sll, iter=index - 1)
1281 END IF
1282 cpassert(ASSOCIATED(pos))
1283
1284 pos%first_el =>value
1285 END SUBROUTINE cp_sll_3d_c_set_el_at
1286! **************************************************************************************************
1287!> \brief sets the element at the given index
1288!> \param sll the list you get the element from
1289!> \param index the position of the element (stating at 1)
1290!> -1 means at the end
1291!> \param value the new element
1292!> \par History
1293!> none
1294!> \author Fawzi Mohamed
1295!> \note
1296!> slow (O(index))
1297! **************************************************************************************************
1298 SUBROUTINE cp_sll_1d_r_set_el_at(sll, index, value)
1299 REAL(kind=dp),dimension(:),pointer,contiguous :: value
1300 TYPE(cp_sll_1d_r_type), POINTER :: sll
1301 INTEGER, INTENT(in) :: index
1302
1303 TYPE(cp_sll_1d_r_type), POINTER :: pos
1304
1305 IF (index == -1) THEN
1306 pos => cp_sll_1d_r_get_rest(sll, iter=-1)
1307 ELSE
1308 pos => cp_sll_1d_r_get_rest(sll, iter=index - 1)
1309 END IF
1310 cpassert(ASSOCIATED(pos))
1311
1312 pos%first_el =>value
1313 END SUBROUTINE cp_sll_1d_r_set_el_at
1314! **************************************************************************************************
1315!> \brief sets the element at the given index
1316!> \param sll the list you get the element from
1317!> \param index the position of the element (stating at 1)
1318!> -1 means at the end
1319!> \param value the new element
1320!> \par History
1321!> none
1322!> \author Fawzi Mohamed
1323!> \note
1324!> slow (O(index))
1325! **************************************************************************************************
1326 SUBROUTINE cp_sll_1d_c_set_el_at(sll, index, value)
1327 COMPLEX(kind=dp),dimension(:),pointer,contiguous :: value
1328 TYPE(cp_sll_1d_c_type), POINTER :: sll
1329 INTEGER, INTENT(in) :: index
1330
1331 TYPE(cp_sll_1d_c_type), POINTER :: pos
1332
1333 IF (index == -1) THEN
1334 pos => cp_sll_1d_c_get_rest(sll, iter=-1)
1335 ELSE
1336 pos => cp_sll_1d_c_get_rest(sll, iter=index - 1)
1337 END IF
1338 cpassert(ASSOCIATED(pos))
1339
1340 pos%first_el =>value
1341 END SUBROUTINE cp_sll_1d_c_set_el_at
1342! **************************************************************************************************
1343!> \brief sets the element at the given index
1344!> \param sll the list you get the element from
1345!> \param index the position of the element (stating at 1)
1346!> -1 means at the end
1347!> \param value the new element
1348!> \par History
1349!> none
1350!> \author Fawzi Mohamed
1351!> \note
1352!> slow (O(index))
1353! **************************************************************************************************
1354 SUBROUTINE cp_sll_rs_set_el_at(sll, index, value)
1355 type(realspace_grid_type),pointer :: value
1356 TYPE(cp_sll_rs_type), POINTER :: sll
1357 INTEGER, INTENT(in) :: index
1358
1359 TYPE(cp_sll_rs_type), POINTER :: pos
1360
1361 IF (index == -1) THEN
1362 pos => cp_sll_rs_get_rest(sll, iter=-1)
1363 ELSE
1364 pos => cp_sll_rs_get_rest(sll, iter=index - 1)
1365 END IF
1366 cpassert(ASSOCIATED(pos))
1367
1368 pos%first_el =>value
1369 END SUBROUTINE cp_sll_rs_set_el_at
1370
1371! * iteration *
1372
1373! **************************************************************************************************
1374!> \brief returns true if the actual element is valid (i.e. iterator ont at end)
1375!> moves the iterator to the next element
1376!> \param iterator iterator that moves along the list
1377!> \param el_att the actual element (valid only if the function returns true)
1378!> \return ...
1379!> \par History
1380!> none
1381!> \author Fawzi Mohamed
1382! **************************************************************************************************
1383 FUNCTION cp_sll_3d_r_next(iterator, el_att) RESULT(res)
1384 TYPE(cp_sll_3d_r_type), POINTER :: iterator
1385 REAL(kind=dp),dimension(:,:,:),pointer,contiguous, OPTIONAL :: el_att
1386 LOGICAL :: res
1387
1388 IF (ASSOCIATED(iterator)) THEN
1389 res = .true.
1390 if (present(el_att)) el_att =>iterator%first_el
1391 iterator => iterator%rest
1392 ELSE
1393 res = .false.
1394 END IF
1395 END FUNCTION cp_sll_3d_r_next
1396! **************************************************************************************************
1397!> \brief returns true if the actual element is valid (i.e. iterator ont at end)
1398!> moves the iterator to the next element
1399!> \param iterator iterator that moves along the list
1400!> \param el_att the actual element (valid only if the function returns true)
1401!> \return ...
1402!> \par History
1403!> none
1404!> \author Fawzi Mohamed
1405! **************************************************************************************************
1406 FUNCTION cp_sll_3d_c_next(iterator, el_att) RESULT(res)
1407 TYPE(cp_sll_3d_c_type), POINTER :: iterator
1408 COMPLEX(kind=dp),dimension(:,:,:),pointer,contiguous, OPTIONAL :: el_att
1409 LOGICAL :: res
1410
1411 IF (ASSOCIATED(iterator)) THEN
1412 res = .true.
1413 if (present(el_att)) el_att =>iterator%first_el
1414 iterator => iterator%rest
1415 ELSE
1416 res = .false.
1417 END IF
1418 END FUNCTION cp_sll_3d_c_next
1419! **************************************************************************************************
1420!> \brief returns true if the actual element is valid (i.e. iterator ont at end)
1421!> moves the iterator to the next element
1422!> \param iterator iterator that moves along the list
1423!> \param el_att the actual element (valid only if the function returns true)
1424!> \return ...
1425!> \par History
1426!> none
1427!> \author Fawzi Mohamed
1428! **************************************************************************************************
1429 FUNCTION cp_sll_1d_r_next(iterator, el_att) RESULT(res)
1430 TYPE(cp_sll_1d_r_type), POINTER :: iterator
1431 REAL(kind=dp),dimension(:),pointer,contiguous, OPTIONAL :: el_att
1432 LOGICAL :: res
1433
1434 IF (ASSOCIATED(iterator)) THEN
1435 res = .true.
1436 if (present(el_att)) el_att =>iterator%first_el
1437 iterator => iterator%rest
1438 ELSE
1439 res = .false.
1440 END IF
1441 END FUNCTION cp_sll_1d_r_next
1442! **************************************************************************************************
1443!> \brief returns true if the actual element is valid (i.e. iterator ont at end)
1444!> moves the iterator to the next element
1445!> \param iterator iterator that moves along the list
1446!> \param el_att the actual element (valid only if the function returns true)
1447!> \return ...
1448!> \par History
1449!> none
1450!> \author Fawzi Mohamed
1451! **************************************************************************************************
1452 FUNCTION cp_sll_1d_c_next(iterator, el_att) RESULT(res)
1453 TYPE(cp_sll_1d_c_type), POINTER :: iterator
1454 COMPLEX(kind=dp),dimension(:),pointer,contiguous, OPTIONAL :: el_att
1455 LOGICAL :: res
1456
1457 IF (ASSOCIATED(iterator)) THEN
1458 res = .true.
1459 if (present(el_att)) el_att =>iterator%first_el
1460 iterator => iterator%rest
1461 ELSE
1462 res = .false.
1463 END IF
1464 END FUNCTION cp_sll_1d_c_next
1465! **************************************************************************************************
1466!> \brief returns true if the actual element is valid (i.e. iterator ont at end)
1467!> moves the iterator to the next element
1468!> \param iterator iterator that moves along the list
1469!> \param el_att the actual element (valid only if the function returns true)
1470!> \return ...
1471!> \par History
1472!> none
1473!> \author Fawzi Mohamed
1474! **************************************************************************************************
1475 FUNCTION cp_sll_rs_next(iterator, el_att) RESULT(res)
1476 TYPE(cp_sll_rs_type), POINTER :: iterator
1477 type(realspace_grid_type),pointer, OPTIONAL :: el_att
1478 LOGICAL :: res
1479
1480 IF (ASSOCIATED(iterator)) THEN
1481 res = .true.
1482 if (present(el_att)) el_att =>iterator%first_el
1483 iterator => iterator%rest
1484 ELSE
1485 res = .false.
1486 END IF
1487 END FUNCTION cp_sll_rs_next
1488
1489! ============ structure modifications ============
1490
1491! **************************************************************************************************
1492!> \brief insert an element at the beginning of the list
1493!> \param sll the single linked list point at the beginning of which
1494!> you want to add the element
1495!> \param el the element to add
1496!> \par History
1497!> none
1498!> \author Fawzi Mohamed
1499!> \note
1500!> fast (O(1))
1501! **************************************************************************************************
1502 SUBROUTINE cp_sll_3d_r_insert_el(sll, el)
1503 TYPE(cp_sll_3d_r_type), POINTER :: sll
1504 REAL(kind=dp),dimension(:,:,:),pointer,contiguous:: el
1505
1506 TYPE(cp_sll_3d_r_type), POINTER :: newslot
1507
1508 NULLIFY (newslot)
1509
1510 CALL cp_sll_3d_r_create(newslot, first_el=el, &
1511 rest=sll)
1512 sll => newslot
1513 END SUBROUTINE cp_sll_3d_r_insert_el
1514! **************************************************************************************************
1515!> \brief insert an element at the beginning of the list
1516!> \param sll the single linked list point at the beginning of which
1517!> you want to add the element
1518!> \param el the element to add
1519!> \par History
1520!> none
1521!> \author Fawzi Mohamed
1522!> \note
1523!> fast (O(1))
1524! **************************************************************************************************
1525 SUBROUTINE cp_sll_3d_c_insert_el(sll, el)
1526 TYPE(cp_sll_3d_c_type), POINTER :: sll
1527 COMPLEX(kind=dp),dimension(:,:,:),pointer,contiguous:: el
1528
1529 TYPE(cp_sll_3d_c_type), POINTER :: newSlot
1530
1531 NULLIFY (newslot)
1532
1533 CALL cp_sll_3d_c_create(newslot, first_el=el, &
1534 rest=sll)
1535 sll => newslot
1536 END SUBROUTINE cp_sll_3d_c_insert_el
1537! **************************************************************************************************
1538!> \brief insert an element at the beginning of the list
1539!> \param sll the single linked list point at the beginning of which
1540!> you want to add the element
1541!> \param el the element to add
1542!> \par History
1543!> none
1544!> \author Fawzi Mohamed
1545!> \note
1546!> fast (O(1))
1547! **************************************************************************************************
1548 SUBROUTINE cp_sll_1d_r_insert_el(sll, el)
1549 TYPE(cp_sll_1d_r_type), POINTER :: sll
1550 REAL(kind=dp),dimension(:),pointer,contiguous:: el
1551
1552 TYPE(cp_sll_1d_r_type), POINTER :: newslot
1553
1554 NULLIFY (newslot)
1555
1556 CALL cp_sll_1d_r_create(newslot, first_el=el, &
1557 rest=sll)
1558 sll => newslot
1559 END SUBROUTINE cp_sll_1d_r_insert_el
1560! **************************************************************************************************
1561!> \brief insert an element at the beginning of the list
1562!> \param sll the single linked list point at the beginning of which
1563!> you want to add the element
1564!> \param el the element to add
1565!> \par History
1566!> none
1567!> \author Fawzi Mohamed
1568!> \note
1569!> fast (O(1))
1570! **************************************************************************************************
1571 SUBROUTINE cp_sll_1d_c_insert_el(sll, el)
1572 TYPE(cp_sll_1d_c_type), POINTER :: sll
1573 COMPLEX(kind=dp),dimension(:),pointer,contiguous:: el
1574
1575 TYPE(cp_sll_1d_c_type), POINTER :: newSlot
1576
1577 NULLIFY (newslot)
1578
1579 CALL cp_sll_1d_c_create(newslot, first_el=el, &
1580 rest=sll)
1581 sll => newslot
1582 END SUBROUTINE cp_sll_1d_c_insert_el
1583! **************************************************************************************************
1584!> \brief insert an element at the beginning of the list
1585!> \param sll the single linked list point at the beginning of which
1586!> you want to add the element
1587!> \param el the element to add
1588!> \par History
1589!> none
1590!> \author Fawzi Mohamed
1591!> \note
1592!> fast (O(1))
1593! **************************************************************************************************
1594 SUBROUTINE cp_sll_rs_insert_el(sll, el)
1595 TYPE(cp_sll_rs_type), POINTER :: sll
1596 type(realspace_grid_type),pointer:: el
1597
1598 TYPE(cp_sll_rs_type), POINTER :: newSlot
1599
1600 NULLIFY (newslot)
1601
1602 CALL cp_sll_rs_create(newslot, first_el=el, &
1603 rest=sll)
1604 sll => newslot
1605 END SUBROUTINE cp_sll_rs_insert_el
1606
1607! **************************************************************************************************
1608!> \brief remove the first element of the linked list
1609!> \param sll the list whose first element has to be removed
1610!> \par History
1611!> none
1612!> \author Fawzi Mohamed
1613!> \note
1614!> fast (O(1))
1615! **************************************************************************************************
1617 TYPE(cp_sll_3d_r_type), POINTER :: sll
1618
1619 TYPE(cp_sll_3d_r_type), POINTER :: node_to_rm
1620 node_to_rm => sll
1621
1622 IF (ASSOCIATED(sll)) THEN
1623 sll => sll%rest
1624 CALL cp_sll_3d_r_dealloc_node(node_to_rm)
1625 ELSE
1626 cpabort("tried to remove first el of an empty list")
1627 END IF
1628 END SUBROUTINE cp_sll_3d_r_rm_first_el
1629! **************************************************************************************************
1630!> \brief remove the first element of the linked list
1631!> \param sll the list whose first element has to be removed
1632!> \par History
1633!> none
1634!> \author Fawzi Mohamed
1635!> \note
1636!> fast (O(1))
1637! **************************************************************************************************
1639 TYPE(cp_sll_3d_c_type), POINTER :: sll
1640
1641 TYPE(cp_sll_3d_c_type), POINTER :: node_to_rm
1642 node_to_rm => sll
1643
1644 IF (ASSOCIATED(sll)) THEN
1645 sll => sll%rest
1646 CALL cp_sll_3d_c_dealloc_node(node_to_rm)
1647 ELSE
1648 cpabort("tried to remove first el of an empty list")
1649 END IF
1650 END SUBROUTINE cp_sll_3d_c_rm_first_el
1651! **************************************************************************************************
1652!> \brief remove the first element of the linked list
1653!> \param sll the list whose first element has to be removed
1654!> \par History
1655!> none
1656!> \author Fawzi Mohamed
1657!> \note
1658!> fast (O(1))
1659! **************************************************************************************************
1661 TYPE(cp_sll_1d_r_type), POINTER :: sll
1662
1663 TYPE(cp_sll_1d_r_type), POINTER :: node_to_rm
1664 node_to_rm => sll
1665
1666 IF (ASSOCIATED(sll)) THEN
1667 sll => sll%rest
1668 CALL cp_sll_1d_r_dealloc_node(node_to_rm)
1669 ELSE
1670 cpabort("tried to remove first el of an empty list")
1671 END IF
1672 END SUBROUTINE cp_sll_1d_r_rm_first_el
1673! **************************************************************************************************
1674!> \brief remove the first element of the linked list
1675!> \param sll the list whose first element has to be removed
1676!> \par History
1677!> none
1678!> \author Fawzi Mohamed
1679!> \note
1680!> fast (O(1))
1681! **************************************************************************************************
1683 TYPE(cp_sll_1d_c_type), POINTER :: sll
1684
1685 TYPE(cp_sll_1d_c_type), POINTER :: node_to_rm
1686 node_to_rm => sll
1687
1688 IF (ASSOCIATED(sll)) THEN
1689 sll => sll%rest
1690 CALL cp_sll_1d_c_dealloc_node(node_to_rm)
1691 ELSE
1692 cpabort("tried to remove first el of an empty list")
1693 END IF
1694 END SUBROUTINE cp_sll_1d_c_rm_first_el
1695! **************************************************************************************************
1696!> \brief remove the first element of the linked list
1697!> \param sll the list whose first element has to be removed
1698!> \par History
1699!> none
1700!> \author Fawzi Mohamed
1701!> \note
1702!> fast (O(1))
1703! **************************************************************************************************
1705 TYPE(cp_sll_rs_type), POINTER :: sll
1706
1707 TYPE(cp_sll_rs_type), POINTER :: node_to_rm
1708 node_to_rm => sll
1709
1710 IF (ASSOCIATED(sll)) THEN
1711 sll => sll%rest
1712 CALL cp_sll_rs_dealloc_node(node_to_rm)
1713 ELSE
1714 cpabort("tried to remove first el of an empty list")
1715 END IF
1716 END SUBROUTINE cp_sll_rs_rm_first_el
1717
1718! **************************************************************************************************
1719!> \brief inserts the element at the given index
1720!> \param sll the list you get the element from
1721!> \param el the new element
1722!> \param index the position of the element (stating at 1).
1723!> If it is -1, it means at end
1724!> \par History
1725!> none
1726!> \author Fawzi Mohamed
1727!> \note
1728!> slow (O(index))
1729! **************************************************************************************************
1730 SUBROUTINE cp_sll_3d_r_insert_el_at(sll, el, index)
1731 REAL(kind=dp),dimension(:,:,:),pointer,contiguous :: el
1732 INTEGER, INTENT(in) :: index
1733 TYPE(cp_sll_3d_r_type), POINTER :: sll
1734
1735 TYPE(cp_sll_3d_r_type), POINTER :: pos
1736
1737 IF (index == 1) THEN
1738 CALL cp_sll_3d_r_insert_el(sll, el)
1739 ELSE
1740 IF (index == -1) THEN
1741 pos => cp_sll_3d_r_get_rest(sll, iter=-1)
1742 ELSE
1743 pos => cp_sll_3d_r_get_rest(sll, iter=index - 2)
1744 END IF
1745 cpassert(ASSOCIATED(pos))
1746 CALL cp_sll_3d_r_insert_el(pos%rest, el)
1747 END IF
1748 END SUBROUTINE cp_sll_3d_r_insert_el_at
1749! **************************************************************************************************
1750!> \brief inserts the element at the given index
1751!> \param sll the list you get the element from
1752!> \param el the new element
1753!> \param index the position of the element (stating at 1).
1754!> If it is -1, it means at end
1755!> \par History
1756!> none
1757!> \author Fawzi Mohamed
1758!> \note
1759!> slow (O(index))
1760! **************************************************************************************************
1761 SUBROUTINE cp_sll_3d_c_insert_el_at(sll, el, index)
1762 COMPLEX(kind=dp),dimension(:,:,:),pointer,contiguous :: el
1763 INTEGER, INTENT(in) :: index
1764 TYPE(cp_sll_3d_c_type), POINTER :: sll
1765
1766 TYPE(cp_sll_3d_c_type), POINTER :: pos
1767
1768 IF (index == 1) THEN
1769 CALL cp_sll_3d_c_insert_el(sll, el)
1770 ELSE
1771 IF (index == -1) THEN
1772 pos => cp_sll_3d_c_get_rest(sll, iter=-1)
1773 ELSE
1774 pos => cp_sll_3d_c_get_rest(sll, iter=index - 2)
1775 END IF
1776 cpassert(ASSOCIATED(pos))
1777 CALL cp_sll_3d_c_insert_el(pos%rest, el)
1778 END IF
1779 END SUBROUTINE cp_sll_3d_c_insert_el_at
1780! **************************************************************************************************
1781!> \brief inserts the element at the given index
1782!> \param sll the list you get the element from
1783!> \param el the new element
1784!> \param index the position of the element (stating at 1).
1785!> If it is -1, it means at end
1786!> \par History
1787!> none
1788!> \author Fawzi Mohamed
1789!> \note
1790!> slow (O(index))
1791! **************************************************************************************************
1792 SUBROUTINE cp_sll_1d_r_insert_el_at(sll, el, index)
1793 REAL(kind=dp),dimension(:),pointer,contiguous :: el
1794 INTEGER, INTENT(in) :: index
1795 TYPE(cp_sll_1d_r_type), POINTER :: sll
1796
1797 TYPE(cp_sll_1d_r_type), POINTER :: pos
1798
1799 IF (index == 1) THEN
1800 CALL cp_sll_1d_r_insert_el(sll, el)
1801 ELSE
1802 IF (index == -1) THEN
1803 pos => cp_sll_1d_r_get_rest(sll, iter=-1)
1804 ELSE
1805 pos => cp_sll_1d_r_get_rest(sll, iter=index - 2)
1806 END IF
1807 cpassert(ASSOCIATED(pos))
1808 CALL cp_sll_1d_r_insert_el(pos%rest, el)
1809 END IF
1810 END SUBROUTINE cp_sll_1d_r_insert_el_at
1811! **************************************************************************************************
1812!> \brief inserts the element at the given index
1813!> \param sll the list you get the element from
1814!> \param el the new element
1815!> \param index the position of the element (stating at 1).
1816!> If it is -1, it means at end
1817!> \par History
1818!> none
1819!> \author Fawzi Mohamed
1820!> \note
1821!> slow (O(index))
1822! **************************************************************************************************
1823 SUBROUTINE cp_sll_1d_c_insert_el_at(sll, el, index)
1824 COMPLEX(kind=dp),dimension(:),pointer,contiguous :: el
1825 INTEGER, INTENT(in) :: index
1826 TYPE(cp_sll_1d_c_type), POINTER :: sll
1827
1828 TYPE(cp_sll_1d_c_type), POINTER :: pos
1829
1830 IF (index == 1) THEN
1831 CALL cp_sll_1d_c_insert_el(sll, el)
1832 ELSE
1833 IF (index == -1) THEN
1834 pos => cp_sll_1d_c_get_rest(sll, iter=-1)
1835 ELSE
1836 pos => cp_sll_1d_c_get_rest(sll, iter=index - 2)
1837 END IF
1838 cpassert(ASSOCIATED(pos))
1839 CALL cp_sll_1d_c_insert_el(pos%rest, el)
1840 END IF
1841 END SUBROUTINE cp_sll_1d_c_insert_el_at
1842! **************************************************************************************************
1843!> \brief inserts the element at the given index
1844!> \param sll the list you get the element from
1845!> \param el the new element
1846!> \param index the position of the element (stating at 1).
1847!> If it is -1, it means at end
1848!> \par History
1849!> none
1850!> \author Fawzi Mohamed
1851!> \note
1852!> slow (O(index))
1853! **************************************************************************************************
1854 SUBROUTINE cp_sll_rs_insert_el_at(sll, el, index)
1855 type(realspace_grid_type),pointer :: el
1856 INTEGER, INTENT(in) :: index
1857 TYPE(cp_sll_rs_type), POINTER :: sll
1858
1859 TYPE(cp_sll_rs_type), POINTER :: pos
1860
1861 IF (index == 1) THEN
1862 CALL cp_sll_rs_insert_el(sll, el)
1863 ELSE
1864 IF (index == -1) THEN
1865 pos => cp_sll_rs_get_rest(sll, iter=-1)
1866 ELSE
1867 pos => cp_sll_rs_get_rest(sll, iter=index - 2)
1868 END IF
1869 cpassert(ASSOCIATED(pos))
1870 CALL cp_sll_rs_insert_el(pos%rest, el)
1871 END IF
1872 END SUBROUTINE cp_sll_rs_insert_el_at
1873
1874! **************************************************************************************************
1875!> \brief removes the element at the given index
1876!> \param sll the list you get the element from
1877!> \param index the position of the element (stating at 1)
1878!> \par History
1879!> none
1880!> \author Fawzi Mohamed
1881!> \note
1882!> slow (O(index))
1883! **************************************************************************************************
1884 SUBROUTINE cp_sll_3d_r_rm_el_at(sll, index)
1885 TYPE(cp_sll_3d_r_type), POINTER :: sll
1886 INTEGER, INTENT(in)::index
1887
1888 TYPE(cp_sll_3d_r_type), POINTER :: pos
1889
1890 IF (index == 1) THEN
1891 CALL cp_sll_3d_r_rm_first_el(sll)
1892 ELSE
1893 IF (index == -1) THEN
1894 pos => cp_sll_3d_r_get_rest(sll, iter=-1)
1895 ELSE
1896 pos => cp_sll_3d_r_get_rest(sll, iter=index - 2)
1897 END IF
1898 cpassert(ASSOCIATED(pos))
1899 CALL cp_sll_3d_r_rm_first_el(pos%rest)
1900 END IF
1901 END SUBROUTINE cp_sll_3d_r_rm_el_at
1902! **************************************************************************************************
1903!> \brief removes the element at the given index
1904!> \param sll the list you get the element from
1905!> \param index the position of the element (stating at 1)
1906!> \par History
1907!> none
1908!> \author Fawzi Mohamed
1909!> \note
1910!> slow (O(index))
1911! **************************************************************************************************
1912 SUBROUTINE cp_sll_3d_c_rm_el_at(sll, index)
1913 TYPE(cp_sll_3d_c_type), POINTER :: sll
1914 INTEGER, INTENT(in)::index
1915
1916 TYPE(cp_sll_3d_c_type), POINTER :: pos
1917
1918 IF (index == 1) THEN
1919 CALL cp_sll_3d_c_rm_first_el(sll)
1920 ELSE
1921 IF (index == -1) THEN
1922 pos => cp_sll_3d_c_get_rest(sll, iter=-1)
1923 ELSE
1924 pos => cp_sll_3d_c_get_rest(sll, iter=index - 2)
1925 END IF
1926 cpassert(ASSOCIATED(pos))
1927 CALL cp_sll_3d_c_rm_first_el(pos%rest)
1928 END IF
1929 END SUBROUTINE cp_sll_3d_c_rm_el_at
1930! **************************************************************************************************
1931!> \brief removes the element at the given index
1932!> \param sll the list you get the element from
1933!> \param index the position of the element (stating at 1)
1934!> \par History
1935!> none
1936!> \author Fawzi Mohamed
1937!> \note
1938!> slow (O(index))
1939! **************************************************************************************************
1940 SUBROUTINE cp_sll_1d_r_rm_el_at(sll, index)
1941 TYPE(cp_sll_1d_r_type), POINTER :: sll
1942 INTEGER, INTENT(in)::index
1943
1944 TYPE(cp_sll_1d_r_type), POINTER :: pos
1945
1946 IF (index == 1) THEN
1947 CALL cp_sll_1d_r_rm_first_el(sll)
1948 ELSE
1949 IF (index == -1) THEN
1950 pos => cp_sll_1d_r_get_rest(sll, iter=-1)
1951 ELSE
1952 pos => cp_sll_1d_r_get_rest(sll, iter=index - 2)
1953 END IF
1954 cpassert(ASSOCIATED(pos))
1955 CALL cp_sll_1d_r_rm_first_el(pos%rest)
1956 END IF
1957 END SUBROUTINE cp_sll_1d_r_rm_el_at
1958! **************************************************************************************************
1959!> \brief removes the element at the given index
1960!> \param sll the list you get the element from
1961!> \param index the position of the element (stating at 1)
1962!> \par History
1963!> none
1964!> \author Fawzi Mohamed
1965!> \note
1966!> slow (O(index))
1967! **************************************************************************************************
1968 SUBROUTINE cp_sll_1d_c_rm_el_at(sll, index)
1969 TYPE(cp_sll_1d_c_type), POINTER :: sll
1970 INTEGER, INTENT(in)::index
1971
1972 TYPE(cp_sll_1d_c_type), POINTER :: pos
1973
1974 IF (index == 1) THEN
1975 CALL cp_sll_1d_c_rm_first_el(sll)
1976 ELSE
1977 IF (index == -1) THEN
1978 pos => cp_sll_1d_c_get_rest(sll, iter=-1)
1979 ELSE
1980 pos => cp_sll_1d_c_get_rest(sll, iter=index - 2)
1981 END IF
1982 cpassert(ASSOCIATED(pos))
1983 CALL cp_sll_1d_c_rm_first_el(pos%rest)
1984 END IF
1985 END SUBROUTINE cp_sll_1d_c_rm_el_at
1986! **************************************************************************************************
1987!> \brief removes the element at the given index
1988!> \param sll the list you get the element from
1989!> \param index the position of the element (stating at 1)
1990!> \par History
1991!> none
1992!> \author Fawzi Mohamed
1993!> \note
1994!> slow (O(index))
1995! **************************************************************************************************
1996 SUBROUTINE cp_sll_rs_rm_el_at(sll, index)
1997 TYPE(cp_sll_rs_type), POINTER :: sll
1998 INTEGER, INTENT(in)::index
1999
2000 TYPE(cp_sll_rs_type), POINTER :: pos
2001
2002 IF (index == 1) THEN
2003 CALL cp_sll_rs_rm_first_el(sll)
2004 ELSE
2005 IF (index == -1) THEN
2006 pos => cp_sll_rs_get_rest(sll, iter=-1)
2007 ELSE
2008 pos => cp_sll_rs_get_rest(sll, iter=index - 2)
2009 END IF
2010 cpassert(ASSOCIATED(pos))
2011 CALL cp_sll_rs_rm_first_el(pos%rest)
2012 END IF
2013 END SUBROUTINE cp_sll_rs_rm_el_at
2014
2015! **************************************************************************************************
2016!> \brief removes all the elements from the list
2017!> \param sll the list that should be removed
2018!> \par History
2019!> none
2020!> \author Fawzi Mohamed
2021!> \note
2022!> check more?
2023! **************************************************************************************************
2025 TYPE(cp_sll_3d_r_type), POINTER :: sll
2026
2027 TYPE(cp_sll_3d_r_type), POINTER :: next_node, actual_node
2028
2029 actual_node => sll
2030 DO
2031 IF (.NOT. ASSOCIATED(actual_node)) EXIT
2032 next_node => actual_node%rest
2033 CALL cp_sll_3d_r_dealloc_node(actual_node)
2034 actual_node => next_node
2035 END DO
2036 NULLIFY (sll)
2037 END SUBROUTINE cp_sll_3d_r_rm_all_el
2038! **************************************************************************************************
2039!> \brief removes all the elements from the list
2040!> \param sll the list that should be removed
2041!> \par History
2042!> none
2043!> \author Fawzi Mohamed
2044!> \note
2045!> check more?
2046! **************************************************************************************************
2048 TYPE(cp_sll_3d_c_type), POINTER :: sll
2049
2050 TYPE(cp_sll_3d_c_type), POINTER :: next_node, actual_node
2051
2052 actual_node => sll
2053 DO
2054 IF (.NOT. ASSOCIATED(actual_node)) EXIT
2055 next_node => actual_node%rest
2056 CALL cp_sll_3d_c_dealloc_node(actual_node)
2057 actual_node => next_node
2058 END DO
2059 NULLIFY (sll)
2060 END SUBROUTINE cp_sll_3d_c_rm_all_el
2061! **************************************************************************************************
2062!> \brief removes all the elements from the list
2063!> \param sll the list that should be removed
2064!> \par History
2065!> none
2066!> \author Fawzi Mohamed
2067!> \note
2068!> check more?
2069! **************************************************************************************************
2071 TYPE(cp_sll_1d_r_type), POINTER :: sll
2072
2073 TYPE(cp_sll_1d_r_type), POINTER :: next_node, actual_node
2074
2075 actual_node => sll
2076 DO
2077 IF (.NOT. ASSOCIATED(actual_node)) EXIT
2078 next_node => actual_node%rest
2079 CALL cp_sll_1d_r_dealloc_node(actual_node)
2080 actual_node => next_node
2081 END DO
2082 NULLIFY (sll)
2083 END SUBROUTINE cp_sll_1d_r_rm_all_el
2084! **************************************************************************************************
2085!> \brief removes all the elements from the list
2086!> \param sll the list that should be removed
2087!> \par History
2088!> none
2089!> \author Fawzi Mohamed
2090!> \note
2091!> check more?
2092! **************************************************************************************************
2094 TYPE(cp_sll_1d_c_type), POINTER :: sll
2095
2096 TYPE(cp_sll_1d_c_type), POINTER :: next_node, actual_node
2097
2098 actual_node => sll
2099 DO
2100 IF (.NOT. ASSOCIATED(actual_node)) EXIT
2101 next_node => actual_node%rest
2102 CALL cp_sll_1d_c_dealloc_node(actual_node)
2103 actual_node => next_node
2104 END DO
2105 NULLIFY (sll)
2106 END SUBROUTINE cp_sll_1d_c_rm_all_el
2107! **************************************************************************************************
2108!> \brief removes all the elements from the list
2109!> \param sll the list that should be removed
2110!> \par History
2111!> none
2112!> \author Fawzi Mohamed
2113!> \note
2114!> check more?
2115! **************************************************************************************************
2116 SUBROUTINE cp_sll_rs_rm_all_el(sll)
2117 TYPE(cp_sll_rs_type), POINTER :: sll
2118
2119 TYPE(cp_sll_rs_type), POINTER :: next_node, actual_node
2120
2121 actual_node => sll
2122 DO
2123 IF (.NOT. ASSOCIATED(actual_node)) EXIT
2124 next_node => actual_node%rest
2125 CALL cp_sll_rs_dealloc_node(actual_node)
2126 actual_node => next_node
2127 END DO
2128 NULLIFY (sll)
2129 END SUBROUTINE cp_sll_rs_rm_all_el
2130
2131! **************************************************************************************************
2132!> \brief returns a newly allocated array with the same contents as
2133!> the linked list
2134!> \param sll the list to transform in array
2135!> \return ...
2136!> \par History
2137!> 07.2002 created [fawzi]
2138!> \author Fawzi Mohamed
2139! **************************************************************************************************
2140 FUNCTION cp_sll_3d_r_to_array(sll) RESULT(res)
2141 TYPE(cp_sll_3d_r_type), POINTER :: sll
2142 type(cp_3d_r_cp_type), DIMENSION(:), POINTER :: res
2143
2144 INTEGER :: len, i
2145 LOGICAL :: ok
2146 TYPE(cp_sll_3d_r_type), POINTER :: iter
2147
2148 len = cp_sll_3d_r_get_length(sll)
2149 ALLOCATE (res(len))
2150 iter => sll
2151 DO i = 1, len
2152 res(i) %array=>iter%first_el
2153 ok = cp_sll_3d_r_next(iter)
2154 cpassert(ok .OR. i == len)
2155 END DO
2156 END FUNCTION cp_sll_3d_r_to_array
2157! **************************************************************************************************
2158!> \brief returns a newly allocated array with the same contents as
2159!> the linked list
2160!> \param sll the list to transform in array
2161!> \return ...
2162!> \par History
2163!> 07.2002 created [fawzi]
2164!> \author Fawzi Mohamed
2165! **************************************************************************************************
2166 FUNCTION cp_sll_3d_c_to_array(sll) RESULT(res)
2167 TYPE(cp_sll_3d_c_type), POINTER :: sll
2168 type(cp_3d_c_cp_type), DIMENSION(:), POINTER :: res
2169
2170 INTEGER :: len, i
2171 LOGICAL :: ok
2172 TYPE(cp_sll_3d_c_type), POINTER :: iter
2173
2174 len = cp_sll_3d_c_get_length(sll)
2175 ALLOCATE (res(len))
2176 iter => sll
2177 DO i = 1, len
2178 res(i) %array=>iter%first_el
2179 ok = cp_sll_3d_c_next(iter)
2180 cpassert(ok .OR. i == len)
2181 END DO
2182 END FUNCTION cp_sll_3d_c_to_array
2183! **************************************************************************************************
2184!> \brief returns a newly allocated array with the same contents as
2185!> the linked list
2186!> \param sll the list to transform in array
2187!> \return ...
2188!> \par History
2189!> 07.2002 created [fawzi]
2190!> \author Fawzi Mohamed
2191! **************************************************************************************************
2192 FUNCTION cp_sll_1d_r_to_array(sll) RESULT(res)
2193 TYPE(cp_sll_1d_r_type), POINTER :: sll
2194 type(cp_1d_r_cp_type), DIMENSION(:), POINTER :: res
2195
2196 INTEGER :: len, i
2197 LOGICAL :: ok
2198 TYPE(cp_sll_1d_r_type), POINTER :: iter
2199
2200 len = cp_sll_1d_r_get_length(sll)
2201 ALLOCATE (res(len))
2202 iter => sll
2203 DO i = 1, len
2204 res(i) %array=>iter%first_el
2205 ok = cp_sll_1d_r_next(iter)
2206 cpassert(ok .OR. i == len)
2207 END DO
2208 END FUNCTION cp_sll_1d_r_to_array
2209! **************************************************************************************************
2210!> \brief returns a newly allocated array with the same contents as
2211!> the linked list
2212!> \param sll the list to transform in array
2213!> \return ...
2214!> \par History
2215!> 07.2002 created [fawzi]
2216!> \author Fawzi Mohamed
2217! **************************************************************************************************
2218 FUNCTION cp_sll_1d_c_to_array(sll) RESULT(res)
2219 TYPE(cp_sll_1d_c_type), POINTER :: sll
2220 type(cp_1d_c_cp_type), DIMENSION(:), POINTER :: res
2221
2222 INTEGER :: len, i
2223 LOGICAL :: ok
2224 TYPE(cp_sll_1d_c_type), POINTER :: iter
2225
2226 len = cp_sll_1d_c_get_length(sll)
2227 ALLOCATE (res(len))
2228 iter => sll
2229 DO i = 1, len
2230 res(i) %array=>iter%first_el
2231 ok = cp_sll_1d_c_next(iter)
2232 cpassert(ok .OR. i == len)
2233 END DO
2234 END FUNCTION cp_sll_1d_c_to_array
2235! **************************************************************************************************
2236!> \brief returns a newly allocated array with the same contents as
2237!> the linked list
2238!> \param sll the list to transform in array
2239!> \return ...
2240!> \par History
2241!> 07.2002 created [fawzi]
2242!> \author Fawzi Mohamed
2243! **************************************************************************************************
2244 FUNCTION cp_sll_rs_to_array(sll) RESULT(res)
2245 TYPE(cp_sll_rs_type), POINTER :: sll
2246 type(realspace_grid_p_type), DIMENSION(:), POINTER :: res
2247
2248 INTEGER :: len, i
2249 LOGICAL :: ok
2250 TYPE(cp_sll_rs_type), POINTER :: iter
2251
2252 len = cp_sll_rs_get_length(sll)
2253 ALLOCATE (res(len))
2254 iter => sll
2255 DO i = 1, len
2256 res(i) %rs_grid=>iter%first_el
2257 ok = cp_sll_rs_next(iter)
2258 cpassert(ok .OR. i == len)
2259 END DO
2260 END FUNCTION cp_sll_rs_to_array
2261END MODULE cp_linked_list_pw
various utilities that regard array of different kinds: output, allocation,... maybe it is not a good...
subroutine, public cp_sll_3d_c_rm_el_at(sll, index)
removes the element at the given index
integer function, public cp_sll_1d_r_get_length(sll)
returns the length of the list
real(kind=dp) function, dimension(:), pointer, contiguous, public cp_sll_1d_r_get_el_at(sll, index)
returns the element at the given index
subroutine, public cp_sll_1d_r_insert_el_at(sll, el, index)
inserts the element at the given index
subroutine, public cp_sll_1d_c_dealloc(sll)
deallocates the singly linked list starting at sll. Does not work if loops are present!
integer function, public cp_sll_3d_r_get_length(sll)
returns the length of the list
integer function, public cp_sll_3d_c_get_length(sll)
returns the length of the list
subroutine, public cp_sll_rs_insert_el(sll, el)
insert an element at the beginning of the list
subroutine, public cp_sll_3d_r_insert_el_at(sll, el, index)
inserts the element at the given index
subroutine, public cp_sll_3d_r_set_el_at(sll, index, value)
sets the element at the given index
subroutine, public cp_sll_1d_r_rm_first_el(sll)
remove the first element of the linked list
type(cp_3d_r_cp_type) function, dimension(:), pointer, public cp_sll_3d_r_to_array(sll)
returns a newly allocated array with the same contents as the linked list
subroutine, public cp_sll_1d_r_dealloc(sll)
deallocates the singly linked list starting at sll. Does not work if loops are present!
subroutine, public cp_sll_1d_c_insert_el(sll, el)
insert an element at the beginning of the list
subroutine, public cp_sll_rs_rm_all_el(sll)
removes all the elements from the list
subroutine, public cp_sll_3d_c_set_el_at(sll, index, value)
sets the element at the given index
subroutine, public cp_sll_3d_r_rm_all_el(sll)
removes all the elements from the list
subroutine, public cp_sll_1d_c_set_el_at(sll, index, value)
sets the element at the given index
subroutine, public cp_sll_3d_c_create(sll, first_el, rest)
allocates and initializes a single linked list
subroutine, public cp_sll_3d_c_rm_first_el(sll)
remove the first element of the linked list
type(cp_1d_r_cp_type) function, dimension(:), pointer, public cp_sll_1d_r_to_array(sll)
returns a newly allocated array with the same contents as the linked list
type(cp_sll_1d_r_type) function, pointer, public cp_sll_1d_r_get_rest(sll, iter)
returns the rest of the list
real(kind=dp) function, dimension(:), pointer, contiguous, public cp_sll_1d_r_get_first_el(sll)
returns the first element stored in the list
subroutine, public cp_sll_1d_c_rm_all_el(sll)
removes all the elements from the list
subroutine, public cp_sll_rs_dealloc(sll)
deallocates the singly linked list starting at sll. Does not work if loops are present!
subroutine, public cp_sll_3d_c_insert_el_at(sll, el, index)
inserts the element at the given index
logical function, public cp_sll_3d_c_next(iterator, el_att)
returns true if the actual element is valid (i.e. iterator ont at end) moves the iterator to the next...
integer function, public cp_sll_rs_get_length(sll)
returns the length of the list
type(realspace_grid_type) function, pointer, public cp_sll_rs_get_first_el(sll)
returns the first element stored in the list
subroutine, public cp_sll_1d_r_rm_el_at(sll, index)
removes the element at the given index
subroutine, public cp_sll_1d_c_rm_el_at(sll, index)
removes the element at the given index
real(kind=dp) function, dimension(:,:,:), pointer, contiguous, public cp_sll_3d_r_get_el_at(sll, index)
returns the element at the given index
subroutine, public cp_sll_rs_rm_first_el(sll)
remove the first element of the linked list
complex(kind=dp) function, dimension(:,:,:), pointer, contiguous, public cp_sll_3d_c_get_el_at(sll, index)
returns the element at the given index
logical function, public cp_sll_rs_next(iterator, el_att)
returns true if the actual element is valid (i.e. iterator ont at end) moves the iterator to the next...
logical function, public cp_sll_1d_r_next(iterator, el_att)
returns true if the actual element is valid (i.e. iterator ont at end) moves the iterator to the next...
subroutine, public cp_sll_3d_c_rm_all_el(sll)
removes all the elements from the list
complex(kind=dp) function, dimension(:), pointer, contiguous, public cp_sll_1d_c_get_first_el(sll)
returns the first element stored in the list
subroutine, public cp_sll_1d_r_set_el_at(sll, index, value)
sets the element at the given index
complex(kind=dp) function, dimension(:), pointer, contiguous, public cp_sll_1d_c_get_el_at(sll, index)
returns the element at the given index
subroutine, public cp_sll_3d_r_rm_el_at(sll, index)
removes the element at the given index
subroutine, public cp_sll_3d_r_insert_el(sll, el)
insert an element at the beginning of the list
subroutine, public cp_sll_1d_c_create(sll, first_el, rest)
allocates and initializes a single linked list
subroutine, public cp_sll_rs_rm_el_at(sll, index)
removes the element at the given index
subroutine, public cp_sll_1d_c_rm_first_el(sll)
remove the first element of the linked list
subroutine, public cp_sll_3d_c_dealloc(sll)
deallocates the singly linked list starting at sll. Does not work if loops are present!
logical function, public cp_sll_3d_r_next(iterator, el_att)
returns true if the actual element is valid (i.e. iterator ont at end) moves the iterator to the next...
subroutine, public cp_sll_rs_insert_el_at(sll, el, index)
inserts the element at the given index
subroutine, public cp_sll_rs_create(sll, first_el, rest)
allocates and initializes a single linked list
integer function, public cp_sll_1d_c_get_length(sll)
returns the length of the list
complex(kind=dp) function, dimension(:,:,:), pointer, contiguous, public cp_sll_3d_c_get_first_el(sll)
returns the first element stored in the list
type(cp_sll_1d_c_type) function, pointer, public cp_sll_1d_c_get_rest(sll, iter)
returns the rest of the list
type(realspace_grid_p_type) function, dimension(:), pointer, public cp_sll_rs_to_array(sll)
returns a newly allocated array with the same contents as the linked list
type(cp_3d_c_cp_type) function, dimension(:), pointer, public cp_sll_3d_c_to_array(sll)
returns a newly allocated array with the same contents as the linked list
real(kind=dp) function, dimension(:,:,:), pointer, contiguous, public cp_sll_3d_r_get_first_el(sll)
returns the first element stored in the list
type(cp_1d_c_cp_type) function, dimension(:), pointer, public cp_sll_1d_c_to_array(sll)
returns a newly allocated array with the same contents as the linked list
type(cp_sll_3d_c_type) function, pointer, public cp_sll_3d_c_get_rest(sll, iter)
returns the rest of the list
subroutine, public cp_sll_1d_r_insert_el(sll, el)
insert an element at the beginning of the list
subroutine, public cp_sll_3d_c_insert_el(sll, el)
insert an element at the beginning of the list
subroutine, public cp_sll_rs_set_el_at(sll, index, value)
sets the element at the given index
subroutine, public cp_sll_1d_c_insert_el_at(sll, el, index)
inserts the element at the given index
subroutine, public cp_sll_1d_r_rm_all_el(sll)
removes all the elements from the list
subroutine, public cp_sll_3d_r_rm_first_el(sll)
remove the first element of the linked list
subroutine, public cp_sll_1d_r_create(sll, first_el, rest)
allocates and initializes a single linked list
type(cp_sll_3d_r_type) function, pointer, public cp_sll_3d_r_get_rest(sll, iter)
returns the rest of the list
subroutine, public cp_sll_3d_r_dealloc(sll)
deallocates the singly linked list starting at sll. Does not work if loops are present!
type(cp_sll_rs_type) function, pointer, public cp_sll_rs_get_rest(sll, iter)
returns the rest of the list
type(realspace_grid_type) function, pointer, public cp_sll_rs_get_el_at(sll, index)
returns the element at the given index
logical function, public cp_sll_1d_c_next(iterator, el_att)
returns true if the actual element is valid (i.e. iterator ont at end) moves the iterator to the next...
subroutine, public cp_sll_3d_r_create(sll, first_el, rest)
allocates and initializes a single linked list
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
An array-based list which grows on demand. When the internal array is full, a new array of twice the ...
Definition list.F:24
represent a pointer to a contiguous 1d array
represent a pointer to a contiguous 1d array
represent a pointer to a contiguous 3d array
represent a pointer to a contiguous 3d array
pointer to a linked list (to make arrays of pointers)
represent a single linked list that stores pointers to the elements
pointer to a linked list (to make arrays of pointers)
represent a single linked list that stores pointers to the elements
pointer to a linked list (to make arrays of pointers)
represent a single linked list that stores pointers to the elements
pointer to a linked list (to make arrays of pointers)
represent a single linked list that stores pointers to the elements
pointer to a linked list (to make arrays of pointers)
represent a single linked list that stores pointers to the elements