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