Line data Source code
1 : !--------------------------------------------------------------------------------------------------!
2 : ! CP2K: A general program to perform molecular dynamics simulations !
3 : ! Copyright 2000-2022 CP2K developers group <https://cp2k.org> !
4 : ! !
5 : ! SPDX-License-Identifier: GPL-2.0-or-later !
6 : !--------------------------------------------------------------------------------------------------!
7 :
8 : ! **************************************************************************************************
9 : !> \brief Define all structure types related to force field kinds
10 : !> \par History
11 : !> 10.2014 Moved kind types out of force_field_types.F [Ole Schuett]
12 : !> \author Ole Schuett
13 : ! **************************************************************************************************
14 : MODULE force_field_kind_types
15 :
16 : USE kinds, ONLY: dp
17 : #include "../base/base_uses.f90"
18 :
19 : IMPLICIT NONE
20 :
21 : PRIVATE
22 :
23 : CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'force_field_kind_types'
24 :
25 : INTEGER, PARAMETER, PUBLIC :: do_ff_undef = 0, &
26 : do_ff_quartic = 1, &
27 : do_ff_g96 = 2, &
28 : do_ff_charmm = 3, &
29 : do_ff_harmonic = 4, &
30 : do_ff_g87 = 5, &
31 : do_ff_morse = 6, &
32 : do_ff_cubic = 7, &
33 : do_ff_mixed_bend_stretch = 8, &
34 : do_ff_amber = 9, &
35 : do_ff_mm2 = 10, &
36 : do_ff_mm3 = 11, &
37 : do_ff_mm4 = 12, &
38 : do_ff_fues = 13, &
39 : do_ff_legendre = 14, &
40 : do_ff_opls = 15
41 :
42 : ! *** Define the derived structure types ***
43 :
44 : ! **************************************************************************************************
45 : TYPE legendre_data_type
46 : INTEGER :: order
47 : REAL(KIND=dp), DIMENSION(:), POINTER :: coeffs
48 : END TYPE legendre_data_type
49 :
50 : ! **************************************************************************************************
51 : TYPE bond_kind_type
52 : INTEGER :: id_type
53 : REAL(KIND=dp) :: k(3), r0, cs
54 : INTEGER :: kind_number
55 : END TYPE bond_kind_type
56 :
57 : ! **************************************************************************************************
58 : TYPE bend_kind_type
59 : INTEGER :: id_type
60 : REAL(KIND=dp) :: k, theta0, cb
61 : REAL(KIND=dp) :: r012, r032, kbs12, kbs32, kss
62 : TYPE(legendre_data_type) :: legendre
63 : INTEGER :: kind_number
64 : END TYPE bend_kind_type
65 :
66 : ! **************************************************************************************************
67 : TYPE ub_kind_type
68 : INTEGER :: id_type
69 : REAL(KIND=dp) :: k(3), r0
70 : INTEGER :: kind_number
71 : END TYPE ub_kind_type
72 :
73 : ! **************************************************************************************************
74 : TYPE torsion_kind_type
75 : INTEGER :: id_type
76 : INTEGER :: nmul
77 : INTEGER, POINTER :: m(:)
78 : REAL(KIND=dp), POINTER :: k(:), phi0(:)
79 : INTEGER :: kind_number
80 : END TYPE torsion_kind_type
81 :
82 : ! **************************************************************************************************
83 : TYPE impr_kind_type
84 : INTEGER :: id_type
85 : REAL(KIND=dp) :: k, phi0
86 : INTEGER :: kind_number
87 : END TYPE impr_kind_type
88 :
89 : ! **************************************************************************************************
90 : TYPE opbend_kind_type
91 : INTEGER :: id_type
92 : REAL(KIND=dp) :: k, phi0
93 : INTEGER :: kind_number
94 : END TYPE opbend_kind_type
95 :
96 : ! *** Public subroutines ***
97 :
98 : PUBLIC :: allocate_bend_kind_set, &
99 : allocate_bond_kind_set, &
100 : allocate_ub_kind_set, &
101 : allocate_torsion_kind_set, &
102 : allocate_impr_kind_set, &
103 : allocate_opbend_kind_set, &
104 : deallocate_bend_kind_set, &
105 : deallocate_bond_kind_set, &
106 : torsion_kind_dealloc_ref, &
107 : impr_kind_dealloc_ref
108 :
109 : ! *** Public data types ***
110 :
111 : PUBLIC :: bend_kind_type, &
112 : bond_kind_type, &
113 : impr_kind_type, &
114 : torsion_kind_type, &
115 : opbend_kind_type, &
116 : ub_kind_type, &
117 : ub_kind_dealloc_ref, &
118 : legendre_data_type
119 : CONTAINS
120 :
121 : ! **************************************************************************************************
122 : !> \brief Allocate and initialize a bend kind set.
123 : !> \param bend_kind_set ...
124 : !> \param nkind ...
125 : ! **************************************************************************************************
126 29623 : SUBROUTINE allocate_bend_kind_set(bend_kind_set, nkind)
127 :
128 : TYPE(bend_kind_type), DIMENSION(:), POINTER :: bend_kind_set
129 : INTEGER, INTENT(IN) :: nkind
130 :
131 : INTEGER :: ikind
132 :
133 29623 : NULLIFY (bend_kind_set)
134 88351 : ALLOCATE (bend_kind_set(nkind))
135 124819 : DO ikind = 1, nkind
136 95196 : bend_kind_set(ikind)%id_type = do_ff_undef
137 95196 : bend_kind_set(ikind)%k = 0.0_dp
138 95196 : bend_kind_set(ikind)%theta0 = 0.0_dp
139 95196 : bend_kind_set(ikind)%cb = 0.0_dp
140 95196 : bend_kind_set(ikind)%r012 = 0.0_dp
141 95196 : bend_kind_set(ikind)%r032 = 0.0_dp
142 95196 : bend_kind_set(ikind)%kbs12 = 0.0_dp
143 95196 : bend_kind_set(ikind)%kbs32 = 0.0_dp
144 95196 : bend_kind_set(ikind)%kss = 0.0_dp
145 95196 : bend_kind_set(ikind)%legendre%order = 0
146 95196 : NULLIFY (bend_kind_set(ikind)%legendre%coeffs)
147 124819 : bend_kind_set(ikind)%kind_number = ikind
148 : END DO
149 29623 : END SUBROUTINE allocate_bend_kind_set
150 :
151 : ! **************************************************************************************************
152 : !> \brief Allocate and initialize a bond kind set.
153 : !> \param bond_kind_set ...
154 : !> \param nkind ...
155 : ! **************************************************************************************************
156 30143 : SUBROUTINE allocate_bond_kind_set(bond_kind_set, nkind)
157 :
158 : TYPE(bond_kind_type), DIMENSION(:), POINTER :: bond_kind_set
159 : INTEGER, INTENT(IN) :: nkind
160 :
161 : INTEGER :: ikind
162 :
163 30143 : NULLIFY (bond_kind_set)
164 89747 : ALLOCATE (bond_kind_set(nkind))
165 97204 : DO ikind = 1, nkind
166 67061 : bond_kind_set(ikind)%id_type = do_ff_undef
167 268244 : bond_kind_set(ikind)%k(:) = 0.0_dp
168 67061 : bond_kind_set(ikind)%r0 = 0.0_dp
169 67061 : bond_kind_set(ikind)%cs = 0.0_dp
170 97204 : bond_kind_set(ikind)%kind_number = ikind
171 : END DO
172 30143 : END SUBROUTINE allocate_bond_kind_set
173 :
174 : ! **************************************************************************************************
175 : !> \brief Allocate and initialize a torsion kind set.
176 : !> \param torsion_kind_set ...
177 : !> \param nkind ...
178 : ! **************************************************************************************************
179 6502 : SUBROUTINE allocate_torsion_kind_set(torsion_kind_set, nkind)
180 :
181 : TYPE(torsion_kind_type), DIMENSION(:), POINTER :: torsion_kind_set
182 : INTEGER, INTENT(IN) :: nkind
183 :
184 : INTEGER :: ikind
185 :
186 6502 : NULLIFY (torsion_kind_set)
187 18602 : ALLOCATE (torsion_kind_set(nkind))
188 :
189 101051 : DO ikind = 1, nkind
190 94549 : torsion_kind_set(ikind)%id_type = do_ff_undef
191 94549 : torsion_kind_set(ikind)%nmul = 0
192 94549 : NULLIFY (torsion_kind_set(ikind)%k)
193 94549 : NULLIFY (torsion_kind_set(ikind)%m)
194 94549 : NULLIFY (torsion_kind_set(ikind)%phi0)
195 101051 : torsion_kind_set(ikind)%kind_number = ikind
196 : END DO
197 6502 : END SUBROUTINE allocate_torsion_kind_set
198 :
199 : ! **************************************************************************************************
200 : !> \brief Allocate and initialize a ub kind set.
201 : !> \param ub_kind_set ...
202 : !> \param nkind ...
203 : ! **************************************************************************************************
204 58018 : SUBROUTINE allocate_ub_kind_set(ub_kind_set, nkind)
205 :
206 : TYPE(ub_kind_type), DIMENSION(:), POINTER :: ub_kind_set
207 : INTEGER, INTENT(IN) :: nkind
208 :
209 : INTEGER :: ikind
210 :
211 58018 : NULLIFY (ub_kind_set)
212 146545 : ALLOCATE (ub_kind_set(nkind))
213 160438 : DO ikind = 1, nkind
214 102420 : ub_kind_set(ikind)%id_type = do_ff_undef
215 409680 : ub_kind_set(ikind)%k = 0.0_dp
216 102420 : ub_kind_set(ikind)%r0 = 0.0_dp
217 160438 : ub_kind_set(ikind)%kind_number = ikind
218 : END DO
219 58018 : END SUBROUTINE allocate_ub_kind_set
220 :
221 : ! **************************************************************************************************
222 : !> \brief Allocate and initialize a impr kind set.
223 : !> \param impr_kind_set ...
224 : !> \param nkind ...
225 : ! **************************************************************************************************
226 2018 : SUBROUTINE allocate_impr_kind_set(impr_kind_set, nkind)
227 :
228 : TYPE(impr_kind_type), DIMENSION(:), POINTER :: impr_kind_set
229 : INTEGER, INTENT(IN) :: nkind
230 :
231 : INTEGER :: ikind
232 :
233 2018 : NULLIFY (impr_kind_set)
234 5768 : ALLOCATE (impr_kind_set(nkind))
235 6762 : DO ikind = 1, nkind
236 4744 : impr_kind_set(ikind)%id_type = do_ff_undef
237 4744 : impr_kind_set(ikind)%k = 0.0_dp
238 4744 : impr_kind_set(ikind)%phi0 = 0.0_dp
239 6762 : impr_kind_set(ikind)%kind_number = ikind
240 : END DO
241 2018 : END SUBROUTINE allocate_impr_kind_set
242 :
243 : ! **************************************************************************************************
244 : !> \brief Allocate and initialize a opbend kind set.
245 : !> \param opbend_kind_set ...
246 : !> \param nkind ...
247 : ! **************************************************************************************************
248 3254 : SUBROUTINE allocate_opbend_kind_set(opbend_kind_set, nkind)
249 :
250 : TYPE(opbend_kind_type), DIMENSION(:), POINTER :: opbend_kind_set
251 : INTEGER, INTENT(IN) :: nkind
252 :
253 : INTEGER :: ikind
254 :
255 3254 : NULLIFY (opbend_kind_set)
256 8136 : ALLOCATE (opbend_kind_set(nkind))
257 7874 : DO ikind = 1, nkind
258 4620 : opbend_kind_set(ikind)%id_type = do_ff_undef
259 4620 : opbend_kind_set(ikind)%k = 0.0_dp
260 4620 : opbend_kind_set(ikind)%phi0 = 0.0_dp
261 7874 : opbend_kind_set(ikind)%kind_number = ikind
262 : END DO
263 3254 : END SUBROUTINE allocate_opbend_kind_set
264 :
265 : ! **************************************************************************************************
266 : !> \brief Deallocate a bend kind set.
267 : !> \param bend_kind_set ...
268 : ! **************************************************************************************************
269 596 : SUBROUTINE deallocate_bend_kind_set(bend_kind_set)
270 :
271 : TYPE(bend_kind_type), DIMENSION(:), POINTER :: bend_kind_set
272 :
273 : INTEGER :: i
274 :
275 596 : IF (.NOT. ASSOCIATED(bend_kind_set)) RETURN
276 2766 : DO i = 1, SIZE(bend_kind_set)
277 2766 : IF (ASSOCIATED(bend_kind_set(i)%legendre%coeffs)) THEN
278 244 : DEALLOCATE (bend_kind_set(i)%legendre%coeffs)
279 244 : NULLIFY (bend_kind_set(i)%legendre%coeffs)
280 : END IF
281 : END DO
282 596 : DEALLOCATE (bend_kind_set)
283 : END SUBROUTINE deallocate_bend_kind_set
284 :
285 : ! **************************************************************************************************
286 : !> \brief Deallocate a bond kind set.
287 : !> \param bond_kind_set ...
288 : ! **************************************************************************************************
289 794 : SUBROUTINE deallocate_bond_kind_set(bond_kind_set)
290 :
291 : TYPE(bond_kind_type), DIMENSION(:), POINTER :: bond_kind_set
292 :
293 794 : DEALLOCATE (bond_kind_set)
294 :
295 794 : END SUBROUTINE deallocate_bond_kind_set
296 :
297 : ! **************************************************************************************************
298 : !> \brief Deallocate a torsion kind element
299 : !> \param torsion_kind ...
300 : ! **************************************************************************************************
301 94549 : SUBROUTINE torsion_kind_dealloc_ref(torsion_kind)
302 :
303 : TYPE(torsion_kind_type), INTENT(INOUT) :: torsion_kind
304 :
305 94549 : IF (ASSOCIATED(torsion_kind%k)) THEN
306 81209 : DEALLOCATE (torsion_kind%k)
307 : END IF
308 94549 : IF (ASSOCIATED(torsion_kind%m)) THEN
309 81209 : DEALLOCATE (torsion_kind%m)
310 : END IF
311 94549 : IF (ASSOCIATED(torsion_kind%phi0)) THEN
312 81209 : DEALLOCATE (torsion_kind%phi0)
313 : END IF
314 :
315 94549 : END SUBROUTINE torsion_kind_dealloc_ref
316 :
317 : ! **************************************************************************************************
318 : !> \brief Deallocate a ub kind set.
319 : !> \param ub_kind_set ...
320 : ! **************************************************************************************************
321 58018 : SUBROUTINE ub_kind_dealloc_ref(ub_kind_set)
322 : TYPE(ub_kind_type), DIMENSION(:), POINTER :: ub_kind_set
323 :
324 58018 : DEALLOCATE (ub_kind_set)
325 :
326 58018 : END SUBROUTINE ub_kind_dealloc_ref
327 :
328 : ! **************************************************************************************************
329 : !> \brief Deallocate a impr kind element
330 : ! **************************************************************************************************
331 4744 : SUBROUTINE impr_kind_dealloc_ref()
332 :
333 : !
334 : ! Questa e' la migliore routine che mente umana abbia concepito! ;-)
335 : ! Translation to english: This is the best subroutine that humanity can imagine! ;-)
336 : !
337 :
338 4744 : END SUBROUTINE impr_kind_dealloc_ref
339 :
340 0 : END MODULE force_field_kind_types
|