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 Initialize the collective variables types
10 : !> \par History
11 : !> 5.2004 created [fawzi and alessandro]
12 : !> 1.2009 Fabio Sterpone : added the population COLVAR
13 : !> \author Teodoro Laino
14 : ! **************************************************************************************************
15 : MODULE colvar_types
16 :
17 : USE input_section_types, ONLY: section_vals_type
18 : USE kinds, ONLY: default_path_length,&
19 : default_string_length,&
20 : dp
21 : USE particle_types, ONLY: particle_type
22 : #include "../base/base_uses.f90"
23 :
24 : IMPLICIT NONE
25 :
26 : PRIVATE
27 :
28 : CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'colvar_types'
29 :
30 : INTEGER, PARAMETER, PUBLIC :: plane_def_atoms = 0, &
31 : plane_def_vec = 1
32 :
33 : INTEGER, PARAMETER, PUBLIC :: do_clv_geo_center = 0, &
34 : do_clv_fix_point = 1, &
35 : do_clv_xyz = 0, &
36 : do_clv_x = 1, &
37 : do_clv_y = 2, &
38 : do_clv_z = 3, &
39 : do_clv_xy = 4, &
40 : do_clv_xz = 5, &
41 : do_clv_yz = 6
42 : PUBLIC :: colvar_type, &
43 : colvar_p_type, &
44 : colvar_p_reallocate, &
45 : colvar_p_release, &
46 : colvar_create, &
47 : colvar_clone, &
48 : colvar_setup, &
49 : colvar_release, &
50 : colvar_counters, &
51 : eval_point_der, &
52 : eval_point_pos, &
53 : eval_point_mass, &
54 : diff_colvar
55 :
56 : INTEGER, PARAMETER, PUBLIC :: no_colvar_id = -2, &
57 : dist_colvar_id = 1, &
58 : coord_colvar_id = 2, &
59 : torsion_colvar_id = 3, &
60 : angle_colvar_id = 4, &
61 : plane_distance_colvar_id = 5, &
62 : rotation_colvar_id = 6, &
63 : dfunct_colvar_id = 7, &
64 : qparm_colvar_id = 8, &
65 : hydronium_shell_colvar_id = 9, &
66 : reaction_path_colvar_id = 10, &
67 : combine_colvar_id = 11, &
68 : population_colvar_id = 12, &
69 : plane_plane_angle_colvar_id = 13, &
70 : gyration_colvar_id = 14, &
71 : rmsd_colvar_id = 15, &
72 : distance_from_path_colvar_id = 16, &
73 : xyz_diag_colvar_id = 17, &
74 : xyz_outerdiag_colvar_id = 18, &
75 : u_colvar_id = 19, &
76 : Wc_colvar_id = 20, &
77 : hbp_colvar_id = 21, &
78 : ring_puckering_colvar_id = 22, &
79 : mindist_colvar_id = 23, &
80 : acid_hyd_dist_colvar_id = 24, &
81 : acid_hyd_shell_colvar_id = 25, &
82 : hydronium_dist_colvar_id = 26
83 :
84 : ! **************************************************************************************************
85 : !> \brief parameters for the distance collective variable
86 : !> \param i_at ,j_at: indexes of the two atoms between which you calculate
87 : !> the distance
88 : !> \author alessandro laio and fawzi mohamed
89 : ! **************************************************************************************************
90 : TYPE dist_colvar_type
91 : INTEGER :: i_at = 0, j_at = 0, axis_id = 0
92 : LOGICAL :: sign_d = .FALSE.
93 : END TYPE dist_colvar_type
94 :
95 : ! **************************************************************************************************
96 : TYPE coord_colvar_type
97 : LOGICAL :: do_chain = .FALSE., use_kinds_from = .FALSE., use_kinds_to = .FALSE., &
98 : use_kinds_to_b = .FALSE.
99 : INTEGER :: n_atoms_to = 0, &
100 : n_atoms_from = 0, &
101 : nncrd = 0, &
102 : ndcrd = 0, &
103 : n_atoms_to_b = 0, &
104 : nncrd_b = 0, &
105 : ndcrd_b = 0
106 : INTEGER, POINTER, DIMENSION(:) :: i_at_from => NULL(), &
107 : i_at_to => NULL(), &
108 : i_at_to_b => NULL()
109 : CHARACTER(LEN=default_string_length), DIMENSION(:), POINTER :: c_kinds_from => NULL(), &
110 : c_kinds_to => NULL(), &
111 : c_kinds_to_b => NULL()
112 : REAL(KIND=dp) :: r_0 = 0.0_dp, r_0_b = 0.0_dp
113 : END TYPE coord_colvar_type
114 :
115 : ! **************************************************************************************************
116 : TYPE population_colvar_type
117 : LOGICAL :: use_kinds_from = .FALSE., use_kinds_to = .FALSE.
118 : INTEGER :: n_atoms_to = 0, &
119 : n_atoms_from = 0, &
120 : nncrd = 0, &
121 : ndcrd = 0, &
122 : n0 = 0
123 : INTEGER, POINTER, DIMENSION(:) :: i_at_from => NULL(), &
124 : i_at_to => NULL()
125 : CHARACTER(LEN=default_string_length), DIMENSION(:), POINTER :: c_kinds_from => NULL(), &
126 : c_kinds_to => NULL()
127 : REAL(KIND=dp) :: r_0 = 0.0_dp, sigma = 0.0_dp
128 : END TYPE population_colvar_type
129 :
130 : ! **************************************************************************************************
131 : TYPE gyration_colvar_type
132 : LOGICAL :: use_kinds = .FALSE.
133 : INTEGER :: n_atoms = 0
134 : INTEGER, POINTER, DIMENSION(:) :: i_at => NULL()
135 : CHARACTER(LEN=default_string_length), DIMENSION(:), POINTER :: c_kinds => NULL()
136 : END TYPE gyration_colvar_type
137 :
138 : ! **************************************************************************************************
139 : TYPE torsion_colvar_type
140 : REAL(KIND=dp) :: o0 = 0.0_dp
141 : INTEGER, DIMENSION(4) :: i_at_tors = 0
142 : END TYPE torsion_colvar_type
143 :
144 : ! **************************************************************************************************
145 : TYPE plane_distance_colvar_type
146 : LOGICAL :: use_pbc = .FALSE.
147 : INTEGER, DIMENSION(3) :: plane = -1
148 : INTEGER :: point = -1
149 : END TYPE plane_distance_colvar_type
150 :
151 : ! **************************************************************************************************
152 : TYPE plane_def_type
153 : INTEGER :: type_of_def = -1
154 : INTEGER, DIMENSION(3) :: points = 0
155 : REAL(KIND=dp), DIMENSION(3) :: normal_vec = 0.0_dp
156 : END TYPE plane_def_type
157 :
158 : TYPE plane_plane_angle_colvar_type
159 : TYPE(plane_def_type) :: plane1 = plane_def_type(), plane2 = plane_def_type()
160 : END TYPE plane_plane_angle_colvar_type
161 :
162 : ! **************************************************************************************************
163 : TYPE angle_colvar_type
164 : INTEGER, DIMENSION(3) :: i_at_angle = 0
165 : END TYPE angle_colvar_type
166 :
167 : ! **************************************************************************************************
168 : TYPE rotation_colvar_type
169 : INTEGER :: i_at1_bond1 = 0, &
170 : i_at2_bond1 = 0, &
171 : i_at1_bond2 = 0, &
172 : i_at2_bond2 = 0
173 : END TYPE rotation_colvar_type
174 :
175 : ! **************************************************************************************************
176 : TYPE dfunct_colvar_type
177 : INTEGER, DIMENSION(4) :: i_at_dfunct = 0
178 : LOGICAL :: use_pbc = .FALSE.
179 : REAL(KIND=dp) :: coeff = 0.0_dp
180 : END TYPE dfunct_colvar_type
181 :
182 : ! **************************************************************************************************
183 : TYPE qparm_colvar_type
184 : INTEGER :: l = 0
185 : INTEGER :: n_atoms_to = 0, &
186 : n_atoms_from = 0
187 : INTEGER, POINTER, DIMENSION(:) :: i_at_from => NULL(), &
188 : i_at_to => NULL()
189 : REAL(KIND=dp) :: rcut = 0.0_dp, rstart = 0.0_dp
190 : LOGICAL :: include_images = .FALSE.
191 : END TYPE qparm_colvar_type
192 :
193 : ! **************************************************************************************************
194 : TYPE hydronium_shell_colvar_type
195 : INTEGER :: n_oxygens = -1, &
196 : n_hydrogens = -1, &
197 : poh = -1, qoh = -1, poo = -1, qoo = -1, &
198 : pm = -1, qm = -1
199 : INTEGER, POINTER, DIMENSION(:) :: i_oxygens => NULL(), &
200 : i_hydrogens => NULL()
201 : REAL(KIND=dp) :: roo = 0.0_dp, roh = 0.0_dp, lambda = 0.0_dp, nh = 0.0_dp
202 : END TYPE hydronium_shell_colvar_type
203 :
204 : ! **************************************************************************************************
205 : TYPE hydronium_dist_colvar_type
206 : INTEGER :: n_oxygens = -1, &
207 : n_hydrogens = -1, &
208 : poh = -1, qoh = -1, &
209 : pf = -1, qf = -1, pm = -1, qm = -1
210 : INTEGER, POINTER, DIMENSION(:) :: i_oxygens => NULL(), &
211 : i_hydrogens => NULL()
212 : REAL(KIND=dp) :: roh = 0.0_dp, lambda = 0.0_dp, nh = 0.0_dp, nn = 0.0_dp
213 : END TYPE hydronium_dist_colvar_type
214 :
215 : ! **************************************************************************************************
216 : TYPE acid_hyd_dist_colvar_type
217 : INTEGER :: n_oxygens_water = -1, &
218 : n_oxygens_acid = -1, &
219 : n_hydrogens = -1, &
220 : pwoh = -1, qwoh = -1, paoh = -1, qaoh = -1, pcut = -1, qcut = -1
221 : INTEGER, POINTER, DIMENSION(:) :: i_oxygens_water => NULL(), i_oxygens_acid => NULL(), &
222 : i_hydrogens => NULL()
223 : REAL(KIND=dp) :: rwoh = 0.0_dp, raoh = 0.0_dp, lambda = 0.0_dp, nc = 0.0_dp
224 : END TYPE acid_hyd_dist_colvar_type
225 :
226 : ! **************************************************************************************************
227 : TYPE acid_hyd_shell_colvar_type
228 : INTEGER :: n_oxygens_water = -1, &
229 : n_oxygens_acid = -1, &
230 : n_hydrogens = -1, &
231 : pwoh = -1, qwoh = -1, paoh = -1, qaoh = -1, &
232 : poo = -1, qoo = -1, pcut = -1, qcut = -1, pm = -1, qm = -1
233 : INTEGER, POINTER, DIMENSION(:) :: i_oxygens_water => NULL(), i_oxygens_acid => NULL(), &
234 : i_hydrogens => NULL()
235 : REAL(KIND=dp) :: rwoh = 0.0_dp, raoh = 0.0_dp, roo = 0.0_dp, lambda = 0.0_dp, nc = 0.0_dp, nh = 0.0_dp
236 : END TYPE acid_hyd_shell_colvar_type
237 :
238 : ! **************************************************************************************************
239 : TYPE reaction_path_colvar_type
240 : INTEGER :: type_id = -1
241 : INTEGER :: n_components = -1, nr_frames = -1, subset = -1
242 : INTEGER, DIMENSION(2) :: function_bounds = -1
243 : INTEGER, POINTER, DIMENSION(:) :: i_rmsd => NULL()
244 : LOGICAL :: align_frames = .FALSE., dist_rmsd = .FALSE., rmsd = .FALSE.
245 : REAL(KIND=dp), DIMENSION(:, :), POINTER :: f_vals => NULL()
246 : REAL(KIND=dp), DIMENSION(:, :), POINTER :: r_ref => NULL()
247 : REAL(KIND=dp) :: lambda = 0.0_dp
248 : REAL(KIND=dp) :: step_size = 0.0_dp
249 : TYPE(colvar_p_type), POINTER, DIMENSION(:) :: colvar_p => NULL()
250 : END TYPE reaction_path_colvar_type
251 :
252 : ! **************************************************************************************************
253 : TYPE combine_colvar_type
254 : INTEGER :: type_id = -1
255 : TYPE(colvar_p_type), POINTER, DIMENSION(:) :: colvar_p => NULL()
256 : REAL(KIND=dp) :: lerr = 0.0_dp, dx = 0.0_dp
257 : CHARACTER(LEN=default_path_length) :: FUNCTION = ""
258 : CHARACTER(LEN=default_string_length), &
259 : DIMENSION(:), POINTER :: c_parameters => NULL(), variables => NULL()
260 : REAL(KIND=dp), DIMENSION(:), POINTER :: v_parameters => NULL()
261 : END TYPE combine_colvar_type
262 : ! **************************************************************************************************
263 : TYPE rmsd_colvar_type
264 : INTEGER :: n_atoms = 0, nr_frames = 0, subset = 0
265 : INTEGER, POINTER, DIMENSION(:) :: i_rmsd => NULL()
266 : LOGICAL :: align_frames = .FALSE.
267 : REAL(KIND=dp), DIMENSION(:), POINTER :: weights => NULL()
268 : REAL(KIND=dp), DIMENSION(:, :), POINTER :: r_ref => NULL()
269 : END TYPE rmsd_colvar_type
270 :
271 : ! **************************************************************************************************
272 : TYPE point_type
273 : INTEGER :: type_id = -1
274 : INTEGER, DIMENSION(:), POINTER :: atoms => NULL()
275 : REAL(KIND=dp), DIMENSION(:), POINTER :: weights => NULL()
276 : REAL(KIND=dp), DIMENSION(3) :: r = 0.0_dp
277 : END TYPE point_type
278 :
279 : ! **************************************************************************************************
280 : TYPE xyz_diag_colvar_type
281 : LOGICAL :: use_pbc = .FALSE.
282 : LOGICAL :: use_absolute_position = .FALSE.
283 : INTEGER :: i_atom = 0
284 : INTEGER :: component = 0
285 : REAL(KIND=dp), DIMENSION(3) :: r0 = 0.0_dp
286 : END TYPE xyz_diag_colvar_type
287 :
288 : ! **************************************************************************************************
289 : TYPE xyz_outerdiag_colvar_type
290 : LOGICAL :: use_pbc = .FALSE.
291 : INTEGER, DIMENSION(2) :: i_atoms = 0
292 : INTEGER, DIMENSION(2) :: components = 0
293 : REAL(KIND=dp), DIMENSION(3, 2) :: r0 = 0.0_dp
294 : END TYPE xyz_outerdiag_colvar_type
295 :
296 : ! **************************************************************************************************
297 : TYPE u_colvar_type
298 : TYPE(section_vals_type), POINTER :: mixed_energy_section => NULL()
299 : INTEGER :: natom = -1
300 : END TYPE u_colvar_type
301 :
302 : ! **************************************************************************************************
303 : TYPE Wc_colvar_type
304 : INTEGER :: ids(3) = -1 ! first is the Od, second the H, third the Oa
305 : REAL(KIND=dp) :: ewc = 0.0_dp
306 : REAL(KIND=dp) :: rcut = 0.0_dp
307 : END TYPE Wc_colvar_type
308 :
309 : ! **************************************************************************************************
310 : TYPE HBP_colvar_type
311 : INTEGER :: nPoints = -1 ! number of the points in the path
312 : INTEGER, POINTER :: ids(:, :) => NULL() ! first is the Od, second the H,
313 : ! third the Oa and contains a row for each intermediate point in the path
314 : REAL(KIND=dp), POINTER :: ewc(:) => NULL() ! one for each point in the path
315 : REAL(KIND=dp) :: rcut = 0.0_dp
316 : REAL(KIND=dp) :: shift = 0.0_dp ! shift applied for each term in the collective variable
317 : END TYPE HBP_colvar_type
318 :
319 : ! **************************************************************************************************
320 : TYPE ring_puckering_colvar_type
321 : INTEGER :: nring = -1
322 : INTEGER, POINTER, DIMENSION(:) :: atoms => NULL()
323 : INTEGER :: iq = -1
324 : END TYPE ring_puckering_colvar_type
325 :
326 : ! **************************************************************************************************
327 : TYPE mindist_colvar_type
328 : LOGICAL :: use_kinds_from = .FALSE., use_kinds_to = .FALSE.
329 : INTEGER :: n_coord_to = 0, &
330 : n_coord_from = 0, &
331 : n_dist_from = 0, &
332 : p_exp = 0, &
333 : q_exp = 0
334 : INTEGER, POINTER, DIMENSION(:) :: i_coord_from => NULL(), &
335 : i_coord_to => NULL(), &
336 : i_dist_from => NULL()
337 : CHARACTER(LEN=default_string_length), DIMENSION(:), POINTER :: k_coord_from => NULL(), &
338 : k_coord_to => NULL()
339 : REAL(KIND=dp) :: lambda = 0.0_dp, r_cut = 0.0_dp
340 : END TYPE mindist_colvar_type
341 :
342 : ! **************************************************************************************************
343 : !> \brief parameters for a collective variable
344 : !> \author alessandro laio and fawzi mohamed
345 : ! **************************************************************************************************
346 : TYPE colvar_type
347 : INTEGER :: type_id = -1
348 : LOGICAL :: use_points = .FALSE.
349 : REAL(kind=dp) :: ss = 0.0_dp ! Value of the colvar
350 : REAL(kind=dp), DIMENSION(:, :), POINTER :: dsdr => NULL() ! Derivative of colvar (3,:)
351 : INTEGER, DIMENSION(:), POINTER :: i_atom => NULL() ! Mapping of dsdr
352 : INTEGER :: n_atom_s = -1
353 : ! Available COLVAR types
354 : TYPE(dist_colvar_type), POINTER :: dist_param => NULL()
355 : TYPE(coord_colvar_type), POINTER :: coord_param => NULL()
356 : TYPE(population_colvar_type), POINTER :: population_param => NULL()
357 : TYPE(gyration_colvar_type), POINTER :: gyration_param => NULL()
358 : TYPE(torsion_colvar_type), POINTER :: torsion_param => NULL()
359 : TYPE(angle_colvar_type), POINTER :: angle_param => NULL()
360 : TYPE(plane_distance_colvar_type), POINTER :: plane_distance_param => NULL()
361 : TYPE(plane_plane_angle_colvar_type), POINTER :: plane_plane_angle_param => NULL()
362 : TYPE(rotation_colvar_type), POINTER :: rotation_param => NULL()
363 : TYPE(dfunct_colvar_type), POINTER :: dfunct_param => NULL()
364 : TYPE(qparm_colvar_type), POINTER :: qparm_param => NULL()
365 : TYPE(hydronium_shell_colvar_type), POINTER :: hydronium_shell_param => NULL()
366 : TYPE(hydronium_dist_colvar_type), POINTER :: hydronium_dist_param => NULL()
367 : TYPE(acid_hyd_dist_colvar_type), POINTER :: acid_hyd_dist_param => NULL()
368 : TYPE(acid_hyd_shell_colvar_type), POINTER :: acid_hyd_shell_param => NULL()
369 : TYPE(reaction_path_colvar_type), POINTER :: reaction_path_param => NULL()
370 : TYPE(combine_colvar_type), POINTER :: combine_cvs_param => NULL()
371 : TYPE(rmsd_colvar_type), POINTER :: rmsd_param => NULL()
372 : TYPE(xyz_diag_colvar_type), POINTER :: xyz_diag_param => NULL()
373 : TYPE(xyz_outerdiag_colvar_type), POINTER :: xyz_outerdiag_param => NULL()
374 : TYPE(u_colvar_type), POINTER :: u_param => NULL()
375 : TYPE(point_type), DIMENSION(:), POINTER :: points => NULL()
376 : TYPE(Wc_colvar_type), POINTER :: Wc => NULL()
377 : TYPE(HBP_colvar_type), POINTER :: HBP => NULL()
378 : TYPE(ring_puckering_colvar_type), POINTER :: ring_puckering_param => NULL()
379 : TYPE(mindist_colvar_type), POINTER :: mindist_param => NULL()
380 : END TYPE colvar_type
381 :
382 : ! **************************************************************************************************
383 : TYPE colvar_p_type
384 : TYPE(colvar_type), POINTER :: colvar => NULL()
385 : END TYPE colvar_p_type
386 :
387 : ! **************************************************************************************************
388 : TYPE colvar_counters
389 : INTEGER :: ndist = 0
390 : INTEGER :: nangle = 0
391 : INTEGER :: ntorsion = 0
392 : INTEGER :: ncoord = 0
393 : INTEGER :: nplane_dist = 0
394 : INTEGER :: nplane_angle = 0
395 : INTEGER :: nrot = 0
396 : INTEGER :: ndfunct = 0
397 : INTEGER :: nqparm = 0
398 : INTEGER :: nhydronium_shell = 0
399 : INTEGER :: nhydronium_dist = 0
400 : INTEGER :: nacid_hyd_dist = 0
401 : INTEGER :: nacid_hyd_shell = 0
402 : INTEGER :: nreactionpath = 0
403 : INTEGER :: ncombinecvs = 0
404 : INTEGER :: nrestraint = 0
405 : INTEGER :: npopulation = 0
406 : INTEGER :: ngyration = 0
407 : INTEGER :: nxyz_diag = 0
408 : INTEGER :: nxyz_outerdiag = 0
409 : INTEGER :: ntot = 0
410 : END TYPE colvar_counters
411 :
412 : CONTAINS
413 :
414 : ! **************************************************************************************************
415 : !> \brief initializes a colvar_param type
416 : !> \param colvar the colvat to initialize
417 : !> \param colvar_id ...
418 : !> \author alessandro laio and fawzi mohamed
419 : ! **************************************************************************************************
420 5664 : SUBROUTINE colvar_create(colvar, colvar_id)
421 : TYPE(colvar_type), POINTER :: colvar
422 : INTEGER, INTENT(in) :: colvar_id
423 :
424 5664 : CPASSERT(.NOT. ASSOCIATED(colvar))
425 5664 : ALLOCATE (colvar)
426 5664 : colvar%type_id = colvar_id
427 : colvar%use_points = .FALSE.
428 4998 : SELECT CASE (colvar_id)
429 : CASE (dist_colvar_id)
430 4998 : ALLOCATE (colvar%dist_param)
431 : colvar%dist_param%axis_id = do_clv_xyz
432 4998 : colvar%dist_param%sign_d = .FALSE.
433 : CASE (coord_colvar_id)
434 58 : ALLOCATE (colvar%coord_param)
435 : CASE (population_colvar_id)
436 8 : ALLOCATE (colvar%population_param)
437 : CASE (gyration_colvar_id)
438 2 : ALLOCATE (colvar%gyration_param)
439 : CASE (angle_colvar_id)
440 1100 : ALLOCATE (colvar%angle_param)
441 : CASE (torsion_colvar_id)
442 960 : ALLOCATE (colvar%torsion_param)
443 : CASE (plane_distance_colvar_id)
444 140 : ALLOCATE (colvar%plane_distance_param)
445 : CASE (plane_plane_angle_colvar_id)
446 272 : ALLOCATE (colvar%plane_plane_angle_param)
447 : CASE (rotation_colvar_id)
448 2 : ALLOCATE (colvar%rotation_param)
449 : CASE (dfunct_colvar_id)
450 108 : ALLOCATE (colvar%dfunct_param)
451 : CASE (qparm_colvar_id)
452 2 : ALLOCATE (colvar%qparm_param)
453 : CASE (xyz_diag_colvar_id)
454 150 : ALLOCATE (colvar%xyz_diag_param)
455 : ! Initialize r0 with dummy..
456 120 : colvar%xyz_diag_param%r0 = HUGE(0.0_dp)
457 : CASE (xyz_outerdiag_colvar_id)
458 480 : ALLOCATE (colvar%xyz_outerdiag_param)
459 : ! Initialize r0 with dummy..
460 270 : colvar%xyz_outerdiag_param%r0 = HUGE(0.0_dp)
461 : CASE (u_colvar_id)
462 6 : ALLOCATE (colvar%u_param)
463 6 : NULLIFY (colvar%u_param%mixed_energy_section)
464 : CASE (hydronium_shell_colvar_id)
465 2 : ALLOCATE (colvar%hydronium_shell_param)
466 : CASE (hydronium_dist_colvar_id)
467 2 : ALLOCATE (colvar%hydronium_dist_param)
468 : CASE (acid_hyd_dist_colvar_id)
469 2 : ALLOCATE (colvar%acid_hyd_dist_param)
470 : CASE (acid_hyd_shell_colvar_id)
471 2 : ALLOCATE (colvar%acid_hyd_shell_param)
472 : CASE (reaction_path_colvar_id)
473 64 : ALLOCATE (colvar%reaction_path_param)
474 : CASE (distance_from_path_colvar_id)
475 32 : ALLOCATE (colvar%reaction_path_param)
476 : CASE (combine_colvar_id)
477 16 : ALLOCATE (colvar%combine_cvs_param)
478 : CASE (rmsd_colvar_id)
479 4 : ALLOCATE (colvar%rmsd_param)
480 : CASE (Wc_colvar_id)
481 0 : ALLOCATE (colvar%Wc)
482 : CASE (HBP_colvar_id)
483 2 : ALLOCATE (colvar%HBP)
484 : CASE (ring_puckering_colvar_id)
485 32 : ALLOCATE (colvar%ring_puckering_param)
486 : CASE (mindist_colvar_id)
487 0 : ALLOCATE (colvar%mindist_param)
488 : CASE (no_colvar_id)
489 : ! Do nothing
490 : CASE DEFAULT
491 5664 : CPABORT("")
492 : END SELECT
493 :
494 5664 : END SUBROUTINE colvar_create
495 :
496 : ! **************************************************************************************************
497 : !> \brief Finalize the setup of the collective variable
498 : !> \param colvar the colvar to initialize
499 : !> \author Teodoro Laino, [teo] 09.03.2006
500 : ! **************************************************************************************************
501 5680 : SUBROUTINE colvar_setup(colvar)
502 : TYPE(colvar_type), INTENT(INOUT) :: colvar
503 :
504 : INTEGER :: i, idum, iend, ii, istart, j, np, stat
505 5680 : INTEGER, DIMENSION(:), POINTER :: list
506 :
507 10678 : SELECT CASE (colvar%type_id)
508 : CASE (dist_colvar_id)
509 4998 : np = 2
510 4998 : i = colvar%dist_param%i_at
511 4998 : j = colvar%dist_param%j_at
512 : ! Number of real atoms involved in the colvar
513 : colvar%n_atom_s = COLV_SIZE(colvar, i) + &
514 4998 : COLV_SIZE(colvar, j)
515 : ! Create a List of points...
516 4998 : ALLOCATE (list(np))
517 4998 : list(1) = colvar%dist_param%i_at
518 4998 : list(2) = colvar%dist_param%j_at
519 : CASE (coord_colvar_id)
520 : np = colvar%coord_param%n_atoms_from + colvar%coord_param%n_atoms_to &
521 64 : + colvar%coord_param%n_atoms_to_b
522 : ! Number of real atoms involved in the colvar
523 64 : colvar%n_atom_s = 0
524 124 : DO ii = 1, colvar%coord_param%n_atoms_from
525 60 : i = colvar%coord_param%i_at_from(ii)
526 124 : colvar%n_atom_s = colvar%n_atom_s + COLV_SIZE(colvar, i)
527 : END DO
528 158 : DO ii = 1, colvar%coord_param%n_atoms_to
529 94 : i = colvar%coord_param%i_at_to(ii)
530 158 : colvar%n_atom_s = colvar%n_atom_s + COLV_SIZE(colvar, i)
531 : END DO
532 64 : IF (colvar%coord_param%n_atoms_to_b /= 0) THEN
533 8 : DO ii = 1, colvar%coord_param%n_atoms_to_b
534 4 : i = colvar%coord_param%i_at_to_b(ii)
535 8 : colvar%n_atom_s = colvar%n_atom_s + COLV_SIZE(colvar, i)
536 : END DO
537 : END IF
538 : ! Create a List of points...
539 186 : ALLOCATE (list(np))
540 64 : idum = 0
541 124 : DO ii = 1, colvar%coord_param%n_atoms_from
542 60 : idum = idum + 1
543 60 : i = colvar%coord_param%i_at_from(ii)
544 124 : list(idum) = i
545 : END DO
546 158 : DO ii = 1, colvar%coord_param%n_atoms_to
547 94 : idum = idum + 1
548 94 : i = colvar%coord_param%i_at_to(ii)
549 158 : list(idum) = i
550 : END DO
551 64 : IF (colvar%coord_param%n_atoms_to_b /= 0) THEN
552 8 : DO ii = 1, colvar%coord_param%n_atoms_to_b
553 4 : idum = idum + 1
554 4 : i = colvar%coord_param%i_at_to_b(ii)
555 8 : list(idum) = i
556 : END DO
557 : END IF
558 64 : CPASSERT(idum == np)
559 : CASE (population_colvar_id)
560 16 : np = colvar%population_param%n_atoms_from + colvar%population_param%n_atoms_to
561 : ! Number of real atoms involved in the colvar
562 16 : colvar%n_atom_s = 0
563 32 : DO ii = 1, colvar%population_param%n_atoms_from
564 16 : i = colvar%population_param%i_at_from(ii)
565 32 : colvar%n_atom_s = colvar%n_atom_s + COLV_SIZE(colvar, i)
566 : END DO
567 32 : DO ii = 1, colvar%population_param%n_atoms_to
568 16 : i = colvar%population_param%i_at_to(ii)
569 32 : colvar%n_atom_s = colvar%n_atom_s + COLV_SIZE(colvar, i)
570 : END DO
571 : ! Create a List of points...
572 48 : ALLOCATE (list(np))
573 16 : idum = 0
574 32 : DO ii = 1, colvar%population_param%n_atoms_from
575 16 : idum = idum + 1
576 16 : i = colvar%population_param%i_at_from(ii)
577 32 : list(idum) = i
578 : END DO
579 32 : DO ii = 1, colvar%population_param%n_atoms_to
580 16 : idum = idum + 1
581 16 : i = colvar%population_param%i_at_to(ii)
582 32 : list(idum) = i
583 : END DO
584 16 : CPASSERT(idum == np)
585 : CASE (gyration_colvar_id)
586 4 : np = colvar%gyration_param%n_atoms
587 : ! Number of real atoms involved in the colvar
588 4 : colvar%n_atom_s = 0
589 30 : DO ii = 1, colvar%gyration_param%n_atoms
590 26 : i = colvar%gyration_param%i_at(ii)
591 30 : colvar%n_atom_s = colvar%n_atom_s + COLV_SIZE(colvar, i)
592 : END DO
593 : ! Create a List of points...
594 10 : ALLOCATE (list(np))
595 4 : idum = 0
596 30 : DO ii = 1, colvar%gyration_param%n_atoms
597 26 : idum = idum + 1
598 26 : i = colvar%gyration_param%i_at(ii)
599 30 : list(idum) = i
600 : END DO
601 4 : CPASSERT(idum == np)
602 : CASE (angle_colvar_id)
603 220 : np = 3
604 : ! Number of real atoms involved in the colvar
605 220 : colvar%n_atom_s = 0
606 880 : DO ii = 1, 3
607 660 : i = colvar%angle_param%i_at_angle(ii)
608 880 : colvar%n_atom_s = colvar%n_atom_s + COLV_SIZE(colvar, i)
609 : END DO
610 : ! Create a List of points...
611 220 : ALLOCATE (list(np))
612 220 : idum = 0
613 880 : DO ii = 1, 3
614 660 : idum = idum + 1
615 660 : i = colvar%angle_param%i_at_angle(ii)
616 880 : list(idum) = i
617 : END DO
618 220 : CPASSERT(idum == np)
619 : CASE (torsion_colvar_id)
620 160 : np = 4
621 : ! Number of real atoms involved in the colvar
622 160 : colvar%n_atom_s = 0
623 800 : DO ii = 1, 4
624 640 : i = colvar%torsion_param%i_at_tors(ii)
625 800 : colvar%n_atom_s = colvar%n_atom_s + COLV_SIZE(colvar, i)
626 : END DO
627 : ! Create a List of points...
628 160 : ALLOCATE (list(np))
629 160 : idum = 0
630 800 : DO ii = 1, 4
631 640 : idum = idum + 1
632 640 : i = colvar%torsion_param%i_at_tors(ii)
633 800 : list(idum) = i
634 : END DO
635 160 : CPASSERT(idum == np)
636 : CASE (plane_distance_colvar_id)
637 28 : np = 4
638 : ! Number of real atoms involved in the colvar
639 28 : colvar%n_atom_s = 0
640 112 : DO ii = 1, 3
641 84 : i = colvar%plane_distance_param%plane(ii)
642 112 : colvar%n_atom_s = colvar%n_atom_s + COLV_SIZE(colvar, i)
643 : END DO
644 28 : i = colvar%plane_distance_param%point
645 28 : colvar%n_atom_s = colvar%n_atom_s + COLV_SIZE(colvar, i)
646 : ! Create a List of points...
647 28 : ALLOCATE (list(np))
648 28 : idum = 0
649 112 : DO ii = 1, 3
650 84 : idum = idum + 1
651 84 : i = colvar%plane_distance_param%plane(ii)
652 112 : list(idum) = i
653 : END DO
654 28 : i = colvar%plane_distance_param%point
655 28 : list(4) = i
656 28 : idum = idum + 1
657 28 : CPASSERT(idum == np)
658 : CASE (plane_plane_angle_colvar_id)
659 16 : np = 0
660 16 : IF (colvar%plane_plane_angle_param%plane1%type_of_def == plane_def_atoms) np = np + 3
661 16 : IF (colvar%plane_plane_angle_param%plane2%type_of_def == plane_def_atoms) np = np + 3
662 : ! if np is equal to zero this means that this is not a COLLECTIVE variable..
663 8 : IF (np == 0) &
664 : CALL cp_abort(__LOCATION__, &
665 : "PLANE_PLANE_ANGLE Colvar defined using two normal vectors! This is "// &
666 : "not a COLLECTIVE VARIABLE! One of the two planes must be defined "// &
667 0 : "using atomic positions.")
668 :
669 : ! Number of real atoms involved in the colvar
670 16 : colvar%n_atom_s = 0
671 16 : IF (colvar%plane_plane_angle_param%plane1%type_of_def == plane_def_atoms) THEN
672 64 : DO ii = 1, 3
673 48 : i = colvar%plane_plane_angle_param%plane1%points(ii)
674 64 : colvar%n_atom_s = colvar%n_atom_s + COLV_SIZE(colvar, i)
675 : END DO
676 : END IF
677 16 : IF (colvar%plane_plane_angle_param%plane2%type_of_def == plane_def_atoms) THEN
678 32 : DO ii = 1, 3
679 24 : i = colvar%plane_plane_angle_param%plane2%points(ii)
680 32 : colvar%n_atom_s = colvar%n_atom_s + COLV_SIZE(colvar, i)
681 : END DO
682 : END IF
683 :
684 : ! Create a List of points...
685 32 : ALLOCATE (list(np))
686 16 : idum = 0
687 16 : IF (colvar%plane_plane_angle_param%plane1%type_of_def == plane_def_atoms) THEN
688 64 : DO ii = 1, 3
689 48 : idum = idum + 1
690 48 : i = colvar%plane_plane_angle_param%plane1%points(ii)
691 64 : list(idum) = i
692 : END DO
693 : END IF
694 16 : IF (colvar%plane_plane_angle_param%plane2%type_of_def == plane_def_atoms) THEN
695 32 : DO ii = 1, 3
696 24 : idum = idum + 1
697 24 : i = colvar%plane_plane_angle_param%plane2%points(ii)
698 32 : list(idum) = i
699 : END DO
700 : END IF
701 16 : CPASSERT(idum == np)
702 : CASE (dfunct_colvar_id)
703 18 : np = 4
704 : ! Number of real atoms involved in the colvar
705 18 : colvar%n_atom_s = 0
706 90 : DO ii = 1, 4
707 72 : i = colvar%dfunct_param%i_at_dfunct(ii)
708 90 : colvar%n_atom_s = colvar%n_atom_s + COLV_SIZE(colvar, i)
709 : END DO
710 : ! Create a List of points...
711 18 : ALLOCATE (list(np))
712 18 : idum = 0
713 90 : DO ii = 1, 4
714 72 : idum = idum + 1
715 72 : i = colvar%dfunct_param%i_at_dfunct(ii)
716 90 : list(idum) = i
717 : END DO
718 18 : CPASSERT(idum == np)
719 : CASE (rotation_colvar_id)
720 2 : np = 4
721 : ! Number of real atoms involved in the colvar
722 2 : colvar%n_atom_s = 0
723 2 : i = colvar%rotation_param%i_at1_bond1
724 2 : colvar%n_atom_s = colvar%n_atom_s + COLV_SIZE(colvar, i)
725 2 : i = colvar%rotation_param%i_at2_bond1
726 2 : colvar%n_atom_s = colvar%n_atom_s + COLV_SIZE(colvar, i)
727 2 : i = colvar%rotation_param%i_at1_bond2
728 2 : colvar%n_atom_s = colvar%n_atom_s + COLV_SIZE(colvar, i)
729 2 : i = colvar%rotation_param%i_at2_bond2
730 2 : colvar%n_atom_s = colvar%n_atom_s + COLV_SIZE(colvar, i)
731 : ! Create a List of points...
732 2 : ALLOCATE (list(np))
733 : i = colvar%rotation_param%i_at1_bond1
734 2 : list(1) = i
735 : i = colvar%rotation_param%i_at2_bond1
736 2 : list(2) = i
737 : i = colvar%rotation_param%i_at1_bond2
738 2 : list(3) = i
739 2 : i = colvar%rotation_param%i_at2_bond2
740 2 : list(4) = i
741 : CASE (qparm_colvar_id)
742 2 : np = colvar%qparm_param%n_atoms_from + colvar%qparm_param%n_atoms_to
743 : ! Number of real atoms involved in the colvar
744 2 : colvar%n_atom_s = 0
745 218 : DO ii = 1, colvar%qparm_param%n_atoms_from
746 216 : i = colvar%qparm_param%i_at_from(ii)
747 218 : colvar%n_atom_s = colvar%n_atom_s + COLV_SIZE(colvar, i)
748 : END DO
749 218 : DO ii = 1, colvar%qparm_param%n_atoms_to
750 216 : i = colvar%qparm_param%i_at_to(ii)
751 218 : colvar%n_atom_s = colvar%n_atom_s + COLV_SIZE(colvar, i)
752 : END DO
753 : ! Create a List of points...
754 6 : ALLOCATE (list(np))
755 2 : idum = 0
756 218 : DO ii = 1, colvar%qparm_param%n_atoms_from
757 216 : idum = idum + 1
758 216 : i = colvar%qparm_param%i_at_from(ii)
759 218 : list(idum) = i
760 : END DO
761 218 : DO ii = 1, colvar%qparm_param%n_atoms_to
762 216 : idum = idum + 1
763 216 : i = colvar%qparm_param%i_at_to(ii)
764 218 : list(idum) = i
765 : END DO
766 2 : CPASSERT(idum == np)
767 : CASE (hydronium_shell_colvar_id)
768 2 : np = colvar%hydronium_shell_param%n_oxygens + colvar%hydronium_shell_param%n_hydrogens
769 6 : ALLOCATE (list(np))
770 2 : CALL setup_hydronium_colvars(colvar, hydronium_shell_colvar_id, list)
771 : CASE (hydronium_dist_colvar_id)
772 2 : np = colvar%hydronium_dist_param%n_oxygens + colvar%hydronium_dist_param%n_hydrogens
773 6 : ALLOCATE (list(np))
774 2 : CALL setup_hydronium_colvars(colvar, hydronium_dist_colvar_id, list)
775 : CASE (acid_hyd_dist_colvar_id)
776 : np = colvar%acid_hyd_dist_param%n_oxygens_water &
777 : + colvar%acid_hyd_dist_param%n_oxygens_acid &
778 2 : + colvar%acid_hyd_dist_param%n_hydrogens
779 6 : ALLOCATE (list(np))
780 2 : CALL setup_acid_hydronium_colvars(colvar, acid_hyd_dist_colvar_id, list)
781 : CASE (acid_hyd_shell_colvar_id)
782 : np = colvar%acid_hyd_shell_param%n_oxygens_water &
783 : + colvar%acid_hyd_shell_param%n_oxygens_acid &
784 2 : + colvar%acid_hyd_shell_param%n_hydrogens
785 6 : ALLOCATE (list(np))
786 2 : CALL setup_acid_hydronium_colvars(colvar, acid_hyd_shell_colvar_id, list)
787 : CASE (rmsd_colvar_id)
788 4 : np = colvar%rmsd_param%n_atoms
789 : ! Number of real atoms involved in the colvar
790 4 : colvar%n_atom_s = 0
791 28 : DO ii = 1, colvar%rmsd_param%n_atoms
792 24 : i = colvar%rmsd_param%i_rmsd(ii)
793 28 : colvar%n_atom_s = colvar%n_atom_s + COLV_SIZE(colvar, i)
794 : END DO
795 : ! Create a List of points...
796 12 : ALLOCATE (list(np))
797 4 : idum = 0
798 28 : DO ii = 1, colvar%rmsd_param%n_atoms
799 24 : idum = idum + 1
800 24 : i = colvar%rmsd_param%i_rmsd(ii)
801 28 : list(idum) = i
802 : END DO
803 : CASE (reaction_path_colvar_id, distance_from_path_colvar_id)
804 24 : colvar%n_atom_s = 0
805 24 : IF (colvar%reaction_path_param%dist_rmsd .OR. colvar%reaction_path_param%rmsd) THEN
806 8 : colvar%n_atom_s = colvar%reaction_path_param%n_components
807 : ELSE
808 48 : DO ii = 1, SIZE(colvar%reaction_path_param%colvar_p)
809 48 : colvar%n_atom_s = colvar%n_atom_s + colvar%reaction_path_param%colvar_p(ii)%colvar%n_atom_s
810 : END DO
811 : END IF
812 72 : ALLOCATE (list(colvar%n_atom_s))
813 24 : idum = 0
814 24 : IF (colvar%reaction_path_param%dist_rmsd .OR. colvar%reaction_path_param%rmsd) THEN
815 80 : DO ii = 1, SIZE(colvar%reaction_path_param%i_rmsd)
816 72 : idum = idum + 1
817 72 : i = colvar%reaction_path_param%i_rmsd(ii)
818 80 : list(idum) = i
819 : END DO
820 : ELSE
821 48 : DO ii = 1, SIZE(colvar%reaction_path_param%colvar_p)
822 112 : DO j = 1, colvar%reaction_path_param%colvar_p(ii)%colvar%n_atom_s
823 64 : idum = idum + 1
824 96 : list(idum) = colvar%reaction_path_param%colvar_p(ii)%colvar%i_atom(j)
825 : END DO
826 : END DO
827 : END IF
828 : CASE (xyz_diag_colvar_id)
829 30 : np = 1
830 : ! Number of real atoms involved in the colvar
831 30 : colvar%n_atom_s = 0
832 30 : i = colvar%xyz_diag_param%i_atom
833 30 : colvar%n_atom_s = colvar%n_atom_s + COLV_SIZE(colvar, i)
834 : ! Create a List of points...
835 30 : ALLOCATE (list(np))
836 : i = colvar%xyz_diag_param%i_atom
837 30 : list(1) = i
838 : CASE (xyz_outerdiag_colvar_id)
839 30 : np = 2
840 : ! Number of real atoms involved in the colvar
841 30 : colvar%n_atom_s = 0
842 30 : i = colvar%xyz_outerdiag_param%i_atoms(1)
843 30 : colvar%n_atom_s = colvar%n_atom_s + COLV_SIZE(colvar, i)
844 30 : i = colvar%xyz_outerdiag_param%i_atoms(2)
845 30 : colvar%n_atom_s = colvar%n_atom_s + COLV_SIZE(colvar, i)
846 : ! Create a List of points...
847 30 : ALLOCATE (list(np))
848 : i = colvar%xyz_outerdiag_param%i_atoms(1)
849 30 : list(1) = i
850 30 : i = colvar%xyz_outerdiag_param%i_atoms(2)
851 30 : list(2) = i
852 : CASE (u_colvar_id)
853 6 : np = 1; ALLOCATE (list(np), stat=stat)
854 0 : CPASSERT(stat == 0)
855 6 : colvar%n_atom_s = np; list(1) = 1
856 : CASE (Wc_colvar_id)
857 0 : np = 3
858 : ! Number of real atoms involved in the colvar
859 0 : colvar%n_atom_s = 0
860 0 : DO ii = 1, 3
861 0 : i = colvar%Wc%ids(ii)
862 0 : colvar%n_atom_s = colvar%n_atom_s + COLV_SIZE(colvar, i)
863 : END DO
864 : ! Create a List of points...
865 0 : ALLOCATE (list(np))
866 0 : idum = 0
867 0 : DO ii = 1, 3
868 0 : idum = idum + 1
869 0 : i = colvar%Wc%ids(ii)
870 0 : list(idum) = i
871 : END DO
872 0 : CPASSERT(idum == np)
873 : CASE (HBP_colvar_id)
874 2 : np = 3*colvar%HBP%nPoints
875 : ! Number of real atoms involved in the colvar
876 2 : colvar%n_atom_s = 0
877 4 : DO j = 1, colvar%HBP%nPoints
878 10 : DO ii = 1, 3
879 6 : i = colvar%HBP%ids(j, ii)
880 8 : colvar%n_atom_s = colvar%n_atom_s + COLV_SIZE(colvar, i)
881 : END DO
882 : END DO
883 : ! Create a List of points...
884 6 : ALLOCATE (list(np))
885 2 : idum = 0
886 4 : DO j = 1, colvar%HBP%nPoints
887 10 : DO ii = 1, 3
888 6 : idum = idum + 1
889 6 : i = colvar%HBP%ids(j, ii)
890 8 : list(idum) = i
891 : END DO
892 : END DO
893 2 : CPASSERT(idum == np)
894 : CASE (ring_puckering_colvar_id)
895 32 : np = colvar%ring_puckering_param%nring
896 : ! Number of real atoms involved in the colvar
897 32 : colvar%n_atom_s = 0
898 210 : DO ii = 1, colvar%ring_puckering_param%nring
899 178 : i = colvar%ring_puckering_param%atoms(ii)
900 210 : colvar%n_atom_s = colvar%n_atom_s + COLV_SIZE(colvar, i)
901 : END DO
902 : ! Create a List of points...
903 96 : ALLOCATE (list(np))
904 32 : idum = 0
905 210 : DO ii = 1, colvar%ring_puckering_param%nring
906 178 : idum = idum + 1
907 178 : i = colvar%ring_puckering_param%atoms(ii)
908 210 : list(idum) = i
909 : END DO
910 32 : CPASSERT(idum == np)
911 : CASE (mindist_colvar_id)
912 : np = colvar%mindist_param%n_dist_from + &
913 0 : colvar%mindist_param%n_coord_from + colvar%mindist_param%n_coord_to
914 : ! Number of real atoms involved in the colvar
915 0 : colvar%n_atom_s = 0
916 0 : DO ii = 1, colvar%mindist_param%n_dist_from
917 0 : i = colvar%mindist_param%i_dist_from(ii)
918 0 : colvar%n_atom_s = colvar%n_atom_s + COLV_SIZE(colvar, i)
919 : END DO
920 0 : DO ii = 1, colvar%mindist_param%n_coord_from
921 0 : i = colvar%mindist_param%i_coord_from(ii)
922 0 : colvar%n_atom_s = colvar%n_atom_s + COLV_SIZE(colvar, i)
923 : END DO
924 0 : DO ii = 1, colvar%mindist_param%n_coord_to
925 0 : i = colvar%mindist_param%i_coord_to(ii)
926 0 : colvar%n_atom_s = colvar%n_atom_s + COLV_SIZE(colvar, i)
927 : END DO
928 : ! Create a List of points...
929 0 : ALLOCATE (list(np))
930 0 : idum = 0
931 0 : DO ii = 1, colvar%mindist_param%n_dist_from
932 0 : idum = idum + 1
933 0 : i = colvar%mindist_param%i_dist_from(ii)
934 0 : list(idum) = i
935 : END DO
936 0 : DO ii = 1, colvar%mindist_param%n_coord_from
937 0 : idum = idum + 1
938 0 : i = colvar%mindist_param%i_coord_from(ii)
939 0 : list(idum) = i
940 : END DO
941 0 : DO ii = 1, colvar%mindist_param%n_coord_to
942 0 : idum = idum + 1
943 0 : i = colvar%mindist_param%i_coord_to(ii)
944 0 : list(idum) = i
945 : END DO
946 0 : CPASSERT(idum == np)
947 : CASE (combine_colvar_id)
948 16 : colvar%n_atom_s = 0
949 48 : DO ii = 1, SIZE(colvar%combine_cvs_param%colvar_p)
950 48 : colvar%n_atom_s = colvar%n_atom_s + colvar%combine_cvs_param%colvar_p(ii)%colvar%n_atom_s
951 : END DO
952 48 : ALLOCATE (list(colvar%n_atom_s))
953 16 : idum = 0
954 48 : DO ii = 1, SIZE(colvar%combine_cvs_param%colvar_p)
955 160 : DO j = 1, colvar%combine_cvs_param%colvar_p(ii)%colvar%n_atom_s
956 112 : idum = idum + 1
957 144 : list(idum) = colvar%combine_cvs_param%colvar_p(ii)%colvar%i_atom(j)
958 : END DO
959 : END DO
960 : END SELECT
961 :
962 5680 : IF (ASSOCIATED(colvar%dsdr)) THEN
963 16 : DEALLOCATE (colvar%dsdr)
964 : END IF
965 5680 : IF (ASSOCIATED(colvar%i_atom)) THEN
966 16 : DEALLOCATE (colvar%i_atom)
967 : END IF
968 17032 : ALLOCATE (colvar%dsdr(3, colvar%n_atom_s))
969 17032 : ALLOCATE (colvar%i_atom(colvar%n_atom_s))
970 : ! And now map real atoms
971 5680 : istart = 0
972 5680 : iend = 0
973 18528 : DO i = 1, SIZE(list)
974 18528 : IF (.NOT. colvar%use_points) THEN
975 : ! No point centers
976 12582 : colvar%i_atom(i) = list(i)
977 12582 : iend = iend + 1
978 : ELSE
979 266 : IF (ASSOCIATED(colvar%points(list(i))%atoms)) THEN
980 256 : iend = istart + SIZE(colvar%points(list(i))%atoms)
981 616 : colvar%i_atom(istart + 1:iend) = colvar%points(list(i))%atoms
982 : istart = iend
983 : END IF
984 : END IF
985 : END DO
986 5680 : CPASSERT(iend == colvar%n_atom_s)
987 5680 : DEALLOCATE (list)
988 :
989 5680 : END SUBROUTINE colvar_setup
990 :
991 : ! **************************************************************************************************
992 : !> \brief Finalize the setup of the collective variable for the autoionization of water
993 : !> \param colvar the colvar to initialize
994 : !> \param colvar_id ...
995 : !> \param list ...
996 : !> \author Dorothea Golze
997 : ! **************************************************************************************************
998 4 : SUBROUTINE setup_hydronium_colvars(colvar, colvar_id, list)
999 : TYPE(colvar_type), INTENT(INOUT) :: colvar
1000 : INTEGER, INTENT(IN) :: colvar_id
1001 : INTEGER, DIMENSION(:), INTENT(INOUT) :: list
1002 :
1003 : INTEGER :: i, idum, ii, n_hydrogens, n_oxygens, np
1004 4 : INTEGER, DIMENSION(:), POINTER :: i_hydrogens, i_oxygens
1005 :
1006 4 : NULLIFY (i_oxygens, i_hydrogens)
1007 :
1008 6 : SELECT CASE (colvar_id)
1009 : CASE (hydronium_shell_colvar_id)
1010 2 : n_oxygens = colvar%hydronium_shell_param%n_oxygens
1011 2 : n_hydrogens = colvar%hydronium_shell_param%n_hydrogens
1012 2 : i_oxygens => colvar%hydronium_shell_param%i_oxygens
1013 2 : i_hydrogens => colvar%hydronium_shell_param%i_hydrogens
1014 : CASE (hydronium_dist_colvar_id)
1015 2 : n_oxygens = colvar%hydronium_dist_param%n_oxygens
1016 2 : n_hydrogens = colvar%hydronium_dist_param%n_hydrogens
1017 2 : i_oxygens => colvar%hydronium_dist_param%i_oxygens
1018 2 : i_hydrogens => colvar%hydronium_dist_param%i_hydrogens
1019 : END SELECT
1020 :
1021 4 : np = n_oxygens + n_hydrogens
1022 : ! Number of real atoms involved in the colvar
1023 4 : colvar%n_atom_s = 0
1024 20 : DO ii = 1, n_oxygens
1025 16 : i = i_oxygens(ii)
1026 20 : colvar%n_atom_s = colvar%n_atom_s + COLV_SIZE(colvar, i)
1027 : END DO
1028 40 : DO ii = 1, n_hydrogens
1029 36 : i = i_hydrogens(ii)
1030 40 : colvar%n_atom_s = colvar%n_atom_s + COLV_SIZE(colvar, i)
1031 : END DO
1032 : idum = 0
1033 20 : DO ii = 1, n_oxygens
1034 16 : idum = idum + 1
1035 16 : i = i_oxygens(ii)
1036 16 : list(idum) = i
1037 160 : IF (ANY(i_hydrogens == i)) &
1038 4 : CPABORT("COLVAR: atoms doubled in OXYGENS and HYDROGENS list")
1039 : END DO
1040 40 : DO ii = 1, n_hydrogens
1041 36 : idum = idum + 1
1042 36 : i = i_hydrogens(ii)
1043 40 : list(idum) = i
1044 : END DO
1045 4 : CPASSERT(idum == np)
1046 56 : DO i = 1, np
1047 368 : DO ii = i + 1, np
1048 364 : IF (list(i) == list(ii)) THEN
1049 0 : IF (i <= n_oxygens) &
1050 0 : CPABORT("atoms doubled in OXYGENS list")
1051 0 : IF (i > n_oxygens) &
1052 0 : CPABORT("atoms doubled in HYDROGENS list")
1053 : END IF
1054 : END DO
1055 : END DO
1056 :
1057 4 : END SUBROUTINE setup_hydronium_colvars
1058 :
1059 : ! **************************************************************************************************
1060 : !> \brief Finalize the setup of the collective variable for the dissociation
1061 : !> of a carboxylic acid in water
1062 : !> \param colvar the colvar to initialize
1063 : !> \param colvar_id ...
1064 : !> \param list ...
1065 : !> \author Dorothea Golze
1066 : ! **************************************************************************************************
1067 4 : SUBROUTINE setup_acid_hydronium_colvars(colvar, colvar_id, list)
1068 : TYPE(colvar_type), INTENT(INOUT) :: colvar
1069 : INTEGER, INTENT(IN) :: colvar_id
1070 : INTEGER, DIMENSION(:), INTENT(INOUT) :: list
1071 :
1072 : INTEGER :: i, idum, ii, n_hydrogens, &
1073 : n_oxygens_acid, n_oxygens_water, np
1074 4 : INTEGER, DIMENSION(:), POINTER :: i_hydrogens, i_oxygens_acid, &
1075 4 : i_oxygens_water
1076 :
1077 4 : NULLIFY (i_oxygens_water, i_oxygens_acid, i_hydrogens)
1078 :
1079 6 : SELECT CASE (colvar_id)
1080 : CASE (acid_hyd_dist_colvar_id)
1081 2 : n_oxygens_water = colvar%acid_hyd_dist_param%n_oxygens_water
1082 2 : n_oxygens_acid = colvar%acid_hyd_dist_param%n_oxygens_acid
1083 2 : n_hydrogens = colvar%acid_hyd_dist_param%n_hydrogens
1084 2 : i_oxygens_water => colvar%acid_hyd_dist_param%i_oxygens_water
1085 2 : i_oxygens_acid => colvar%acid_hyd_dist_param%i_oxygens_acid
1086 2 : i_hydrogens => colvar%acid_hyd_dist_param%i_hydrogens
1087 : CASE (acid_hyd_shell_colvar_id)
1088 2 : n_oxygens_water = colvar%acid_hyd_shell_param%n_oxygens_water
1089 2 : n_oxygens_acid = colvar%acid_hyd_shell_param%n_oxygens_acid
1090 2 : n_hydrogens = colvar%acid_hyd_shell_param%n_hydrogens
1091 2 : i_oxygens_water => colvar%acid_hyd_shell_param%i_oxygens_water
1092 2 : i_oxygens_acid => colvar%acid_hyd_shell_param%i_oxygens_acid
1093 2 : i_hydrogens => colvar%acid_hyd_shell_param%i_hydrogens
1094 : END SELECT
1095 :
1096 4 : np = n_oxygens_water + n_oxygens_acid + n_hydrogens
1097 : ! Number of real atoms involved in the colvar
1098 4 : colvar%n_atom_s = 0
1099 12 : DO ii = 1, n_oxygens_water
1100 8 : i = i_oxygens_water(ii)
1101 12 : colvar%n_atom_s = colvar%n_atom_s + COLV_SIZE(colvar, i)
1102 : END DO
1103 12 : DO ii = 1, n_oxygens_acid
1104 8 : i = i_oxygens_acid(ii)
1105 12 : colvar%n_atom_s = colvar%n_atom_s + COLV_SIZE(colvar, i)
1106 : END DO
1107 24 : DO ii = 1, n_hydrogens
1108 20 : i = i_hydrogens(ii)
1109 24 : colvar%n_atom_s = colvar%n_atom_s + COLV_SIZE(colvar, i)
1110 : END DO
1111 : idum = 0
1112 12 : DO ii = 1, n_oxygens_water
1113 8 : idum = idum + 1
1114 8 : i = i_oxygens_water(ii)
1115 8 : list(idum) = i
1116 48 : IF (ANY(i_hydrogens == i)) &
1117 0 : CPABORT("COLVAR: atoms doubled in OXYGENS_WATER and HYDROGENS list")
1118 24 : IF (ANY(i_oxygens_acid == i)) &
1119 4 : CPABORT("COLVAR: atoms doubled in OXYGENS_WATER and OXYGENS_ACID list")
1120 : END DO
1121 12 : DO ii = 1, n_oxygens_acid
1122 8 : idum = idum + 1
1123 8 : i = i_oxygens_acid(ii)
1124 8 : list(idum) = i
1125 48 : IF (ANY(i_hydrogens == i)) &
1126 4 : CPABORT("COLVAR: atoms doubled in OXYGENS_ACID and HYDROGENS list")
1127 : END DO
1128 24 : DO ii = 1, n_hydrogens
1129 20 : idum = idum + 1
1130 20 : i = i_hydrogens(ii)
1131 24 : list(idum) = i
1132 : END DO
1133 4 : CPASSERT(idum == np)
1134 40 : DO i = 1, np
1135 184 : DO ii = i + 1, np
1136 180 : IF (list(i) == list(ii)) THEN
1137 0 : IF (i <= n_oxygens_water) &
1138 0 : CPABORT("atoms doubled in OXYGENS_WATER list")
1139 0 : IF (i > n_oxygens_water .AND. i <= n_oxygens_water + n_oxygens_acid) &
1140 0 : CPABORT("atoms doubled in OXYGENS_ACID list")
1141 0 : IF (i > n_oxygens_water + n_oxygens_acid) &
1142 0 : CPABORT("atoms doubled in HYDROGENS list")
1143 : END IF
1144 : END DO
1145 : END DO
1146 :
1147 4 : END SUBROUTINE setup_acid_hydronium_colvars
1148 :
1149 : ! **************************************************************************************************
1150 : !> \brief Gives back the size of an array of integer. If not associated gives back 1
1151 : !> \param colvar ...
1152 : !> \param i ...
1153 : !> \return ...
1154 : !> \author Teodoro Laino - 03.2007
1155 : ! **************************************************************************************************
1156 12594 : FUNCTION colv_size(colvar, i) RESULT(my_size)
1157 : TYPE(colvar_type), INTENT(IN) :: colvar
1158 : INTEGER :: i, my_size
1159 :
1160 12594 : my_size = 1
1161 12594 : IF (ASSOCIATED(colvar%points)) THEN
1162 266 : IF (ASSOCIATED(colvar%points(i)%atoms)) THEN
1163 256 : my_size = SIZE(colvar%points(i)%atoms)
1164 : ELSE
1165 : my_size = 0
1166 : END IF
1167 : END IF
1168 12594 : END FUNCTION colv_size
1169 :
1170 : ! **************************************************************************************************
1171 : !> \brief releases the memory that might have been allocated by the colvar
1172 : !> \param colvar the colvar to deallocate
1173 : !> \author alessandro laio and fawzi mohamed
1174 : ! **************************************************************************************************
1175 5664 : RECURSIVE SUBROUTINE colvar_release(colvar)
1176 : TYPE(colvar_type), POINTER :: colvar
1177 :
1178 : INTEGER :: i
1179 :
1180 5664 : CPASSERT(ASSOCIATED(colvar))
1181 5664 : IF (ASSOCIATED(colvar%dsdr)) THEN
1182 5664 : DEALLOCATE (colvar%dsdr)
1183 : END IF
1184 5664 : IF (ASSOCIATED(colvar%i_atom)) THEN
1185 5664 : DEALLOCATE (colvar%i_atom)
1186 : END IF
1187 5664 : IF (ASSOCIATED(colvar%points)) THEN
1188 366 : DO i = 1, SIZE(colvar%points)
1189 266 : IF (ASSOCIATED(colvar%points(i)%atoms)) THEN
1190 256 : DEALLOCATE (colvar%points(i)%atoms)
1191 : END IF
1192 366 : IF (ASSOCIATED(colvar%points(i)%weights)) THEN
1193 256 : DEALLOCATE (colvar%points(i)%weights)
1194 : END IF
1195 : END DO
1196 100 : DEALLOCATE (colvar%points)
1197 : END IF
1198 10662 : SELECT CASE (colvar%type_id)
1199 : CASE (dist_colvar_id)
1200 4998 : DEALLOCATE (colvar%dist_param)
1201 : CASE (coord_colvar_id)
1202 58 : IF (ASSOCIATED(colvar%coord_param%i_at_from)) THEN
1203 58 : DEALLOCATE (colvar%coord_param%i_at_from)
1204 : END IF
1205 58 : IF (ASSOCIATED(colvar%coord_param%i_at_to)) THEN
1206 58 : DEALLOCATE (colvar%coord_param%i_at_to)
1207 : END IF
1208 58 : IF (ASSOCIATED(colvar%coord_param%c_kinds_from)) THEN
1209 6 : DEALLOCATE (colvar%coord_param%c_kinds_from)
1210 : END IF
1211 58 : IF (ASSOCIATED(colvar%coord_param%c_kinds_to)) THEN
1212 6 : DEALLOCATE (colvar%coord_param%c_kinds_to)
1213 : END IF
1214 58 : IF (ASSOCIATED(colvar%coord_param%i_at_to_b)) THEN
1215 4 : DEALLOCATE (colvar%coord_param%i_at_to_b)
1216 : END IF
1217 58 : IF (ASSOCIATED(colvar%coord_param%c_kinds_to_b)) THEN
1218 2 : DEALLOCATE (colvar%coord_param%c_kinds_to_b)
1219 : END IF
1220 58 : DEALLOCATE (colvar%coord_param)
1221 : CASE (population_colvar_id)
1222 8 : IF (ASSOCIATED(colvar%population_param%i_at_from)) THEN
1223 8 : DEALLOCATE (colvar%population_param%i_at_from)
1224 : END IF
1225 8 : IF (ASSOCIATED(colvar%population_param%i_at_to)) THEN
1226 8 : DEALLOCATE (colvar%population_param%i_at_to)
1227 : END IF
1228 8 : IF (ASSOCIATED(colvar%population_param%c_kinds_from)) THEN
1229 0 : DEALLOCATE (colvar%population_param%c_kinds_from)
1230 : END IF
1231 8 : IF (ASSOCIATED(colvar%population_param%c_kinds_to)) THEN
1232 8 : DEALLOCATE (colvar%population_param%c_kinds_to)
1233 : END IF
1234 8 : DEALLOCATE (colvar%population_param)
1235 : CASE (gyration_colvar_id)
1236 2 : IF (ASSOCIATED(colvar%gyration_param%i_at)) THEN
1237 2 : DEALLOCATE (colvar%gyration_param%i_at)
1238 : END IF
1239 2 : IF (ASSOCIATED(colvar%gyration_param%c_kinds)) THEN
1240 2 : DEALLOCATE (colvar%gyration_param%c_kinds)
1241 : END IF
1242 2 : DEALLOCATE (colvar%gyration_param)
1243 : CASE (angle_colvar_id)
1244 220 : DEALLOCATE (colvar%angle_param)
1245 : CASE (torsion_colvar_id)
1246 160 : DEALLOCATE (colvar%torsion_param)
1247 : CASE (plane_distance_colvar_id)
1248 28 : DEALLOCATE (colvar%plane_distance_param)
1249 : CASE (plane_plane_angle_colvar_id)
1250 16 : DEALLOCATE (colvar%plane_plane_angle_param)
1251 : CASE (dfunct_colvar_id)
1252 18 : DEALLOCATE (colvar%dfunct_param)
1253 : CASE (rotation_colvar_id)
1254 2 : DEALLOCATE (colvar%rotation_param)
1255 : CASE (qparm_colvar_id)
1256 2 : DEALLOCATE (colvar%qparm_param%i_at_from)
1257 2 : DEALLOCATE (colvar%qparm_param%i_at_to)
1258 2 : DEALLOCATE (colvar%qparm_param)
1259 : CASE (xyz_diag_colvar_id)
1260 30 : DEALLOCATE (colvar%xyz_diag_param)
1261 : CASE (xyz_outerdiag_colvar_id)
1262 30 : DEALLOCATE (colvar%xyz_outerdiag_param)
1263 : CASE (u_colvar_id)
1264 6 : NULLIFY (colvar%u_param%mixed_energy_section)
1265 6 : DEALLOCATE (colvar%u_param)
1266 : CASE (hydronium_shell_colvar_id)
1267 2 : DEALLOCATE (colvar%hydronium_shell_param%i_oxygens)
1268 2 : DEALLOCATE (colvar%hydronium_shell_param%i_hydrogens)
1269 2 : DEALLOCATE (colvar%hydronium_shell_param)
1270 : CASE (hydronium_dist_colvar_id)
1271 2 : DEALLOCATE (colvar%hydronium_dist_param%i_oxygens)
1272 2 : DEALLOCATE (colvar%hydronium_dist_param%i_hydrogens)
1273 2 : DEALLOCATE (colvar%hydronium_dist_param)
1274 : CASE (acid_hyd_dist_colvar_id)
1275 2 : DEALLOCATE (colvar%acid_hyd_dist_param%i_oxygens_water)
1276 2 : DEALLOCATE (colvar%acid_hyd_dist_param%i_oxygens_acid)
1277 2 : DEALLOCATE (colvar%acid_hyd_dist_param%i_hydrogens)
1278 2 : DEALLOCATE (colvar%acid_hyd_dist_param)
1279 : CASE (acid_hyd_shell_colvar_id)
1280 2 : DEALLOCATE (colvar%acid_hyd_shell_param%i_oxygens_water)
1281 2 : DEALLOCATE (colvar%acid_hyd_shell_param%i_oxygens_acid)
1282 2 : DEALLOCATE (colvar%acid_hyd_shell_param%i_hydrogens)
1283 2 : DEALLOCATE (colvar%acid_hyd_shell_param)
1284 : CASE (reaction_path_colvar_id, distance_from_path_colvar_id)
1285 24 : IF (colvar%reaction_path_param%dist_rmsd .OR. colvar%reaction_path_param%rmsd) THEN
1286 8 : DEALLOCATE (colvar%reaction_path_param%r_ref)
1287 8 : DEALLOCATE (colvar%reaction_path_param%i_rmsd)
1288 : ELSE
1289 48 : DO i = 1, SIZE(colvar%reaction_path_param%colvar_p)
1290 48 : CALL colvar_release(colvar%reaction_path_param%colvar_p(i)%colvar)
1291 : END DO
1292 16 : DEALLOCATE (colvar%reaction_path_param%colvar_p)
1293 16 : DEALLOCATE (colvar%reaction_path_param%f_vals)
1294 : END IF
1295 24 : DEALLOCATE (colvar%reaction_path_param)
1296 : CASE (combine_colvar_id)
1297 48 : DO i = 1, SIZE(colvar%combine_cvs_param%colvar_p)
1298 48 : CALL colvar_release(colvar%combine_cvs_param%colvar_p(i)%colvar)
1299 : END DO
1300 16 : DEALLOCATE (colvar%combine_cvs_param%colvar_p)
1301 16 : DEALLOCATE (colvar%combine_cvs_param%c_parameters)
1302 16 : DEALLOCATE (colvar%combine_cvs_param%v_parameters)
1303 16 : DEALLOCATE (colvar%combine_cvs_param%variables)
1304 16 : DEALLOCATE (colvar%combine_cvs_param)
1305 : CASE (rmsd_colvar_id)
1306 4 : DEALLOCATE (colvar%rmsd_param%weights)
1307 4 : DEALLOCATE (colvar%rmsd_param%r_ref)
1308 4 : DEALLOCATE (colvar%rmsd_param%i_rmsd)
1309 4 : DEALLOCATE (colvar%rmsd_param)
1310 : CASE (Wc_colvar_id)
1311 0 : DEALLOCATE (colvar%Wc)
1312 : CASE (HBP_colvar_id)
1313 2 : DEALLOCATE (colvar%HBP%ewc)
1314 2 : DEALLOCATE (colvar%HBP%ids)
1315 2 : DEALLOCATE (colvar%HBP)
1316 : CASE (ring_puckering_colvar_id)
1317 32 : DEALLOCATE (colvar%ring_puckering_param%atoms)
1318 32 : DEALLOCATE (colvar%ring_puckering_param)
1319 : CASE (mindist_colvar_id)
1320 0 : IF (ASSOCIATED(colvar%mindist_param%i_dist_from)) THEN
1321 0 : DEALLOCATE (colvar%mindist_param%i_dist_from)
1322 : END IF
1323 0 : IF (ASSOCIATED(colvar%mindist_param%i_coord_from)) THEN
1324 0 : DEALLOCATE (colvar%mindist_param%i_coord_from)
1325 : END IF
1326 0 : IF (ASSOCIATED(colvar%mindist_param%i_coord_to)) THEN
1327 0 : DEALLOCATE (colvar%mindist_param%i_coord_to)
1328 : END IF
1329 0 : IF (ASSOCIATED(colvar%mindist_param%k_coord_from)) THEN
1330 0 : DEALLOCATE (colvar%mindist_param%k_coord_from)
1331 : END IF
1332 0 : IF (ASSOCIATED(colvar%mindist_param%k_coord_to)) THEN
1333 0 : DEALLOCATE (colvar%mindist_param%k_coord_to)
1334 : END IF
1335 0 : DEALLOCATE (colvar%mindist_param)
1336 : CASE (no_colvar_id)
1337 : ! Do nothing
1338 : CASE default
1339 5664 : CPABORT("")
1340 : END SELECT
1341 5664 : DEALLOCATE (colvar)
1342 :
1343 5664 : END SUBROUTINE colvar_release
1344 :
1345 : ! **************************************************************************************************
1346 : !> \brief Clone a colvar type
1347 : !> \param colvar_out ...
1348 : !> \param colvar_in the colvar to deallocate
1349 : !> \param i_atom_offset ...
1350 : !> \author Teodoro Laino [tlaino] 04.2006
1351 : ! **************************************************************************************************
1352 4986 : RECURSIVE SUBROUTINE colvar_clone(colvar_out, colvar_in, i_atom_offset)
1353 : TYPE(colvar_type), INTENT(INOUT), POINTER :: colvar_out
1354 : TYPE(colvar_type), INTENT(IN) :: colvar_in
1355 : INTEGER, INTENT(IN), OPTIONAL :: i_atom_offset
1356 :
1357 : INTEGER :: i, my_offset, ndim, ndim2, stat
1358 :
1359 4986 : my_offset = 0
1360 4986 : IF (PRESENT(i_atom_offset)) my_offset = i_atom_offset
1361 4986 : CALL colvar_create(colvar_out, colvar_in%type_id)
1362 4986 : CALL colvar_clone_points(colvar_out, colvar_in, my_offset)
1363 4986 : IF (colvar_in%use_points) my_offset = 0
1364 9598 : SELECT CASE (colvar_out%type_id)
1365 : CASE (dist_colvar_id)
1366 4612 : colvar_out%dist_param%i_at = colvar_in%dist_param%i_at + my_offset
1367 4612 : colvar_out%dist_param%j_at = colvar_in%dist_param%j_at + my_offset
1368 4612 : colvar_out%dist_param%axis_id = colvar_in%dist_param%axis_id
1369 4612 : colvar_out%dist_param%sign_d = colvar_in%dist_param%sign_d
1370 : CASE (coord_colvar_id)
1371 6 : colvar_out%coord_param%n_atoms_to = colvar_in%coord_param%n_atoms_to
1372 6 : colvar_out%coord_param%n_atoms_to_b = colvar_in%coord_param%n_atoms_to_b
1373 6 : colvar_out%coord_param%n_atoms_from = colvar_in%coord_param%n_atoms_from
1374 6 : colvar_out%coord_param%nncrd = colvar_in%coord_param%nncrd
1375 6 : colvar_out%coord_param%ndcrd = colvar_in%coord_param%ndcrd
1376 6 : colvar_out%coord_param%r_0 = colvar_in%coord_param%r_0
1377 6 : colvar_out%coord_param%nncrd_b = colvar_in%coord_param%nncrd_b
1378 6 : colvar_out%coord_param%ndcrd_b = colvar_in%coord_param%ndcrd_b
1379 6 : colvar_out%coord_param%r_0_b = colvar_in%coord_param%r_0_b
1380 6 : colvar_out%coord_param%use_kinds_from = colvar_in%coord_param%use_kinds_from
1381 6 : colvar_out%coord_param%use_kinds_to = colvar_in%coord_param%use_kinds_to
1382 6 : colvar_out%coord_param%use_kinds_to_b = colvar_in%coord_param%use_kinds_to_b
1383 6 : IF (colvar_in%coord_param%use_kinds_from) THEN
1384 : ! KINDS
1385 0 : ndim = SIZE(colvar_in%coord_param%c_kinds_from)
1386 0 : ALLOCATE (colvar_out%coord_param%c_kinds_from(ndim))
1387 0 : colvar_out%coord_param%c_kinds_from = colvar_in%coord_param%c_kinds_from
1388 : ELSE
1389 : ! INDEX
1390 6 : ndim = SIZE(colvar_in%coord_param%i_at_from)
1391 18 : ALLOCATE (colvar_out%coord_param%i_at_from(ndim))
1392 12 : colvar_out%coord_param%i_at_from = colvar_in%coord_param%i_at_from + my_offset
1393 : END IF
1394 6 : IF (colvar_in%coord_param%use_kinds_to) THEN
1395 : ! KINDS
1396 0 : ndim = SIZE(colvar_in%coord_param%c_kinds_to)
1397 0 : ALLOCATE (colvar_out%coord_param%c_kinds_to(ndim))
1398 0 : colvar_out%coord_param%c_kinds_to = colvar_in%coord_param%c_kinds_to
1399 : ELSE
1400 : ! INDEX
1401 6 : ndim = SIZE(colvar_in%coord_param%i_at_to)
1402 18 : ALLOCATE (colvar_out%coord_param%i_at_to(ndim))
1403 18 : colvar_out%coord_param%i_at_to = colvar_in%coord_param%i_at_to + my_offset
1404 : END IF
1405 6 : IF (colvar_in%coord_param%use_kinds_to_b) THEN
1406 : ! KINDS
1407 0 : ndim = SIZE(colvar_in%coord_param%c_kinds_to_b)
1408 0 : ALLOCATE (colvar_out%coord_param%c_kinds_to_b(ndim))
1409 0 : colvar_out%coord_param%c_kinds_to_b = colvar_in%coord_param%c_kinds_to_b
1410 6 : ELSEIF (ASSOCIATED(colvar_in%coord_param%i_at_to_b)) THEN
1411 : ! INDEX
1412 0 : ndim = SIZE(colvar_in%coord_param%i_at_to_b)
1413 0 : ALLOCATE (colvar_out%coord_param%i_at_to_b(ndim))
1414 0 : colvar_out%coord_param%i_at_to_b = colvar_in%coord_param%i_at_to_b + my_offset
1415 : END IF
1416 :
1417 : CASE (population_colvar_id)
1418 0 : colvar_out%population_param%n_atoms_to = colvar_in%population_param%n_atoms_to
1419 0 : colvar_out%population_param%n_atoms_from = colvar_in%population_param%n_atoms_from
1420 0 : colvar_out%population_param%nncrd = colvar_in%population_param%nncrd
1421 0 : colvar_out%population_param%ndcrd = colvar_in%population_param%ndcrd
1422 0 : colvar_out%population_param%r_0 = colvar_in%population_param%r_0
1423 0 : colvar_out%population_param%use_kinds_from = colvar_in%population_param%use_kinds_from
1424 0 : colvar_out%population_param%use_kinds_to = colvar_in%population_param%use_kinds_to
1425 0 : IF (colvar_in%population_param%use_kinds_from) THEN
1426 : ! KINDS
1427 0 : ndim = SIZE(colvar_in%population_param%c_kinds_from)
1428 0 : ALLOCATE (colvar_out%population_param%c_kinds_from(ndim))
1429 0 : colvar_out%population_param%c_kinds_from = colvar_in%population_param%c_kinds_from
1430 : ELSE
1431 : ! INDEX
1432 0 : ndim = SIZE(colvar_in%population_param%i_at_from)
1433 0 : ALLOCATE (colvar_out%population_param%i_at_from(ndim))
1434 0 : colvar_out%population_param%i_at_from = colvar_in%population_param%i_at_from + my_offset
1435 : END IF
1436 0 : IF (colvar_in%population_param%use_kinds_to) THEN
1437 : ! KINDS
1438 0 : ndim = SIZE(colvar_in%population_param%c_kinds_to)
1439 0 : ALLOCATE (colvar_out%population_param%c_kinds_to(ndim))
1440 0 : colvar_out%population_param%c_kinds_to = colvar_in%population_param%c_kinds_to
1441 : ELSE
1442 : ! INDEX
1443 0 : ndim = SIZE(colvar_in%population_param%i_at_to)
1444 0 : ALLOCATE (colvar_out%population_param%i_at_to(ndim))
1445 0 : colvar_out%population_param%i_at_to = colvar_in%population_param%i_at_to + my_offset
1446 : END IF
1447 :
1448 : CASE (gyration_colvar_id)
1449 0 : colvar_out%gyration_param%n_atoms = colvar_in%gyration_param%n_atoms
1450 0 : colvar_out%gyration_param%use_kinds = colvar_in%gyration_param%use_kinds
1451 0 : IF (colvar_in%gyration_param%use_kinds) THEN
1452 : ! KINDS
1453 0 : ndim = SIZE(colvar_in%gyration_param%c_kinds)
1454 0 : ALLOCATE (colvar_out%gyration_param%c_kinds(ndim))
1455 0 : colvar_out%gyration_param%c_kinds = colvar_in%gyration_param%c_kinds
1456 : ELSE
1457 : ! INDEX
1458 0 : ndim = SIZE(colvar_in%gyration_param%i_at)
1459 0 : ALLOCATE (colvar_out%gyration_param%i_at(ndim))
1460 0 : colvar_out%gyration_param%i_at = colvar_in%gyration_param%i_at + my_offset
1461 : END IF
1462 : CASE (angle_colvar_id)
1463 672 : colvar_out%angle_param%i_at_angle = colvar_in%angle_param%i_at_angle + my_offset
1464 : CASE (torsion_colvar_id)
1465 570 : colvar_out%torsion_param%i_at_tors = colvar_in%torsion_param%i_at_tors + my_offset
1466 114 : colvar_out%torsion_param%o0 = colvar_in%torsion_param%o0
1467 : CASE (plane_distance_colvar_id)
1468 0 : colvar_out%plane_distance_param%use_pbc = colvar_in%plane_distance_param%use_pbc
1469 0 : colvar_out%plane_distance_param%plane = colvar_in%plane_distance_param%plane + my_offset
1470 0 : colvar_out%plane_distance_param%point = colvar_in%plane_distance_param%point + my_offset
1471 : CASE (plane_plane_angle_colvar_id)
1472 12 : colvar_out%plane_plane_angle_param%plane1%type_of_def = colvar_in%plane_plane_angle_param%plane1%type_of_def
1473 12 : IF (colvar_out%plane_plane_angle_param%plane1%type_of_def == plane_def_vec) THEN
1474 0 : colvar_out%plane_plane_angle_param%plane1%normal_vec = colvar_in%plane_plane_angle_param%plane1%normal_vec
1475 : ELSE
1476 48 : colvar_out%plane_plane_angle_param%plane1%points = colvar_in%plane_plane_angle_param%plane1%points + my_offset
1477 : END IF
1478 :
1479 12 : colvar_out%plane_plane_angle_param%plane2%type_of_def = colvar_in%plane_plane_angle_param%plane2%type_of_def
1480 12 : IF (colvar_out%plane_plane_angle_param%plane2%type_of_def == plane_def_vec) THEN
1481 24 : colvar_out%plane_plane_angle_param%plane2%normal_vec = colvar_in%plane_plane_angle_param%plane2%normal_vec
1482 : ELSE
1483 24 : colvar_out%plane_plane_angle_param%plane2%points = colvar_in%plane_plane_angle_param%plane2%points + my_offset
1484 : END IF
1485 : CASE (rotation_colvar_id)
1486 0 : colvar_out%rotation_param%i_at1_bond1 = colvar_in%rotation_param%i_at1_bond1 + my_offset
1487 0 : colvar_out%rotation_param%i_at2_bond1 = colvar_in%rotation_param%i_at2_bond1 + my_offset
1488 0 : colvar_out%rotation_param%i_at1_bond2 = colvar_in%rotation_param%i_at1_bond2 + my_offset
1489 0 : colvar_out%rotation_param%i_at2_bond2 = colvar_in%rotation_param%i_at2_bond2 + my_offset
1490 : CASE (dfunct_colvar_id)
1491 60 : colvar_out%dfunct_param%i_at_dfunct = colvar_in%dfunct_param%i_at_dfunct + my_offset
1492 12 : colvar_out%dfunct_param%coeff = colvar_in%dfunct_param%coeff
1493 12 : colvar_out%dfunct_param%use_pbc = colvar_in%dfunct_param%use_pbc
1494 : CASE (qparm_colvar_id)
1495 0 : colvar_out%qparm_param%n_atoms_to = colvar_in%qparm_param%n_atoms_to
1496 0 : colvar_out%qparm_param%n_atoms_from = colvar_in%qparm_param%n_atoms_from
1497 0 : colvar_out%qparm_param%rcut = colvar_in%qparm_param%rcut
1498 0 : colvar_out%qparm_param%l = colvar_in%qparm_param%l
1499 0 : colvar_out%qparm_param%rstart = colvar_in%qparm_param%rstart
1500 0 : colvar_out%qparm_param%include_images = colvar_in%qparm_param%include_images
1501 0 : ndim = SIZE(colvar_in%qparm_param%i_at_from)
1502 0 : ALLOCATE (colvar_out%qparm_param%i_at_from(ndim))
1503 0 : ndim = SIZE(colvar_in%qparm_param%i_at_to)
1504 0 : ALLOCATE (colvar_out%qparm_param%i_at_to(ndim))
1505 0 : colvar_out%qparm_param%i_at_from = colvar_in%qparm_param%i_at_from + my_offset
1506 0 : colvar_out%qparm_param%i_at_to = colvar_in%qparm_param%i_at_from + my_offset
1507 : CASE (xyz_diag_colvar_id)
1508 24 : colvar_out%xyz_diag_param%i_atom = colvar_in%xyz_diag_param%i_atom + my_offset
1509 24 : colvar_out%xyz_diag_param%component = colvar_in%xyz_diag_param%component
1510 96 : colvar_out%xyz_diag_param%r0 = colvar_in%xyz_diag_param%r0
1511 24 : colvar_out%xyz_diag_param%use_pbc = colvar_in%xyz_diag_param%use_pbc
1512 24 : colvar_out%xyz_diag_param%use_absolute_position = colvar_in%xyz_diag_param%use_absolute_position
1513 : CASE (xyz_outerdiag_colvar_id)
1514 72 : colvar_out%xyz_outerdiag_param%i_atoms = colvar_in%xyz_outerdiag_param%i_atoms + my_offset
1515 72 : colvar_out%xyz_outerdiag_param%components = colvar_in%xyz_outerdiag_param%components
1516 216 : colvar_out%xyz_outerdiag_param%r0 = colvar_in%xyz_outerdiag_param%r0
1517 24 : colvar_out%xyz_outerdiag_param%use_pbc = colvar_in%xyz_outerdiag_param%use_pbc
1518 : CASE (u_colvar_id)
1519 0 : colvar_out%u_param%natom = colvar_in%u_param%natom
1520 : CASE (hydronium_shell_colvar_id)
1521 0 : colvar_out%hydronium_shell_param%n_hydrogens = colvar_in%hydronium_shell_param%n_hydrogens
1522 0 : colvar_out%hydronium_shell_param%n_oxygens = colvar_in%hydronium_shell_param%n_oxygens
1523 0 : colvar_out%hydronium_shell_param%nh = colvar_in%hydronium_shell_param%nh
1524 0 : colvar_out%hydronium_shell_param%poh = colvar_in%hydronium_shell_param%poh
1525 0 : colvar_out%hydronium_shell_param%poo = colvar_in%hydronium_shell_param%poo
1526 0 : colvar_out%hydronium_shell_param%qoh = colvar_in%hydronium_shell_param%qoh
1527 0 : colvar_out%hydronium_shell_param%qoo = colvar_in%hydronium_shell_param%qoo
1528 0 : colvar_out%hydronium_shell_param%pm = colvar_in%hydronium_shell_param%pm
1529 0 : colvar_out%hydronium_shell_param%qm = colvar_in%hydronium_shell_param%qm
1530 0 : colvar_out%hydronium_shell_param%roo = colvar_in%hydronium_shell_param%roo
1531 0 : colvar_out%hydronium_shell_param%roh = colvar_in%hydronium_shell_param%roh
1532 0 : colvar_out%hydronium_shell_param%lambda = colvar_in%hydronium_shell_param%lambda
1533 0 : ndim = SIZE(colvar_in%hydronium_shell_param%i_oxygens)
1534 0 : ALLOCATE (colvar_out%hydronium_shell_param%i_oxygens(ndim))
1535 0 : ndim = SIZE(colvar_in%hydronium_shell_param%i_hydrogens)
1536 0 : ALLOCATE (colvar_out%hydronium_shell_param%i_hydrogens(ndim))
1537 0 : colvar_out%hydronium_shell_param%i_oxygens = colvar_in%hydronium_shell_param%i_oxygens + my_offset
1538 0 : colvar_out%hydronium_shell_param%i_hydrogens = colvar_in%hydronium_shell_param%i_hydrogens + my_offset
1539 : CASE (hydronium_dist_colvar_id)
1540 0 : colvar_out%hydronium_dist_param%n_hydrogens = colvar_in%hydronium_dist_param%n_hydrogens
1541 0 : colvar_out%hydronium_dist_param%n_oxygens = colvar_in%hydronium_dist_param%n_oxygens
1542 0 : colvar_out%hydronium_dist_param%nh = colvar_in%hydronium_dist_param%nh
1543 0 : colvar_out%hydronium_dist_param%nn = colvar_in%hydronium_dist_param%nn
1544 0 : colvar_out%hydronium_dist_param%poh = colvar_in%hydronium_dist_param%poh
1545 0 : colvar_out%hydronium_dist_param%qoh = colvar_in%hydronium_dist_param%qoh
1546 0 : colvar_out%hydronium_dist_param%pf = colvar_in%hydronium_dist_param%pf
1547 0 : colvar_out%hydronium_dist_param%qf = colvar_in%hydronium_dist_param%qf
1548 0 : colvar_out%hydronium_dist_param%pm = colvar_in%hydronium_dist_param%pm
1549 0 : colvar_out%hydronium_dist_param%qm = colvar_in%hydronium_dist_param%qm
1550 0 : colvar_out%hydronium_dist_param%roh = colvar_in%hydronium_dist_param%roh
1551 0 : colvar_out%hydronium_dist_param%lambda = colvar_in%hydronium_dist_param%lambda
1552 0 : ndim = SIZE(colvar_in%hydronium_dist_param%i_oxygens)
1553 0 : ALLOCATE (colvar_out%hydronium_dist_param%i_oxygens(ndim))
1554 0 : ndim = SIZE(colvar_in%hydronium_dist_param%i_hydrogens)
1555 0 : ALLOCATE (colvar_out%hydronium_dist_param%i_hydrogens(ndim))
1556 0 : colvar_out%hydronium_dist_param%i_oxygens = colvar_in%hydronium_dist_param%i_oxygens + my_offset
1557 0 : colvar_out%hydronium_dist_param%i_hydrogens = colvar_in%hydronium_dist_param%i_hydrogens + my_offset
1558 : CASE (acid_hyd_dist_colvar_id)
1559 0 : colvar_out%acid_hyd_dist_param%n_hydrogens = colvar_in%acid_hyd_dist_param%n_hydrogens
1560 0 : colvar_out%acid_hyd_dist_param%n_oxygens_water = colvar_in%acid_hyd_dist_param%n_oxygens_water
1561 0 : colvar_out%acid_hyd_dist_param%n_oxygens_acid = colvar_in%acid_hyd_dist_param%n_oxygens_acid
1562 0 : colvar_out%acid_hyd_dist_param%nc = colvar_in%acid_hyd_dist_param%nc
1563 0 : colvar_out%acid_hyd_dist_param%pwoh = colvar_in%acid_hyd_dist_param%pwoh
1564 0 : colvar_out%acid_hyd_dist_param%qwoh = colvar_in%acid_hyd_dist_param%qwoh
1565 0 : colvar_out%acid_hyd_dist_param%paoh = colvar_in%acid_hyd_dist_param%paoh
1566 0 : colvar_out%acid_hyd_dist_param%qaoh = colvar_in%acid_hyd_dist_param%qaoh
1567 0 : colvar_out%acid_hyd_dist_param%pcut = colvar_in%acid_hyd_dist_param%pcut
1568 0 : colvar_out%acid_hyd_dist_param%qcut = colvar_in%acid_hyd_dist_param%qcut
1569 0 : colvar_out%acid_hyd_dist_param%rwoh = colvar_in%acid_hyd_dist_param%rwoh
1570 0 : colvar_out%acid_hyd_dist_param%raoh = colvar_in%acid_hyd_dist_param%raoh
1571 0 : colvar_out%acid_hyd_dist_param%lambda = colvar_in%acid_hyd_dist_param%lambda
1572 0 : ndim = SIZE(colvar_in%acid_hyd_dist_param%i_oxygens_water)
1573 0 : ALLOCATE (colvar_out%acid_hyd_dist_param%i_oxygens_water(ndim))
1574 0 : ndim = SIZE(colvar_in%acid_hyd_dist_param%i_oxygens_acid)
1575 0 : ALLOCATE (colvar_out%acid_hyd_dist_param%i_oxygens_acid(ndim))
1576 0 : ndim = SIZE(colvar_in%acid_hyd_dist_param%i_hydrogens)
1577 0 : ALLOCATE (colvar_out%acid_hyd_dist_param%i_hydrogens(ndim))
1578 0 : colvar_out%acid_hyd_dist_param%i_oxygens_water = colvar_in%acid_hyd_dist_param%i_oxygens_water + my_offset
1579 0 : colvar_out%acid_hyd_dist_param%i_oxygens_acid = colvar_in%acid_hyd_dist_param%i_oxygens_acid + my_offset
1580 0 : colvar_out%acid_hyd_dist_param%i_hydrogens = colvar_in%acid_hyd_dist_param%i_hydrogens + my_offset
1581 : CASE (acid_hyd_shell_colvar_id)
1582 0 : colvar_out%acid_hyd_shell_param%n_hydrogens = colvar_in%acid_hyd_shell_param%n_hydrogens
1583 0 : colvar_out%acid_hyd_shell_param%n_oxygens_water = colvar_in%acid_hyd_shell_param%n_oxygens_water
1584 0 : colvar_out%acid_hyd_shell_param%n_oxygens_acid = colvar_in%acid_hyd_shell_param%n_oxygens_acid
1585 0 : colvar_out%acid_hyd_shell_param%nc = colvar_in%acid_hyd_shell_param%nc
1586 0 : colvar_out%acid_hyd_shell_param%nh = colvar_in%acid_hyd_shell_param%nh
1587 0 : colvar_out%acid_hyd_shell_param%pwoh = colvar_in%acid_hyd_shell_param%pwoh
1588 0 : colvar_out%acid_hyd_shell_param%qwoh = colvar_in%acid_hyd_shell_param%qwoh
1589 0 : colvar_out%acid_hyd_shell_param%paoh = colvar_in%acid_hyd_shell_param%paoh
1590 0 : colvar_out%acid_hyd_shell_param%qaoh = colvar_in%acid_hyd_shell_param%qaoh
1591 0 : colvar_out%acid_hyd_shell_param%poo = colvar_in%acid_hyd_shell_param%poo
1592 0 : colvar_out%acid_hyd_shell_param%qoo = colvar_in%acid_hyd_shell_param%qoo
1593 0 : colvar_out%acid_hyd_shell_param%pm = colvar_in%acid_hyd_shell_param%pm
1594 0 : colvar_out%acid_hyd_shell_param%qm = colvar_in%acid_hyd_shell_param%qm
1595 0 : colvar_out%acid_hyd_shell_param%pcut = colvar_in%acid_hyd_shell_param%pcut
1596 0 : colvar_out%acid_hyd_shell_param%qcut = colvar_in%acid_hyd_shell_param%qcut
1597 0 : colvar_out%acid_hyd_shell_param%rwoh = colvar_in%acid_hyd_shell_param%rwoh
1598 0 : colvar_out%acid_hyd_shell_param%raoh = colvar_in%acid_hyd_shell_param%raoh
1599 0 : colvar_out%acid_hyd_shell_param%roo = colvar_in%acid_hyd_shell_param%roo
1600 0 : colvar_out%acid_hyd_shell_param%lambda = colvar_in%acid_hyd_shell_param%lambda
1601 0 : ndim = SIZE(colvar_in%acid_hyd_shell_param%i_oxygens_water)
1602 0 : ALLOCATE (colvar_out%acid_hyd_shell_param%i_oxygens_water(ndim))
1603 0 : ndim = SIZE(colvar_in%acid_hyd_shell_param%i_oxygens_acid)
1604 0 : ALLOCATE (colvar_out%acid_hyd_shell_param%i_oxygens_acid(ndim))
1605 0 : ndim = SIZE(colvar_in%acid_hyd_shell_param%i_hydrogens)
1606 0 : ALLOCATE (colvar_out%acid_hyd_shell_param%i_hydrogens(ndim))
1607 0 : colvar_out%acid_hyd_shell_param%i_oxygens_water = colvar_in%acid_hyd_shell_param%i_oxygens_water + my_offset
1608 0 : colvar_out%acid_hyd_shell_param%i_oxygens_acid = colvar_in%acid_hyd_shell_param%i_oxygens_acid + my_offset
1609 0 : colvar_out%acid_hyd_shell_param%i_hydrogens = colvar_in%acid_hyd_shell_param%i_hydrogens + my_offset
1610 : CASE (reaction_path_colvar_id, distance_from_path_colvar_id)
1611 6 : colvar_out%reaction_path_param%dist_rmsd = colvar_in%reaction_path_param%dist_rmsd
1612 6 : colvar_out%reaction_path_param%rmsd = colvar_in%reaction_path_param%rmsd
1613 6 : colvar_out%reaction_path_param%nr_frames = colvar_in%reaction_path_param%nr_frames
1614 6 : IF (colvar_in%reaction_path_param%dist_rmsd .OR. colvar_in%reaction_path_param%rmsd) THEN
1615 0 : colvar_out%reaction_path_param%align_frames = colvar_in%reaction_path_param%align_frames
1616 0 : colvar_out%reaction_path_param%subset = colvar_in%reaction_path_param%subset
1617 0 : ndim = SIZE(colvar_in%reaction_path_param%i_rmsd)
1618 0 : ALLOCATE (colvar_out%reaction_path_param%i_rmsd(ndim), stat=stat)
1619 0 : colvar_out%reaction_path_param%i_rmsd = colvar_in%reaction_path_param%i_rmsd
1620 0 : ndim = SIZE(colvar_in%reaction_path_param%r_ref, 1)
1621 0 : ndim2 = SIZE(colvar_in%reaction_path_param%r_ref, 2)
1622 0 : ALLOCATE (colvar_out%reaction_path_param%r_ref(ndim, ndim2), stat=stat)
1623 0 : colvar_out%reaction_path_param%r_ref = colvar_in%reaction_path_param%r_ref
1624 : ELSE
1625 6 : ndim = SIZE(colvar_in%reaction_path_param%colvar_p)
1626 30 : ALLOCATE (colvar_out%reaction_path_param%colvar_p(ndim))
1627 18 : DO i = 1, ndim
1628 : CALL colvar_clone(colvar_out%reaction_path_param%colvar_p(i)%colvar, &
1629 : colvar_in%reaction_path_param%colvar_p(i)%colvar, &
1630 18 : my_offset)
1631 : END DO
1632 18 : colvar_out%reaction_path_param%function_bounds = colvar_in%reaction_path_param%function_bounds
1633 6 : ndim = SIZE(colvar_in%reaction_path_param%f_vals, 1)
1634 6 : ndim2 = SIZE(colvar_in%reaction_path_param%f_vals, 2)
1635 24 : ALLOCATE (colvar_out%reaction_path_param%f_vals(ndim, ndim2))
1636 70224 : colvar_out%reaction_path_param%f_vals = colvar_in%reaction_path_param%f_vals
1637 : END IF
1638 6 : colvar_out%reaction_path_param%step_size = colvar_in%reaction_path_param%step_size
1639 6 : colvar_out%reaction_path_param%n_components = colvar_in%reaction_path_param%n_components
1640 6 : colvar_out%reaction_path_param%lambda = colvar_in%reaction_path_param%lambda
1641 : CASE (combine_colvar_id)
1642 8 : ndim = SIZE(colvar_in%combine_cvs_param%colvar_p)
1643 40 : ALLOCATE (colvar_out%combine_cvs_param%colvar_p(ndim))
1644 24 : DO i = 1, ndim
1645 : CALL colvar_clone(colvar_out%combine_cvs_param%colvar_p(i)%colvar, &
1646 : colvar_in%combine_cvs_param%colvar_p(i)%colvar, &
1647 24 : my_offset)
1648 : END DO
1649 8 : colvar_out%combine_cvs_param%lerr = colvar_in%combine_cvs_param%lerr
1650 8 : colvar_out%combine_cvs_param%dx = colvar_in%combine_cvs_param%dx
1651 8 : colvar_out%combine_cvs_param%function = colvar_in%combine_cvs_param%function
1652 : !
1653 8 : ndim = SIZE(colvar_in%combine_cvs_param%c_parameters)
1654 24 : ALLOCATE (colvar_out%combine_cvs_param%c_parameters(ndim))
1655 16 : colvar_out%combine_cvs_param%c_parameters = colvar_in%combine_cvs_param%c_parameters
1656 : !
1657 8 : ndim = SIZE(colvar_in%combine_cvs_param%v_parameters)
1658 24 : ALLOCATE (colvar_out%combine_cvs_param%v_parameters(ndim))
1659 16 : colvar_out%combine_cvs_param%v_parameters = colvar_in%combine_cvs_param%v_parameters
1660 : !
1661 8 : ndim = SIZE(colvar_in%combine_cvs_param%variables)
1662 24 : ALLOCATE (colvar_out%combine_cvs_param%variables(ndim))
1663 24 : colvar_out%combine_cvs_param%variables = colvar_in%combine_cvs_param%variables
1664 : CASE (rmsd_colvar_id)
1665 0 : colvar_out%rmsd_param%n_atoms = colvar_in%rmsd_param%n_atoms
1666 0 : colvar_out%rmsd_param%align_frames = colvar_in%rmsd_param%align_frames
1667 0 : colvar_out%rmsd_param%nr_frames = colvar_in%rmsd_param%nr_frames
1668 0 : colvar_out%rmsd_param%subset = colvar_in%rmsd_param%subset
1669 : ! INDEX
1670 0 : ndim = SIZE(colvar_in%rmsd_param%i_rmsd)
1671 0 : ALLOCATE (colvar_out%rmsd_param%i_rmsd(ndim))
1672 0 : colvar_out%rmsd_param%i_rmsd = colvar_in%rmsd_param%i_rmsd + my_offset
1673 : ! A and Bconfigurations and weights
1674 0 : ndim = SIZE(colvar_in%rmsd_param%weights)
1675 0 : ALLOCATE (colvar_out%rmsd_param%weights(ndim))
1676 0 : colvar_out%rmsd_param%weights = colvar_in%rmsd_param%weights
1677 0 : ndim = SIZE(colvar_in%rmsd_param%r_ref, 1)
1678 0 : ndim2 = SIZE(colvar_in%rmsd_param%r_ref, 2)
1679 0 : ALLOCATE (colvar_out%rmsd_param%r_ref(ndim, ndim2))
1680 0 : colvar_out%rmsd_param%r_ref = colvar_in%rmsd_param%r_ref
1681 : CASE (Wc_colvar_id)
1682 0 : colvar_out%Wc%ids = colvar_in%Wc%ids + my_offset
1683 0 : colvar_out%Wc%rcut = colvar_in%Wc%rcut
1684 : CASE (HBP_colvar_id)
1685 0 : ndim = colvar_out%HBP%nPoints
1686 0 : ALLOCATE (colvar_out%HBP%ids(ndim, 3))
1687 0 : ALLOCATE (colvar_out%HBP%ewc(ndim))
1688 0 : colvar_out%HBP%ids = colvar_in%HBP%ids + my_offset
1689 0 : colvar_out%HBP%ewc = colvar_in%HBP%ewc + my_offset
1690 0 : colvar_out%HBP%nPoints = colvar_in%HBP%nPoints
1691 0 : colvar_out%HBP%rcut = colvar_in%HBP%rcut
1692 0 : colvar_out%HBP%shift = colvar_in%HBP%shift
1693 : CASE (ring_puckering_colvar_id)
1694 0 : ndim = colvar_in%ring_puckering_param%nring
1695 0 : colvar_out%ring_puckering_param%nring = colvar_in%ring_puckering_param%nring
1696 0 : colvar_out%ring_puckering_param%iq = colvar_in%ring_puckering_param%iq
1697 0 : ALLOCATE (colvar_out%ring_puckering_param%atoms(ndim))
1698 0 : colvar_out%ring_puckering_param%atoms = colvar_in%ring_puckering_param%atoms + my_offset
1699 : CASE (mindist_colvar_id)
1700 0 : colvar_out%mindist_param%n_dist_from = colvar_in%mindist_param%n_dist_from
1701 0 : colvar_out%mindist_param%n_coord_to = colvar_in%mindist_param%n_coord_to
1702 0 : colvar_out%mindist_param%n_coord_from = colvar_in%mindist_param%n_coord_from
1703 0 : colvar_out%mindist_param%p_exp = colvar_in%mindist_param%p_exp
1704 0 : colvar_out%mindist_param%q_exp = colvar_in%mindist_param%q_exp
1705 0 : colvar_out%mindist_param%r_cut = colvar_in%mindist_param%r_cut
1706 0 : colvar_out%mindist_param%lambda = colvar_in%mindist_param%lambda
1707 0 : colvar_out%mindist_param%use_kinds_from = colvar_in%mindist_param%use_kinds_from
1708 0 : colvar_out%mindist_param%use_kinds_to = colvar_in%mindist_param%use_kinds_to
1709 : ! INDEX
1710 0 : ndim = SIZE(colvar_in%mindist_param%i_dist_from)
1711 0 : ALLOCATE (colvar_out%mindist_param%i_dist_from(ndim))
1712 0 : colvar_out%mindist_param%i_dist_from = colvar_in%mindist_param%i_dist_from + my_offset
1713 0 : IF (colvar_in%mindist_param%use_kinds_from) THEN
1714 : ! KINDS
1715 0 : ndim = SIZE(colvar_in%mindist_param%k_coord_from)
1716 0 : ALLOCATE (colvar_out%mindist_param%k_coord_from(ndim))
1717 0 : colvar_out%mindist_param%k_coord_from = colvar_in%mindist_param%k_coord_from
1718 : ELSE
1719 : ! INDEX
1720 0 : ndim = SIZE(colvar_in%mindist_param%i_coord_from)
1721 0 : ALLOCATE (colvar_out%mindist_param%i_coord_from(ndim))
1722 0 : colvar_out%mindist_param%i_coord_from = colvar_in%mindist_param%i_coord_from + my_offset
1723 : END IF
1724 4986 : IF (colvar_in%mindist_param%use_kinds_to) THEN
1725 : ! KINDS
1726 0 : ndim = SIZE(colvar_in%mindist_param%k_coord_to)
1727 0 : ALLOCATE (colvar_out%mindist_param%k_coord_to(ndim))
1728 0 : colvar_out%mindist_param%k_coord_to = colvar_in%mindist_param%k_coord_to
1729 : ELSE
1730 : ! INDEX
1731 0 : ndim = SIZE(colvar_in%mindist_param%i_coord_to)
1732 0 : ALLOCATE (colvar_out%mindist_param%i_coord_to(ndim))
1733 0 : colvar_out%mindist_param%i_coord_to = colvar_in%mindist_param%i_coord_to + my_offset
1734 : END IF
1735 :
1736 : END SELECT
1737 4986 : CALL colvar_setup(colvar_out)
1738 4986 : END SUBROUTINE colvar_clone
1739 :
1740 : ! **************************************************************************************************
1741 : !> \brief Clone points type of a colvar type
1742 : !> \param colvar_out ...
1743 : !> \param colvar_in the colvar to deallocate
1744 : !> \param offset ...
1745 : !> \author Teodoro Laino [tlaino] 03.2007
1746 : ! **************************************************************************************************
1747 4986 : SUBROUTINE colvar_clone_points(colvar_out, colvar_in, offset)
1748 : TYPE(colvar_type), INTENT(INOUT) :: colvar_out
1749 : TYPE(colvar_type), INTENT(IN) :: colvar_in
1750 : INTEGER, INTENT(IN) :: offset
1751 :
1752 : INTEGER :: i, natoms, npoints
1753 :
1754 4986 : colvar_out%use_points = colvar_in%use_points
1755 4986 : IF (colvar_in%use_points) THEN
1756 74 : CPASSERT(ASSOCIATED(colvar_in%points))
1757 74 : npoints = SIZE(colvar_in%points)
1758 634 : ALLOCATE (colvar_out%points(npoints))
1759 264 : DO i = 1, npoints
1760 190 : IF (ASSOCIATED(colvar_in%points(i)%atoms)) THEN
1761 182 : natoms = SIZE(colvar_in%points(i)%atoms)
1762 546 : ALLOCATE (colvar_out%points(i)%atoms(natoms))
1763 444 : colvar_out%points(i)%atoms = colvar_in%points(i)%atoms + offset
1764 : ELSE
1765 8 : NULLIFY (colvar_out%points(i)%atoms)
1766 : END IF
1767 190 : IF (ASSOCIATED(colvar_in%points(i)%weights)) THEN
1768 182 : natoms = SIZE(colvar_in%points(i)%weights)
1769 546 : ALLOCATE (colvar_out%points(i)%weights(natoms))
1770 444 : colvar_out%points(i)%weights = colvar_in%points(i)%weights
1771 : ELSE
1772 8 : NULLIFY (colvar_out%points(i)%weights)
1773 : END IF
1774 190 : colvar_out%points(i)%type_id = colvar_in%points(i)%type_id
1775 834 : colvar_out%points(i)%r = colvar_in%points(i)%r
1776 : END DO
1777 : ELSE
1778 4912 : NULLIFY (colvar_out%points)
1779 : END IF
1780 :
1781 4986 : END SUBROUTINE colvar_clone_points
1782 :
1783 : ! **************************************************************************************************
1784 : !> \brief Change the dimension of a colvar_p_type
1785 : !> \param colvar_set ...
1786 : !> \param lb1_new ...
1787 : !> \param ub1_new ...
1788 : !> \author Teodoro Laino [tlaino] 04.2006
1789 : ! **************************************************************************************************
1790 16 : SUBROUTINE colvar_p_reallocate(colvar_set, lb1_new, ub1_new)
1791 : TYPE(colvar_p_type), DIMENSION(:), POINTER :: colvar_set
1792 : INTEGER, INTENT(IN) :: lb1_new, ub1_new
1793 :
1794 : INTEGER :: j, lb1, lb1_old, ub1, ub1_old
1795 16 : TYPE(colvar_p_type), DIMENSION(:), POINTER :: work
1796 :
1797 16 : NULLIFY (work)
1798 16 : IF (ASSOCIATED(colvar_set)) THEN
1799 0 : lb1_old = LBOUND(colvar_set, 1)
1800 0 : ub1_old = UBOUND(colvar_set, 1)
1801 0 : lb1 = MAX(lb1_new, lb1_old)
1802 0 : ub1 = MIN(ub1_new, ub1_old)
1803 0 : ALLOCATE (work(lb1:ub1))
1804 0 : DO j = lb1, ub1
1805 0 : CALL colvar_clone(work(j)%colvar, colvar_set(j)%colvar)
1806 : END DO
1807 0 : DO j = lb1, ub1
1808 0 : CALL colvar_release(colvar_set(j)%colvar)
1809 : END DO
1810 0 : DEALLOCATE (colvar_set)
1811 : END IF
1812 :
1813 228 : ALLOCATE (colvar_set(lb1_new:ub1_new))
1814 :
1815 16 : IF (ASSOCIATED(work)) THEN
1816 0 : lb1 = MAX(lb1_new, lb1_old)
1817 0 : ub1 = MIN(ub1_new, ub1_old)
1818 0 : DO j = lb1, ub1
1819 0 : CALL colvar_clone(colvar_set(j)%colvar, work(j)%colvar)
1820 : END DO
1821 0 : DO j = lb1, ub1
1822 0 : CALL colvar_release(work(j)%colvar)
1823 : END DO
1824 0 : DEALLOCATE (work)
1825 : END IF
1826 16 : END SUBROUTINE colvar_p_reallocate
1827 :
1828 : ! **************************************************************************************************
1829 : !> \brief Deallocate a set of colvar_p_type
1830 : !> \param colvar_p ...
1831 : !> \par History
1832 : !> 07.2003 created [fawzi]
1833 : !> 01.2014 moved from cp_subsys_release() into separate routine.
1834 : !> \author Ole Schuett
1835 : ! **************************************************************************************************
1836 9512 : SUBROUTINE colvar_p_release(colvar_p)
1837 : TYPE(colvar_p_type), DIMENSION(:), POINTER :: colvar_p
1838 :
1839 : INTEGER :: i
1840 :
1841 : ! Colvar info
1842 :
1843 9512 : IF (ASSOCIATED(colvar_p)) THEN
1844 9443 : DO i = 1, SIZE(colvar_p)
1845 462 : IF (ASSOCIATED(colvar_p(i)%colvar)) &
1846 9443 : CALL colvar_release(colvar_p(i)%colvar)
1847 : END DO
1848 8981 : DEALLOCATE (colvar_p)
1849 : END IF
1850 9512 : END SUBROUTINE colvar_p_release
1851 :
1852 : ! **************************************************************************************************
1853 : !> \brief Evaluate the position of the geometrical point
1854 : !> \param point ...
1855 : !> \param particles ...
1856 : !> \param r ...
1857 : !> \author Teodoro Laino - 03.2007
1858 : ! **************************************************************************************************
1859 8644 : SUBROUTINE eval_point_pos(point, particles, r)
1860 : TYPE(point_type), INTENT(IN) :: point
1861 : TYPE(particle_type), DIMENSION(:), INTENT(IN) :: particles
1862 : REAL(KIND=dp), DIMENSION(3), INTENT(OUT) :: r
1863 :
1864 : INTEGER :: i
1865 :
1866 17186 : SELECT CASE (point%type_id)
1867 : CASE (do_clv_geo_center)
1868 8542 : r = 0.0_dp
1869 18088 : DO i = 1, SIZE(point%atoms)
1870 46726 : r = r + particles(point%atoms(i))%r*point%weights(i)
1871 : END DO
1872 : CASE (do_clv_fix_point)
1873 9052 : r = point%r
1874 : END SELECT
1875 :
1876 8644 : END SUBROUTINE eval_point_pos
1877 :
1878 : ! **************************************************************************************************
1879 : !> \brief ...
1880 : !> \param point ...
1881 : !> \param particles ...
1882 : !> \param m ...
1883 : ! **************************************************************************************************
1884 0 : SUBROUTINE eval_point_mass(point, particles, m)
1885 : TYPE(point_type), INTENT(IN) :: point
1886 : TYPE(particle_type), DIMENSION(:), INTENT(IN) :: particles
1887 : REAL(KIND=dp), INTENT(OUT) :: m
1888 :
1889 : INTEGER :: i
1890 :
1891 0 : SELECT CASE (point%type_id)
1892 : CASE (do_clv_geo_center)
1893 0 : m = 0.0_dp
1894 0 : DO i = 1, SIZE(point%atoms)
1895 0 : m = m + particles(point%atoms(i))%atomic_kind%mass*point%weights(i)
1896 : END DO
1897 : CASE (do_clv_fix_point)
1898 0 : m = 0.0_dp
1899 : END SELECT
1900 :
1901 0 : END SUBROUTINE eval_point_mass
1902 :
1903 : ! **************************************************************************************************
1904 : !> \brief Evaluate the position of the geometrical point
1905 : !> \param points ...
1906 : !> \param i ...
1907 : !> \param dsdr ...
1908 : !> \param f ...
1909 : !> \author Teodoro Laino - 03.2007
1910 : ! **************************************************************************************************
1911 8664 : SUBROUTINE eval_point_der(points, i, dsdr, f)
1912 : TYPE(point_type), DIMENSION(:), INTENT(IN) :: points
1913 : INTEGER, INTENT(IN) :: i
1914 : REAL(KIND=dp), DIMENSION(:, :), INTENT(INOUT) :: dsdr
1915 : REAL(KIND=dp), DIMENSION(3), INTENT(IN) :: f
1916 :
1917 : INTEGER :: ind, j
1918 : REAL(KIND=dp) :: fac
1919 :
1920 8664 : SELECT CASE (points(i)%type_id)
1921 : CASE (do_clv_geo_center)
1922 : ind = 0
1923 17054 : DO j = 1, i - 1
1924 17054 : IF (ASSOCIATED(points(j)%atoms)) THEN
1925 8492 : ind = ind + SIZE(points(j)%atoms)
1926 : END IF
1927 : END DO
1928 26792 : DO j = 1, SIZE(points(i)%atoms)
1929 9566 : fac = points(i)%weights(j)
1930 46826 : dsdr(:, ind + j) = dsdr(:, ind + j) + f*fac
1931 : END DO
1932 : CASE (do_clv_fix_point)
1933 : ! Do nothing if it's a fixed point in space
1934 : END SELECT
1935 :
1936 8664 : END SUBROUTINE eval_point_der
1937 :
1938 : ! **************************************************************************************************
1939 : !> \brief subtract b from the ss value of a colvar: general function for handling
1940 : !> periodic/non-periodic colvar
1941 : !> \param colvar ...
1942 : !> \param b ...
1943 : !> \return ...
1944 : !> \author Teodoro Laino [tlaino] - University of Zurich 10.2008
1945 : ! **************************************************************************************************
1946 366739 : FUNCTION diff_colvar(colvar, b) RESULT(diff)
1947 : TYPE(colvar_type), INTENT(IN) :: colvar
1948 : REAL(KIND=dp), INTENT(IN) :: b
1949 : REAL(KIND=dp) :: diff
1950 :
1951 366739 : diff = colvar%ss - b
1952 366739 : IF (colvar%type_id == torsion_colvar_id) THEN
1953 : ! The difference of a periodic COLVAR is always within [-pi,pi]
1954 1584 : diff = SIGN(1.0_dp, ASIN(SIN(diff)))*ACOS(COS(diff))
1955 : END IF
1956 366739 : END FUNCTION diff_colvar
1957 :
1958 0 : END MODULE colvar_types
|