added cp-style md output in PW

This commit is contained in:
Riccardo Bertossa 2023-09-29 14:25:05 +02:00
parent 89e27d67a3
commit 21104a4b83
6 changed files with 28 additions and 5 deletions

View File

@ -74,7 +74,6 @@ set(src_cpv
src/potentials.f90
src/pres_ai_mod.f90
src/print_out.f90
src/printout_base.f90
src/problem_size.f90
src/pseudo_base.f90
src/pseudopot.f90

View File

@ -81,7 +81,6 @@ plugin_utilities.o \
potentials.o \
pres_ai_mod.o \
print_out.o \
printout_base.o \
problem_size.o \
pseudo_base.o \
pseudopot.o \

View File

@ -52,6 +52,7 @@ set(src_modules
plugin_flags.f90
plugin_arguments.f90
plugin_variables.f90
printout_base.f90
pw_dot.f90
qmmm.f90
random_numbers.f90

View File

@ -61,6 +61,7 @@ parser.o \
plugin_flags.o \
plugin_arguments.o \
plugin_variables.o \
printout_base.o \
pw_dot.o \
qmmm.o \
random_numbers.o \

View File

@ -57,7 +57,8 @@ end function
SUBROUTINE printout_pos( iunit, tau, nat, ityp, what, nfi, tps, label, fact, head )
!
!
INTEGER, INTENT(IN) :: iunit, nat, ityp(:)
INTEGER, INTENT(IN) :: iunit, nat
INTEGER, INTENT(IN), OPTIONAL :: ityp(:)
REAL(DP), INTENT(IN) :: tau( :, : )
CHARACTER(LEN=3), INTENT(IN), OPTIONAL :: what
INTEGER, INTENT(IN), OPTIONAL :: nfi
@ -95,7 +96,7 @@ end function
END IF
END IF
!
IF( PRESENT( label ) ) THEN
IF( PRESENT( label ) .and. PRESENT(ityp) ) THEN
DO ia = 1, nat
WRITE( iunit, 255 ) label(ityp(ia)), ( f * tau(k,ia),k = 1,3)
END DO

View File

@ -46,7 +46,7 @@ SUBROUTINE move_ions( idone, ions_status, optimizer_failed )
USE bfgs_module, ONLY : bfgs, terminate_bfgs
USE basic_algebra_routines, ONLY : norm
USE dynamics_module, ONLY : verlet, terminate_verlet, proj_verlet, fire
USE dynamics_module, ONLY : smart_MC, langevin_md, dt
USE dynamics_module, ONLY : smart_MC, langevin_md, dt, vel
USE dynamics_module, ONLY : fire_nmin, fire_f_inc, fire_f_dec, &
fire_alpha_init, fire_falpha, fire_dtmax
USE klist, ONLY : nelec, tot_charge
@ -54,6 +54,8 @@ SUBROUTINE move_ions( idone, ions_status, optimizer_failed )
USE fcp_module, ONLY : lfcp, fcp_eps, fcp_mu, fcp_relax, &
fcp_verlet, fcp_terminate, output_fcp
USE rism_module, ONLY : lrism, rism_new_conv_thr
USE printout_base, ONLY : printout_base_open, printout_base_close, &
printout_cell, printout_pos, printout_stress
!
IMPLICIT NONE
!
@ -72,6 +74,8 @@ SUBROUTINE move_ions( idone, ions_status, optimizer_failed )
REAL(DP) :: relec, felec, helec, capacitance, tot_charge_
LOGICAL :: conv_ions
CHARACTER(LEN=320) :: filebfgs
INTEGER :: iunit
REAL(DP) :: tps !time in picoseconds
!
optimizer_failed = .FALSE.
!
@ -389,6 +393,24 @@ SUBROUTINE move_ions( idone, ions_status, optimizer_failed )
! ... FIXME 2: why not impose symmetry instead of just checking it?
!
CALL checkallsym( nat, tau, ityp)
! write trajectory output files
tps = dt*real(istep,DP) !TODO: this is wrong if we change the timestep during the run!
iunit = printout_base_open('.pos')
call printout_pos(iunit, tau, nat, tps=tps, nfi=istep)
call printout_base_close(iunit)
iunit = printout_base_open('.cel')
call printout_cell(iunit,at,istep,tps)
call printout_base_close(iunit)
iunit = printout_base_open('.for')
call printout_pos(iunit, force, nat, tps=tps, nfi=istep)
call printout_base_close(iunit)
iunit = printout_base_open('.vel')
call printout_pos(iunit, vel, nat, tps=tps, nfi=istep)
call printout_base_close(iunit)
!
ENDIF
!