(git:1f1a7a2)
Loading...
Searching...
No Matches
cp_output_handling_openpmd.F
Go to the documentation of this file.
1!--------------------------------------------------------------------------------------------------!
2! CP2K: A general program to perform molecular dynamics simulations !
3! Copyright 2000-2026 CP2K developers group <https://cp2k.org> !
4! !
5! SPDX-License-Identifier: GPL-2.0-or-later !
6!--------------------------------------------------------------------------------------------------!
7
8! **************************************************************************************************
9!> \brief routines to handle the output, The idea is to remove the
10!> decision of wheter to output and what to output from the code
11!> that does the output, and centralize it here.
12!> \note
13!> These were originally together with the log handling routines,
14!> but have been spawned off. Some dependencies are still there,
15!> and some of the comments about log handling also applies to output
16!> handling: @see cp_log_handling
17! **************************************************************************************************
20 USE cp_files, ONLY: close_file, &
43 USE kinds, ONLY: default_path_length, &
45 USE machine, ONLY: m_mov
50#ifdef __OPENPMD
51 USE openpmd_api, ONLY: &
52 openpmd_access_create, &
53 openpmd_attributable_type, openpmd_iteration_type, openpmd_mesh_type, &
54 openpmd_particle_species_type, &
55 openpmd_record_type, &
56 openpmd_series_create, openpmd_series_type, &
57 openpmd_type_int, openpmd_json_merge, openpmd_get_default_extension
58#endif
59 USE string_utilities, ONLY: compress, &
60 s2a
61#include "../base/base_uses.f90"
62
63 IMPLICIT NONE
64 PRIVATE
65
66 LOGICAL, PRIVATE, PARAMETER :: debug_this_module = .true.
67 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'cp_output_handling_openpmd'
73
74#ifdef __OPENPMD
76 TYPE(openpmd_series_type) :: series = openpmd_series_type()
77 TYPE(openpmd_iteration_type) :: iteration = openpmd_iteration_type()
78 ! TYPE(openpmd_mesh_type) :: mesh = openpmd_mesh_type()
79 ! TYPE(openpmd_particle_species_type) :: particle_species = openpmd_particle_species_type()
80 CHARACTER(len=default_string_length) :: name_prefix = "" ! e.g. 'WFN_00008_1'
82
83 TYPE :: cp_openpmd_per_call_type
84 INTEGER :: key = -1 ! unit_nr
85 TYPE(cp_openpmd_per_call_value_type) :: value = cp_openpmd_per_call_value_type()
86 END TYPE cp_openpmd_per_call_type
87
88 TYPE :: cp_current_iteration_counter_type
89 INTEGER :: flat_iteration = 0
90 INTEGER, ALLOCATABLE :: complex_iteration(:)
91 INTEGER :: complex_iteration_depth = 0
92 END TYPE cp_current_iteration_counter_type
93
94 TYPE :: cp_openpmd_per_callsite_value_type
95 ! openPMD output Series.
96 TYPE(openpmd_series_type) :: output_series = openpmd_series_type()
97 ! Information on the last Iteration that was written to, including
98 ! CP2Ks complex Iteration number and its associated contiguous scalar
99 ! openPMD Iteration number.
100 TYPE(cp_current_iteration_counter_type) :: iteration_counter = cp_current_iteration_counter_type()
101 END TYPE cp_openpmd_per_callsite_value_type
102
103 TYPE :: cp_openpmd_per_callsite_type
104 CHARACTER(len=default_string_length) :: key = "" ! openpmd_basename
105 TYPE(cp_openpmd_per_callsite_value_type) :: value = cp_openpmd_per_callsite_value_type()
106 END TYPE cp_openpmd_per_callsite_type
107
108 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
109 ! Begin data members for openPMD output. !
110 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
111
112 ! Map that associates opened unit numbers with their associated openPMD content.
113 ! Since CP2K logically opens a new file for every single dataset, multiple
114 ! unit numbers may point to the same openPMD Series.
115 TYPE(cp_openpmd_per_call_type), ALLOCATABLE :: cp_openpmd_per_call(:)
116 INTEGER :: cp_num_openpmd_per_call = 0
117 INTEGER :: cp_capacity_openpmd_per_call = 0
118
119 ! Map that associates callsites from which functions of this module may be invoked
120 ! to their associated openPMD content.
121 ! This stores the actual output Series (which stays open across calls from the
122 ! same callsite) and the Iteration counter (which associates complex CP2k
123 ! Iterations with flattened scalar Iteration indexes in the openPMD output).
124 TYPE(cp_openpmd_per_callsite_type), ALLOCATABLE, TARGET :: cp_openpmd_per_callsite(:)
125 INTEGER :: cp_num_openpmd_per_callsite = 0
126 INTEGER :: cp_capacity_openpmd_per_callsite = 0
127
128 ! This is currently hardcoded, reallocation in case of greater needed map sizes
129 ! is not (yet) supported. However, the maps should normally not grow to large
130 ! sizes:
131 !
132 ! * cp_openpmd_per_call will normally contain one single element, since a
133 ! (virtual) file is opened, written and then closed.
134 ! The output routines normally do not contain interleaved open-write-close
135 ! logic.
136 ! * cp_openpmd_per_callsite will normally contain a handful of elements,
137 ! equal to the number of output modules activated in the input file
138 ! (and in openPMD: equal to the number of output Series).
139 ! There are not 100 of them.
140 INTEGER, PARAMETER :: cp_allocation_size = 100
141 ! Some default settings. May be overwritten / extended by specifying a JSON/TOML
142 ! config in the input file.
143 CHARACTER(len=*), PARAMETER :: cp_default_backend_config = &
144 "[hdf5]"//new_line('a')// &
145 "# will be overridden by particle flushes"//new_line('a')// &
146 "independent_stores = false"//new_line('a')// &
147 "dont_warn_unused_keys = ['independent_stores']"//new_line('a')// &
148 ""//new_line('a')// &
149 "[adios2]"//new_line('a')// &
150 "# discard any attributes written on ranks other than 0"//new_line('a')// &
151 "attribute_writing_ranks = 0"//new_line('a')// &
152 "[adios2.engine]"//new_line('a')// &
153 "# CP2K generally has many small IO operations, "//new_line('a')// &
154 "# so stage IO memory to the buffer first and then "//new_line('a')// &
155 "# run it all at once, instead of writing to disk directly."//new_line('a')// &
156 "# Save memory by specifying 'disk' here instead."//new_line('a')// &
157 "# TODO: In future, maybe implement some input variable"//new_line('a')// &
158 "# to specify intervals at which to flush to disk."//new_line('a')// &
159 "preferred_flush_target = 'buffer'"//new_line('a')
160#ifndef _WIN32
161 CHARACTER(len=*), PARAMETER :: cp_default_backend_config_non_windows = &
162 "# Raise the BufferChunkSize to the maximum (2GB), since large operations"//new_line('a')// &
163 "# improve IO performance and the allocation overhead only cuts into"//new_line('a')// &
164 "# virtual memory (except on Windows, hence do not do that there)"//new_line('a')// &
165 "[adios2.engine.parameters]"//new_line('a')// &
166 "BufferChunkSize = 2147381248"//new_line('a')
167#endif
168
169 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
170 ! End data members for openPMD output. !
171 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
172
173#else ! defined(__OPENPMD)
174
176 ! nothing there
178
179#endif
180
181CONTAINS
182
183#ifdef __OPENPMD
184 ! Helper functions for interacting with the two maps declared above.
185
186
187 ! TODO No reallocation support for now, change cp_allocation_size if larger sizes needed.
188
189 ! **************************************************************************************************
190 !> \brief ...
191 !> \param key ...
192 !> \param value ...
193 ! **************************************************************************************************
194 FUNCTION cp_openpmd_add_unit_nr (key, value) RESULT(index)
195 INTEGER, INTENT(in) :: key
196 TYPE(cp_openpmd_per_call_value_type), INTENT(in) :: value
197 INTEGER :: index
198
199 LOGICAL :: check_capacity
200 INTEGER :: i
201
202 ! Check if the key already exists
203 DO i = 1, cp_num_openpmd_per_call
204 IF (cp_openpmd_per_call(i)%key == key) THEN
205 cp_openpmd_per_call(i)%value = value
206 index = i
207 RETURN
208 END IF
209 END DO
210
211 IF (cp_capacity_openpmd_per_call == 0) THEN
212 ALLOCATE (cp_openpmd_per_call(cp_allocation_size))
213 cp_capacity_openpmd_per_call = cp_allocation_size
214 END IF
215
216 ! No idea how to do reallocations, so for now just assert that they're not needed
217 check_capacity = cp_num_openpmd_per_call < cp_capacity_openpmd_per_call
218 cpassert(check_capacity)
219
220 ! Add a new entry
221 cp_num_openpmd_per_call = cp_num_openpmd_per_call+1
222 cp_openpmd_per_call(cp_num_openpmd_per_call)%key = key
223 cp_openpmd_per_call(cp_num_openpmd_per_call)%value = value
224 index = cp_num_openpmd_per_call
225 END FUNCTION cp_openpmd_add_unit_nr
226
227 ! **************************************************************************************************
228 !> \brief ...
229 !> \param key ...
230 !> \return ...
231 ! **************************************************************************************************
232 FUNCTION cp_openpmd_get_index_unit_nr (key) RESULT(index)
233 INTEGER, INTENT(in) :: key
234 INTEGER :: index
235
236 INTEGER :: i
237
238 index = -1
239
240 DO i = 1, cp_num_openpmd_per_call
241 IF (cp_openpmd_per_call(i)%key == key) THEN
242 index = i
243 RETURN
244 END IF
245 END DO
246 END FUNCTION cp_openpmd_get_index_unit_nr
247
248 FUNCTION cp_openpmd_get_value_unit_nr (key) RESULT(value)
249 INTEGER, INTENT(in) :: key
250 TYPE(cp_openpmd_per_call_value_type) :: value
251
252 INTEGER :: i
253
254 i = cp_openpmd_get_index_unit_nr(key)
255 IF (i == -1) RETURN
256
257 value = cp_openpmd_per_call(i)%value
259
260 ! **************************************************************************************************
261 !> \brief ...
262 !> \param key ...
263 !> \return ...
264 ! **************************************************************************************************
265 FUNCTION cp_openpmd_remove_unit_nr (key) RESULT(was_found)
266 INTEGER, INTENT(in) :: key
267 LOGICAL :: was_found
268
269 INTEGER :: i
270
271 was_found = .false.
272
273 DO i = 1, cp_num_openpmd_per_call
274 IF (cp_openpmd_per_call(i)%key == key) THEN
275 was_found = .true.
276 IF (i /= cp_num_openpmd_per_call) THEN
277 ! Swap last element to now freed place
278 cp_openpmd_per_call(i) = cp_openpmd_per_call(cp_num_openpmd_per_call)
279 END IF
280
281 cp_num_openpmd_per_call = cp_num_openpmd_per_call-1
282 IF (cp_num_openpmd_per_call == 0) THEN
283 DEALLOCATE (cp_openpmd_per_call)
284 cp_capacity_openpmd_per_call = 0
285 END IF
286 RETURN
287 END IF
288 END DO
289 END FUNCTION cp_openpmd_remove_unit_nr
290
291
292 ! TODO No reallocation support for now, change cp_allocation_size if larger sizes needed.
293
294 ! **************************************************************************************************
295 !> \brief ...
296 !> \param key ...
297 !> \param value ...
298 ! **************************************************************************************************
299 FUNCTION cp_openpmd_add_filedata (key, value) RESULT(index)
300 CHARACTER(len=default_string_length), INTENT(in) :: key
301 TYPE(cp_openpmd_per_callsite_value_type), INTENT(in) :: value
302 INTEGER :: index
303
304 LOGICAL :: check_capacity
305 INTEGER :: i
306
307 ! Check if the key already exists
308 DO i = 1, cp_num_openpmd_per_callsite
309 IF (cp_openpmd_per_callsite(i)%key == key) THEN
310 cp_openpmd_per_callsite(i)%value = value
311 index = i
312 RETURN
313 END IF
314 END DO
315
316 IF (cp_capacity_openpmd_per_callsite == 0) THEN
317 ALLOCATE (cp_openpmd_per_callsite(cp_allocation_size))
318 cp_capacity_openpmd_per_callsite = cp_allocation_size
319 END IF
320
321 ! No idea how to do reallocations, so for now just assert that they're not needed
322 check_capacity = cp_num_openpmd_per_callsite < cp_capacity_openpmd_per_callsite
323 cpassert(check_capacity)
324
325 ! Add a new entry
326 cp_num_openpmd_per_callsite = cp_num_openpmd_per_callsite+1
327 cp_openpmd_per_callsite(cp_num_openpmd_per_callsite)%key = key
328 cp_openpmd_per_callsite(cp_num_openpmd_per_callsite)%value = value
329 index = cp_num_openpmd_per_callsite
330 END FUNCTION cp_openpmd_add_filedata
331
332 ! **************************************************************************************************
333 !> \brief ...
334 !> \param key ...
335 !> \return ...
336 ! **************************************************************************************************
337 FUNCTION cp_openpmd_get_index_filedata (key) RESULT(index)
338 CHARACTER(len=default_string_length), INTENT(in) :: key
339 INTEGER :: index
340
341 INTEGER :: i
342
343 index = -1
344
345 DO i = 1, cp_num_openpmd_per_callsite
346 IF (cp_openpmd_per_callsite(i)%key == key) THEN
347 index = i
348 RETURN
349 END IF
350 END DO
351 END FUNCTION cp_openpmd_get_index_filedata
352
353 FUNCTION cp_openpmd_get_value_filedata (key) RESULT(value)
354 CHARACTER(len=default_string_length), INTENT(in) :: key
355 TYPE(cp_openpmd_per_callsite_value_type) :: value
356
357 INTEGER :: i
358
359 i = cp_openpmd_get_index_filedata(key)
360 IF (i == -1) RETURN
361
362 value = cp_openpmd_per_callsite(i)%value
363 END FUNCTION cp_openpmd_get_value_filedata
364
365 ! **************************************************************************************************
366 !> \brief ...
367 !> \param key ...
368 !> \return ...
369 ! **************************************************************************************************
370 FUNCTION cp_openpmd_remove_filedata (key) RESULT(was_found)
371 CHARACTER(len=default_string_length), INTENT(in) :: key
372 LOGICAL :: was_found
373
374 INTEGER :: i
375
376 was_found = .false.
377
378 DO i = 1, cp_num_openpmd_per_callsite
379 IF (cp_openpmd_per_callsite(i)%key == key) THEN
380 was_found = .true.
381 IF (i /= cp_num_openpmd_per_callsite) THEN
382 ! Swap last element to now freed place
383 cp_openpmd_per_callsite(i) = cp_openpmd_per_callsite(cp_num_openpmd_per_callsite)
384 END IF
385
386 cp_num_openpmd_per_callsite = cp_num_openpmd_per_callsite-1
387 IF (cp_num_openpmd_per_callsite == 0) THEN
388 DEALLOCATE (cp_openpmd_per_callsite)
389 cp_capacity_openpmd_per_callsite = 0
390 END IF
391 RETURN
392 END IF
393 END DO
394 END FUNCTION cp_openpmd_remove_filedata
395
396
397! **************************************************************************************************
398!> \brief Simplified version of cp_print_key_generate_filename. Since an openPMD Series encompasses
399! multiple datasets that would be separate outputs in e.g. .cube files, this needs not
400! consider dataset names for creation of a filename.
401!> \param logger ...
402!> \param print_key ...
403!> \param openpmd_basename ...
404!> \param extension ...
405!> \param my_local ...
406!> \return ...
407! **************************************************************************************************
408 FUNCTION cp_print_key_generate_openpmd_filename(logger, print_key, openpmd_basename, extension) RESULT(filename)
409 TYPE(cp_logger_type), POINTER :: logger
410 TYPE(section_vals_type), POINTER :: print_key
411 CHARACTER(len=*), INTENT(IN) :: openpmd_basename, extension
412 CHARACTER(len=default_path_length) :: filename
413
414 CHARACTER(len=default_path_length) :: outPath, root
415 CHARACTER(len=default_string_length) :: outName
416 INTEGER :: my_ind1, my_ind2
417 LOGICAL :: has_root
418
419 CALL section_vals_val_get(print_key, "FILENAME", c_val=outpath)
420 IF (outpath(1:1) == '=') THEN
421 cpassert(len(outpath) - 1 <= len(filename))
422 filename = outpath(2:)
423 RETURN
424 END IF
425 IF (outpath == "__STD_OUT__") outpath = ""
426 outname = outpath
427 has_root = .false.
428 my_ind1 = index(outpath, "/")
429 my_ind2 = len_trim(outpath)
430 IF (my_ind1 /= 0) THEN
431 has_root = .true.
432 DO WHILE (index(outpath(my_ind1 + 1:my_ind2), "/") /= 0)
433 my_ind1 = index(outpath(my_ind1 + 1:my_ind2), "/") + my_ind1
434 END DO
435 IF (my_ind1 == my_ind2) THEN
436 outname = ""
437 ELSE
438 outname = outpath(my_ind1 + 1:my_ind2)
439 END IF
440 END IF
441
442 IF (.NOT. has_root) THEN
443 root = trim(logger%iter_info%project_name)
444 ELSE IF (outname == "") THEN
445 root = outpath(1:my_ind1)//trim(logger%iter_info%project_name)
446 ELSE
447 root = outpath(1:my_ind1)
448 END IF
449
450 filename = adjustl(trim(root)//"_"//trim(openpmd_basename)//trim(extension))
451
452 END FUNCTION cp_print_key_generate_openpmd_filename
453
454! **************************************************************************************************
455!> \brief CP2K Iteration numbers are n-dimensional while openPMD Iteration numbers are scalars.
456! This checks if the Iteration number has changed from the previous call (stored in
457! openpmd_file%iteration_counter) and updates it if needed.
458!> \param logger ...
459!> \return ...
460! **************************************************************************************************
461 FUNCTION cp_advance_iteration_number(logger, openpmd_file) RESULT(did_advance_iteration)
462 TYPE(cp_logger_type), POINTER :: logger
463 TYPE(cp_openpmd_per_callsite_value_type) :: openpmd_file
464 LOGICAL :: did_advance_iteration
465
466 INTEGER :: len
467
468
469 did_advance_iteration = .false.
470 len = SIZE(logger%iter_info%iteration)
471 IF (len /= openpmd_file%iteration_counter%complex_iteration_depth) THEN
472 did_advance_iteration = .true.
473 openpmd_file%iteration_counter%complex_iteration_depth = len
474 ALLOCATE (openpmd_file%iteration_counter%complex_iteration(len))
475 ELSE
476 did_advance_iteration &
477 = any(openpmd_file%iteration_counter%complex_iteration(1:len) &
478 /= logger%iter_info%iteration(1:len))
479 END IF
480
481 IF (.NOT. did_advance_iteration) RETURN
482
483 openpmd_file%iteration_counter%flat_iteration = openpmd_file%iteration_counter%flat_iteration + 1
484 openpmd_file%iteration_counter%complex_iteration(1:len) &
485 = logger%iter_info%iteration(1:len)
486
487 END FUNCTION cp_advance_iteration_number
488
489! **************************************************************************************************
490!> \brief CP2K deals with output handles in terms of unit numbers.
491! The openPMD output logic does not change this association.
492! For this, we need to emulate unit numbers as (1) they are not native to openPMD and
493! (2) a single openPMD Series might contain multiple datasets treated logically by CP2K
494! as distinct outputs. As a result, a single unit number is resolved by the openPMD logic
495! to the values represented by the cp_openpmd_per_call_value_type struct,
496! containing the output Series and the referred datasets therein (Iteration number,
497! name prefix for meshes and particles, referred output Series ...).
498!> \param series ...
499!> \param middle_name ...
500!> \param logger ...
501!> \return ...
502! **************************************************************************************************
503 FUNCTION cp_openpmd_create_unit_nr_entry(openpmd_file_index, middle_name, logger) RESULT(res)
504 INTEGER :: openpmd_file_index
505 CHARACTER(len=*), INTENT(IN) :: middle_name
506 TYPE(cp_logger_type), POINTER :: logger
507 TYPE(cp_openpmd_per_call_value_type) :: res
508
509 LOGICAL, SAVE :: opened_new_iteration = .false.
510 TYPE(openpmd_attributable_type) :: attr
511 TYPE(cp_openpmd_per_callsite_value_type), POINTER :: opmd
512
513 opmd => cp_openpmd_per_callsite(openpmd_file_index)%value
514
515 res%series = opmd%output_series
516
517 opened_new_iteration = cp_advance_iteration_number(logger, opmd)
518
519 res%iteration = opmd%output_series%write_iteration(opmd%iteration_counter%flat_iteration)
520 res%name_prefix = trim(middle_name)
521
522 IF (opened_new_iteration) THEN
523 attr = res%iteration%as_attributable()
524 CALL attr%set_attribute_vec_int( &
525 "ndim_iteration_index", &
526 opmd%iteration_counter%complex_iteration)
527 END IF
528 END FUNCTION cp_openpmd_create_unit_nr_entry
529
530! **************************************************************************************************
531!> \brief Check if there is already an output Series created for the callsite identified
532! by openpmd_basename. If so, then return it (by index), otherwise open the Series now
533! and return the index then.
534 FUNCTION cp_openpmd_get_openpmd_file_entry(openpmd_basename, filename, openpmd_config, logger, use_mpi) RESULT(file_index)
535 CHARACTER(len=*), INTENT(IN) :: openpmd_basename, filename, openpmd_config
536 TYPE(cp_logger_type), POINTER :: logger
537 LOGICAL :: use_mpi
538 INTEGER :: file_index
539 CHARACTER(:), ALLOCATABLE :: merged_config
540
541 CHARACTER(len=default_string_length), SAVE :: basename_copied = ' '
542 TYPE(cp_openpmd_per_callsite_value_type) :: emplace_new
543
544 INTEGER :: handle
545 TYPE(cp_openpmd_per_callsite_value_type) :: series_data
546 TYPE(openpmd_iteration_type) :: iteration
547 INTEGER :: i
548
549 basename_copied(1:len_trim(openpmd_basename)) = trim(openpmd_basename)
550
551 file_index = cp_openpmd_get_index_filedata(basename_copied)
552
553 CALL timeset('openpmd_close_iterations', handle)
554 DO i = 1, cp_num_openpmd_per_callsite
555 IF (i /= file_index) THEN
556 series_data = cp_openpmd_per_callsite(i)%value
557 iteration = series_data%output_series%get_iteration( &
558 series_data%iteration_counter%flat_iteration)
559 IF (.NOT. iteration%closed()) THEN
560 CALL iteration%close()
561 END IF
562 END IF
563 END DO
564 CALL timestop(handle)
565
566 IF (file_index /= -1) RETURN
567
568#ifndef _WIN32
569 merged_config = openpmd_json_merge(cp_default_backend_config, cp_default_backend_config_non_windows)
570#else
571 merged_config = cp_default_backend_config
572#endif
573 IF (use_mpi) THEN
574 merged_config = openpmd_json_merge(merged_config, openpmd_config, logger%para_env)
575 emplace_new%output_series = openpmd_series_create( &
576 filename, openpmd_access_create, logger%para_env, merged_config)
577 ELSE
578 merged_config = openpmd_json_merge(merged_config, openpmd_config)
579 emplace_new%output_series = openpmd_series_create( &
580 filename, openpmd_access_create, config=merged_config)
581 END IF
582 DEALLOCATE (merged_config)
583 file_index = cp_openpmd_add_filedata(basename_copied, emplace_new)
584 END FUNCTION cp_openpmd_get_openpmd_file_entry
585
586#else ! defined(__OPENPMD)
587
588 FUNCTION cp_openpmd_get_value_unit_nr(key) RESULT(value)
589 INTEGER, INTENT(in) :: key
590 TYPE(cp_openpmd_per_call_value_type) :: value
591
592 mark_used(key)
593 mark_used(value)
594 cpabort("CP2K compiled without the openPMD-api")
595
597
598#endif
599
600! **************************************************************************************************
601!> \brief Close all outputs.
602! **************************************************************************************************
604#ifdef __OPENPMD
605 INTEGER :: i
606 DO i = 1, cp_num_openpmd_per_callsite
607 DEALLOCATE (cp_openpmd_per_callsite(i)%value%iteration_counter%complex_iteration)
608 CALL cp_openpmd_per_callsite(i)%value%output_series%close()
609 END DO
610 IF (ALLOCATED(cp_openpmd_per_callsite)) THEN
611 DEALLOCATE (cp_openpmd_per_callsite)
612 END IF
613 cp_num_openpmd_per_callsite = 0
614#endif
615 END SUBROUTINE cp_openpmd_output_finalize
616
617! **************************************************************************************************
618!> \brief ...
619!> \param logger ...
620!> \param basis_section ...
621!> \param print_key_path ...
622!> \param extension ...
623!> \param middle_name ...
624!> \param local ...
625!> \param log_filename ...
626!> \param ignore_should_output ...
627!> \param do_backup ...
628!> \param is_new_file true if this rank created a new (or rewound) file, false otherwise
629!> \param mpi_io True if the file should be opened in parallel on all processors belonging to
630!> the communicator group. Automatically disabled if the file form or access mode
631!> is unsuitable for MPI IO. Return value indicates whether MPI was actually used
632!> and therefore the flag must also be passed to the file closing directive.
633!> \param fout Name of the actual file where the output will be written. Needed mainly for MPI IO
634!> because inquiring the filename from the MPI filehandle does not work across
635!> all MPI libraries.
636!> \param openpmd_basename Used to associate an identifier to each callsite of this module
637!> \param use_openpmd ...
638!> \return ...
639! **************************************************************************************************
640 FUNCTION cp_openpmd_print_key_unit_nr(logger, basis_section, print_key_path, &
641 middle_name, ignore_should_output, &
642 mpi_io, &
643 fout, openpmd_basename) RESULT(res)
644 TYPE(cp_logger_type), POINTER :: logger
645 TYPE(section_vals_type), INTENT(IN) :: basis_section
646 CHARACTER(len=*), INTENT(IN), OPTIONAL :: print_key_path
647 CHARACTER(len=*), INTENT(IN), OPTIONAL :: middle_name
648 LOGICAL, INTENT(IN), OPTIONAL :: ignore_should_output
649 LOGICAL, INTENT(INOUT), OPTIONAL :: mpi_io
650 CHARACTER(len=default_path_length), INTENT(OUT), &
651 OPTIONAL :: fout
652 CHARACTER(len=*), INTENT(IN), OPTIONAL :: openpmd_basename
653 INTEGER :: res
654
655#ifdef __OPENPMD
656
657 CHARACTER(len=default_path_length) :: filename
658
659 CHARACTER(len=default_string_length) :: openpmd_config, outpath, file_extension
660 LOGICAL :: found, &
661 my_mpi_io, &
662 my_should_output, &
663 replace
664 INTEGER :: openpmd_file_index, openpmd_call_index
665 TYPE(section_vals_type), POINTER :: print_key
666
667 my_mpi_io = .false.
668 replace = .false.
669 found = .false.
670 res = -1
671 IF (PRESENT(mpi_io)) THEN
672#if defined(__parallel)
673 IF (logger%para_env%num_pe > 1 .AND. mpi_io) THEN
674 my_mpi_io = .true.
675 ELSE
676 my_mpi_io = .false.
677 END IF
678#else
679 my_mpi_io = .false.
680#endif
681 ! Set return value
682 mpi_io = my_mpi_io
683 END IF
684 NULLIFY (print_key)
685 cpassert(ASSOCIATED(logger))
686 cpassert(basis_section%ref_count > 0)
687 cpassert(logger%ref_count > 0)
688 my_should_output = btest(cp_print_key_should_output(logger%iter_info, &
689 basis_section, print_key_path, used_print_key=print_key), cp_p_file)
690 IF (PRESENT(ignore_should_output)) my_should_output = my_should_output .OR. ignore_should_output
691 IF (.NOT. my_should_output) RETURN
692 IF (logger%para_env%is_source() .OR. my_mpi_io) THEN
693
694 CALL section_vals_val_get(print_key, "FILENAME", c_val=outpath)
695 CALL section_vals_val_get(print_key, "OPENPMD_EXTENSION", c_val=file_extension)
696 CALL section_vals_val_get(print_key, "OPENPMD_CFG_FILE", c_val=openpmd_config)
697 IF (len_trim(openpmd_config) == 0) THEN
698 CALL section_vals_val_get(print_key, "OPENPMD_CFG", c_val=openpmd_config)
699 ELSE
700 openpmd_config = "@"//openpmd_config
701 END IF
702 filename = cp_print_key_generate_openpmd_filename(logger, print_key, openpmd_basename, file_extension)
703
704 IF (PRESENT(fout)) THEN
705 fout = filename
706 END IF
707
708 openpmd_file_index = cp_openpmd_get_openpmd_file_entry( &
709 openpmd_basename, filename, openpmd_config, logger, my_mpi_io)
710
711 OPEN (newunit=res, status='scratch', action='write')
712 openpmd_call_index = cp_openpmd_add_unit_nr( &
713 res, &
714 cp_openpmd_create_unit_nr_entry( &
715 openpmd_file_index, middle_name, logger))
716
717 ELSE
718 res = -1
719 END IF
720#else
721 mark_used(logger)
722 mark_used(basis_section)
723 mark_used(print_key_path)
724 mark_used(middle_name)
725 mark_used(ignore_should_output)
726 mark_used(mpi_io)
727 mark_used(fout)
728 mark_used(openpmd_basename)
729 res = 0
730 cpabort("CP2K compiled without the openPMD-api")
731#endif
733
734! **************************************************************************************************
735!> \brief should be called after you finish working with a unit obtained with
736!> cp_openpmd_print_key_unit_nr, so that the file that might have been opened
737!> can be closed.
738!>
739!> the inputs should be exactly the same of the corresponding
740!> cp_openpmd_print_key_unit_nr
741!> \param unit_nr ...
742!> \param logger ...
743!> \param basis_section ...
744!> \param print_key_path ...
745!> \param local ...
746!> \param ignore_should_output ...
747!> \param mpi_io True if file was opened in parallel with MPI
748!> \param use_openpmd ...
749!> \note
750!> closes if the corresponding filename of the printkey is
751!> not __STD_OUT__
752! **************************************************************************************************
753 SUBROUTINE cp_openpmd_print_key_finished_output(unit_nr, logger, basis_section, &
754 print_key_path, local, ignore_should_output, &
755 mpi_io)
756 INTEGER, INTENT(INOUT) :: unit_nr
757 TYPE(cp_logger_type), POINTER :: logger
758 TYPE(section_vals_type), INTENT(IN) :: basis_section
759 CHARACTER(len=*), INTENT(IN), OPTIONAL :: print_key_path
760 LOGICAL, INTENT(IN), OPTIONAL :: local, ignore_should_output, &
761 mpi_io
762
763#ifdef __OPENPMD
764
765 CHARACTER(len=default_string_length) :: outpath
766 LOGICAL :: my_local, my_mpi_io, &
767 my_should_output
768 TYPE(section_vals_type), POINTER :: print_key
769
770 my_local = .false.
771 my_mpi_io = .false.
772 NULLIFY (print_key)
773 IF (PRESENT(local)) my_local = local
774 IF (PRESENT(mpi_io)) my_mpi_io = mpi_io
775 cpassert(ASSOCIATED(logger))
776 cpassert(basis_section%ref_count > 0)
777 cpassert(logger%ref_count > 0)
778 my_should_output = btest(cp_print_key_should_output(logger%iter_info, basis_section, &
779 print_key_path, used_print_key=print_key), cp_p_file)
780 IF (PRESENT(ignore_should_output)) my_should_output = my_should_output .OR. ignore_should_output
781 IF (my_should_output .AND. (my_local .OR. &
782 logger%para_env%is_source() .OR. &
783 my_mpi_io)) THEN
784 CALL section_vals_val_get(print_key, "FILENAME", c_val=outpath)
785 IF (cp_openpmd_remove_unit_nr(unit_nr)) THEN
786 CLOSE (unit_nr)
787 END IF
788
789 unit_nr = -1
790 END IF
791 cpassert(unit_nr == -1)
792 unit_nr = -1
793#else
794 mark_used(unit_nr)
795 mark_used(logger)
796 mark_used(basis_section)
797 mark_used(print_key_path)
798 mark_used(local)
799 mark_used(ignore_should_output)
800 mark_used(mpi_io)
801 cpabort("CP2K compiled without the openPMD-api")
802#endif
804
806#ifdef __OPENPMD
807 INTEGER :: handle
808 TYPE(cp_openpmd_per_callsite_value_type) :: series_data
809 TYPE(openpmd_iteration_type) :: iteration
810 INTEGER :: i
811
812 CALL timeset('openpmd_close_iterations', handle)
813 DO i = 1, cp_num_openpmd_per_callsite
814 series_data = cp_openpmd_per_callsite(i)%value
815 iteration = series_data%output_series%get_iteration( &
816 series_data%iteration_counter%flat_iteration)
817 IF (.NOT. iteration%closed()) THEN
818 CALL iteration%close()
819 END IF
820 END DO
821 CALL timestop(handle)
822#endif
823 END SUBROUTINE cp_openpmd_close_iterations
824
825 FUNCTION cp_openpmd_get_default_extension() RESULT(extension)
826 CHARACTER(len=default_string_length) :: extension
827
828#ifdef __OPENPMD
829 extension = openpmd_get_default_extension()
830#else
831 extension = ".bp5"
832#endif
833
835
Utility routines to open and close files. Tracking of preconnections.
Definition cp_files.F:16
subroutine, public open_file(file_name, file_status, file_form, file_action, file_position, file_pad, unit_number, debug, skip_get_unit_number, file_access)
Opens the requested file using a free unit number.
Definition cp_files.F:311
subroutine, public close_file(unit_number, file_status, keep_preconnection)
Close an open file given by its logical unit number. Optionally, keep the file and unit preconnected.
Definition cp_files.F:122
Collection of routines to handle the iteration info.
character(len=default_path_length), dimension(18), parameter, public each_possible_labels
subroutine, public cp_iteration_info_retain(iteration_info)
retains the iteration_info (see doc/ReferenceCounting.html)
subroutine, public cp_iteration_info_release(iteration_info)
releases the iteration_info (see doc/ReferenceCounting.html)
character(len=default_path_length), dimension(18), parameter, public each_desc_labels
various routines to log and control the output. The idea is that decisions about where to log should ...
recursive integer function, public cp_logger_get_default_unit_nr(logger, local, skip_not_ionode)
asks the default unit number of the given logger. try to use cp_logger_get_unit_nr
integer function, public cp_logger_get_unit_nr(logger, local)
returns the unit nr for the requested kind of log.
subroutine, public cp_logger_generate_filename(logger, res, root, postfix, local)
generates a unique filename (ie adding eventual suffixes and process ids)
routines to handle the output, The idea is to remove the decision of wheter to output and what to out...
subroutine, public cp_openpmd_close_iterations()
character(len=default_string_length) function, public cp_openpmd_get_default_extension()
subroutine, public cp_openpmd_output_finalize()
Close all outputs.
type(cp_openpmd_per_call_value_type) function, public cp_openpmd_get_value_unit_nr(key)
integer function, public cp_openpmd_print_key_unit_nr(logger, basis_section, print_key_path, middle_name, ignore_should_output, mpi_io, fout, openpmd_basename)
...
subroutine, public cp_openpmd_print_key_finished_output(unit_nr, logger, basis_section, print_key_path, local, ignore_should_output, mpi_io)
should be called after you finish working with a unit obtained with cp_openpmd_print_key_unit_nr,...
routines to handle the output, The idea is to remove the decision of wheter to output and what to out...
integer, parameter, public cp_p_file
integer function, public cp_print_key_should_output(iteration_info, basis_section, print_key_path, used_print_key, first_time)
returns what should be done with the given property if btest(res,cp_p_store) then the property should...
represents keywords in an input
subroutine, public keyword_release(keyword)
releases the given keyword (see doc/ReferenceCounting.html)
subroutine, public keyword_create(keyword, location, name, description, usage, type_of_var, n_var, repeats, variants, default_val, default_l_val, default_r_val, default_lc_val, default_c_val, default_i_val, default_l_vals, default_r_vals, default_c_vals, default_i_vals, lone_keyword_val, lone_keyword_l_val, lone_keyword_r_val, lone_keyword_c_val, lone_keyword_i_val, lone_keyword_l_vals, lone_keyword_r_vals, lone_keyword_c_vals, lone_keyword_i_vals, enum_c_vals, enum_i_vals, enum, enum_strict, enum_desc, unit_str, citations, deprecation_notice, removed)
creates a keyword object
objects that represent the structure of input sections and the data contained in an input section
subroutine, public section_create(section, location, name, description, n_keywords, n_subsections, repeats, citations, deprecation_notice)
creates a list of keywords
subroutine, public section_add_keyword(section, keyword)
adds a keyword to the given section
subroutine, public section_add_subsection(section, subsection)
adds a subsection to the given section
recursive type(section_vals_type) function, pointer, public section_vals_get_subs_vals(section_vals, subsection_name, i_rep_section, can_return_null)
returns the values of the requested subsection
recursive subroutine, public section_release(section)
releases the given keyword list (see doc/ReferenceCounting.html)
subroutine, public section_vals_val_get(section_vals, keyword_name, i_rep_section, i_rep_val, n_rep_val, val, l_val, i_val, r_val, c_val, l_vals, i_vals, r_vals, c_vals, explicit)
returns the requested value
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public default_string_length
Definition kinds.F:57
integer, parameter, public default_path_length
Definition kinds.F:58
Machine interface based on Fortran 2003 and POSIX.
Definition machine.F:17
subroutine, public m_mov(source, target)
...
Definition machine.F:707
Utility routines for the memory handling.
Interface to the message passing library MPI.
subroutine, public mp_file_delete(filepath, info)
Deletes a file. Auxiliary routine to emulate 'replace' action for mp_file_open. Only the master proce...
subroutine, public mp_file_get_amode(mpi_io, replace, amode, form, action, status, position)
(parallel) Utility routine to determine MPI file access mode based on variables
Utilities for string manipulations.
subroutine, public compress(string, full)
Eliminate multiple space characters in a string. If full is .TRUE., then all spaces are eliminated.
contains the information about the current state of the program to be able to decide if output is nec...
type of a logger, at the moment it contains just a print level starting at which level it should be l...
represent a keyword in the input
represent a section of the input file