(git:374b731)
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-2024 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
155! =========== creation / destruction ========
156
157! **************************************************************************************************
158!> \brief allocates and initializes a single linked list
159!> \param sll the single linked list to initialize
160!> \param first_el the first element of this list
161!> \param rest the following elements (if not given: empty)
162!> \par History
163!> none
164!> \author Fawzi Mohamed
165! **************************************************************************************************
166 SUBROUTINE cp_sll_fm_create(sll, first_el, rest)
167 TYPE(cp_sll_fm_type), POINTER :: sll
168 type(cp_fm_type),pointer, OPTIONAL :: first_el
169 TYPE(cp_sll_fm_type), POINTER, OPTIONAL :: rest
170
171 IF (.NOT. PRESENT(first_el)) THEN
172 NULLIFY (sll)
173 IF (PRESENT(rest)) sll => rest
174 ELSE
175 ALLOCATE (sll)
176 sll%first_el =>first_el
177 NULLIFY (sll%rest)
178 IF (PRESENT(rest)) sll%rest => rest
179 END IF
180 END SUBROUTINE cp_sll_fm_create
181
182! **************************************************************************************************
183!> \brief deallocates the singly linked list starting at sll.
184!> Does not work if loops are present!
185!> \param sll the list to be deallocated
186!> \par History
187!> none
188!> \author Fawzi Mohamed
189!> \note
190!> does not deallocate the elements that are stored in the list
191!> check more?
192! **************************************************************************************************
193 SUBROUTINE cp_sll_fm_dealloc(sll)
194 TYPE(cp_sll_fm_type), POINTER :: sll
195
196 CALL cp_sll_fm_rm_all_el(sll)
197 END SUBROUTINE cp_sll_fm_dealloc
198
199! * low-level *
200
201! **************************************************************************************************
202!> \brief deallocates a node of a singly linked list (low level)
203!> \param sll the node to be deallocated
204!> \par History
205!> none
206!> \author Fawzi Mohamed
207! **************************************************************************************************
208 SUBROUTINE cp_sll_fm_dealloc_node(sll)
209 TYPE(cp_sll_fm_type), POINTER :: sll
210
211 DEALLOCATE (sll)
212 END SUBROUTINE cp_sll_fm_dealloc_node
213
214! ============= get/set ============
215
216! **************************************************************************************************
217!> \brief returns the first element stored in the list
218!> \param sll the single linked list to get the element from
219!> \return ...
220!> \par History
221!> none
222!> \author Fawzi Mohamed
223! **************************************************************************************************
224 FUNCTION cp_sll_fm_get_first_el(sll) RESULT(res)
225 TYPE(cp_sll_fm_type), POINTER :: sll
226 type(cp_fm_type),pointer :: res
227
228 res =>sll%first_el
229 END FUNCTION cp_sll_fm_get_first_el
230
231! **************************************************************************************************
232!> \brief returns the rest of the list
233!> \param sll the single linked list to get the rest from
234!> \param iter how many times the call to rest should be iterated,
235!> defaults to 1; -1 means till end of the list.
236!> \return ...
237!> \par History
238!> none
239!> \author Fawzi Mohamed
240!> \note
241!> split the case iter=1 to make it more optimized?
242! **************************************************************************************************
243 FUNCTION cp_sll_fm_get_rest(sll, iter) RESULT(res)
244 TYPE(cp_sll_fm_type), POINTER :: sll
245 INTEGER, OPTIONAL :: iter
246
247 TYPE(cp_sll_fm_type), POINTER :: res
248
249 INTEGER :: i
250
251 IF (.NOT. ASSOCIATED(sll)) THEN
252 NULLIFY (res)
253 ELSE
254 IF (PRESENT(iter)) THEN
255 res => sll
256 DO i = 1, iter
257 IF (ASSOCIATED(res%rest)) THEN
258 res => res%rest
259 ELSE
260 cpabort("tried to go past end")
261 END IF
262 END DO
263 IF (iter == -1) THEN
264 DO
265 IF (.NOT. ASSOCIATED(res%rest)) EXIT
266 res => res%rest
267 END DO
268 END IF
269 ELSE
270 res => sll%rest ! make the common case fast...
271 END IF
272 END IF
273 END FUNCTION cp_sll_fm_get_rest
274
275! **************************************************************************************************
276!> \brief returns the length of the list
277!> \param sll the list you want to know the length of
278!> \return ...
279!> \par History
280!> none
281!> \author Fawzi Mohamed
282!> \note
283!> slow (O(n))
284! **************************************************************************************************
285 FUNCTION cp_sll_fm_get_length(sll) RESULT(res)
286 TYPE(cp_sll_fm_type), pointer :: sll
287 INTEGER ::res
288
289 TYPE(cp_sll_fm_type), POINTER :: iterator
290
291 res = 0
292 iterator => sll
293 DO
294 IF (ASSOCIATED(iterator)) THEN
295 res = res + 1
296 iterator => iterator%rest
297 ELSE
298 EXIT
299 END IF
300 END DO
301 END FUNCTION cp_sll_fm_get_length
302
303! **************************************************************************************************
304!> \brief returns the element at the given index
305!> \param sll the list you get the element from
306!> \param index the position of the element (stating at 1)
307!> \return ...
308!> \par History
309!> none
310!> \author Fawzi Mohamed
311!> \note
312!> slow (O(index))
313! **************************************************************************************************
314 FUNCTION cp_sll_fm_get_el_at(sll, index) RESULT(res)
315 type(cp_fm_type),pointer :: res
316 TYPE(cp_sll_fm_type), POINTER :: sll
317 INTEGER, INTENT(in) :: index
318
319 TYPE(cp_sll_fm_type), POINTER :: pos
320
321 IF (index == -1) THEN
322 pos => cp_sll_fm_get_rest(sll, iter=-1)
323 ELSE
324 pos => cp_sll_fm_get_rest(sll, iter=index - 1)
325 END IF
326 cpassert(ASSOCIATED(pos))
327
328 res =>pos%first_el
329 END FUNCTION cp_sll_fm_get_el_at
330
331! **************************************************************************************************
332!> \brief sets the element at the given index
333!> \param sll the list you get the element from
334!> \param index the position of the element (stating at 1)
335!> -1 means at the end
336!> \param value the new element
337!> \par History
338!> none
339!> \author Fawzi Mohamed
340!> \note
341!> slow (O(index))
342! **************************************************************************************************
343 SUBROUTINE cp_sll_fm_set_el_at(sll, index, value)
344 type(cp_fm_type),pointer :: value
345 TYPE(cp_sll_fm_type), POINTER :: sll
346 INTEGER, INTENT(in) :: index
347
348 TYPE(cp_sll_fm_type), POINTER :: pos
349
350 IF (index == -1) THEN
351 pos => cp_sll_fm_get_rest(sll, iter=-1)
352 ELSE
353 pos => cp_sll_fm_get_rest(sll, iter=index - 1)
354 END IF
355 cpassert(ASSOCIATED(pos))
356
357 pos%first_el =>value
358 END SUBROUTINE cp_sll_fm_set_el_at
359
360! * iteration *
361
362! **************************************************************************************************
363!> \brief returns true if the actual element is valid (i.e. iterator ont at end)
364!> moves the iterator to the next element
365!> \param iterator iterator that moves along the list
366!> \param el_att the actual element (valid only if the function returns true)
367!> \return ...
368!> \par History
369!> none
370!> \author Fawzi Mohamed
371! **************************************************************************************************
372 FUNCTION cp_sll_fm_next(iterator, el_att) RESULT(res)
373 TYPE(cp_sll_fm_type), POINTER :: iterator
374 type(cp_fm_type),pointer, OPTIONAL :: el_att
375 LOGICAL :: res
376
377 IF (ASSOCIATED(iterator)) THEN
378 res = .true.
379 if (present(el_att)) el_att =>iterator%first_el
380 iterator => iterator%rest
381 ELSE
382 res = .false.
383 END IF
384 END FUNCTION cp_sll_fm_next
385
386! ============ structure modifications ============
387
388! **************************************************************************************************
389!> \brief insert an element at the beginning of the list
390!> \param sll the single linked list point at the beginning of which
391!> you want to add the element
392!> \param el the element to add
393!> \par History
394!> none
395!> \author Fawzi Mohamed
396!> \note
397!> fast (O(1))
398! **************************************************************************************************
399 SUBROUTINE cp_sll_fm_insert_el(sll, el)
400 TYPE(cp_sll_fm_type), POINTER :: sll
401 type(cp_fm_type),pointer:: el
402
403 TYPE(cp_sll_fm_type), POINTER :: newSlot
404
405 NULLIFY (newslot)
406
407 CALL cp_sll_fm_create(newslot, first_el=el, &
408 rest=sll)
409 sll => newslot
410 END SUBROUTINE cp_sll_fm_insert_el
411
412! **************************************************************************************************
413!> \brief remove the first element of the linked list
414!> \param sll the list whose first element has to be removed
415!> \par History
416!> none
417!> \author Fawzi Mohamed
418!> \note
419!> fast (O(1))
420! **************************************************************************************************
421 SUBROUTINE cp_sll_fm_rm_first_el(sll)
422 TYPE(cp_sll_fm_type), POINTER :: sll
423
424 TYPE(cp_sll_fm_type), POINTER :: node_to_rm
425 node_to_rm => sll
426
427 IF (ASSOCIATED(sll)) THEN
428 sll => sll%rest
429 CALL cp_sll_fm_dealloc_node(node_to_rm)
430 ELSE
431 cpabort("tried to remove first el of an empty list")
432 END IF
433 END SUBROUTINE cp_sll_fm_rm_first_el
434
435! **************************************************************************************************
436!> \brief inserts the element at the given index
437!> \param sll the list you get the element from
438!> \param el the new element
439!> \param index the position of the element (stating at 1).
440!> If it is -1, it means at end
441!> \par History
442!> none
443!> \author Fawzi Mohamed
444!> \note
445!> slow (O(index))
446! **************************************************************************************************
447 SUBROUTINE cp_sll_fm_insert_el_at(sll, el, index)
448 type(cp_fm_type),pointer :: el
449 INTEGER, INTENT(in) :: index
450 TYPE(cp_sll_fm_type), POINTER :: sll
451
452 TYPE(cp_sll_fm_type), POINTER :: pos
453
454 IF (index == 1) THEN
455 CALL cp_sll_fm_insert_el(sll, el)
456 ELSE
457 IF (index == -1) THEN
458 pos => cp_sll_fm_get_rest(sll, iter=-1)
459 ELSE
460 pos => cp_sll_fm_get_rest(sll, iter=index - 2)
461 END IF
462 cpassert(ASSOCIATED(pos))
463 CALL cp_sll_fm_insert_el(pos%rest, el)
464 END IF
465 END SUBROUTINE cp_sll_fm_insert_el_at
466
467! **************************************************************************************************
468!> \brief removes the element at the given index
469!> \param sll the list you get the element from
470!> \param index the position of the element (stating at 1)
471!> \par History
472!> none
473!> \author Fawzi Mohamed
474!> \note
475!> slow (O(index))
476! **************************************************************************************************
477 SUBROUTINE cp_sll_fm_rm_el_at(sll, index)
478 TYPE(cp_sll_fm_type), POINTER :: sll
479 INTEGER, INTENT(in)::index
480
481 TYPE(cp_sll_fm_type), POINTER :: pos
482
483 IF (index == 1) THEN
484 CALL cp_sll_fm_rm_first_el(sll)
485 ELSE
486 IF (index == -1) THEN
487 pos => cp_sll_fm_get_rest(sll, iter=-1)
488 ELSE
489 pos => cp_sll_fm_get_rest(sll, iter=index - 2)
490 END IF
491 cpassert(ASSOCIATED(pos))
492 CALL cp_sll_fm_rm_first_el(pos%rest)
493 END IF
494 END SUBROUTINE cp_sll_fm_rm_el_at
495
496! **************************************************************************************************
497!> \brief removes all the elements from the list
498!> \param sll the list that should be removed
499!> \par History
500!> none
501!> \author Fawzi Mohamed
502!> \note
503!> check more?
504! **************************************************************************************************
505 SUBROUTINE cp_sll_fm_rm_all_el(sll)
506 TYPE(cp_sll_fm_type), POINTER :: sll
507
508 TYPE(cp_sll_fm_type), POINTER :: next_node, actual_node
509
510 actual_node => sll
511 DO
512 IF (.NOT. ASSOCIATED(actual_node)) EXIT
513 next_node => actual_node%rest
514 CALL cp_sll_fm_dealloc_node(actual_node)
515 actual_node => next_node
516 END DO
517 NULLIFY (sll)
518 END SUBROUTINE cp_sll_fm_rm_all_el
519
520! **************************************************************************************************
521!> \brief returns a newly allocated array with the same contents as
522!> the linked list
523!> \param sll the list to transform in array
524!> \return ...
525!> \par History
526!> 07.2002 created [fawzi]
527!> \author Fawzi Mohamed
528! **************************************************************************************************
529 FUNCTION cp_sll_fm_to_array(sll) RESULT(res)
530 TYPE(cp_sll_fm_type), POINTER :: sll
531 type(cp_fm_p_type), DIMENSION(:), POINTER :: res
532
533 INTEGER :: len, i
534 LOGICAL :: ok
535 TYPE(cp_sll_fm_type), POINTER :: iter
536
537 len = cp_sll_fm_get_length(sll)
538 ALLOCATE (res(len))
539 iter => sll
540 DO i = 1, len
541 res(i) %matrix=>iter%first_el
542 ok = cp_sll_fm_next(iter)
543 cpassert(ok .OR. i == len)
544 END DO
545 END FUNCTION cp_sll_fm_to_array
546END MODULE
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