49#include "../base/base_uses.f90"
55 LOGICAL,
PRIVATE,
PARAMETER :: debug_this_module = .true.
56 CHARACTER(len=*),
PARAMETER,
PRIVATE :: moduleN =
'pint_io'
77 CHARACTER(len=*),
INTENT(IN) :: line
79 CHARACTER(len=default_string_length) :: my_label
87 IF (logger%para_env%is_source())
THEN
89 WRITE (unit_nr,
'(T2,A)') trim(my_label)//
" "//trim(line)
106 CHARACTER(len=*),
PARAMETER :: routinen =
'pint_write_centroids'
107 INTEGER,
PARAMETER :: n_ids = 2, pos_id = 1, vel_id = 2
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, &
114 LOGICAL :: new_file, print_kind
115 REAL(kind=
dp) :: nb, ss, unit_conv, vv
123 CALL timeset(routinen, handle1)
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, &
142 CALL pint_u2x(pint_env, ux=pint_env%uv, x=pint_env%v)
152 iteration_info=logger%iter_info, &
153 basis_section=print_key)
154 IF (.NOT. btest(should_output,
cp_p_file))
CONTINUE
166 SELECT CASE (outformat)
182 NULLIFY (f_env, cell, subsys)
184 f_env=f_env, handle=handle)
186 cell=cell, subsys=subsys)
191 nb = real(pint_env%p,
dp)
193 DO iat = 1, pint_env%ndim/3
199 DO ib = 1, pint_env%p
200 ss = ss + pint_env%x(ib, idim)
201 vv = vv + pint_env%v(ib, idim)
204 particles%els(iat)%r(idir) = ss/nb
205 particles%els(iat)%v(idir) = vv/nb
212 my_middle_name = trim(middle_name(id))
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)
219 IF (.NOT. new_file .AND. (pint_env%iter .LE. pint_env%first_step))
THEN
226 IF (unit_nr > 0)
THEN
231 output_format=outformat, &
232 content=content_id(id), &
235 unit_conv=unit_conv, &
236 print_kind=print_kind)
239 print_key,
"", local=.false.)
248 CALL timestop(handle1)
261 CHARACTER(len=*),
PARAMETER :: routinen =
'pint_write_trajectory'
262 INTEGER,
PARAMETER :: force_id = 3, n_ids = 3, pos_id = 1, &
265 CHARACTER(len=default_string_length) :: ext, form, ib_str, my_middle_name, &
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
272 REAL(kind=
dp) :: unit_conv
280 CALL timeset(routinen, handle1)
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"
295 CALL pint_u2x(pint_env, ux=pint_env%uv, x=pint_env%v)
305 iteration_info=logger%iter_info, &
306 basis_section=print_key)
307 IF (.NOT. btest(should_output,
cp_p_file))
CONTINUE
317 SELECT CASE (outformat)
331 NULLIFY (f_env, cell, subsys)
333 f_env=f_env, handle=handle)
335 cell=cell, subsys=subsys)
340 "MOTION%PINT%PRINT%IMAGINARY_TIME_STRIDE", &
344 DO ib = 1, pint_env%p, imag_stride
349 DO iat = 1, pint_env%ndim/3
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)
362 my_middle_name = trim(middle_name(id))//trim(adjustl(ib_str))
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)
369 IF (.NOT. new_file .AND. (pint_env%iter .LE. pint_env%first_step))
THEN
376 IF (unit_nr > 0)
THEN
379 WRITE (unit=title, fmt=
"(A,I8,A,F20.10)") &
380 " i =", pint_env%iter, &
381 ", E =", pint_env%e_pot_bead(ib)
387 output_format=outformat, &
388 content=content_id(id), &
394 print_key,
"", local=.false.)
405 CALL timestop(handle1)
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
431 "MOTION%PINT%PRINT%COM")
433 iteration_info=logger%iter_info, &
435 IF (.NOT. should_output)
THEN
445 middle_name=
"com-pos", extension=
".xyz")
448 IF (.NOT. new_file .AND. (pint_env%iter .LE. pint_env%first_step))
THEN
455 IF (unit_nr > 0)
THEN
457 WRITE (unit_nr,
'(I2)') 1
458 WRITE (stmp1, *) pint_env%iter
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)
483 INTEGER :: ndof, unit_nr
484 LOGICAL :: file_is_new
485 REAL(kind=
dp) :: t, temp
489 NULLIFY (print_key, logger)
491 "MOTION%PINT%PRINT%ENERGY")
494 basis_section=print_key),
cp_p_file))
THEN
497 extension=
".dat", is_new_file=file_is_new)
500 IF (.NOT. file_is_new .AND. (pint_env%iter .LE. pint_env%first_step))
THEN
507 IF (unit_nr > 0)
THEN
511 IF (file_is_new)
THEN
512 WRITE (unit_nr,
"(A8,1X,A12,1X,5(A20,1X),A12)") &
516 " VirialKin [a.u.]", &
517 " Temperature [K]", &
518 " Potential [a.u.]", &
526 IF (pint_env%first_propagated_mode .EQ. 2)
THEN
530 REAL(ndof,
dp)/
REAL(pint_env%ndim, dp), &
531 "K")*pint_env%propagator%temp_sim2phys
533 WRITE (unit_nr,
"(I8,1X,F12.3,1X,5(F20.9,1X),F12.1)") &
541 pint_env%time_per_step
560 LOGICAL :: file_is_new
565 NULLIFY (print_key, logger)
567 "MOTION%PINT%PRINT%ACTION")
570 basis_section=print_key),
cp_p_file))
THEN
573 extension=
".dat", is_new_file=file_is_new)
576 IF (.NOT. file_is_new .AND. (pint_env%iter .LE. pint_env%first_step))
THEN
583 IF (unit_nr > 0)
THEN
587 IF (file_is_new)
THEN
588 WRITE (unit_nr,
"(A8,1X,A12,1X,2(A25,1X))") &
591 " Link Action [a.u.]", &
592 " Potential Action [a.u.]"
597 WRITE (unit_nr,
"(I8,1X,F12.3,1X,5(F20.9,1X),F12.1)") &
600 pint_env%link_action, &
622 CHARACTER(len=default_string_length) :: msgstr, stmp, time_unit
624 REAL(kind=
dp) :: time_used
631 time_used = pint_env%time_per_step
633 IF (time_used .GE. 60.0_dp)
THEN
634 time_used = time_used/60.0_dp
637 IF (time_used .GE. 60.0_dp)
THEN
638 time_used = time_used/60.0_dp
643 WRITE (stmp, *) pint_env%iter
644 msgstr = trim(adjustl(msgstr))//
" "//trim(adjustl(stmp))//
" of"
646 WRITE (stmp, *) pint_env%last_step
647 msgstr = trim(adjustl(msgstr))//
" "//trim(adjustl(stmp))//
" in"
649 WRITE (stmp,
'(F20.1)') time_used
650 msgstr = trim(adjustl(msgstr))//
" "//trim(adjustl(stmp))
651 msgstr = trim(adjustl(msgstr))//
" "//trim(adjustl(time_unit))//
"."
653 IF (logger%para_env%is_source())
THEN
655 WRITE (unit_nr,
'(T2,A)')
"PINT| "//trim(adjustl(msgstr))
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))
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
691 "MOTION%PINT%PRINT%CENTROID_GYR")
693 iteration_info=logger%iter_info, &
695 IF (.NOT. should_output)
THEN
704 nb = real(pint_env%p,
dp)
706 DO ia = 1, pint_env%ndim/3
710 DO ib = 1, pint_env%p
711 ss = ss + pint_env%x(ib, idim)
713 pint_env%rtmp_ndim(idim) = ss/nb
719 DO ia = 1, pint_env%ndim/3
723 DO ib = 1, pint_env%p
724 ss = ss + (pint_env%x(ib, idim) - pint_env%rtmp_ndim(idim))**2
727 pint_env%rtmp_natom(ia) = sqrt(ss/nb)*unit_conv
731 middle_name=
"centroid-gyr", extension=
".dat")
734 IF (.NOT. new_file .AND. (pint_env%iter .LE. pint_env%first_step))
THEN
741 IF (unit_nr > 0)
THEN
743 DO ia = 1, pint_env%ndim/3
744 WRITE (unit_nr,
'(F20.10,1X)', advance=
'NO') pint_env%rtmp_natom(ia)
746 WRITE (unit_nr,
'(A)')
""
Handles all functions related to the CELL.
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
real(kind=dp) function, public cp_unit_from_cp2k(value, unit_str, defaults, power)
converts from the internal cp2k units to the given unit
interface to use cp2k as library
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, ipi_env)
returns various attributes about the force environment
Defines the basic variable types.
integer, parameter, public dp
integer, parameter, public default_string_length
Machine interface based on Fortran 2003 and POSIX.
subroutine, public m_flush(lunit)
flushes units if the &GLOBAL flag is set accordingly
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.
subroutine, public pint_write_action(pint_env)
Writes out the actions according to PINTPRINTACTION.
subroutine, public pint_write_centroids(pint_env)
Write out the trajectory of the centroid (positions and velocities)
subroutine, public pint_write_rgyr(pint_env)
Write radii of gyration according to PINTPRINTCENTROID_GYR.
subroutine, public pint_write_step_info(pint_env)
Write step info to the output file.
subroutine, public pint_write_ener(pint_env)
Writes out the energies according to PINTPRINTENERGY.
subroutine, public pint_write_line(line)
Writes out a line of text to the default output unit.
subroutine, public pint_write_trajectory(pint_env)
Write out the trajectory of the beads (positions and velocities)
subroutine, public pint_write_com(pint_env)
Write center of mass (COM) position according to PINTPRINTCOM.
Public path integral routines that can be called from other modules.
pure real(kind=dp) function, dimension(3), public pint_com_pos(pint_env)
Return the center of mass of the PI system.
integer, parameter, public e_kin_thermo_id
integer, parameter, public e_conserved_id
integer, parameter, public e_potential_id
integer, parameter, public e_kin_virial_id
Type defining parameters related to the simulation cell.
type of a logger, at the moment it contains just a print level starting at which level it should be l...
represents a system: atoms, molecules, their pos,vel,...
represent a list of objects
environment for a path integral run