(git:374b731)
Loading...
Searching...
No Matches
force_field_kind_types.F
Go to the documentation of this file.
1!--------------------------------------------------------------------------------------------------!
2! CP2K: A general program to perform molecular dynamics simulations !
3! Copyright 2000-2024 CP2K developers group <https://cp2k.org> !
4! !
5! SPDX-License-Identifier: GPL-2.0-or-later !
6!--------------------------------------------------------------------------------------------------!
7
8! **************************************************************************************************
9!> \brief 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! **************************************************************************************************
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, &
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! **************************************************************************************************
46 INTEGER :: order = 0
47 REAL(kind=dp), DIMENSION(:), POINTER :: coeffs => null()
48 END TYPE legendre_data_type
49
50! **************************************************************************************************
52 INTEGER :: id_type = do_ff_undef
53 REAL(kind=dp) :: k(3) = 0.0_dp, r0 = 0.0_dp, cs = 0.0_dp
54 INTEGER :: kind_number = 0
55 END TYPE bond_kind_type
56
57! **************************************************************************************************
59 INTEGER :: id_type = do_ff_undef
60 REAL(kind=dp) :: k = 0.0_dp, theta0 = 0.0_dp, cb = 0.0_dp
61 REAL(kind=dp) :: r012 = 0.0_dp, r032 = 0.0_dp, kbs12 = 0.0_dp, kbs32 = 0.0_dp, kss = 0.0_dp
63 INTEGER :: kind_number = 0
64 END TYPE bend_kind_type
65
66! **************************************************************************************************
68 INTEGER :: id_type = do_ff_undef
69 REAL(kind=dp) :: k(3) = 0.0_dp, r0 = 0.0_dp
70 INTEGER :: kind_number = 0
71 END TYPE ub_kind_type
72
73! **************************************************************************************************
75 INTEGER :: id_type = do_ff_undef
76 INTEGER :: nmul = 0
77 INTEGER, POINTER :: m(:) => null()
78 REAL(kind=dp), POINTER :: k(:) => null(), phi0(:) => null()
79 INTEGER :: kind_number = 0
80 END TYPE torsion_kind_type
81
82! **************************************************************************************************
84 INTEGER :: id_type = do_ff_undef
85 REAL(kind=dp) :: k = 0.0_dp, phi0 = 0.0_dp
86 INTEGER :: kind_number = 0
87 END TYPE impr_kind_type
88
89! **************************************************************************************************
91 INTEGER :: id_type = do_ff_undef
92 REAL(kind=dp) :: k = 0.0_dp, phi0 = 0.0_dp
93 INTEGER :: kind_number = 0
94 END TYPE opbend_kind_type
95
96! *** Public subroutines ***
97
98 PUBLIC :: allocate_bend_kind_set, &
108
109! *** Public data types ***
110
111 PUBLIC :: bend_kind_type, &
116 ub_kind_type, &
119CONTAINS
120
121! **************************************************************************************************
122!> \brief Allocate and initialize a bend kind set.
123!> \param bend_kind_set ...
124!> \param nkind ...
125! **************************************************************************************************
126 PURE 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 NULLIFY (bend_kind_set)
134 ALLOCATE (bend_kind_set(nkind))
135 DO ikind = 1, nkind
136 bend_kind_set(ikind)%kind_number = ikind
137 END DO
138 END SUBROUTINE allocate_bend_kind_set
139
140! **************************************************************************************************
141!> \brief Allocate and initialize a bond kind set.
142!> \param bond_kind_set ...
143!> \param nkind ...
144! **************************************************************************************************
145 PURE SUBROUTINE allocate_bond_kind_set(bond_kind_set, nkind)
146
147 TYPE(bond_kind_type), DIMENSION(:), POINTER :: bond_kind_set
148 INTEGER, INTENT(IN) :: nkind
149
150 INTEGER :: ikind
151
152 NULLIFY (bond_kind_set)
153 ALLOCATE (bond_kind_set(nkind))
154 DO ikind = 1, nkind
155 bond_kind_set(ikind)%kind_number = ikind
156 END DO
157 END SUBROUTINE allocate_bond_kind_set
158
159! **************************************************************************************************
160!> \brief Allocate and initialize a torsion kind set.
161!> \param torsion_kind_set ...
162!> \param nkind ...
163! **************************************************************************************************
164 PURE SUBROUTINE allocate_torsion_kind_set(torsion_kind_set, nkind)
165
166 TYPE(torsion_kind_type), DIMENSION(:), POINTER :: torsion_kind_set
167 INTEGER, INTENT(IN) :: nkind
168
169 INTEGER :: ikind
170
171 NULLIFY (torsion_kind_set)
172 ALLOCATE (torsion_kind_set(nkind))
173 DO ikind = 1, nkind
174 torsion_kind_set(ikind)%kind_number = ikind
175 END DO
176 END SUBROUTINE allocate_torsion_kind_set
177
178! **************************************************************************************************
179!> \brief Allocate and initialize a ub kind set.
180!> \param ub_kind_set ...
181!> \param nkind ...
182! **************************************************************************************************
183 PURE SUBROUTINE allocate_ub_kind_set(ub_kind_set, nkind)
184
185 TYPE(ub_kind_type), DIMENSION(:), POINTER :: ub_kind_set
186 INTEGER, INTENT(IN) :: nkind
187
188 INTEGER :: ikind
189
190 NULLIFY (ub_kind_set)
191 ALLOCATE (ub_kind_set(nkind))
192 DO ikind = 1, nkind
193 ub_kind_set(ikind)%kind_number = ikind
194 END DO
195 END SUBROUTINE allocate_ub_kind_set
196
197! **************************************************************************************************
198!> \brief Allocate and initialize a impr kind set.
199!> \param impr_kind_set ...
200!> \param nkind ...
201! **************************************************************************************************
202 PURE SUBROUTINE allocate_impr_kind_set(impr_kind_set, nkind)
203
204 TYPE(impr_kind_type), DIMENSION(:), POINTER :: impr_kind_set
205 INTEGER, INTENT(IN) :: nkind
206
207 INTEGER :: ikind
208
209 NULLIFY (impr_kind_set)
210 ALLOCATE (impr_kind_set(nkind))
211 DO ikind = 1, nkind
212 impr_kind_set(ikind)%kind_number = ikind
213 END DO
214 END SUBROUTINE allocate_impr_kind_set
215
216! **************************************************************************************************
217!> \brief Allocate and initialize a opbend kind set.
218!> \param opbend_kind_set ...
219!> \param nkind ...
220! **************************************************************************************************
221 PURE SUBROUTINE allocate_opbend_kind_set(opbend_kind_set, nkind)
222
223 TYPE(opbend_kind_type), DIMENSION(:), POINTER :: opbend_kind_set
224 INTEGER, INTENT(IN) :: nkind
225
226 INTEGER :: ikind
227
228 NULLIFY (opbend_kind_set)
229 ALLOCATE (opbend_kind_set(nkind))
230 DO ikind = 1, nkind
231 opbend_kind_set(ikind)%kind_number = ikind
232 END DO
233 END SUBROUTINE allocate_opbend_kind_set
234
235! **************************************************************************************************
236!> \brief Deallocate a bend kind set.
237!> \param bend_kind_set ...
238! **************************************************************************************************
239 PURE SUBROUTINE deallocate_bend_kind_set(bend_kind_set)
240
241 TYPE(bend_kind_type), DIMENSION(:), POINTER :: bend_kind_set
242
243 INTEGER :: i
244
245 IF (.NOT. ASSOCIATED(bend_kind_set)) RETURN
246 DO i = 1, SIZE(bend_kind_set)
247 IF (ASSOCIATED(bend_kind_set(i)%legendre%coeffs)) THEN
248 DEALLOCATE (bend_kind_set(i)%legendre%coeffs)
249 END IF
250 END DO
251 DEALLOCATE (bend_kind_set)
252 END SUBROUTINE deallocate_bend_kind_set
253
254! **************************************************************************************************
255!> \brief Deallocate a bond kind set.
256!> \param bond_kind_set ...
257! **************************************************************************************************
258 PURE SUBROUTINE deallocate_bond_kind_set(bond_kind_set)
259
260 TYPE(bond_kind_type), DIMENSION(:), POINTER :: bond_kind_set
261
262 DEALLOCATE (bond_kind_set)
263
264 END SUBROUTINE deallocate_bond_kind_set
265
266! **************************************************************************************************
267!> \brief Deallocate a torsion kind element
268!> \param torsion_kind ...
269! **************************************************************************************************
270 PURE SUBROUTINE torsion_kind_dealloc_ref(torsion_kind)
271
272 TYPE(torsion_kind_type), INTENT(INOUT) :: torsion_kind
273
274 IF (ASSOCIATED(torsion_kind%k)) THEN
275 DEALLOCATE (torsion_kind%k)
276 END IF
277 IF (ASSOCIATED(torsion_kind%m)) THEN
278 DEALLOCATE (torsion_kind%m)
279 END IF
280 IF (ASSOCIATED(torsion_kind%phi0)) THEN
281 DEALLOCATE (torsion_kind%phi0)
282 END IF
283
284 END SUBROUTINE torsion_kind_dealloc_ref
285
286! **************************************************************************************************
287!> \brief Deallocate a ub kind set.
288!> \param ub_kind_set ...
289! **************************************************************************************************
290 PURE SUBROUTINE ub_kind_dealloc_ref(ub_kind_set)
291 TYPE(ub_kind_type), DIMENSION(:), POINTER :: ub_kind_set
292
293 DEALLOCATE (ub_kind_set)
294
295 END SUBROUTINE ub_kind_dealloc_ref
296
297! **************************************************************************************************
298!> \brief Deallocate a impr kind element
299! **************************************************************************************************
300 PURE SUBROUTINE impr_kind_dealloc_ref()
301
302!
303! Questa e' la migliore routine che mente umana abbia concepito! ;-)
304! Translation to english: This is the best subroutine that humanity can imagine! ;-)
305!
306
307 END SUBROUTINE impr_kind_dealloc_ref
308
309END MODULE force_field_kind_types
Define all structure types related to force field kinds.
integer, parameter, public do_ff_legendre
pure subroutine, public deallocate_bend_kind_set(bend_kind_set)
Deallocate a bend kind set.
integer, parameter, public do_ff_undef
integer, parameter, public do_ff_mm4
pure subroutine, public allocate_impr_kind_set(impr_kind_set, nkind)
Allocate and initialize a impr kind set.
pure subroutine, public torsion_kind_dealloc_ref(torsion_kind)
Deallocate a torsion kind element.
pure subroutine, public allocate_torsion_kind_set(torsion_kind_set, nkind)
Allocate and initialize a torsion kind set.
pure subroutine, public allocate_bond_kind_set(bond_kind_set, nkind)
Allocate and initialize a bond kind set.
integer, parameter, public do_ff_charmm
pure subroutine, public allocate_opbend_kind_set(opbend_kind_set, nkind)
Allocate and initialize a opbend kind set.
integer, parameter, public do_ff_mm3
integer, parameter, public do_ff_g87
integer, parameter, public do_ff_g96
pure subroutine, public ub_kind_dealloc_ref(ub_kind_set)
Deallocate a ub kind set.
integer, parameter, public do_ff_morse
integer, parameter, public do_ff_mm2
integer, parameter, public do_ff_harmonic
pure subroutine, public allocate_bend_kind_set(bend_kind_set, nkind)
Allocate and initialize a bend kind set.
integer, parameter, public do_ff_amber
pure subroutine, public deallocate_bond_kind_set(bond_kind_set)
Deallocate a bond kind set.
integer, parameter, public do_ff_mixed_bend_stretch
integer, parameter, public do_ff_cubic
integer, parameter, public do_ff_quartic
pure subroutine, public allocate_ub_kind_set(ub_kind_set, nkind)
Allocate and initialize a ub kind set.
pure subroutine, public impr_kind_dealloc_ref()
Deallocate a impr kind element.
integer, parameter, public do_ff_fues
integer, parameter, public do_ff_opls
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34