(git:e7e05ae)
pint_io.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 ! **************************************************************************************************
9 !> \brief I/O subroutines for pint_env
10 !> \author Lukasz Walewski
11 !> \date 2009-06-04
12 ! **************************************************************************************************
13 MODULE pint_io
14 
15  USE cell_types, ONLY: cell_type
18  cp_logger_type
19  USE cp_output_handling, ONLY: cp_p_file,&
23  USE cp_subsys_types, ONLY: cp_subsys_get,&
24  cp_subsys_type
25  USE cp_units, ONLY: cp_unit_from_cp2k
28  f_env_type
30  USE input_constants, ONLY: dump_atomic,&
31  dump_dcd,&
33  dump_xmol
35  section_vals_type,&
37  USE kinds, ONLY: default_string_length,&
38  dp
39  USE machine, ONLY: m_flush
40  USE particle_list_types, ONLY: particle_list_type
42  USE pint_public, ONLY: pint_com_pos
44  USE pint_types, ONLY: e_conserved_id,&
48  pint_env_type
49 #include "../base/base_uses.f90"
50 
51  IMPLICIT NONE
52 
53  PRIVATE
54 
55  LOGICAL, PRIVATE, PARAMETER :: debug_this_module = .true.
56  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'pint_io'
57 
58  PUBLIC :: pint_write_line
59  PUBLIC :: pint_write_centroids
60  PUBLIC :: pint_write_trajectory
61  PUBLIC :: pint_write_com
62  PUBLIC :: pint_write_ener
63  PUBLIC :: pint_write_action
64  PUBLIC :: pint_write_step_info
65  PUBLIC :: pint_write_rgyr
66 
67 CONTAINS
68 
69 ! ***************************************************************************
70 !> \brief Writes out a line of text to the default output unit.
71 !> \param line ...
72 !> \date 2009-07-10
73 !> \author Lukasz Walewski
74 ! **************************************************************************************************
75  SUBROUTINE pint_write_line(line)
76 
77  CHARACTER(len=*), INTENT(IN) :: line
78 
79  CHARACTER(len=default_string_length) :: my_label
80  INTEGER :: unit_nr
81  TYPE(cp_logger_type), POINTER :: logger
82 
83  NULLIFY (logger)
84  logger => cp_get_default_logger()
85  my_label = "PINT|"
86 
87  IF (logger%para_env%is_source()) THEN
88  unit_nr = cp_logger_get_default_unit_nr(logger)
89  WRITE (unit_nr, '(T2,A)') trim(my_label)//" "//trim(line)
90  END IF
91 
92  END SUBROUTINE pint_write_line
93 
94 ! ***************************************************************************
95 !> \brief Write out the trajectory of the centroid (positions and velocities)
96 !> \param pint_env ...
97 !> \par History
98 !> various bug fixes - hforbert
99 !> 2010-11-25 rewritten, added support for velocity printing,
100 !> calc of the stddev of the beads turned off [lwalewski]
101 !> \author fawzi
102 ! **************************************************************************************************
103  SUBROUTINE pint_write_centroids(pint_env)
104  TYPE(pint_env_type), INTENT(IN) :: pint_env
105 
106  CHARACTER(len=*), PARAMETER :: routinen = 'pint_write_centroids'
107  INTEGER, PARAMETER :: n_ids = 2, pos_id = 1, vel_id = 2
108 
109  CHARACTER(len=default_string_length) :: ext, form, my_middle_name, unit_str
110  CHARACTER(len=default_string_length), DIMENSION(2) :: content_id, middle_name, sect_path, title
111  INTEGER :: handle, handle1, iat, ib, id, idim, &
112  idir, ierr, outformat, should_output, &
113  unit_nr
114  LOGICAL :: new_file, print_kind
115  REAL(kind=dp) :: nb, ss, unit_conv, vv
116  TYPE(cell_type), POINTER :: cell
117  TYPE(cp_logger_type), POINTER :: logger
118  TYPE(cp_subsys_type), POINTER :: subsys
119  TYPE(f_env_type), POINTER :: f_env
120  TYPE(particle_list_type), POINTER :: particles
121  TYPE(section_vals_type), POINTER :: print_key
122 
123  CALL timeset(routinen, handle1)
124 
125  sect_path(pos_id) = "MOTION%PINT%PRINT%CENTROID_POS"
126  sect_path(vel_id) = "MOTION%PINT%PRINT%CENTROID_VEL"
127  middle_name(pos_id) = "centroid-pos"
128  middle_name(vel_id) = "centroid-vel"
129  content_id(pos_id) = "POS"
130  content_id(vel_id) = "VEL"
131  WRITE (unit=title(pos_id), fmt="(A,I8,A,F20.10)") &
132  " i =", pint_env%iter, &
133  ", E =", sum(pint_env%e_pot_bead)*pint_env%propagator%physpotscale
134  WRITE (unit=title(vel_id), fmt="(A,I8,A,F20.10,A,F20.10)") &
135  " i =", pint_env%iter, &
136  ", E_trm =", pint_env%energy(e_kin_thermo_id), &
137  ", E_vir =", pint_env%energy(e_kin_virial_id)
138 
139  NULLIFY (logger)
140  logger => cp_get_default_logger()
141 
142  CALL pint_u2x(pint_env, ux=pint_env%uv, x=pint_env%v)
143 
144  ! iterate over the properties that we know how to print
145  ! (currently positions and velocities)
146  DO id = 1, n_ids
147 
148  print_key => section_vals_get_subs_vals(pint_env%input, &
149  trim(sect_path(id)))
150 
151  should_output = cp_print_key_should_output( &
152  iteration_info=logger%iter_info, &
153  basis_section=print_key)
154  IF (.NOT. btest(should_output, cp_p_file)) CONTINUE
155 
156  print_kind = .false.
157 
158  ! get units of measure for output (if available)
159  CALL section_vals_val_get(print_key, "UNIT", &
160  c_val=unit_str)
161  unit_conv = cp_unit_from_cp2k(1.0_dp, trim(unit_str))
162 
163  ! get the format for output
164  CALL section_vals_val_get(print_key, "FORMAT", i_val=outformat)
165 
166  SELECT CASE (outformat)
168  form = "UNFORMATTED"
169  ext = ".dcd"
170  CASE (dump_atomic)
171  form = "FORMATTED"
172  ext = ""
173  CASE (dump_xmol)
174  CALL section_vals_val_get(print_key, "PRINT_ATOM_KIND", &
175  l_val=print_kind)
176  form = "FORMATTED"
177  ext = ".xyz"
178  CASE default
179  cpabort("")
180  END SELECT
181 
182  NULLIFY (f_env, cell, subsys)
183  CALL f_env_add_defaults(f_env_id=pint_env%replicas%f_env_id, &
184  f_env=f_env, handle=handle)
185  CALL force_env_get(force_env=f_env%force_env, &
186  cell=cell, subsys=subsys)
187  CALL cp_subsys_get(subsys, particles=particles)
188 
189  ! calculate and copy the requested property
190  ! to the particles structure
191  nb = real(pint_env%p, dp)
192  idim = 0
193  DO iat = 1, pint_env%ndim/3
194  DO idir = 1, 3
195  idim = idim + 1
196  ss = 0.0_dp
197  vv = 0.0_dp
198 ! ss2=0.0_dp
199  DO ib = 1, pint_env%p
200  ss = ss + pint_env%x(ib, idim)
201  vv = vv + pint_env%v(ib, idim)
202 ! ss2=ss2+pint_env%x(ib,idim)**2
203  END DO
204  particles%els(iat)%r(idir) = ss/nb
205  particles%els(iat)%v(idir) = vv/nb
206 ! particles%els(iat)%v(idir)=SQRT(ss2/nb-(ss/nb)**2)
207  END DO
208  END DO
209 
210  ! set up the output unit number and file name
211  ! for the current property
212  my_middle_name = trim(middle_name(id))
213  unit_nr = cp_print_key_unit_nr(logger=logger, &
214  basis_section=print_key, print_key_path="", &
215  extension=trim(ext), middle_name=trim(my_middle_name), &
216  local=.false., file_form=form, is_new_file=new_file)
217 
218  ! don't write the 0-th frame if the file already exists
219  IF (.NOT. new_file .AND. (pint_env%iter .LE. pint_env%first_step)) THEN
220  CALL cp_print_key_finished_output(unit_nr, logger, &
221  print_key)
222  CONTINUE
223  END IF
224 
225  ! actually perform the i/o - on the ionode only
226  IF (unit_nr > 0) THEN
227 
229  particles%els, &
230  iunit=unit_nr, &
231  output_format=outformat, &
232  content=content_id(id), &
233  title=title(id), &
234  cell=cell, &
235  unit_conv=unit_conv, &
236  print_kind=print_kind)
237 
238  CALL cp_print_key_finished_output(unit_nr, logger, &
239  print_key, "", local=.false.)
240 
241  END IF
242 
243  CALL f_env_rm_defaults(f_env, ierr, handle)
244  cpassert(ierr == 0)
245 
246  END DO
247 
248  CALL timestop(handle1)
249  END SUBROUTINE pint_write_centroids
250 
251 ! ***************************************************************************
252 !> \brief Write out the trajectory of the beads (positions and velocities)
253 !> \param pint_env ...
254 !> \par History
255 !> 2010-11-25 added support for velocity printing [lwalewski]
256 !> \author hforbert
257 ! **************************************************************************************************
258  SUBROUTINE pint_write_trajectory(pint_env)
259  TYPE(pint_env_type), INTENT(IN) :: pint_env
260 
261  CHARACTER(len=*), PARAMETER :: routinen = 'pint_write_trajectory'
262  INTEGER, PARAMETER :: force_id = 3, n_ids = 3, pos_id = 1, &
263  vel_id = 2
264 
265  CHARACTER(len=default_string_length) :: ext, form, ib_str, my_middle_name, &
266  title, unit_str
267  CHARACTER(len=default_string_length), DIMENSION(3) :: content_id, middle_name, sect_path
268  INTEGER :: handle, handle1, iat, ib, id, idim, &
269  idir, ierr, imag_stride, outformat, &
270  should_output, unit_nr
271  LOGICAL :: new_file
272  REAL(kind=dp) :: unit_conv
273  TYPE(cell_type), POINTER :: cell
274  TYPE(cp_logger_type), POINTER :: logger
275  TYPE(cp_subsys_type), POINTER :: subsys
276  TYPE(f_env_type), POINTER :: f_env
277  TYPE(particle_list_type), POINTER :: particles
278  TYPE(section_vals_type), POINTER :: print_key
279 
280  CALL timeset(routinen, handle1)
281 
282  sect_path(pos_id) = "MOTION%PRINT%TRAJECTORY"
283  sect_path(vel_id) = "MOTION%PRINT%VELOCITIES"
284  sect_path(force_id) = "MOTION%PRINT%FORCES"
285  middle_name(pos_id) = "pos-"
286  middle_name(vel_id) = "vel-"
287  middle_name(force_id) = "force-"
288  content_id(pos_id) = "POS"
289  content_id(vel_id) = "VEL"
290  content_id(force_id) = "FORCE"
291 
292  NULLIFY (logger)
293  logger => cp_get_default_logger()
294 
295  CALL pint_u2x(pint_env, ux=pint_env%uv, x=pint_env%v)
296 
297  ! iterate over the properties that we know how to print
298  ! (currently positions and velocities)
299  DO id = 1, n_ids
300 
301  print_key => section_vals_get_subs_vals(pint_env%input, &
302  trim(sect_path(id)))
303 
304  should_output = cp_print_key_should_output( &
305  iteration_info=logger%iter_info, &
306  basis_section=print_key)
307  IF (.NOT. btest(should_output, cp_p_file)) CONTINUE
308 
309  ! get units of measure for output (if available)
310  CALL section_vals_val_get(print_key, "UNIT", &
311  c_val=unit_str)
312  unit_conv = cp_unit_from_cp2k(1.0_dp, trim(unit_str))
313 
314  ! get the format for output
315  CALL section_vals_val_get(print_key, "FORMAT", i_val=outformat)
316 
317  SELECT CASE (outformat)
319  form = "UNFORMATTED"
320  ext = ".dcd"
321  CASE (dump_atomic)
322  form = "FORMATTED"
323  ext = ""
324  CASE (dump_xmol)
325  form = "FORMATTED"
326  ext = ".xyz"
327  CASE default
328  cpabort("")
329  END SELECT
330 
331  NULLIFY (f_env, cell, subsys)
332  CALL f_env_add_defaults(f_env_id=pint_env%replicas%f_env_id, &
333  f_env=f_env, handle=handle)
334  CALL force_env_get(force_env=f_env%force_env, &
335  cell=cell, subsys=subsys)
336  CALL cp_subsys_get(subsys, particles=particles)
337 
338  !Get print stride for bead trajectories
339  CALL section_vals_val_get(pint_env%input, &
340  "MOTION%PINT%PRINT%IMAGINARY_TIME_STRIDE", &
341  i_val=imag_stride)
342 
343  ! iterate over beads
344  DO ib = 1, pint_env%p, imag_stride
345 
346  ! copy the requested property of the current bead
347  ! to the particles structure
348  idim = 0
349  DO iat = 1, pint_env%ndim/3
350  DO idir = 1, 3
351  idim = idim + 1
352  particles%els(iat)%r(idir) = pint_env%x(ib, idim)
353  particles%els(iat)%v(idir) = pint_env%v(ib, idim)
354  particles%els(iat)%f(idir) = pint_env%f(ib, idim)
355  END DO
356  END DO
357 
358  ! set up the output unit number and file name
359  ! for the current property and bead
360  ib_str = ""
361  WRITE (ib_str, *) ib
362  my_middle_name = trim(middle_name(id))//trim(adjustl(ib_str))
363  unit_nr = cp_print_key_unit_nr(logger=logger, &
364  basis_section=print_key, print_key_path="", &
365  extension=trim(ext), middle_name=trim(my_middle_name), &
366  local=.false., file_form=form, is_new_file=new_file)
367 
368  ! don't write the 0-th frame if the file already exists
369  IF (.NOT. new_file .AND. (pint_env%iter .LE. pint_env%first_step)) THEN
370  CALL cp_print_key_finished_output(unit_nr, logger, &
371  print_key)
372  CONTINUE
373  END IF
374 
375  ! actually perform the i/o - on the ionode only
376  IF (unit_nr > 0) THEN
377 
378  IF (outformat == dump_xmol) THEN
379  WRITE (unit=title, fmt="(A,I8,A,F20.10)") &
380  " i =", pint_env%iter, &
381  ", E =", pint_env%e_pot_bead(ib)
382  END IF
383 
385  particles%els, &
386  iunit=unit_nr, &
387  output_format=outformat, &
388  content=content_id(id), &
389  title=title, &
390  cell=cell, &
391  unit_conv=unit_conv)
392 
393  CALL cp_print_key_finished_output(unit_nr, logger, &
394  print_key, "", local=.false.)
395 
396  END IF
397 
398  END DO
399 
400  CALL f_env_rm_defaults(f_env, ierr, handle)
401  cpassert(ierr == 0)
402 
403  END DO
404 
405  CALL timestop(handle1)
406  END SUBROUTINE pint_write_trajectory
407 
408 ! ***************************************************************************
409 !> \brief Write center of mass (COM) position according to PINT%PRINT%COM
410 !> \param pint_env ...
411 !> \date 2010-02-17
412 !> \author Lukasz Walewski
413 ! **************************************************************************************************
414  SUBROUTINE pint_write_com(pint_env)
415 
416  TYPE(pint_env_type), INTENT(IN) :: pint_env
417 
418  CHARACTER(len=default_string_length) :: stmp1, stmp2
419  INTEGER :: ic, unit_nr
420  LOGICAL :: new_file, should_output
421  REAL(kind=dp), DIMENSION(3) :: com_r
422  TYPE(cp_logger_type), POINTER :: logger
423  TYPE(section_vals_type), POINTER :: print_key
424 
425  NULLIFY (logger)
426  logger => cp_get_default_logger()
427 
428  ! decide whether to write anything or not
429  NULLIFY (print_key)
430  print_key => section_vals_get_subs_vals(pint_env%input, &
431  "MOTION%PINT%PRINT%COM")
432  should_output = btest(cp_print_key_should_output( &
433  iteration_info=logger%iter_info, &
434  basis_section=print_key), cp_p_file)
435  IF (.NOT. should_output) THEN
436  RETURN
437  END IF
438 
439  com_r = pint_com_pos(pint_env)
440  DO ic = 1, 3
441  com_r(ic) = cp_unit_from_cp2k(com_r(ic), "angstrom")
442  END DO
443 
444  unit_nr = cp_print_key_unit_nr(logger, print_key, is_new_file=new_file, &
445  middle_name="com-pos", extension=".xyz")
446 
447  ! don't write the 0-th frame if the file already exists
448  IF (.NOT. new_file .AND. (pint_env%iter .LE. pint_env%first_step)) THEN
449  CALL cp_print_key_finished_output(unit_nr, logger, &
450  print_key)
451  RETURN
452  END IF
453 
454  ! actually perform the i/o - on the ionode only
455  IF (unit_nr > 0) THEN
456 
457  WRITE (unit_nr, '(I2)') 1
458  WRITE (stmp1, *) pint_env%iter
459  WRITE (stmp2, '(F20.10)') pint_env%energy(e_conserved_id)
460  WRITE (unit_nr, '(4A)') " Iteration = ", trim(adjustl(stmp1)), &
461  ", E_conserved = ", trim(adjustl(stmp2))
462  WRITE (unit_nr, '(A2,3(1X,F20.10))') "X ", (com_r(ic), ic=1, 3)
463 
464  CALL m_flush(unit_nr)
465 
466  END IF
467 
468  CALL cp_print_key_finished_output(unit_nr, logger, print_key)
469 
470  END SUBROUTINE pint_write_com
471 
472 ! ***************************************************************************
473 !> \brief Writes out the energies according to PINT%PRINT%ENERGY
474 !> \param pint_env path integral environment
475 !> \par History
476 !> various bug fixes [hforbert]
477 !> 2009-11-16 energy components calc moved out of here [lwalewski]
478 !> \author fawzi
479 ! **************************************************************************************************
480  SUBROUTINE pint_write_ener(pint_env)
481  TYPE(pint_env_type), INTENT(IN) :: pint_env
482 
483  INTEGER :: ndof, unit_nr
484  LOGICAL :: file_is_new
485  REAL(kind=dp) :: t, temp
486  TYPE(cp_logger_type), POINTER :: logger
487  TYPE(section_vals_type), POINTER :: print_key
488 
489  NULLIFY (print_key, logger)
490  print_key => section_vals_get_subs_vals(pint_env%input, &
491  "MOTION%PINT%PRINT%ENERGY")
492  logger => cp_get_default_logger()
493  IF (btest(cp_print_key_should_output(iteration_info=logger%iter_info, &
494  basis_section=print_key), cp_p_file)) THEN
495 
496  unit_nr = cp_print_key_unit_nr(logger, print_key, middle_name="energy", &
497  extension=".dat", is_new_file=file_is_new)
498 
499  ! don't write the 0-th frame if the file already exists
500  IF (.NOT. file_is_new .AND. (pint_env%iter .LE. pint_env%first_step)) THEN
501  CALL cp_print_key_finished_output(unit_nr, logger, &
502  print_key)
503  RETURN
504  END IF
505 
506  ! cp_print_key_unit_nr returns -1 on nodes other than logger%para_env%is_source()
507  IF (unit_nr > 0) THEN
508 
509  ! please keep the format explanation up to date
510  ! keep the constant of motion the true constant of motion !
511  IF (file_is_new) THEN
512  WRITE (unit_nr, "(A8,1X,A12,1X,5(A20,1X),A12)") &
513  "# StepNr", &
514  " Time [fs]", &
515  " Kinetic [a.u.]", &
516  " VirialKin [a.u.]", &
517  " Temperature [K]", &
518  " Potential [a.u.]", &
519  " ConsQty [a.u.]", &
520  " CPU [s]"
521  END IF
522 
523  t = cp_unit_from_cp2k(pint_env%t, "fs")
524 
525  ndof = pint_env%p
526  IF (pint_env%first_propagated_mode .EQ. 2) THEN
527  ndof = ndof - 1
528  END IF
529  temp = cp_unit_from_cp2k(2.0_dp*pint_env%e_kin_beads/ &
530  REAL(ndof, dp)/REAL(pint_env%ndim, dp), &
531  "K")*pint_env%propagator%temp_sim2phys
532 
533  WRITE (unit_nr, "(I8,1X,F12.3,1X,5(F20.9,1X),F12.1)") &
534  pint_env%iter, &
535  t, &
536  pint_env%energy(e_kin_thermo_id), &
537  pint_env%energy(e_kin_virial_id), &
538  temp, &
539  pint_env%energy(e_potential_id), &
540  pint_env%energy(e_conserved_id), &
541  pint_env%time_per_step
542  CALL m_flush(unit_nr)
543 
544  END IF
545 
546  CALL cp_print_key_finished_output(unit_nr, logger, print_key)
547  END IF
548 
549  END SUBROUTINE pint_write_ener
550 
551 ! ***************************************************************************
552 !> \brief Writes out the actions according to PINT%PRINT%ACTION
553 !> \param pint_env path integral environment
554 !> \author Felix Uhl
555 ! **************************************************************************************************
556  SUBROUTINE pint_write_action(pint_env)
557  TYPE(pint_env_type), INTENT(IN) :: pint_env
558 
559  INTEGER :: unit_nr
560  LOGICAL :: file_is_new
561  REAL(kind=dp) :: t
562  TYPE(cp_logger_type), POINTER :: logger
563  TYPE(section_vals_type), POINTER :: print_key
564 
565  NULLIFY (print_key, logger)
566  print_key => section_vals_get_subs_vals(pint_env%input, &
567  "MOTION%PINT%PRINT%ACTION")
568  logger => cp_get_default_logger()
569  IF (btest(cp_print_key_should_output(iteration_info=logger%iter_info, &
570  basis_section=print_key), cp_p_file)) THEN
571 
572  unit_nr = cp_print_key_unit_nr(logger, print_key, middle_name="action", &
573  extension=".dat", is_new_file=file_is_new)
574 
575  ! don't write the 0-th frame if the file already exists
576  IF (.NOT. file_is_new .AND. (pint_env%iter .LE. pint_env%first_step)) THEN
577  CALL cp_print_key_finished_output(unit_nr, logger, &
578  print_key)
579  RETURN
580  END IF
581 
582  ! cp_print_key_unit_nr returns -1 on nodes other than logger%para_env%is_source()
583  IF (unit_nr > 0) THEN
584 
585  ! please keep the format explanation up to date
586  ! keep the constant of motion the true constant of motion !
587  IF (file_is_new) THEN
588  WRITE (unit_nr, "(A8,1X,A12,1X,2(A25,1X))") &
589  "# StepNr", &
590  " Time [fs]", &
591  " Link Action [a.u.]", &
592  " Potential Action [a.u.]"
593  END IF
594 
595  t = cp_unit_from_cp2k(pint_env%t, "fs")
596 
597  WRITE (unit_nr, "(I8,1X,F12.3,1X,5(F20.9,1X),F12.1)") &
598  pint_env%iter, &
599  t, &
600  pint_env%link_action, &
601  pint_env%pot_action
602  CALL m_flush(unit_nr)
603 
604  END IF
605 
606  CALL cp_print_key_finished_output(unit_nr, logger, print_key)
607  END IF
608 
609  END SUBROUTINE pint_write_action
610 
611 ! ***************************************************************************
612 !> \brief Write step info to the output file.
613 !> \param pint_env ...
614 !> \date 2009-11-16
615 !> \par History
616 !> 2010-01-27 getting default unit nr now only on ionode [lwalewski]
617 !> \author Lukasz Walewski
618 ! **************************************************************************************************
619  SUBROUTINE pint_write_step_info(pint_env)
620  TYPE(pint_env_type), INTENT(IN) :: pint_env
621 
622  CHARACTER(len=default_string_length) :: msgstr, stmp, time_unit
623  INTEGER :: unit_nr
624  REAL(kind=dp) :: time_used
625  TYPE(cp_logger_type), POINTER :: logger
626 
627  unit_nr = 0
628  NULLIFY (logger)
629  logger => cp_get_default_logger()
630 
631  time_used = pint_env%time_per_step
632  time_unit = "sec"
633  IF (time_used .GE. 60.0_dp) THEN
634  time_used = time_used/60.0_dp
635  time_unit = "min"
636  END IF
637  IF (time_used .GE. 60.0_dp) THEN
638  time_used = time_used/60.0_dp
639  time_unit = "hours"
640  END IF
641  msgstr = "PINT step"
642  stmp = ""
643  WRITE (stmp, *) pint_env%iter
644  msgstr = trim(adjustl(msgstr))//" "//trim(adjustl(stmp))//" of"
645  stmp = ""
646  WRITE (stmp, *) pint_env%last_step
647  msgstr = trim(adjustl(msgstr))//" "//trim(adjustl(stmp))//" in"
648  stmp = ""
649  WRITE (stmp, '(F20.1)') time_used
650  msgstr = trim(adjustl(msgstr))//" "//trim(adjustl(stmp))
651  msgstr = trim(adjustl(msgstr))//" "//trim(adjustl(time_unit))//"."
652 
653  IF (logger%para_env%is_source()) THEN
654  unit_nr = cp_logger_get_default_unit_nr(logger)
655  WRITE (unit_nr, '(T2,A)') "PINT| "//trim(adjustl(msgstr))
656  END IF
657 
658  ! print out the total energy - for regtest evaluation
659  stmp = ""
660  WRITE (stmp, *) pint_env%energy(e_conserved_id)
661  msgstr = "Total energy = "//trim(adjustl(stmp))
662  IF (logger%para_env%is_source()) THEN
663  WRITE (unit_nr, '(T2,A)') "PINT| "//trim(adjustl(msgstr))
664  END IF
665 
666  END SUBROUTINE pint_write_step_info
667 
668 ! ***************************************************************************
669 !> \brief Write radii of gyration according to PINT%PRINT%CENTROID_GYR
670 !> \param pint_env ...
671 !> \date 2011-01-07
672 !> \author Lukasz Walewski
673 ! **************************************************************************************************
674  SUBROUTINE pint_write_rgyr(pint_env)
675 
676  TYPE(pint_env_type), INTENT(IN) :: pint_env
677 
678  CHARACTER(len=default_string_length) :: unit_str
679  INTEGER :: ia, ib, ic, idim, unit_nr
680  LOGICAL :: new_file, should_output
681  REAL(kind=dp) :: nb, ss, unit_conv
682  TYPE(cp_logger_type), POINTER :: logger
683  TYPE(section_vals_type), POINTER :: print_key
684 
685  NULLIFY (logger)
686  logger => cp_get_default_logger()
687 
688  ! decide whether to write anything or not
689  NULLIFY (print_key)
690  print_key => section_vals_get_subs_vals(pint_env%input, &
691  "MOTION%PINT%PRINT%CENTROID_GYR")
692  should_output = btest(cp_print_key_should_output( &
693  iteration_info=logger%iter_info, &
694  basis_section=print_key), cp_p_file)
695  IF (.NOT. should_output) THEN
696  RETURN
697  END IF
698 
699  ! get the units conversion factor
700  CALL section_vals_val_get(print_key, "UNIT", c_val=unit_str)
701  unit_conv = cp_unit_from_cp2k(1.0_dp, trim(unit_str))
702 
703  ! calculate the centroid positions
704  nb = real(pint_env%p, dp)
705  idim = 0
706  DO ia = 1, pint_env%ndim/3
707  DO ic = 1, 3
708  idim = idim + 1
709  ss = 0.0_dp
710  DO ib = 1, pint_env%p
711  ss = ss + pint_env%x(ib, idim)
712  END DO
713  pint_env%rtmp_ndim(idim) = ss/nb
714  END DO
715  END DO
716 
717  ! calculate the radii of gyration
718  idim = 0
719  DO ia = 1, pint_env%ndim/3
720  ss = 0.0_dp
721  DO ic = 1, 3
722  idim = idim + 1
723  DO ib = 1, pint_env%p
724  ss = ss + (pint_env%x(ib, idim) - pint_env%rtmp_ndim(idim))**2
725  END DO
726  END DO
727  pint_env%rtmp_natom(ia) = sqrt(ss/nb)*unit_conv
728  END DO
729 
730  unit_nr = cp_print_key_unit_nr(logger, print_key, is_new_file=new_file, &
731  middle_name="centroid-gyr", extension=".dat")
732 
733  ! don't write the 0-th frame if the file already exists
734  IF (.NOT. new_file .AND. (pint_env%iter .LE. pint_env%first_step)) THEN
735  CALL cp_print_key_finished_output(unit_nr, logger, &
736  print_key)
737  RETURN
738  END IF
739 
740  ! actually perform the i/o - on the ionode only
741  IF (unit_nr > 0) THEN
742 
743  DO ia = 1, pint_env%ndim/3
744  WRITE (unit_nr, '(F20.10,1X)', advance='NO') pint_env%rtmp_natom(ia)
745  END DO
746  WRITE (unit_nr, '(A)') ""
747 
748  CALL m_flush(unit_nr)
749 
750  END IF
751 
752  CALL cp_print_key_finished_output(unit_nr, logger, print_key)
753 
754  END SUBROUTINE pint_write_rgyr
755 
756 END MODULE pint_io
Handles all functions related to the CELL.
Definition: cell_types.F:15
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
type(cp_logger_type) function, pointer, public cp_get_default_logger()
returns the default logger
routines to handle the output, The idea is to remove the decision of wheter to output and what to out...
integer function, public cp_print_key_unit_nr(logger, basis_section, print_key_path, extension, middle_name, local, log_filename, ignore_should_output, file_form, file_position, file_action, file_status, do_backup, on_file, is_new_file, mpi_io, fout)
...
subroutine, public cp_print_key_finished_output(unit_nr, logger, basis_section, print_key_path, local, ignore_should_output, on_file, mpi_io)
should be called after you finish working with a unit obtained with cp_print_key_unit_nr,...
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...
types that represent a subsys, i.e. a part of the system
subroutine, public cp_subsys_get(subsys, ref_count, atomic_kinds, atomic_kind_set, particles, particle_set, local_particles, molecules, molecule_set, molecule_kinds, molecule_kind_set, local_molecules, para_env, colvar_p, shell_particles, core_particles, gci, multipoles, natom, nparticle, ncore, nshell, nkind, atprop, virial, results, cell)
returns information about various attributes of the given subsys
unit conversion facility
Definition: cp_units.F:30
real(kind=dp) function, public cp_unit_from_cp2k(value, unit_str, defaults, power)
converts from the internal cp2k units to the given unit
Definition: cp_units.F:1179
interface to use cp2k as library
Definition: f77_interface.F:20
subroutine, public f_env_add_defaults(f_env_id, f_env, handle)
adds the default environments of the f_env to the stack of the defaults, and returns a new error and ...
subroutine, public f_env_rm_defaults(f_env, ierr, handle)
removes the default environments of the f_env to the stack of the defaults, and sets ierr accordingly...
Interface for the force calculations.
recursive subroutine, public force_env_get(force_env, in_use, fist_env, qs_env, meta_env, fp_env, subsys, para_env, potential_energy, additional_potential, kinetic_energy, harmonic_shell, kinetic_shell, cell, sub_force_env, qmmm_env, qmmmx_env, eip_env, pwdft_env, globenv, input, force_env_section, method_name_id, root_section, mixed_env, nnp_env, embed_env)
returns various attributes about the force environment
collects all constants needed in input so that they can be used without circular dependencies
integer, parameter, public dump_xmol
integer, parameter, public dump_atomic
integer, parameter, public dump_dcd_aligned_cell
integer, parameter, public dump_dcd
objects that represent the structure of input sections and the data contained in an input 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
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 dp
Definition: kinds.F:34
integer, parameter, public default_string_length
Definition: kinds.F:57
Machine interface based on Fortran 2003 and POSIX.
Definition: machine.F:17
subroutine, public m_flush(lunit)
flushes units if the &GLOBAL flag is set accordingly
Definition: machine.F:106
represent a simple array based list of the given type
Define methods related to particle_type.
subroutine, public write_particle_coordinates(particle_set, iunit, output_format, content, title, cell, array, unit_conv, charge_occup, charge_beta, charge_extended, print_kind)
Should be able to write a few formats e.g. xmol, and some binary format (dcd) some format can be used...
I/O subroutines for pint_env.
Definition: pint_io.F:13
subroutine, public pint_write_action(pint_env)
Writes out the actions according to PINTPRINTACTION.
Definition: pint_io.F:557
subroutine, public pint_write_centroids(pint_env)
Write out the trajectory of the centroid (positions and velocities)
Definition: pint_io.F:104
subroutine, public pint_write_rgyr(pint_env)
Write radii of gyration according to PINTPRINTCENTROID_GYR.
Definition: pint_io.F:675
subroutine, public pint_write_step_info(pint_env)
Write step info to the output file.
Definition: pint_io.F:620
subroutine, public pint_write_ener(pint_env)
Writes out the energies according to PINTPRINTENERGY.
Definition: pint_io.F:481
subroutine, public pint_write_line(line)
Writes out a line of text to the default output unit.
Definition: pint_io.F:76
subroutine, public pint_write_trajectory(pint_env)
Write out the trajectory of the beads (positions and velocities)
Definition: pint_io.F:259
subroutine, public pint_write_com(pint_env)
Write center of mass (COM) position according to PINTPRINTCOM.
Definition: pint_io.F:415
Public path integral routines that can be called from other modules.
Definition: pint_public.F:15
pure real(kind=dp) function, dimension(3), public pint_com_pos(pint_env)
Return the center of mass of the PI system.
Definition: pint_public.F:45
subroutine, public pint_u2x(pint_env, ux, x)
transform from the u variable to the x (inverse of x2u)
integer, parameter, public e_kin_thermo_id
Definition: pint_types.F:25
integer, parameter, public e_conserved_id
Definition: pint_types.F:25
integer, parameter, public e_potential_id
Definition: pint_types.F:25
integer, parameter, public e_kin_virial_id
Definition: pint_types.F:25