11#include "../base/base_uses.f90"
30 LOGICAL,
PRIVATE,
PARAMETER :: debug_this_module = .true.
93 INTERFACE cp_insert_at
169 type(
cp_fm_type),
pointer,
OPTIONAL :: first_el
172 IF (.NOT.
PRESENT(first_el))
THEN
174 IF (
PRESENT(rest)) sll => rest
177 sll%first_el =>first_el
179 IF (
PRESENT(rest)) sll%rest => rest
209 SUBROUTINE cp_sll_fm_dealloc_node(sll)
213 END SUBROUTINE cp_sll_fm_dealloc_node
246 INTEGER,
OPTIONAL :: iter
252 IF (.NOT.
ASSOCIATED(sll))
THEN
255 IF (
PRESENT(iter))
THEN
258 IF (
ASSOCIATED(res%rest))
THEN
261 cpabort(
"tried to go past end")
266 IF (.NOT.
ASSOCIATED(res%rest))
EXIT
295 IF (
ASSOCIATED(iterator))
THEN
297 iterator => iterator%rest
318 INTEGER,
INTENT(in) :: index
322 IF (index == -1)
THEN
327 cpassert(
ASSOCIATED(pos))
347 INTEGER,
INTENT(in) :: index
351 IF (index == -1)
THEN
356 cpassert(
ASSOCIATED(pos))
378 IF (
ASSOCIATED(iterator))
THEN
380 if (
present(el_att)) el_att =>iterator%first_el
381 iterator => iterator%rest
428 IF (
ASSOCIATED(sll))
THEN
430 CALL cp_sll_fm_dealloc_node(node_to_rm)
432 cpabort(
"tried to remove first el of an empty list")
450 INTEGER,
INTENT(in) :: index
458 IF (index == -1)
THEN
463 cpassert(
ASSOCIATED(pos))
480 INTEGER,
INTENT(in)::index
487 IF (index == -1)
THEN
492 cpassert(
ASSOCIATED(pos))
513 IF (.NOT.
ASSOCIATED(actual_node))
EXIT
514 next_node => actual_node%rest
515 CALL cp_sll_fm_dealloc_node(actual_node)
516 actual_node => next_node
542 res(i) %matrix=>iter%first_el
544 cpassert(ok .OR. i == len)
represent a full matrix distributed on many processors
integer function, public cp_sll_fm_get_length(sll)
returns the length of the list
subroutine, public cp_sll_fm_insert_el(sll, el)
insert an element at the beginning of the list
subroutine, public cp_sll_fm_rm_el_at(sll, index)
removes the element at the given index
subroutine, public cp_sll_fm_rm_all_el(sll)
removes all the elements from the list
subroutine, public cp_sll_fm_create(sll, first_el, rest)
allocates and initializes a single linked list
type(cp_sll_fm_type) function, pointer, public cp_sll_fm_get_rest(sll, iter)
returns the rest of the list
logical function, public cp_sll_fm_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_fm_insert_el_at(sll, el, index)
inserts the element at the given index
type(cp_fm_p_type) function, dimension(:), pointer, public cp_sll_fm_to_array(sll)
returns a newly allocated array with the same contents as the linked list
type(cp_fm_type) function, pointer, public cp_sll_fm_get_first_el(sll)
returns the first element stored in the list
subroutine, public cp_sll_fm_dealloc(sll)
deallocates the singly linked list starting at sll. Does not work if loops are present!
type(cp_fm_type) function, pointer, public cp_sll_fm_get_el_at(sll, index)
returns the element at the given index
subroutine, public cp_sll_fm_set_el_at(sll, index, value)
sets the element at the given index
subroutine, public cp_sll_fm_rm_first_el(sll)
remove the first element of the linked list
An array-based list which grows on demand. When the internal array is full, a new array of twice the ...
just to build arrays of pointers to matrices
pointer to a linked list (to make arrays of pointers)
represent a single linked list that stores pointers to the elements