(git:ab76537)
Loading...
Searching...
No Matches
cp_linked_list_fm.F
Go to the documentation of this file.
1!--------------------------------------------------------------------------------------------------!
2! CP2K: A general program to perform molecular dynamics simulations !
3! Copyright 2000-2025 CP2K developers group <https://cp2k.org> !
4! !
5! SPDX-License-Identifier: GPL-2.0-or-later !
6!--------------------------------------------------------------------------------------------------!
7
8
11#include "../base/base_uses.f90"
12
13
14! **************************************************************************************************
15!> \brief describes a generic linked list template.
16!> Linked list are supposed to always use pointers to the nodes for
17!> basically everything: a pointer to the node is a list, an element of
18!> the list, an iterator between the elment of the list.
19!> An empty list is represented by an unassociated pointer.
20!> \par History
21!> 1.2002 created
22!> 4.2002 changed most of the methods, by making access to the list
23!> always through pointers (identifying pointer, list and iterators)
24!> 6.2004 removed %initialized from list elements
25!> \author Fawzi Mohamed
26! **************************************************************************************************
27 IMPLICIT NONE
28 PRIVATE
29
30 LOGICAL, PRIVATE, PARAMETER :: debug_this_module = .true.
31
32
33!API type
35
36!API common methods
37 PUBLIC :: cp_create, cp_dealloc, cp_next
38!API special get
40!API special set
41 PUBLIC :: cp_set_element_at
42!API structure manipulation
44
45 !API underlying routines
46
56
57! creation of an object (from a pointer)
58 INTERFACE cp_create
59 MODULE PROCEDURE cp_sll_fm_create
60 END INTERFACE
61! destruction of an object (from a pointer)
62 INTERFACE cp_dealloc
63 MODULE PROCEDURE cp_sll_fm_dealloc
64 END INTERFACE
65! iterates to the next element
66 INTERFACE cp_next
67 MODULE PROCEDURE cp_sll_fm_next
68 END INTERFACE
69! returns the first element
71 MODULE PROCEDURE cp_sll_fm_get_first_el
72 END INTERFACE
73! returns the rest of the list
74 INTERFACE cp_get_rest
75 MODULE PROCEDURE cp_sll_fm_get_rest
76 END INTERFACE
77! returns the length of the list
78 INTERFACE cp_get_length
79 MODULE PROCEDURE cp_sll_fm_get_length
80 END INTERFACE
81! returns the element at the given position
83 MODULE PROCEDURE cp_sll_fm_get_el_at
84 END INTERFACE
85! sets the element at the given position
87 MODULE PROCEDURE cp_sll_fm_set_el_at
88 END INTERFACE
89! inserts one element call cp_insert(list,element,...)
90 INTERFACE cp_insert
91 MODULE PROCEDURE cp_sll_fm_insert_el
92 END INTERFACE
93 INTERFACE cp_insert_at
94 MODULE PROCEDURE cp_sll_fm_insert_el_at
95 END INTERFACE
96! removes an element
97 INTERFACE cp_remove_el
98 MODULE PROCEDURE cp_sll_fm_rm_first_el, &
100 END INTERFACE
101! removes the first el
103 MODULE PROCEDURE cp_sll_fm_rm_first_el
104 END INTERFACE
105! remove all the elements
107 MODULE PROCEDURE cp_sll_fm_rm_all_el
108 END INTERFACE
109! transorms the list in array
110 INTERFACE cp_to_array
111 module procedure cp_sll_fm_to_array
112 END INTERFACE
113
114! **************************************************************************************************
115!> \brief represent a single linked list that stores pointers to the elements
116!> \param first_el the element that is stored in this node.
117!> \param rest the rest of the list
118!>
119!> \param empty true if the list pointer is not associated, if it points to
120!> to a not it is always false (as there is at least the
121!> first_el in the list)
122!> \param length the number of elements in the list
123!> \note
124!> List are alway accessed through pointers, so every node of the
125!> linked list can be seen as a list, its first element
126!> a pointer to the position before itself, in a very natural way:
127!> all the insertions take place before the actual element, and
128!> you still can insert an element at the end.
129!> This way I could identify nodes, lists and pointers between the
130!> elements of the list.
131!> Indexing is 1 based.
132!> \par History
133!> none
134!> \author Fawzi Mohamed
135! **************************************************************************************************
137 type(cp_fm_type),pointer :: first_el => null()
138 TYPE(cp_sll_fm_type), POINTER :: rest => null()
139 END TYPE cp_sll_fm_type
140
141! **************************************************************************************************
142!> \brief pointer to a linked list (to make arrays of pointers)
143!> \param list the pointer to the list
144!> \par History
145!> none
146!> \author Fawzi Mohamed
147! **************************************************************************************************
149 TYPE(cp_sll_fm_type), POINTER :: list => null()
150 END TYPE cp_sll_fm_p_type
151
152 CONTAINS
153
154 ! this comment prevents trailing whitespace
155
156! =========== creation / destruction ========
157
158! **************************************************************************************************
159!> \brief allocates and initializes a single linked list
160!> \param sll the single linked list to initialize
161!> \param first_el the first element of this list
162!> \param rest the following elements (if not given: empty)
163!> \par History
164!> none
165!> \author Fawzi Mohamed
166! **************************************************************************************************
167 SUBROUTINE cp_sll_fm_create(sll, first_el, rest)
168 TYPE(cp_sll_fm_type), POINTER :: sll
169 type(cp_fm_type),pointer, OPTIONAL :: first_el
170 TYPE(cp_sll_fm_type), POINTER, OPTIONAL :: rest
171
172 IF (.NOT. PRESENT(first_el)) THEN
173 NULLIFY (sll)
174 IF (PRESENT(rest)) sll => rest
175 ELSE
176 ALLOCATE (sll)
177 sll%first_el =>first_el
178 NULLIFY (sll%rest)
179 IF (PRESENT(rest)) sll%rest => rest
180 END IF
181 END SUBROUTINE cp_sll_fm_create
182
183! **************************************************************************************************
184!> \brief deallocates the singly linked list starting at sll.
185!> Does not work if loops are present!
186!> \param sll the list to be deallocated
187!> \par History
188!> none
189!> \author Fawzi Mohamed
190!> \note
191!> does not deallocate the elements that are stored in the list
192!> check more?
193! **************************************************************************************************
194 SUBROUTINE cp_sll_fm_dealloc(sll)
195 TYPE(cp_sll_fm_type), POINTER :: sll
196
197 CALL cp_sll_fm_rm_all_el(sll)
198 END SUBROUTINE cp_sll_fm_dealloc
199
200! * low-level *
201
202! **************************************************************************************************
203!> \brief deallocates a node of a singly linked list (low level)
204!> \param sll the node to be deallocated
205!> \par History
206!> none
207!> \author Fawzi Mohamed
208! **************************************************************************************************
209 SUBROUTINE cp_sll_fm_dealloc_node(sll)
210 TYPE(cp_sll_fm_type), POINTER :: sll
211
212 DEALLOCATE (sll)
213 END SUBROUTINE cp_sll_fm_dealloc_node
214
215! ============= get/set ============
216
217! **************************************************************************************************
218!> \brief returns the first element stored in the list
219!> \param sll the single linked list to get the element from
220!> \return ...
221!> \par History
222!> none
223!> \author Fawzi Mohamed
224! **************************************************************************************************
225 FUNCTION cp_sll_fm_get_first_el(sll) RESULT(res)
226 TYPE(cp_sll_fm_type), POINTER :: sll
227 type(cp_fm_type),pointer :: res
228
229 res =>sll%first_el
230 END FUNCTION cp_sll_fm_get_first_el
231
232! **************************************************************************************************
233!> \brief returns the rest of the list
234!> \param sll the single linked list to get the rest from
235!> \param iter how many times the call to rest should be iterated,
236!> defaults to 1; -1 means till end of the list.
237!> \return ...
238!> \par History
239!> none
240!> \author Fawzi Mohamed
241!> \note
242!> split the case iter=1 to make it more optimized?
243! **************************************************************************************************
244 FUNCTION cp_sll_fm_get_rest(sll, iter) RESULT(res)
245 TYPE(cp_sll_fm_type), POINTER :: sll
246 INTEGER, OPTIONAL :: iter
247
248 TYPE(cp_sll_fm_type), POINTER :: res
249
250 INTEGER :: i
251
252 IF (.NOT. ASSOCIATED(sll)) THEN
253 NULLIFY (res)
254 ELSE
255 IF (PRESENT(iter)) THEN
256 res => sll
257 DO i = 1, iter
258 IF (ASSOCIATED(res%rest)) THEN
259 res => res%rest
260 ELSE
261 cpabort("tried to go past end")
262 END IF
263 END DO
264 IF (iter == -1) THEN
265 DO
266 IF (.NOT. ASSOCIATED(res%rest)) EXIT
267 res => res%rest
268 END DO
269 END IF
270 ELSE
271 res => sll%rest ! make the common case fast...
272 END IF
273 END IF
274 END FUNCTION cp_sll_fm_get_rest
275
276! **************************************************************************************************
277!> \brief returns the length of the list
278!> \param sll the list you want to know the length of
279!> \return ...
280!> \par History
281!> none
282!> \author Fawzi Mohamed
283!> \note
284!> slow (O(n))
285! **************************************************************************************************
286 FUNCTION cp_sll_fm_get_length(sll) RESULT(res)
287 TYPE(cp_sll_fm_type), pointer :: sll
288 INTEGER ::res
289
290 TYPE(cp_sll_fm_type), POINTER :: iterator
291
292 res = 0
293 iterator => sll
294 DO
295 IF (ASSOCIATED(iterator)) THEN
296 res = res + 1
297 iterator => iterator%rest
298 ELSE
299 EXIT
300 END IF
301 END DO
302 END FUNCTION cp_sll_fm_get_length
303
304! **************************************************************************************************
305!> \brief returns the element at the given index
306!> \param sll the list you get the element from
307!> \param index the position of the element (stating at 1)
308!> \return ...
309!> \par History
310!> none
311!> \author Fawzi Mohamed
312!> \note
313!> slow (O(index))
314! **************************************************************************************************
315 FUNCTION cp_sll_fm_get_el_at(sll, index) RESULT(res)
316 type(cp_fm_type),pointer :: res
317 TYPE(cp_sll_fm_type), POINTER :: sll
318 INTEGER, INTENT(in) :: index
319
320 TYPE(cp_sll_fm_type), POINTER :: pos
321
322 IF (index == -1) THEN
323 pos => cp_sll_fm_get_rest(sll, iter=-1)
324 ELSE
325 pos => cp_sll_fm_get_rest(sll, iter=index - 1)
326 END IF
327 cpassert(ASSOCIATED(pos))
328
329 res =>pos%first_el
330 END FUNCTION cp_sll_fm_get_el_at
331
332! **************************************************************************************************
333!> \brief sets the element at the given index
334!> \param sll the list you get the element from
335!> \param index the position of the element (stating at 1)
336!> -1 means at the end
337!> \param value the new element
338!> \par History
339!> none
340!> \author Fawzi Mohamed
341!> \note
342!> slow (O(index))
343! **************************************************************************************************
344 SUBROUTINE cp_sll_fm_set_el_at(sll, index, value)
345 type(cp_fm_type),pointer :: value
346 TYPE(cp_sll_fm_type), POINTER :: sll
347 INTEGER, INTENT(in) :: index
348
349 TYPE(cp_sll_fm_type), POINTER :: pos
350
351 IF (index == -1) THEN
352 pos => cp_sll_fm_get_rest(sll, iter=-1)
353 ELSE
354 pos => cp_sll_fm_get_rest(sll, iter=index - 1)
355 END IF
356 cpassert(ASSOCIATED(pos))
357
358 pos%first_el =>value
359 END SUBROUTINE cp_sll_fm_set_el_at
360
361! * iteration *
362
363! **************************************************************************************************
364!> \brief returns true if the actual element is valid (i.e. iterator ont at end)
365!> moves the iterator to the next element
366!> \param iterator iterator that moves along the list
367!> \param el_att the actual element (valid only if the function returns true)
368!> \return ...
369!> \par History
370!> none
371!> \author Fawzi Mohamed
372! **************************************************************************************************
373 FUNCTION cp_sll_fm_next(iterator, el_att) RESULT(res)
374 TYPE(cp_sll_fm_type), POINTER :: iterator
375 type(cp_fm_type),pointer, OPTIONAL :: el_att
376 LOGICAL :: res
377
378 IF (ASSOCIATED(iterator)) THEN
379 res = .true.
380 if (present(el_att)) el_att =>iterator%first_el
381 iterator => iterator%rest
382 ELSE
383 res = .false.
384 END IF
385 END FUNCTION cp_sll_fm_next
386
387! ============ structure modifications ============
388
389! **************************************************************************************************
390!> \brief insert an element at the beginning of the list
391!> \param sll the single linked list point at the beginning of which
392!> you want to add the element
393!> \param el the element to add
394!> \par History
395!> none
396!> \author Fawzi Mohamed
397!> \note
398!> fast (O(1))
399! **************************************************************************************************
400 SUBROUTINE cp_sll_fm_insert_el(sll, el)
401 TYPE(cp_sll_fm_type), POINTER :: sll
402 type(cp_fm_type),pointer:: el
403
404 TYPE(cp_sll_fm_type), POINTER :: newSlot
405
406 NULLIFY (newslot)
407
408 CALL cp_sll_fm_create(newslot, first_el=el, &
409 rest=sll)
410 sll => newslot
411 END SUBROUTINE cp_sll_fm_insert_el
412
413! **************************************************************************************************
414!> \brief remove the first element of the linked list
415!> \param sll the list whose first element has to be removed
416!> \par History
417!> none
418!> \author Fawzi Mohamed
419!> \note
420!> fast (O(1))
421! **************************************************************************************************
422 SUBROUTINE cp_sll_fm_rm_first_el(sll)
423 TYPE(cp_sll_fm_type), POINTER :: sll
424
425 TYPE(cp_sll_fm_type), POINTER :: node_to_rm
426 node_to_rm => sll
427
428 IF (ASSOCIATED(sll)) THEN
429 sll => sll%rest
430 CALL cp_sll_fm_dealloc_node(node_to_rm)
431 ELSE
432 cpabort("tried to remove first el of an empty list")
433 END IF
434 END SUBROUTINE cp_sll_fm_rm_first_el
435
436! **************************************************************************************************
437!> \brief inserts the element at the given index
438!> \param sll the list you get the element from
439!> \param el the new element
440!> \param index the position of the element (stating at 1).
441!> If it is -1, it means at end
442!> \par History
443!> none
444!> \author Fawzi Mohamed
445!> \note
446!> slow (O(index))
447! **************************************************************************************************
448 SUBROUTINE cp_sll_fm_insert_el_at(sll, el, index)
449 type(cp_fm_type),pointer :: el
450 INTEGER, INTENT(in) :: index
451 TYPE(cp_sll_fm_type), POINTER :: sll
452
453 TYPE(cp_sll_fm_type), POINTER :: pos
454
455 IF (index == 1) THEN
456 CALL cp_sll_fm_insert_el(sll, el)
457 ELSE
458 IF (index == -1) THEN
459 pos => cp_sll_fm_get_rest(sll, iter=-1)
460 ELSE
461 pos => cp_sll_fm_get_rest(sll, iter=index - 2)
462 END IF
463 cpassert(ASSOCIATED(pos))
464 CALL cp_sll_fm_insert_el(pos%rest, el)
465 END IF
466 END SUBROUTINE cp_sll_fm_insert_el_at
467
468! **************************************************************************************************
469!> \brief removes the element at the given index
470!> \param sll the list you get the element from
471!> \param index the position of the element (stating at 1)
472!> \par History
473!> none
474!> \author Fawzi Mohamed
475!> \note
476!> slow (O(index))
477! **************************************************************************************************
478 SUBROUTINE cp_sll_fm_rm_el_at(sll, index)
479 TYPE(cp_sll_fm_type), POINTER :: sll
480 INTEGER, INTENT(in)::index
481
482 TYPE(cp_sll_fm_type), POINTER :: pos
483
484 IF (index == 1) THEN
485 CALL cp_sll_fm_rm_first_el(sll)
486 ELSE
487 IF (index == -1) THEN
488 pos => cp_sll_fm_get_rest(sll, iter=-1)
489 ELSE
490 pos => cp_sll_fm_get_rest(sll, iter=index - 2)
491 END IF
492 cpassert(ASSOCIATED(pos))
493 CALL cp_sll_fm_rm_first_el(pos%rest)
494 END IF
495 END SUBROUTINE cp_sll_fm_rm_el_at
496
497! **************************************************************************************************
498!> \brief removes all the elements from the list
499!> \param sll the list that should be removed
500!> \par History
501!> none
502!> \author Fawzi Mohamed
503!> \note
504!> check more?
505! **************************************************************************************************
506 SUBROUTINE cp_sll_fm_rm_all_el(sll)
507 TYPE(cp_sll_fm_type), POINTER :: sll
508
509 TYPE(cp_sll_fm_type), POINTER :: next_node, actual_node
510
511 actual_node => sll
512 DO
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
517 END DO
518 NULLIFY (sll)
519 END SUBROUTINE cp_sll_fm_rm_all_el
520
521! **************************************************************************************************
522!> \brief returns a newly allocated array with the same contents as
523!> the linked list
524!> \param sll the list to transform in array
525!> \return ...
526!> \par History
527!> 07.2002 created [fawzi]
528!> \author Fawzi Mohamed
529! **************************************************************************************************
530 FUNCTION cp_sll_fm_to_array(sll) RESULT(res)
531 TYPE(cp_sll_fm_type), POINTER :: sll
532 type(cp_fm_p_type), DIMENSION(:), POINTER :: res
533
534 INTEGER :: len, i
535 LOGICAL :: ok
536 TYPE(cp_sll_fm_type), POINTER :: iter
537
538 len = cp_sll_fm_get_length(sll)
539 ALLOCATE (res(len))
540 iter => sll
541 DO i = 1, len
542 res(i) %matrix=>iter%first_el
543 ok = cp_sll_fm_next(iter)
544 cpassert(ok .OR. i == len)
545 END DO
546 END FUNCTION cp_sll_fm_to_array
547END MODULE cp_linked_list_fm
represent a full matrix distributed on many processors
Definition cp_fm_types.F:15
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 ...
Definition list.F:24
just to build arrays of pointers to matrices
represent a full matrix
pointer to a linked list (to make arrays of pointers)
represent a single linked list that stores pointers to the elements