Line data Source code
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 Methods and functions on the EIP environment
10 : !> \par History
11 : !> 03.2006 initial create [tdk]
12 : !> \author Thomas D. Kuehne (tkuehne@phys.chem.ethz.ch)
13 : ! **************************************************************************************************
14 : MODULE eip_environment
15 : USE atomic_kind_types, ONLY: atomic_kind_type,&
16 : get_atomic_kind
17 : USE cell_methods, ONLY: read_cell,&
18 : write_cell
19 : USE cell_types, ONLY: cell_release,&
20 : cell_type,&
21 : get_cell
22 : USE cp_subsys_methods, ONLY: cp_subsys_create
23 : USE cp_subsys_types, ONLY: cp_subsys_set,&
24 : cp_subsys_type
25 : USE distribution_1d_types, ONLY: distribution_1d_release,&
26 : distribution_1d_type
27 : USE distribution_methods, ONLY: distribute_molecules_1d
28 : USE eip_environment_types, ONLY: eip_env_set,&
29 : eip_environment_type
30 : USE input_section_types, ONLY: section_vals_get_subs_vals,&
31 : section_vals_type,&
32 : section_vals_val_get
33 : USE kinds, ONLY: default_string_length,&
34 : dp
35 : USE message_passing, ONLY: mp_para_env_type
36 : USE molecule_kind_types, ONLY: molecule_kind_type,&
37 : write_molecule_kind_set
38 : USE molecule_types, ONLY: molecule_type
39 : USE particle_methods, ONLY: write_fist_particle_coordinates,&
40 : write_particle_distances,&
41 : write_structure_data
42 : USE particle_types, ONLY: particle_type
43 : #include "./base/base_uses.f90"
44 :
45 : IMPLICIT NONE
46 :
47 : PRIVATE
48 :
49 : ! *** Global parameters ***
50 :
51 : CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'eip_environment'
52 :
53 : ! *** Public subroutines ***
54 :
55 : PUBLIC :: eip_init
56 :
57 : CONTAINS
58 :
59 : ! **************************************************************************************************
60 : !> \brief Initialize the eip environment
61 : !> \param eip_env The eip environment to retain
62 : !> \param root_section ...
63 : !> \param para_env ...
64 : !> \param force_env_section ...
65 : !> \param subsys_section ...
66 : !> \par History
67 : !> 03.2006 initial create [tdk]
68 : !> \author Thomas D. Kuehne (tkuehne@phys.chem.ethz.ch)
69 : ! **************************************************************************************************
70 2 : SUBROUTINE eip_init(eip_env, root_section, para_env, force_env_section, &
71 : subsys_section)
72 : TYPE(eip_environment_type), POINTER :: eip_env
73 : TYPE(section_vals_type), POINTER :: root_section
74 : TYPE(mp_para_env_type), POINTER :: para_env
75 : TYPE(section_vals_type), POINTER :: force_env_section, subsys_section
76 :
77 : CHARACTER(len=*), PARAMETER :: routineN = 'eip_init'
78 :
79 : INTEGER :: handle
80 : LOGICAL :: use_ref_cell
81 : REAL(KIND=dp), DIMENSION(3) :: abc
82 : TYPE(cell_type), POINTER :: cell, cell_ref
83 : TYPE(cp_subsys_type), POINTER :: subsys
84 : TYPE(section_vals_type), POINTER :: cell_section, colvar_section, eip_section
85 :
86 2 : CALL timeset(routineN, handle)
87 :
88 2 : CPASSERT(ASSOCIATED(eip_env))
89 :
90 : ! nullifying pointers
91 2 : NULLIFY (cell_section, colvar_section, eip_section, cell, cell_ref, &
92 2 : subsys)
93 :
94 2 : IF (.NOT. ASSOCIATED(subsys_section)) THEN
95 0 : subsys_section => section_vals_get_subs_vals(force_env_section, "SUBSYS")
96 : END IF
97 2 : cell_section => section_vals_get_subs_vals(subsys_section, "CELL")
98 2 : colvar_section => section_vals_get_subs_vals(subsys_section, "COLVAR")
99 2 : eip_section => section_vals_get_subs_vals(force_env_section, "EIP")
100 :
101 : CALL eip_env_set(eip_env=eip_env, eip_input=eip_section, &
102 2 : force_env_input=force_env_section)
103 :
104 : CALL read_cell(cell=cell, cell_ref=cell_ref, use_ref_cell=use_ref_cell, cell_section=cell_section, &
105 2 : para_env=para_env)
106 2 : CALL get_cell(cell=cell, abc=abc)
107 2 : CALL write_cell(cell=cell, subsys_section=subsys_section)
108 :
109 2 : CALL cp_subsys_create(subsys, para_env, root_section)
110 :
111 : CALL eip_init_subsys(eip_env=eip_env, subsys=subsys, cell=cell, &
112 : cell_ref=cell_ref, use_ref_cell=use_ref_cell, &
113 2 : subsys_section=subsys_section)
114 :
115 2 : CALL cell_release(cell)
116 2 : CALL cell_release(cell_ref)
117 :
118 2 : CALL timestop(handle)
119 :
120 2 : END SUBROUTINE eip_init
121 :
122 : ! **************************************************************************************************
123 : !> \brief Initialize the eip environment
124 : !> \param eip_env The eip environment of matter
125 : !> \param subsys the subsys
126 : !> \param cell Pointer to the actual simulation cell
127 : !> \param cell_ref Pointer to the reference cell, used e.g. in NPT simulations
128 : !> \param use_ref_cell Logical which indicates if cell_ref is in use
129 : !> \param subsys_section ...
130 : !> \par History
131 : !> 03.2006 initial create [tdk]
132 : !> \author Thomas D. Kuehne (tkuehne@phys.chem.ethz.ch)
133 : ! **************************************************************************************************
134 2 : SUBROUTINE eip_init_subsys(eip_env, subsys, cell, cell_ref, use_ref_cell, subsys_section)
135 : TYPE(eip_environment_type), POINTER :: eip_env
136 : TYPE(cp_subsys_type), POINTER :: subsys
137 : TYPE(cell_type), POINTER :: cell, cell_ref
138 : LOGICAL, INTENT(in) :: use_ref_cell
139 : TYPE(section_vals_type), POINTER :: subsys_section
140 :
141 : CHARACTER(len=*), PARAMETER :: routineN = 'eip_init_subsys'
142 :
143 : INTEGER :: handle, natom
144 2 : TYPE(atomic_kind_type), DIMENSION(:), POINTER :: atomic_kind_set
145 : TYPE(distribution_1d_type), POINTER :: local_molecules, local_particles
146 2 : TYPE(molecule_kind_type), DIMENSION(:), POINTER :: molecule_kind_set
147 2 : TYPE(molecule_type), DIMENSION(:), POINTER :: molecule_set
148 2 : TYPE(particle_type), DIMENSION(:), POINTER :: particle_set
149 :
150 : ! ------------------------------------------------------------------------
151 :
152 2 : CALL timeset(routineN, handle)
153 :
154 : NULLIFY (atomic_kind_set, molecule_kind_set, particle_set, molecule_set, &
155 2 : local_molecules, local_particles)
156 :
157 2 : particle_set => subsys%particles%els
158 2 : atomic_kind_set => subsys%atomic_kinds%els
159 2 : molecule_kind_set => subsys%molecule_kinds%els
160 2 : molecule_set => subsys%molecules%els
161 :
162 : ! *** Print the molecule kind set ***
163 2 : CALL write_molecule_kind_set(molecule_kind_set, subsys_section)
164 :
165 : ! *** Print the atomic coordinates
166 2 : CALL write_fist_particle_coordinates(particle_set, subsys_section)
167 : CALL write_particle_distances(particle_set, cell=cell, &
168 2 : subsys_section=subsys_section)
169 : CALL write_structure_data(particle_set, cell=cell, &
170 2 : input_section=subsys_section)
171 :
172 : ! *** Distribute molecules and atoms using the new data structures ***
173 : CALL distribute_molecules_1d(atomic_kind_set=atomic_kind_set, &
174 : particle_set=particle_set, &
175 : local_particles=local_particles, &
176 : molecule_kind_set=molecule_kind_set, &
177 : molecule_set=molecule_set, &
178 : local_molecules=local_molecules, &
179 2 : force_env_section=eip_env%force_env_input)
180 :
181 2 : natom = SIZE(particle_set)
182 :
183 6 : ALLOCATE (eip_env%eip_forces(3, natom))
184 :
185 8002 : eip_env%eip_forces(:, :) = 0.0_dp
186 :
187 2 : CALL cp_subsys_set(subsys, cell=cell)
188 : CALL eip_env_set(eip_env=eip_env, subsys=subsys, &
189 : cell_ref=cell_ref, use_ref_cell=use_ref_cell, &
190 : local_molecules=local_molecules, &
191 2 : local_particles=local_particles)
192 :
193 2 : CALL distribution_1d_release(local_particles)
194 2 : CALL distribution_1d_release(local_molecules)
195 :
196 2 : CALL eip_init_model(eip_env=eip_env)
197 :
198 2 : CALL timestop(handle)
199 :
200 2 : END SUBROUTINE eip_init_subsys
201 :
202 : ! **************************************************************************************************
203 : !> \brief Initialize the empirical interatomic potnetial (force field) model
204 : !> \param eip_env The eip environment to retain
205 : !> \par History
206 : !> 03.2006 initial create [tdk]
207 : !> \author Thomas D. Kuehne (tkuehne@phys.chem.ethz.ch)
208 : ! **************************************************************************************************
209 2 : SUBROUTINE eip_init_model(eip_env)
210 : TYPE(eip_environment_type), POINTER :: eip_env
211 :
212 : CHARACTER(len=*), PARAMETER :: routineN = 'eip_init_model'
213 :
214 : CHARACTER(LEN=default_string_length) :: eip_atomic_kind_name
215 : INTEGER :: handle, i
216 2 : TYPE(atomic_kind_type), DIMENSION(:), POINTER :: atomic_kind_set
217 : TYPE(atomic_kind_type), POINTER :: atomic_kind_ptr
218 : TYPE(section_vals_type), POINTER :: eip_section
219 :
220 : ! ------------------------------------------------------------------------
221 :
222 2 : CALL timeset(routineN, handle)
223 :
224 2 : NULLIFY (atomic_kind_set, atomic_kind_ptr, eip_section)
225 :
226 : eip_section => section_vals_get_subs_vals(eip_env%force_env_input, &
227 2 : "EIP")
228 :
229 2 : atomic_kind_set => eip_env%subsys%atomic_kinds%els
230 :
231 : ! loop over all kinds
232 4 : DO i = 1, SIZE(atomic_kind_set)
233 2 : atomic_kind_ptr => eip_env%subsys%atomic_kinds%els(i)
234 : CALL get_atomic_kind(atomic_kind=atomic_kind_ptr, &
235 2 : name=eip_atomic_kind_name)
236 2 : SELECT CASE (eip_atomic_kind_name)
237 : CASE ("SI", "Si")
238 : CALL section_vals_val_get(section_vals=eip_section, &
239 : keyword_name="EIP-Model", &
240 2 : i_val=eip_env%eip_model)
241 : CASE DEFAULT
242 2 : CPABORT("EIP models for other elements than Si isn't implemented yet.")
243 : END SELECT
244 : END DO
245 :
246 2 : CALL timestop(handle)
247 :
248 2 : END SUBROUTINE eip_init_model
249 :
250 : END MODULE eip_environment
|