(git:374b731)
Loading...
Searching...
No Matches
neb_types.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 Typo for Nudged Elastic Band Calculation
10!> \note
11!> Numerical accuracy for parallel runs:
12!> Each replica starts the SCF run from the one optimized
13!> in a previous run. It may happen then energies and derivatives
14!> of a serial run and a parallel run could be slightly different
15!> 'cause of a different starting density matrix.
16!> Exact results are obtained using:
17!> EXTRAPOLATION USE_GUESS in QS section (Teo 09.2006)
18!> \author Teodoro Laino 10.2006
19! **************************************************************************************************
21
23 USE input_constants, ONLY: band_md_opt,&
24 do_b_neb,&
29 USE kinds, ONLY: default_string_length,&
30 dp
31#include "../base/base_uses.f90"
32
33 IMPLICIT NONE
34 PRIVATE
35 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'neb_types'
36
37 PUBLIC :: neb_type, &
41
42! **************************************************************************************************
44 ! NEB parameters
45 INTEGER :: id_type = do_b_neb
46 INTEGER :: opt_type = band_md_opt
47 INTEGER :: pot_type = pot_neb_full
48 INTEGER :: number_of_replica = 0, nsize_xyz = 0, nsize_int = 0
49 INTEGER :: nsteps_it = 0, istep = 0
50 INTEGER :: nr_he_image = 0
51 LOGICAL :: rotate_frames = .false., align_frames = .false.
52 LOGICAL :: optimize_end_points = .false.
53 LOGICAL :: use_colvar = .false.
54 LOGICAL :: reparametrize_frames = .false.
55 INTEGER :: spline_order = 0
56 REAL(kind=dp) :: k = 0.0_dp, spring_energy = 0.0_dp, avg_distance = 0.0_dp
57 REAL(kind=dp) :: smoothing = 0.0_dp
58 CHARACTER(LEN=default_string_length) :: opt_type_label = ""
59 ! Section used for restart
60 TYPE(force_env_type), POINTER :: force_env => null()
61 TYPE(section_vals_type), POINTER :: root_section => null()
62 TYPE(section_vals_type), POINTER :: motion_print_section => null()
63 TYPE(section_vals_type), POINTER :: force_env_section => null()
64 TYPE(section_vals_type), POINTER :: neb_section => null()
65 END TYPE neb_type
66
67! **************************************************************************************************
69 INTEGER :: in_use = do_band_collective, size_wrk(2) = 0
70 REAL(kind=dp), DIMENSION(:, :), POINTER :: xyz => null(), int => null(), wrk => null()
71 REAL(kind=dp), DIMENSION(:, :, :), POINTER :: mmatrix => null()
72 END TYPE neb_var_type
73
74CONTAINS
75! **************************************************************************************************
76!> \brief Creates a variable type for BAND calculation
77!> \param neb_var ...
78!> \param neb_env ...
79!> \param full_allocation ...
80!> \date 05.2007
81!> \author Teodoro Laino [tlaino] - University of Zurich
82! **************************************************************************************************
83 SUBROUTINE neb_var_create(neb_var, neb_env, full_allocation)
84 TYPE(neb_var_type), POINTER :: neb_var
85 TYPE(neb_type), POINTER :: neb_env
86 LOGICAL, INTENT(IN), OPTIONAL :: full_allocation
87
88 INTEGER :: neb_nr_replica
89 LOGICAL :: allocate_all
90
91 cpassert(.NOT. ASSOCIATED(neb_var))
92 allocate_all = .false.
93 IF (PRESENT(full_allocation)) allocate_all = full_allocation
94 neb_nr_replica = neb_env%number_of_replica
95 ALLOCATE (neb_var)
96 NULLIFY (neb_var%xyz, neb_var%int, neb_var%wrk, neb_var%Mmatrix)
97 IF (allocate_all) THEN
98 ALLOCATE (neb_var%xyz(neb_env%nsize_xyz, neb_nr_replica))
99 neb_var%xyz = 0.0_dp
100 END IF
101 IF (neb_env%use_colvar) THEN
102 neb_var%in_use = do_band_collective
103 cpassert(neb_env%nsize_int > 0)
104 ALLOCATE (neb_var%int(neb_env%nsize_int, neb_nr_replica))
105 neb_var%int = 0.0_dp
106 neb_var%wrk => neb_var%int
107 ELSE
108 neb_var%in_use = do_band_cartesian
109 IF (.NOT. allocate_all) THEN
110 ALLOCATE (neb_var%xyz(neb_env%nsize_xyz, neb_nr_replica))
111 neb_var%xyz = 0.0_dp
112 END IF
113 neb_var%wrk => neb_var%xyz
114 END IF
115 neb_var%size_wrk(1) = SIZE(neb_var%wrk, 1)
116 neb_var%size_wrk(2) = SIZE(neb_var%wrk, 2)
117
118 END SUBROUTINE neb_var_create
119
120! **************************************************************************************************
121!> \brief Releases a variable type for BAND calculation
122!> \param neb_var ...
123!> \date 05.2007
124!> \author Teodoro Laino [tlaino] - University of Zurich
125! **************************************************************************************************
126 SUBROUTINE neb_var_release(neb_var)
127 TYPE(neb_var_type), POINTER :: neb_var
128
129 cpassert(ASSOCIATED(neb_var))
130 IF (ASSOCIATED(neb_var%xyz)) THEN
131 DEALLOCATE (neb_var%xyz)
132 END IF
133 IF (neb_var%in_use == do_band_collective) THEN
134 DEALLOCATE (neb_var%int)
135 END IF
136 NULLIFY (neb_var%wrk)
137 DEALLOCATE (neb_var)
138
139 END SUBROUTINE neb_var_release
140
141END MODULE neb_types
Interface for the force calculations.
collects all constants needed in input so that they can be used without circular dependencies
integer, parameter, public band_md_opt
integer, parameter, public do_band_cartesian
integer, parameter, public do_b_neb
integer, parameter, public do_band_collective
integer, parameter, public pot_neb_full
objects that represent the structure of input sections and the data contained in an input section
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
Typo for Nudged Elastic Band Calculation.
Definition neb_types.F:20
subroutine, public neb_var_release(neb_var)
Releases a variable type for BAND calculation.
Definition neb_types.F:127
subroutine, public neb_var_create(neb_var, neb_env, full_allocation)
Creates a variable type for BAND calculation.
Definition neb_types.F:84
wrapper to abstract the force evaluation of the various methods