70#include "../base/base_uses.f90"
89 SUBROUTINE cp_eval_at(gopt_env, x, f, gradient, master, &
90 final_evaluation, para_env)
96 TYPE(gopt_f_type),
POINTER :: gopt_env
97 REAL(KIND=
dp),
DIMENSION(:),
POINTER :: x
98 REAL(KIND=
dp),
INTENT(out),
OPTIONAL :: f
99 REAL(KIND=
dp),
DIMENSION(:),
OPTIONAL, &
101 INTEGER,
INTENT(IN) :: master
102 LOGICAL,
INTENT(IN),
OPTIONAL :: final_evaluation
103 TYPE(mp_para_env_type),
POINTER :: para_env
109 LOGICAL,
PRIVATE,
PARAMETER :: debug_this_module = .true.
110 CHARACTER(len=*),
PARAMETER,
PRIVATE :: moduleN =
"gopt_f_methods"
129 TYPE(gopt_f_type),
POINTER :: gopt_env
130 REAL(kind=dp),
DIMENSION(:),
POINTER :: x0
132 INTEGER :: i, idg, j, nparticle
139 SELECT CASE (gopt_env%type_id)
143 IF (gopt_env%force_env%in_use ==
use_qmmm) &
145 IF (gopt_env%force_env%in_use ==
use_qmmmx) &
148 ALLOCATE (x0(3*nparticle))
151 SELECT CASE (gopt_env%cell_method_id)
153 CALL force_env_get(gopt_env%force_env, subsys=subsys, cell=cell)
155 gopt_env%h_ref = cell%hmat
157 IF (gopt_env%force_env%in_use ==
use_qmmm) &
159 IF (gopt_env%force_env%in_use ==
use_qmmmx) &
162 ALLOCATE (x0(3*nparticle + 6))
168 x0(idg) = cell%hmat(j, i)
178 x0(idg) = cell%hmat(j, i)
198 INTEGER,
INTENT(IN) :: its, output_unit
200 IF (output_unit > 0)
THEN
201 WRITE (unit=output_unit, fmt=
"(/,T2,26('-'))")
202 WRITE (unit=output_unit, fmt=
"(T2,A,I6)")
"OPTIMIZATION STEP: ", its
203 WRITE (unit=output_unit, fmt=
"(T2,26('-'))")
219 SUBROUTINE gopt_f_io_init(gopt_env, output_unit, opt_energy, wildcard, its, used_time)
221 TYPE(gopt_f_type),
POINTER :: gopt_env
222 INTEGER,
INTENT(IN) :: output_unit
223 REAL(kind=dp) :: opt_energy
224 CHARACTER(LEN=5) :: wildcard
225 INTEGER,
INTENT(IN) :: its
226 REAL(kind=dp) :: used_time
228 TYPE(mp_para_env_type),
POINTER :: para_env
229 CHARACTER(LEN=default_string_length) :: energy_unit, stress_unit
230 REAL(kind=dp) :: pres_int
231 INTEGER(KIND=int_8) :: max_memory
232 LOGICAL :: print_memory
237 IF (print_memory)
THEN
243 "PRINT%PROGRAM_RUN_INFO%ENERGY_UNIT", &
246 "PRINT%STRESS_TENSOR%STRESS_UNIT", &
249 SELECT CASE (gopt_env%type_id)
252 IF (.NOT. gopt_env%dimer_rotation)
THEN
253 CALL write_cycle_infos(output_unit, &
257 used_time=used_time, &
258 max_memory=max_memory, &
259 energy_unit=energy_unit, &
260 stress_unit=stress_unit)
262 CALL write_rot_cycle_infos(output_unit, &
265 dimer_env=gopt_env%dimer_env, &
267 used_time=used_time, &
268 max_memory=max_memory)
272 pres_int = gopt_env%cell_env%pres_int
273 CALL write_cycle_infos(output_unit, &
278 used_time=used_time, &
279 max_memory=max_memory, &
280 energy_unit=energy_unit, &
281 stress_unit=stress_unit)
283 CALL write_cycle_infos(output_unit, &
287 used_time=used_time, &
288 max_memory=max_memory, &
289 energy_unit=energy_unit, &
290 stress_unit=stress_unit)
318 SUBROUTINE gopt_f_io(gopt_env, force_env, root_section, its, opt_energy, &
319 output_unit, eold, emin, wildcard, gopt_param, ndf, dx, xi, conv, pred, rat, &
320 step, rad, used_time)
322 TYPE(gopt_f_type),
POINTER :: gopt_env
325 INTEGER,
INTENT(IN) :: its
326 REAL(kind=dp),
INTENT(IN) :: opt_energy
327 INTEGER,
INTENT(IN) :: output_unit
328 REAL(kind=dp) :: eold, emin
329 CHARACTER(LEN=5) :: wildcard
331 INTEGER,
INTENT(IN),
OPTIONAL :: ndf
332 REAL(kind=dp),
DIMENSION(:),
INTENT(IN),
OPTIONAL :: dx
333 REAL(kind=dp),
DIMENSION(:),
OPTIONAL,
POINTER :: xi
334 LOGICAL,
OPTIONAL :: conv
335 REAL(kind=dp),
INTENT(IN),
OPTIONAL :: pred, rat, step, rad
336 REAL(kind=dp) :: used_time
338 CHARACTER(LEN=default_string_length) :: energy_unit, stress_unit
339 INTEGER(KIND=int_8) :: max_memory
340 LOGICAL :: print_memory
341 REAL(kind=dp) :: pres_diff, pres_diff_constr, pres_int, &
343 TYPE(mp_para_env_type),
POINTER :: para_env
348 IF (print_memory)
THEN
354 "PRINT%PROGRAM_RUN_INFO%ENERGY_UNIT", &
357 "PRINT%STRESS_TENSOR%STRESS_UNIT", &
360 SELECT CASE (gopt_env%type_id)
363 IF (.NOT. gopt_env%dimer_rotation)
THEN
364 CALL geo_opt_io(force_env=force_env, root_section=root_section, &
365 motion_section=gopt_env%motion_section, its=its, opt_energy=opt_energy)
366 CALL write_cycle_infos(output_unit, &
369 ediff=(opt_energy - eold), &
376 used_time=used_time, &
377 max_memory=max_memory, &
378 energy_unit=energy_unit, &
379 stress_unit=stress_unit)
381 IF (
PRESENT(conv))
THEN
382 cpassert(
PRESENT(ndf))
383 cpassert(
PRESENT(dx))
384 cpassert(
PRESENT(xi))
385 CALL check_converg(ndf, dx, xi, output_unit, conv, gopt_param, max_memory, stress_unit)
389 CALL write_restart(force_env=force_env, root_section=root_section)
390 CALL write_rot_cycle_infos(output_unit, its, opt_energy, opt_energy - eold, emin, gopt_env%dimer_env, &
391 wildcard=wildcard, used_time=used_time, max_memory=max_memory)
393 IF (
PRESENT(conv))
THEN
394 cpassert(
ASSOCIATED(gopt_env%dimer_env))
395 CALL check_rot_conv(gopt_env%dimer_env, output_unit, conv)
400 pres_diff = gopt_env%cell_env%pres_int - gopt_env%cell_env%pres_ext
401 pres_int = gopt_env%cell_env%pres_int
402 pres_tol = gopt_env%cell_env%pres_tol
403 CALL geo_opt_io(force_env=force_env, root_section=root_section, &
404 motion_section=gopt_env%motion_section, its=its, opt_energy=opt_energy)
405 CALL write_cycle_infos(output_unit, &
408 ediff=(opt_energy - eold), &
416 used_time=used_time, &
417 max_memory=max_memory, &
418 energy_unit=energy_unit, &
419 stress_unit=stress_unit)
421 IF (
PRESENT(conv))
THEN
422 cpassert(
PRESENT(ndf))
423 cpassert(
PRESENT(dx))
424 cpassert(
PRESENT(xi))
425 IF (gopt_env%cell_env%constraint_id ==
fix_none)
THEN
426 CALL check_converg(ndf, dx, xi, output_unit, conv, gopt_param, max_memory, stress_unit, &
429 pres_diff_constr = gopt_env%cell_env%pres_constr - gopt_env%cell_env%pres_ext
430 CALL check_converg(ndf, dx, xi, output_unit, conv, gopt_param, max_memory, stress_unit, &
431 pres_diff, pres_tol, pres_diff_constr)
435 CALL write_cycle_infos(output_unit, &
438 ediff=(opt_energy - eold), &
445 used_time=used_time, &
446 max_memory=max_memory, &
447 energy_unit=energy_unit, &
448 stress_unit=stress_unit)
450 IF (
PRESENT(conv))
THEN
451 cpassert(
PRESENT(ndf))
452 cpassert(
PRESENT(dx))
453 cpassert(
PRESENT(xi))
454 CALL check_converg(ndf, dx, xi, output_unit, conv, gopt_param, max_memory, stress_unit)
474 para_env, master, output_unit)
475 TYPE(gopt_f_type),
POINTER :: gopt_env
477 REAL(kind=dp),
DIMENSION(:),
POINTER :: x0
481 TYPE(mp_para_env_type),
POINTER :: para_env
482 INTEGER,
INTENT(IN) :: master, output_unit
484 IF (gopt_env%eval_opt_geo)
THEN
485 IF (.NOT. gopt_env%dimer_rotation)
THEN
486 CALL write_final_info(output_unit, conv, its, gopt_env, x0, master, &
487 para_env, force_env, gopt_env%motion_section, root_section)
490 CALL write_restart(force_env=force_env, root_section=root_section)
511 SUBROUTINE write_cycle_infos(output_unit, it, etot, ediff, pred, rat, step, rad, emin, &
512 pres_int, wildcard, used_time, max_memory, energy_unit, stress_unit)
514 INTEGER,
INTENT(IN) :: output_unit, it
515 REAL(kind=dp),
INTENT(IN) :: etot
516 REAL(kind=dp),
INTENT(IN),
OPTIONAL :: ediff, pred, rat, step, rad, emin, &
518 CHARACTER(LEN=5),
INTENT(IN) :: wildcard
519 REAL(kind=dp),
INTENT(IN) :: used_time
520 INTEGER(KIND=int_8),
INTENT(IN) :: max_memory
521 CHARACTER(LEN=default_string_length),
INTENT(IN) :: energy_unit, stress_unit
523 CHARACTER(LEN=5) :: tag
525 IF (output_unit > 0)
THEN
527 WRITE (unit=output_unit, fmt=
"(/,T2,A)") tag//repeat(
"*", 74)
528 WRITE (unit=output_unit, fmt=
"(T2,A,T55,1X,I25)") &
529 tag//
"Step number", it
530 WRITE (unit=output_unit, fmt=
"(T2,A,T55,1X,A25)") &
531 tag//
"Optimization method", wildcard
532 WRITE (unit=output_unit, fmt=
"(T2,A,T55,1X,F25.10)") &
533 tag//
"Total energy ["//trim(adjustl(energy_unit))//
"]", &
535 IF (
PRESENT(pres_int))
THEN
536 WRITE (unit=output_unit, fmt=
"(T2,A,T55,1X,F25.10)") &
537 tag//
"Internal pressure ["//trim(adjustl(stress_unit))//
"]", &
540 IF (
PRESENT(ediff))
THEN
541 WRITE (unit=output_unit, fmt=
"(T2,A,T55,1X,F25.10)") &
542 tag//
"Effective energy change ["//trim(adjustl(energy_unit))//
"]", &
545 IF (
PRESENT(pred))
THEN
546 WRITE (unit=output_unit, fmt=
"(T2,A,T55,1X,F25.10)") &
547 tag//
"Predicted energy change ["//trim(adjustl(energy_unit))//
"]", &
550 IF (
PRESENT(rat))
THEN
551 WRITE (unit=output_unit, fmt=
"(T2,A,T55,1X,F25.10)") &
552 tag//
"Scaling factor", rat
554 IF (
PRESENT(step))
THEN
555 WRITE (unit=output_unit, fmt=
"(T2,A,T55,1X,F25.10)") &
556 tag//
"Step size", step
558 IF (
PRESENT(rad))
THEN
559 WRITE (unit=output_unit, fmt=
"(T2,A,T55,1X,F25.10)") &
560 tag//
"Trust radius", rad
562 IF (
PRESENT(emin))
THEN
563 IF (etot < emin)
THEN
564 WRITE (unit=output_unit, fmt=
"(T2,A,T77,A4)") &
565 tag//
"Decrease in energy",
" YES"
567 WRITE (unit=output_unit, fmt=
"(T2,A,T77,A4)") &
568 tag//
"Decrease in energy",
" NO"
571 WRITE (unit=output_unit, fmt=
"(T2,A,T55,1X,F25.3)") &
572 tag//
"Used time [s]", used_time
574 WRITE (unit=output_unit, fmt=
"(T2,A)") tag//repeat(
"*", 74)
575 IF (max_memory /= 0)
THEN
576 WRITE (unit=output_unit, fmt=
"(T2,A,T60,1X,I20)") &
577 tag//
"Estimated peak process memory [MiB]", &
578 (max_memory + (1024*1024) - 1)/(1024*1024)
583 END SUBROUTINE write_cycle_infos
598 SUBROUTINE write_rot_cycle_infos(output_unit, it, etot, ediff, emin, dimer_env, used_time, &
599 wildcard, max_memory)
601 INTEGER,
INTENT(IN) :: output_unit, it
602 REAL(kind=dp),
INTENT(IN) :: etot
603 REAL(kind=dp),
INTENT(IN),
OPTIONAL :: ediff, emin
605 REAL(kind=dp),
INTENT(IN) :: used_time
606 CHARACTER(LEN=5),
INTENT(IN) :: wildcard
607 INTEGER(KIND=int_8),
INTENT(IN) :: max_memory
609 CHARACTER(LEN=5) :: tag
611 IF (output_unit > 0)
THEN
613 WRITE (unit=output_unit, fmt=
"(/,T2,A)") tag//repeat(
"*", 74)
614 WRITE (unit=output_unit, fmt=
"(T2,A,T55,1X,I25)") &
615 tag//
"Rotational step number", it
616 WRITE (unit=output_unit, fmt=
"(T2,A,T55,1X,A25)") &
617 tag//
"Optimization method", wildcard
618 WRITE (unit=output_unit, fmt=
"(T2,A,T55,1X,F25.10)") &
619 tag//
"Local curvature", dimer_env%rot%curvature, &
620 tag//
"Total rotational force", etot
621 IF (
PRESENT(ediff))
THEN
622 WRITE (unit=output_unit, fmt=
"(T2,A,T55,1X,F25.10)") &
623 tag//
"Rotational force change", ediff
625 IF (
PRESENT(emin))
THEN
626 IF (etot < emin)
THEN
627 WRITE (unit=output_unit, fmt=
"(T2,A,T77,A4)") &
628 tag//
"Decrease in rotational force",
" YES"
630 WRITE (unit=output_unit, fmt=
"(T2,A,T77,A4)") &
631 tag//
"Decrease in rotational force",
" NO"
634 WRITE (unit=output_unit, fmt=
"(T2,A,T55,1X,F25.3)") &
635 tag//
"Used time [s]", used_time
637 WRITE (unit=output_unit, fmt=
"(T2,A)") tag//repeat(
"*", 74)
638 IF (max_memory /= 0)
THEN
639 WRITE (unit=output_unit, fmt=
"(T2,A,T60,1X,I20)") &
640 tag//
"Estimated peak process memory [MiB]", &
641 (max_memory + (1024*1024) - 1)/(1024*1024)
646 END SUBROUTINE write_rot_cycle_infos
661 SUBROUTINE check_converg(ndf, dr, g, output_unit, conv, gopt_param, max_memory, stress_unit, &
662 pres_diff, pres_tol, pres_diff_constr)
664 INTEGER,
INTENT(IN) :: ndf
665 REAL(kind=dp),
INTENT(IN) :: dr(ndf), g(ndf)
666 INTEGER,
INTENT(IN) :: output_unit
667 LOGICAL,
INTENT(OUT) :: conv
669 INTEGER(KIND=int_8),
INTENT(IN) :: max_memory
670 CHARACTER(LEN=default_string_length),
INTENT(IN) :: stress_unit
671 REAL(kind=dp),
INTENT(IN),
OPTIONAL :: pres_diff, pres_tol, pres_diff_constr
673 CHARACTER(LEN=5) :: tag
675 LOGICAL :: conv_dx, conv_g, conv_p, conv_rdx, &
677 REAL(kind=dp) :: dumm, dxcon, gcon, maxdum(4), rmsgcon, &
680 dxcon = gopt_param%max_dr
681 gcon = gopt_param%max_force
682 rmsgcon = gopt_param%rms_force
683 rmsxcon = gopt_param%rms_dr
694 IF (indf == 1) maxdum(1) = abs(dr(indf))
695 dumm = dumm + dr(indf)**2
696 IF (abs(dr(indf)) > dxcon) conv_dx = .false.
697 IF (abs(dr(indf)) > maxdum(1)) maxdum(1) = abs(dr(indf))
700 IF (dumm > (rmsxcon*rmsxcon*ndf)) conv_rdx = .false.
701 maxdum(2) = sqrt(dumm/ndf)
705 IF (indf == 1) maxdum(3) = abs(g(indf))
706 dumm = dumm + g(indf)**2
707 IF (abs(g(indf)) > gcon) conv_g = .false.
708 IF (abs(g(indf)) > maxdum(3)) maxdum(3) = abs(g(indf))
711 IF (dumm > (rmsgcon*rmsgcon*ndf)) conv_rg = .false.
712 maxdum(4) = sqrt(dumm/ndf)
714 IF (
PRESENT(pres_diff_constr) .AND.
PRESENT(pres_tol))
THEN
715 conv_p = abs(pres_diff_constr) < abs(pres_tol)
716 ELSEIF (
PRESENT(pres_diff) .AND.
PRESENT(pres_tol))
THEN
717 conv_p = abs(pres_diff) < abs(pres_tol)
720 IF (output_unit > 0)
THEN
724 WRITE (unit=output_unit, fmt=
"(T2,A)") trim(tag)
725 WRITE (unit=output_unit, fmt=
"(T2,A,T55,1X,F25.10)") &
726 tag//
"Maximum step size", maxdum(1), &
727 tag//
"Convergence limit for maximum step size", dxcon
729 WRITE (unit=output_unit, fmt=
"(T2,A,T77,A4)") &
730 tag//
"Maximum step size is converged",
" YES"
732 WRITE (unit=output_unit, fmt=
"(T2,A,T77,A4)") &
733 tag//
"Maximum step size is converged",
" NO"
736 WRITE (unit=output_unit, fmt=
"(T2,A)") trim(tag)
737 WRITE (unit=output_unit, fmt=
"(T2,A,T55,1X,F25.10)") &
738 tag//
"RMS step size", maxdum(2), &
739 tag//
"Convergence limit for RMS step size", rmsxcon
741 WRITE (unit=output_unit, fmt=
"(T2,A,T77,A4)") &
742 tag//
"RMS step size is converged",
" YES"
744 WRITE (unit=output_unit, fmt=
"(T2,A,T77,A4)") &
745 tag//
"RMS step size is converged",
" NO"
748 WRITE (unit=output_unit, fmt=
"(T2,A)") trim(tag)
749 WRITE (unit=output_unit, fmt=
"(T2,A,T55,1X,F25.10)") &
750 tag//
"Maximum gradient", maxdum(3), &
751 tag//
"Convergence limit for maximum gradient", gcon
753 WRITE (unit=output_unit, fmt=
"(T2,A,T77,A4)") &
754 tag//
"Maximum gradient is converged",
" YES"
756 WRITE (unit=output_unit, fmt=
"(T2,A,T77,A4)") &
757 tag//
"Maximum gradient is converged",
" NO"
760 WRITE (unit=output_unit, fmt=
"(T2,A)") trim(tag)
761 WRITE (unit=output_unit, fmt=
"(T2,A,T55,1X,F25.10)") &
762 tag//
"RMS gradient", maxdum(4), &
763 tag//
"Convergence limit for RMS gradient", rmsgcon
765 WRITE (unit=output_unit, fmt=
"(T2,A,T77,A4)") &
766 tag//
"RMS gradient is converged",
" YES"
768 WRITE (unit=output_unit, fmt=
"(T2,A,T77,A4)") &
769 tag//
"RMS gradient is converged",
" NO"
772 IF (
PRESENT(pres_diff) .AND.
PRESENT(pres_tol))
THEN
773 WRITE (unit=output_unit, fmt=
"(T2,A)") trim(tag)
774 IF (
PRESENT(pres_diff_constr))
THEN
775 WRITE (unit=output_unit, fmt=
"(T2,A,T55,1X,F25.10)") &
776 tag//
"Pressure deviation without constraint ["// &
777 trim(adjustl(stress_unit))//
"]", &
779 WRITE (unit=output_unit, fmt=
"(T2,A,T55,1X,F25.10)") &
780 tag//
"Pressure deviation with constraint ["// &
781 trim(adjustl(stress_unit))//
"]", &
784 WRITE (unit=output_unit, fmt=
"(T2,A,T55,1X,F25.10)") &
785 tag//
"Pressure deviation ["//trim(adjustl(stress_unit))//
"]", &
788 WRITE (unit=output_unit, fmt=
"(T2,A,T55,1X,F25.10)") &
789 tag//
"Pressure tolerance ["//trim(adjustl(stress_unit))//
"]", &
792 WRITE (unit=output_unit, fmt=
"(T2,A,T77,A4)") &
793 tag//
"Pressure is converged",
" YES"
795 WRITE (unit=output_unit, fmt=
"(T2,A,T77,A4)") &
796 tag//
"Pressure is converged",
" NO"
800 WRITE (unit=output_unit, fmt=
"(T2,A)") tag//repeat(
"*", 74)
802 IF (max_memory /= 0)
THEN
803 WRITE (unit=output_unit, fmt=
"(T2,A,T60,1X,I20)") &
804 tag//
"Estimated peak process memory after this step [MiB]", &
805 (max_memory + (1024*1024) - 1)/(1024*1024)
810 IF (conv_dx .AND. conv_rdx .AND. conv_g .AND. conv_rg .AND. conv_p) conv = .true.
812 IF ((conv) .AND. (output_unit > 0))
THEN
813 WRITE (unit=output_unit, fmt=
"(/,T2,A)") repeat(
"*", 79)
814 WRITE (unit=output_unit, fmt=
"(T2,A,T25,A,T78,A)") &
815 "***",
"GEOMETRY OPTIMIZATION COMPLETED",
"***"
816 WRITE (unit=output_unit, fmt=
"(T2,A)") repeat(
"*", 79)
819 END SUBROUTINE check_converg
829 SUBROUTINE check_rot_conv(dimer_env, output_unit, conv)
832 INTEGER,
INTENT(IN) :: output_unit
833 LOGICAL,
INTENT(OUT) :: conv
835 CHARACTER(LEN=5) :: tag
837 conv = (abs(dimer_env%rot%angle2) < dimer_env%rot%angle_tol)
839 IF (output_unit > 0)
THEN
841 WRITE (unit=output_unit, fmt=
"(T2,A)") trim(tag)
842 WRITE (unit=output_unit, fmt=
"(T2,A,T55,1X,F25.10)") &
843 tag//
"Predicted angle step size", dimer_env%rot%angle1, &
844 tag//
"Effective angle step size", dimer_env%rot%angle2, &
845 tag//
"Convergence limit for angle step size", dimer_env%rot%angle_tol
847 WRITE (unit=output_unit, fmt=
"(T2,A,T77,A4)") &
848 tag//
"Angle step size is converged",
" YES"
850 WRITE (unit=output_unit, fmt=
"(T2,A,T77,A4)") &
851 tag//
"Angle step size is converged",
" NO"
853 WRITE (unit=output_unit, fmt=
"(T2,A)") tag//repeat(
"*", 74)
856 IF ((conv) .AND. (output_unit > 0))
THEN
857 WRITE (unit=output_unit, fmt=
"(/,T2,A)") repeat(
"*", 79)
858 WRITE (unit=output_unit, fmt=
"(T2,A,T25,A,T78,A)") &
859 "***",
"ROTATION OPTIMIZATION COMPLETED",
"***"
860 WRITE (unit=output_unit, fmt=
"(T2,A)") repeat(
"*", 79)
863 END SUBROUTINE check_rot_conv
880 RECURSIVE SUBROUTINE write_final_info(output_unit, conv, it, gopt_env, x0, master, para_env, force_env, &
881 motion_section, root_section)
882 INTEGER,
INTENT(IN) :: output_unit
883 LOGICAL,
INTENT(IN) :: conv
884 INTEGER,
INTENT(INOUT) :: it
885 TYPE(gopt_f_type),
POINTER :: gopt_env
886 REAL(kind=dp),
DIMENSION(:),
POINTER :: x0
887 INTEGER,
INTENT(IN) :: master
888 TYPE(mp_para_env_type),
POINTER :: para_env
892 REAL(kind=dp) :: etot
900 particle_set => particles%els
904 CALL write_restart(force_env=force_env, root_section=root_section)
906 IF (output_unit > 0) &
907 WRITE (unit=output_unit, fmt=
"(/,T20,' Reevaluating energy at the minimum')")
909 CALL cp_eval_at(gopt_env, x0, f=etot, master=master, final_evaluation=.true., &
911 CALL write_geo_traj(force_env, root_section, it, etot)
914 END SUBROUTINE write_final_info
927 SUBROUTINE write_geo_traj(force_env, root_section, it, etot)
931 INTEGER,
INTENT(IN) :: it
932 REAL(kind=dp),
INTENT(IN) :: etot
934 LOGICAL :: shell_adiabatic, shell_present
940 NULLIFY (atomic_kinds)
941 NULLIFY (atomic_kind_set)
942 NULLIFY (core_particles)
943 NULLIFY (shell_particles)
948 CALL write_trajectory(force_env, root_section, it, 0.0_dp, 0.0_dp, etot,
"FORCES", middle_name=
"frc")
951 atomic_kind_set => atomic_kinds%els
953 shell_present=shell_present, &
954 shell_adiabatic=shell_adiabatic)
955 IF (shell_present)
THEN
957 core_particles=core_particles, &
958 shell_particles=shell_particles)
959 CALL write_trajectory(force_env, root_section, it=it, time=0.0_dp, dtime=0.0_dp, &
960 etot=etot, pk_name=
"SHELL_TRAJECTORY", middle_name=
"shpos", &
961 particles=shell_particles)
962 IF (shell_adiabatic)
THEN
963 CALL write_trajectory(force_env, root_section, it=it, time=0.0_dp, dtime=0.0_dp, &
964 etot=etot, pk_name=
"SHELL_FORCES", middle_name=
"shfrc", &
965 particles=shell_particles)
966 CALL write_trajectory(force_env, root_section, it=it, time=0.0_dp, dtime=0.0_dp, &
967 etot=etot, pk_name=
"CORE_TRAJECTORY", middle_name=
"copos", &
968 particles=core_particles)
969 CALL write_trajectory(force_env, root_section, it=it, time=0.0_dp, dtime=0.0_dp, &
970 etot=etot, pk_name=
"CORE_FORCES", middle_name=
"cofrc", &
971 particles=core_particles)
975 END SUBROUTINE write_geo_traj
987 TYPE(gopt_f_type),
POINTER :: gopt_env
988 INTEGER,
INTENT(IN) :: output_unit
989 CHARACTER(LEN=*),
INTENT(IN) :: label
991 CHARACTER(LEN=default_string_length) :: my_format, my_label
994 IF (output_unit > 0)
THEN
995 WRITE (unit=output_unit, fmt=
"(/,T2,A)") repeat(
"*", 79)
996 IF (gopt_env%dimer_rotation)
THEN
997 my_label =
"OPTIMIZING DIMER ROTATION"
999 my_label =
"STARTING "//gopt_env%tag(1:8)//
" OPTIMIZATION"
1002 ix = (80 - 7 - len_trim(my_label))/2
1005 WRITE (unit=output_unit, fmt=trim(my_format))
"***", trim(my_label),
"***"
1007 ix = (80 - 7 - len_trim(label))/2
1010 WRITE (unit=output_unit, fmt=trim(my_format))
"***", trim(label),
"***"
1012 WRITE (unit=output_unit, fmt=
"(T2,A)") repeat(
"*", 79)
1026 TYPE(gopt_f_type),
POINTER :: gopt_env
1027 INTEGER,
INTENT(IN) :: output_unit
1029 IF (output_unit > 0)
THEN
1030 WRITE (unit=output_unit, fmt=
"(/,T2,A)") &
1031 "*** MAXIMUM NUMBER OF OPTIMIZATION STEPS REACHED ***"
1032 IF (.NOT. gopt_env%dimer_rotation)
THEN
1033 WRITE (unit=output_unit, fmt=
"(T2,A)") &
1034 "*** EXITING GEOMETRY OPTIMIZATION ***"
1036 WRITE (unit=output_unit, fmt=
"(T2,A)") &
1037 "*** EXITING ROTATION OPTIMIZATION ***"
1055 SUBROUTINE geo_opt_io(force_env, root_section, motion_section, its, opt_energy)
1059 INTEGER,
INTENT(IN) :: its
1060 REAL(kind=dp),
INTENT(IN) :: opt_energy
1067 TYPE(mp_para_env_type),
POINTER :: para_env
1072 NULLIFY (para_env, atomic_kind_set, subsys, particle_set, &
1073 local_particles, atomic_kinds, particles)
1076 CALL write_restart(force_env=force_env, root_section=root_section)
1079 CALL write_geo_traj(force_env, root_section, its, opt_energy)
1082 CALL force_env_get(force_env, cell=cell, para_env=para_env, &
1084 CALL cp_subsys_get(subsys=subsys, atomic_kinds=atomic_kinds, local_particles=local_particles, &
1085 particles=particles, virial=virial)
1086 atomic_kind_set => atomic_kinds%els
1087 particle_set => particles%els
1088 CALL virial_evaluate(atomic_kind_set, particle_set, local_particles, &
1095 END SUBROUTINE geo_opt_io
1109 TYPE(gopt_f_type),
POINTER :: gopt_env
1111 REAL(kind=dp),
DIMENSION(:),
POINTER :: x
1112 LOGICAL,
INTENT(IN) :: update_forces
1114 INTEGER :: i, iatom, idg, j, natom, nparticle, &
1116 REAL(kind=dp) :: fc, fs, mass
1117 REAL(kind=dp),
DIMENSION(3) :: s
1124 NULLIFY (core_particles)
1126 NULLIFY (shell_particles)
1134 core_particles=core_particles, &
1135 particles=particles, &
1136 shell_particles=shell_particles)
1140 CALL cell_copy(cell, cell_ref, tag=
"CELL_OPT_REF")
1143 SELECT CASE (gopt_env%cell_method_id)
1146 CALL init_cell(cell_ref, hmat=gopt_env%h_ref)
1150 cpassert((
SIZE(x) == idg + 6))
1152 IF (update_forces)
THEN
1168 cell%hmat(j, i) = x(idg)
1175 SELECT CASE (gopt_env%cell_method_id)
1180 shell_index = particles%els(iatom)%shell_index
1181 IF (shell_index == 0)
THEN
1185 i = 3*(natom + shell_index - 1) + 1
1189 mass = particles%els(iatom)%atomic_kind%mass
1190 fc = core_particles%els(shell_index)%atomic_kind%shell%mass_core/mass
1191 fs = shell_particles%els(shell_index)%atomic_kind%shell%mass_shell/mass
1192 particles%els(iatom)%r(1:3) = fc*core_particles%els(shell_index)%r(1:3) + &
1193 fs*shell_particles%els(shell_index)%r(1:3)
1199 shell_index = particles%els(iatom)%shell_index
1200 IF (shell_index == 0)
THEN
1204 CALL real_to_scaled(s, core_particles%els(shell_index)%r, cell_ref)
1206 i = 3*(natom + shell_index - 1) + 1
1207 CALL real_to_scaled(s, shell_particles%els(shell_index)%r, cell_ref)
1210 mass = particles%els(iatom)%atomic_kind%mass
1211 fc = core_particles%els(shell_index)%atomic_kind%shell%mass_core/mass
1212 fs = shell_particles%els(shell_index)%atomic_kind%shell%mass_shell/mass
1213 particles%els(iatom)%r(1:3) = fc*core_particles%els(shell_index)%r(1:3) + &
1214 fs*shell_particles%els(shell_index)%r(1:3)
subroutine cp_eval_at(gopt_env, x, f, gradient, master, final_evaluation, para_env)
evaluete the potential energy and its gradients using an array with same dimension as the particle_se...
represent a simple array based list of the given type
Define the atomic kind types and their sub types.
subroutine, public get_atomic_kind_set(atomic_kind_set, atom_of_kind, kind_of, natom_of_kind, maxatom, natom, nshell, fist_potential_present, shell_present, shell_adiabatic, shell_check_distance, damping_present)
Get attributes of an atomic kind set.
Handles all functions related to the CELL.
subroutine, public init_cell(cell, hmat, periodic)
Initialise/readjust a simulation cell after hmat has been changed.
subroutine, public cell_create(cell, hmat, periodic, tag)
allocates and initializes a cell
Handles all functions related to the CELL.
subroutine, public scaled_to_real(r, s, cell)
Transform scaled cell coordinates real coordinates. r=h*s.
subroutine, public real_to_scaled(s, r, cell)
Transform real to scaled cell coordinates. s=h_inv*r.
subroutine, public cell_release(cell)
releases the given cell (see doc/ReferenceCounting.html)
subroutine, public cell_copy(cell_in, cell_out, tag)
Copy cell variable.
various routines to log and control the output. The idea is that decisions about where to log should ...
types that represent a subsys, i.e. a part of the system
subroutine, public cp_subsys_set(subsys, atomic_kinds, particles, local_particles, molecules, molecule_kinds, local_molecules, para_env, colvar_p, shell_particles, core_particles, gci, multipoles, results, cell)
sets various propreties of the subsys
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
subroutine, public pack_subsys_particles(subsys, f, r, s, v, fscale, cell)
Pack components of a subsystem particle sets into a single vector.
real(kind=dp) function, public cp_unit_from_cp2k(value, unit_str, defaults, power)
converts from the internal cp2k units to the given unit
Contains types used for a Dimer Method calculations.
Contains utilities for a Dimer Method calculations.
subroutine, public update_dimer_vec(dimer_env, motion_section)
Updates the orientation of the dimer vector in the input file.
stores a lists of integer that are local to a processor. The idea is that these integers represent ob...
Interface for the force calculations.
integer function, public force_env_get_natom(force_env)
returns the number of atoms
integer, parameter, public use_qmmm
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
integer, parameter, public use_qmmmx
integer function, public force_env_get_nparticle(force_env)
returns the number of particles in a force environment
contains a functional that calculates the energy and its derivatives for the geometry optimizer
subroutine, public print_geo_opt_header(gopt_env, output_unit, label)
...
subroutine, public gopt_f_io_init(gopt_env, output_unit, opt_energy, wildcard, its, used_time)
Handles the Output during an optimization run.
subroutine, public gopt_f_create_x0(gopt_env, x0)
returns the value of the parameters for the actual configuration
recursive subroutine, public gopt_f_io_finalize(gopt_env, force_env, x0, conv, its, root_section, para_env, master, output_unit)
Handles the Output at the end of an optimization run.
subroutine, public apply_cell_change(gopt_env, cell, x, update_forces)
Apply coordinate transformations after cell (shape) change.
subroutine, public gopt_f_io(gopt_env, force_env, root_section, its, opt_energy, output_unit, eold, emin, wildcard, gopt_param, ndf, dx, xi, conv, pred, rat, step, rad, used_time)
Handles the Output during an optimization run.
subroutine, public print_geo_opt_nc(gopt_env, output_unit)
...
subroutine, public gopt_f_ii(its, output_unit)
Prints iteration step of the optimization procedure on screen.
contains a functional that calculates the energy and its derivatives for the geometry optimizer
contains typo and related routines to handle parameters controlling the GEO_OPT module
Defines the basic variable types.
integer, parameter, public int_8
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
prints all energy info per timestep to the screen or to user defined output files
integer(kind=int_8) function, public sample_memory(para_env)
Samples memory usage.
Interface to the message passing library MPI.
Output Utilities for MOTION_SECTION.
subroutine, public write_simulation_cell(cell, motion_section, itimes, time, pos, act)
Prints the Simulation Cell.
subroutine, public write_trajectory(force_env, root_section, it, time, dtime, etot, pk_name, pos, act, middle_name, particles, extended_xmol_title)
Prints the information controlled by the TRAJECTORY section.
subroutine, public write_stress_tensor_to_file(virial, cell, motion_section, itimes, time, pos, act)
Prints the Stress Tensor.
represent a simple array based list of the given type
Define methods related to particle_type.
subroutine, public write_structure_data(particle_set, cell, input_section)
Write structure data requested by a separate structure data input section to the output unit....
Define the data structure for the particle information.
subroutine, public apply_qmmm_translate(qmmm_env)
Apply translation to the full system in order to center the QM system into the QM box.
Routines used for force-mixing QM/MM calculations.
subroutine, public apply_qmmmx_translate(qmmmx_env)
Apply translation to the full system in order to center the QM system into the QM box.
subroutine, public virial_evaluate(atomic_kind_set, particle_set, local_particles, virial, igroup)
Computes the kinetic part of the pressure tensor and updates the full VIRIAL (PV)
represent a list of objects
Provides all information about an atomic kind.
Type defining parameters related to the simulation cell.
represents a system: atoms, molecules, their pos,vel,...
Defines the environment for a Dimer Method calculation.
structure to store local (to a processor) ordered lists of integers.
wrapper to abstract the force evaluation of the various methods
calculates the potential energy of a system, and its derivatives
stores all the informations relevant to an mpi environment
represent a list of objects