(git:d18deda)
Loading...
Searching...
No Matches
semi_empirical_types.F
Go to the documentation of this file.
1!--------------------------------------------------------------------------------------------------!
2! CP2K: A general program to perform molecular dynamics simulations !
3! Copyright 2000-2025 CP2K developers group <https://cp2k.org> !
4! !
5! SPDX-License-Identifier: GPL-2.0-or-later !
6!--------------------------------------------------------------------------------------------------!
7
8! **************************************************************************************************
9!> \brief Definition of the semi empirical parameter types.
10!> \author JGH (14.08.2004)
11! **************************************************************************************************
18 USE cp_output_handling, ONLY: cp_p_file,&
22 USE dg_types, ONLY: dg_type
23 USE input_constants, ONLY: &
28 USE kinds, ONLY: default_string_length,&
29 dp
34 USE physcon, ONLY: angstrom,&
35 evolt,&
42 USE taper_types, ONLY: taper_create,&
45#include "./base/base_uses.f90"
46
47 IMPLICIT NONE
48
49 PRIVATE
50
51! *** Global parameters ***
52 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'semi_empirical_types'
53
54! **************************************************************************************************
55!> \brief Semi-empirical type
56! **************************************************************************************************
58 INTEGER :: typ = -1
59 INTEGER :: nr = -1
60 INTEGER :: core_size = -1, atm_int_size = -1
61 CHARACTER(LEN=default_string_length) :: name = ""
62 LOGICAL :: defined = .false., dorb = .false., extended_basis_set = .false.
63 LOGICAL :: p_orbitals_on_h = .false.
64 INTEGER :: z = -1
65 REAL(kind=dp) :: zeff = -1.0_dp
66 INTEGER :: natorb = -1
67 REAL(kind=dp), DIMENSION(:), POINTER :: beta => null()
68 REAL(kind=dp), DIMENSION(:), POINTER :: sto_exponents => null()
69 REAL(kind=dp), DIMENSION(:), POINTER :: zn => null()
70 TYPE(sto_basis_set_type), POINTER :: basis => null()
71 INTEGER :: ngauss = -1
72 REAL(kind=dp) :: eheat = -1.0_dp
73 REAL(kind=dp) :: uss = -1.0_dp, upp = -1.0_dp, udd = -1.0_dp, uff = -1.0_dp
74 REAL(kind=dp) :: alp = -1.0_dp
75 REAL(kind=dp) :: eisol = -1.0_dp
76 REAL(kind=dp) :: ass = -1.0_dp, asp = -1.0_dp, app = -1.0_dp, de = -1.0_dp, acoul = -1.0_dp
77 REAL(kind=dp) :: gss = -1.0_dp, gsp = -1.0_dp, gpp = -1.0_dp, gp2 = -1.0_dp
78 REAL(kind=dp) :: gsd = -1.0_dp, gpd = -1.0_dp, gdd = -1.0_dp
79 REAL(kind=dp) :: hsp = -1.0_dp
80 REAL(kind=dp) :: dd = -1.0_dp, qq = -1.0_dp, am = -1.0_dp, ad = -1.0_dp, aq = -1.0_dp
81 REAL(kind=dp), DIMENSION(2) :: pre = -1.0_dp, d = -1.0_dp
82 REAL(kind=dp), DIMENSION(4) :: fn1 = -1.0_dp, fn2 = -1.0_dp, fn3 = -1.0_dp
83 REAL(kind=dp), DIMENSION(4, 4) :: bfn1 = -1.0_dp, bfn2 = -1.0_dp, bfn3 = -1.0_dp
84 REAL(kind=dp) :: f0dd = -1.0_dp, f2dd = -1.0_dp, f4dd = -1.0_dp, &
85 f0sd = -1.0_dp, f0pd = -1.0_dp, f2pd = -1.0_dp, &
86 g1pd = -1.0_dp, g2sd = -1.0_dp, g3pd = -1.0_dp
87 REAL(kind=dp), DIMENSION(9) :: ko = -1.0_dp
88 REAL(kind=dp), DIMENSION(6) :: cs = -1.0_dp
89 REAL(kind=dp), DIMENSION(52) :: onec2el = -1.0_dp
90 ! Specific for PM6 & PM6-FM
91 REAL(kind=dp), DIMENSION(0:115) :: xab = -1.0_dp
92 REAL(kind=dp), DIMENSION(0:115) :: aab = -1.0_dp
93 REAL(kind=dp) :: a = -1.0_dp, b = -1.0_dp, c = -1.0_dp, rho = -1.0_dp
94 ! One center - two electron integrals
95 REAL(kind=dp), DIMENSION(:, :), &
96 POINTER :: w => null()
98 POINTER, DIMENSION(:) :: w_mpole => null()
99 ! 1/R^3 residual integral part
101 POINTER, DIMENSION(:) :: expns3_int => null()
102 END TYPE semi_empirical_type
103
105 TYPE(semi_empirical_type), POINTER :: se_param => null()
106 END TYPE semi_empirical_p_type
107
108! **************************************************************************************************
109!> \brief Rotation Matrix Type
110!> \author 05.2008 Teodoro Laino [tlaino] - University of Zurich
111! **************************************************************************************************
113 ! Value of Rotation Matrices
114 REAL(kind=dp), DIMENSION(3, 3) :: sp = -1.0_dp
115 REAL(kind=dp), DIMENSION(5, 5) :: sd = -1.0_dp
116 REAL(kind=dp), DIMENSION(6, 3, 3) :: pp = -1.0_dp
117 REAL(kind=dp), DIMENSION(15, 5, 3) :: pd = -1.0_dp
118 REAL(kind=dp), DIMENSION(15, 5, 5) :: dd = -1.0_dp
119 ! Derivatives of Rotation Matrices
120 REAL(kind=dp), DIMENSION(3, 3, 3) :: sp_d = -1.0_dp
121 REAL(kind=dp), DIMENSION(3, 5, 5) :: sd_d = -1.0_dp
122 REAL(kind=dp), DIMENSION(3, 6, 3, 3) :: pp_d = -1.0_dp
123 REAL(kind=dp), DIMENSION(3, 15, 5, 3) :: pd_d = -1.0_dp
124 REAL(kind=dp), DIMENSION(3, 15, 5, 5) :: dd_d = -1.0_dp
125 END TYPE rotmat_type
126
127! **************************************************************************************************
128!> \brief Ewald control type (for periodic SE)
129!> \author Teodoro Laino [tlaino] - 12.2008
130! **************************************************************************************************
131 TYPE ewald_gks_type
132 REAL(kind=dp) :: alpha = -1.0_dp
133 TYPE(dg_type), POINTER :: dg => null()
134 TYPE(pw_pool_type), POINTER :: pw_pool => null()
135 END TYPE ewald_gks_type
136
138 LOGICAL :: shortrange = .false.
139 LOGICAL :: do_ewald_r3 = .false.
140 LOGICAL :: do_ewald_gks = .false.
141 LOGICAL :: pc_coulomb_int = .false.
142 INTEGER :: integral_screening = -1
143 INTEGER :: max_multipole = -1
144 TYPE(ewald_gks_type) :: ewald_gks = ewald_gks_type()
145 END TYPE se_int_control_type
146
147! **************************************************************************************************
148!> \brief Store the value of the tapering function and possibly its derivative
149!> for screened integrals
150! **************************************************************************************************
152 REAL(kind=dp) :: ft = -1.0_dp, dft = -1.0_dp
153 END TYPE se_int_screen_type
154
155! **************************************************************************************************
156!> \brief Taper type use in semi-empirical calculations
157! **************************************************************************************************
159 TYPE(taper_type), POINTER :: taper => null()
160 TYPE(taper_type), POINTER :: taper_cou => null()
161 TYPE(taper_type), POINTER :: taper_exc => null()
162 TYPE(taper_type), POINTER :: taper_lrc => null()
163 ! This taper is for KDSO-D integrals
164 TYPE(taper_type), POINTER :: taper_add => null()
165 END TYPE se_taper_type
166
167 PUBLIC :: semi_empirical_type, &
171 rotmat_type, &
174 get_se_param, &
182
183CONTAINS
184
185! **************************************************************************************************
186!> \brief Allocate semi-empirical type
187!> \param sep ...
188! **************************************************************************************************
189 SUBROUTINE semi_empirical_create(sep)
190 TYPE(semi_empirical_type), POINTER :: sep
191
192 cpassert(.NOT. ASSOCIATED(sep))
193 ALLOCATE (sep)
194 ALLOCATE (sep%beta(0:3))
195 ALLOCATE (sep%sto_exponents(0:3))
196 ALLOCATE (sep%zn(0:3))
197 NULLIFY (sep%basis)
198 NULLIFY (sep%w)
199 NULLIFY (sep%w_mpole)
200 NULLIFY (sep%expns3_int)
201 CALL zero_se_param(sep)
202
203 END SUBROUTINE semi_empirical_create
204
205! **************************************************************************************************
206!> \brief Deallocate the semi-empirical type
207!> \param sep ...
208! **************************************************************************************************
210
211 TYPE(semi_empirical_type), POINTER :: sep
212
213 INTEGER :: i
214
215 IF (ASSOCIATED(sep)) THEN
216 CALL deallocate_sto_basis_set(sep%basis)
217 CALL semi_empirical_mpole_p_release(sep%w_mpole)
218 IF (ASSOCIATED(sep%beta)) THEN
219 DEALLOCATE (sep%beta)
220 END IF
221 IF (ASSOCIATED(sep%sto_exponents)) THEN
222 DEALLOCATE (sep%sto_exponents)
223 END IF
224 IF (ASSOCIATED(sep%zn)) THEN
225 DEALLOCATE (sep%zn)
226 END IF
227 IF (ASSOCIATED(sep%w)) THEN
228 DEALLOCATE (sep%w)
229 END IF
230 IF (ASSOCIATED(sep%expns3_int)) THEN
231 DO i = 1, SIZE(sep%expns3_int)
232 CALL semi_empirical_expns3_release(sep%expns3_int(i)%expns3)
233 END DO
234 DEALLOCATE (sep%expns3_int)
235 END IF
236 DEALLOCATE (sep)
237 END IF
238
239 END SUBROUTINE semi_empirical_release
240
241! **************************************************************************************************
242!> \brief Zero the whole semi-empirical type
243!> \param sep ...
244! **************************************************************************************************
245 SUBROUTINE zero_se_param(sep)
246 TYPE(semi_empirical_type), POINTER :: sep
247
248 cpassert(ASSOCIATED(sep))
249 sep%defined = .false.
250 sep%dorb = .false.
251 sep%extended_basis_set = .false.
252 sep%p_orbitals_on_h = .false.
253 sep%name = ""
254 sep%typ = huge(0)
255 sep%core_size = huge(0)
256 sep%atm_int_size = huge(0)
257 sep%z = huge(0)
258 sep%zeff = huge(0.0_dp)
259 sep%natorb = 0
260 sep%ngauss = 0
261 sep%eheat = huge(0.0_dp)
262
263 sep%zn = 0.0_dp
264 sep%sto_exponents = 0.0_dp
265 sep%beta = 0.0_dp
266
267 sep%uss = 0.0_dp !eV
268 sep%upp = 0.0_dp !eV
269 sep%udd = 0.0_dp !eV
270 sep%uff = 0.0_dp
271 sep%alp = 0.0_dp
272 sep%eisol = 0.0_dp
273 sep%nr = 1
274 sep%acoul = 0.0_dp
275 sep%de = 0.0_dp
276 sep%ass = 0.0_dp
277 sep%asp = 0.0_dp
278 sep%app = 0.0_dp
279 sep%gss = 0.0_dp
280 sep%gsp = 0.0_dp
281 sep%gpp = 0.0_dp
282 sep%gp2 = 0.0_dp
283 sep%gsd = 0.0_dp
284 sep%gpd = 0.0_dp
285 sep%gdd = 0.0_dp
286 sep%hsp = 0.0_dp
287 sep%dd = 0.0_dp
288 sep%qq = 0.0_dp
289 sep%am = 0.0_dp
290 sep%ad = 0.0_dp
291 sep%aq = 0.0_dp
292
293 sep%fn1 = 0.0_dp
294 sep%fn2 = 0.0_dp
295 sep%fn3 = 0.0_dp
296 sep%bfn1 = 0.0_dp
297 sep%bfn2 = 0.0_dp
298 sep%bfn3 = 0.0_dp
299
300 sep%pre = 0.0_dp
301 sep%d = 0.0_dp
302
303 sep%xab = 0.0_dp
304 sep%aab = 0.0_dp
305 sep%a = 0.0_dp
306 sep%b = 0.0_dp
307 sep%c = 0.0_dp
308 sep%rho = 0.0_dp
309
310 sep%f0dd = 0.0_dp
311 sep%f2dd = 0.0_dp
312 sep%f4dd = 0.0_dp
313 sep%f0sd = 0.0_dp
314 sep%f0pd = 0.0_dp
315 sep%f2pd = 0.0_dp
316 sep%g1pd = 0.0_dp
317 sep%g2sd = 0.0_dp
318 sep%g3pd = 0.0_dp
319 sep%ko = 0.0_dp
320 sep%cs = 0.0_dp
321 sep%onec2el = 0.0_dp
322
323 END SUBROUTINE zero_se_param
324
325! **************************************************************************************************
326!> \brief Get info from the semi-empirical type
327!> \param sep ...
328!> \param name ...
329!> \param typ ...
330!> \param defined ...
331!> \param z ...
332!> \param zeff ...
333!> \param natorb ...
334!> \param eheat ...
335!> \param beta ...
336!> \param sto_exponents ...
337!> \param uss ...
338!> \param upp ...
339!> \param udd ...
340!> \param uff ...
341!> \param alp ...
342!> \param eisol ...
343!> \param gss ...
344!> \param gsp ...
345!> \param gpp ...
346!> \param gp2 ...
347!> \param acoul ...
348!> \param nr ...
349!> \param de ...
350!> \param ass ...
351!> \param asp ...
352!> \param app ...
353!> \param hsp ...
354!> \param gsd ...
355!> \param gpd ...
356!> \param gdd ...
357!> \param ppddg ...
358!> \param dpddg ...
359!> \param ngauss ...
360! **************************************************************************************************
361 SUBROUTINE get_se_param(sep, name, typ, defined, z, zeff, natorb, eheat, &
362 beta, sto_exponents, uss, upp, udd, uff, alp, eisol, gss, gsp, gpp, gp2, &
363 acoul, nr, de, ass, asp, app, hsp, gsd, gpd, gdd, ppddg, dpddg, ngauss)
364
365 TYPE(semi_empirical_type), POINTER :: sep
366 CHARACTER(LEN=default_string_length), &
367 INTENT(OUT), OPTIONAL :: name
368 INTEGER, INTENT(OUT), OPTIONAL :: typ
369 LOGICAL, INTENT(OUT), OPTIONAL :: defined
370 INTEGER, INTENT(OUT), OPTIONAL :: z
371 REAL(kind=dp), INTENT(OUT), OPTIONAL :: zeff
372 INTEGER, INTENT(OUT), OPTIONAL :: natorb
373 REAL(kind=dp), OPTIONAL :: eheat
374 REAL(kind=dp), DIMENSION(:), OPTIONAL, POINTER :: beta, sto_exponents
375 REAL(kind=dp), OPTIONAL :: uss, upp, udd, uff, alp, eisol, gss, &
376 gsp, gpp, gp2, acoul
377 INTEGER, INTENT(OUT), OPTIONAL :: nr
378 REAL(kind=dp), OPTIONAL :: de, ass, asp, app, hsp, gsd, gpd, gdd
379 REAL(kind=dp), DIMENSION(2), OPTIONAL :: ppddg, dpddg
380 INTEGER, INTENT(OUT), OPTIONAL :: ngauss
381
382 IF (ASSOCIATED(sep)) THEN
383 IF (PRESENT(name)) name = sep%name
384 IF (PRESENT(typ)) typ = sep%typ
385 IF (PRESENT(defined)) defined = sep%defined
386 IF (PRESENT(z)) z = sep%z
387 IF (PRESENT(zeff)) zeff = sep%zeff
388 IF (PRESENT(natorb)) natorb = sep%natorb
389 IF (PRESENT(eheat)) eheat = sep%eheat
390 IF (PRESENT(beta)) beta => sep%beta
391 IF (PRESENT(sto_exponents)) sto_exponents => sep%sto_exponents
392 IF (PRESENT(ngauss)) ngauss = sep%ngauss
393 IF (PRESENT(uss)) uss = sep%uss
394 IF (PRESENT(upp)) upp = sep%upp
395 IF (PRESENT(udd)) udd = sep%udd
396 IF (PRESENT(uff)) uff = sep%uff
397 IF (PRESENT(alp)) alp = sep%alp
398 IF (PRESENT(eisol)) eisol = sep%eisol
399 IF (PRESENT(nr)) nr = sep%nr
400 IF (PRESENT(acoul)) acoul = sep%acoul
401 IF (PRESENT(de)) de = sep%de
402 IF (PRESENT(ass)) ass = sep%ass
403 IF (PRESENT(asp)) asp = sep%asp
404 IF (PRESENT(app)) app = sep%app
405 IF (PRESENT(gss)) gss = sep%gss
406 IF (PRESENT(gsp)) gsp = sep%gsp
407 IF (PRESENT(gpp)) gpp = sep%gpp
408 IF (PRESENT(gp2)) gp2 = sep%gp2
409 IF (PRESENT(hsp)) hsp = sep%hsp
410 IF (PRESENT(gsd)) gsd = sep%gsd
411 IF (PRESENT(gpd)) gpd = sep%gpd
412 IF (PRESENT(gdd)) gdd = sep%gdd
413 IF (PRESENT(ppddg)) ppddg = sep%pre
414 IF (PRESENT(dpddg)) dpddg = sep%d
415 ELSE
416 cpabort("The pointer sep is not associated")
417 END IF
418
419 END SUBROUTINE get_se_param
420
421! **************************************************************************************************
422!> \brief Set info from the semi-empirical type
423!> \param sep ...
424!> \param name ...
425!> \param typ ...
426!> \param defined ...
427!> \param z ...
428!> \param zeff ...
429!> \param natorb ...
430!> \param eheat ...
431!> \param beta ...
432!> \param sto_exponents ...
433!> \param uss ...
434!> \param upp ...
435!> \param udd ...
436!> \param uff ...
437!> \param alp ...
438!> \param eisol ...
439!> \param gss ...
440!> \param gsp ...
441!> \param gpp ...
442!> \param gp2 ...
443!> \param acoul ...
444!> \param nr ...
445!> \param de ...
446!> \param ass ...
447!> \param asp ...
448!> \param app ...
449!> \param hsp ...
450!> \param gsd ...
451!> \param gpd ...
452!> \param gdd ...
453!> \param ppddg ...
454!> \param dpddg ...
455!> \param ngauss ...
456! **************************************************************************************************
457 SUBROUTINE set_se_param(sep, name, typ, defined, z, zeff, natorb, eheat, &
458 beta, sto_exponents, uss, upp, udd, uff, alp, eisol, gss, gsp, gpp, gp2, &
459 acoul, nr, de, ass, asp, app, hsp, gsd, gpd, gdd, ppddg, dpddg, ngauss)
460
461 TYPE(semi_empirical_type), POINTER :: sep
462 CHARACTER(LEN=default_string_length), INTENT(IN), &
463 OPTIONAL :: name
464 INTEGER, INTENT(IN), OPTIONAL :: typ
465 LOGICAL, INTENT(IN), OPTIONAL :: defined
466 INTEGER, INTENT(IN), OPTIONAL :: z
467 REAL(kind=dp), INTENT(IN), OPTIONAL :: zeff
468 INTEGER, INTENT(IN), OPTIONAL :: natorb
469 REAL(kind=dp), OPTIONAL :: eheat
470 REAL(dp), DIMENSION(0:), OPTIONAL :: beta
471 REAL(kind=dp), DIMENSION(:), OPTIONAL :: sto_exponents
472 REAL(kind=dp), OPTIONAL :: uss, upp, udd, uff, alp, eisol, gss, &
473 gsp, gpp, gp2, acoul
474 INTEGER, INTENT(IN), OPTIONAL :: nr
475 REAL(kind=dp), OPTIONAL :: de, ass, asp, app, hsp, gsd, gpd, gdd
476 REAL(dp), DIMENSION(2), OPTIONAL :: ppddg, dpddg
477 INTEGER, INTENT(IN), OPTIONAL :: ngauss
478
479 IF (ASSOCIATED(sep)) THEN
480 IF (PRESENT(name)) sep%name = name
481 IF (PRESENT(typ)) sep%typ = typ
482 IF (PRESENT(defined)) sep%defined = defined
483 IF (PRESENT(z)) sep%z = z
484 IF (PRESENT(zeff)) sep%zeff = zeff
485 IF (PRESENT(natorb)) sep%natorb = natorb
486 IF (PRESENT(eheat)) sep%eheat = eheat
487 IF (PRESENT(beta)) sep%beta = beta
488 IF (PRESENT(sto_exponents)) sep%sto_exponents = sto_exponents
489 IF (PRESENT(ngauss)) sep%ngauss = ngauss
490 IF (PRESENT(uss)) sep%uss = uss
491 IF (PRESENT(upp)) sep%upp = upp
492 IF (PRESENT(udd)) sep%udd = udd
493 IF (PRESENT(uff)) sep%uff = uff
494 IF (PRESENT(alp)) sep%alp = alp
495 IF (PRESENT(eisol)) sep%eisol = eisol
496 IF (PRESENT(acoul)) sep%acoul = acoul
497 IF (PRESENT(nr)) sep%nr = nr
498 IF (PRESENT(de)) sep%de = de
499 IF (PRESENT(ass)) sep%ass = ass
500 IF (PRESENT(asp)) sep%asp = asp
501 IF (PRESENT(app)) sep%app = app
502 IF (PRESENT(gss)) sep%gss = gss
503 IF (PRESENT(gsp)) sep%gsp = gsp
504 IF (PRESENT(gpp)) sep%gpp = gpp
505 IF (PRESENT(gp2)) sep%gp2 = gp2
506 IF (PRESENT(hsp)) sep%hsp = hsp
507 IF (PRESENT(gsd)) sep%gsd = gsd
508 IF (PRESENT(gpd)) sep%gpd = gpd
509 IF (PRESENT(gdd)) sep%gdd = gdd
510 IF (PRESENT(ppddg)) sep%pre = ppddg
511 IF (PRESENT(dpddg)) sep%d = dpddg
512 ELSE
513 cpabort("The pointer sep is not associated")
514 END IF
515
516 END SUBROUTINE set_se_param
517
518! **************************************************************************************************
519!> \brief Creates rotmat type
520!> \param rotmat ...
521! **************************************************************************************************
522 SUBROUTINE rotmat_create(rotmat)
523 TYPE(rotmat_type), POINTER :: rotmat
524
525 cpassert(.NOT. ASSOCIATED(rotmat))
526 ALLOCATE (rotmat)
527
528 END SUBROUTINE rotmat_create
529
530! **************************************************************************************************
531!> \brief Releases rotmat type
532!> \param rotmat ...
533! **************************************************************************************************
534 SUBROUTINE rotmat_release(rotmat)
535 TYPE(rotmat_type), POINTER :: rotmat
536
537 IF (ASSOCIATED(rotmat)) THEN
538 DEALLOCATE (rotmat)
539 END IF
540
541 END SUBROUTINE rotmat_release
542
543! **************************************************************************************************
544!> \brief Setup the Semiempirical integral control type
545!> \param se_int_control ...
546!> \param shortrange ...
547!> \param do_ewald_r3 ...
548!> \param do_ewald_gks ...
549!> \param integral_screening ...
550!> \param max_multipole ...
551!> \param pc_coulomb_int ...
552!> \author Teodoro Laino [tlaino] - 12.2008
553! **************************************************************************************************
554 SUBROUTINE setup_se_int_control_type(se_int_control, shortrange, do_ewald_r3, &
555 do_ewald_gks, integral_screening, max_multipole, pc_coulomb_int)
556 TYPE(se_int_control_type) :: se_int_control
557 LOGICAL, INTENT(IN) :: shortrange, do_ewald_r3, do_ewald_gks
558 INTEGER, INTENT(IN) :: integral_screening, max_multipole
559 LOGICAL, INTENT(IN) :: pc_coulomb_int
560
561 se_int_control%shortrange = shortrange
562 se_int_control%do_ewald_r3 = do_ewald_r3
563 se_int_control%integral_screening = integral_screening
564 ! This makes the assignment independent of the value of the different constants
565 SELECT CASE (max_multipole)
566 CASE (do_multipole_none)
567 se_int_control%max_multipole = -1
569 se_int_control%max_multipole = 0
571 se_int_control%max_multipole = 1
573 se_int_control%max_multipole = 2
574 END SELECT
575
576 se_int_control%do_ewald_gks = do_ewald_gks
577 se_int_control%pc_coulomb_int = pc_coulomb_int
578 NULLIFY (se_int_control%ewald_gks%dg, se_int_control%ewald_gks%pw_pool)
579
580 END SUBROUTINE setup_se_int_control_type
581
582! **************************************************************************************************
583!> \brief Creates the taper type used in SE calculations
584!> \param se_taper ...
585!> \param integral_screening ...
586!> \param do_ewald ...
587!> \param taper_cou ...
588!> \param range_cou ...
589!> \param taper_exc ...
590!> \param range_exc ...
591!> \param taper_scr ...
592!> \param range_scr ...
593!> \param taper_lrc ...
594!> \param range_lrc ...
595!> \author Teodoro Laino [tlaino] - 03.2009
596! **************************************************************************************************
597 SUBROUTINE se_taper_create(se_taper, integral_screening, do_ewald, &
598 taper_cou, range_cou, taper_exc, range_exc, taper_scr, range_scr, &
599 taper_lrc, range_lrc)
600 TYPE(se_taper_type), POINTER :: se_taper
601 INTEGER, INTENT(IN) :: integral_screening
602 LOGICAL, INTENT(IN) :: do_ewald
603 REAL(kind=dp), INTENT(IN) :: taper_cou, range_cou, taper_exc, &
604 range_exc, taper_scr, range_scr, &
605 taper_lrc, range_lrc
606
607 cpassert(.NOT. ASSOCIATED(se_taper))
608 ALLOCATE (se_taper)
609 NULLIFY (se_taper%taper)
610 NULLIFY (se_taper%taper_cou)
611 NULLIFY (se_taper%taper_exc)
612 NULLIFY (se_taper%taper_lrc)
613 NULLIFY (se_taper%taper_add)
614 ! Create the sub-typo taper
615 CALL taper_create(se_taper%taper_cou, taper_cou, range_cou)
616 CALL taper_create(se_taper%taper_exc, taper_exc, range_exc)
617 IF (integral_screening == do_se_is_kdso_d) THEN
618 CALL taper_create(se_taper%taper_add, taper_scr, range_scr)
619 END IF
620 IF ((integral_screening /= do_se_is_slater) .AND. do_ewald) THEN
621 CALL taper_create(se_taper%taper_lrc, taper_lrc, range_lrc)
622 END IF
623 END SUBROUTINE se_taper_create
624
625! **************************************************************************************************
626!> \brief Releases the taper type used in SE calculations
627!> \param se_taper ...
628!> \author Teodoro Laino [tlaino] - 03.2009
629! **************************************************************************************************
630 SUBROUTINE se_taper_release(se_taper)
631 TYPE(se_taper_type), POINTER :: se_taper
632
633 IF (ASSOCIATED(se_taper)) THEN
634 CALL taper_release(se_taper%taper_cou)
635 CALL taper_release(se_taper%taper_exc)
636 CALL taper_release(se_taper%taper_lrc)
637 CALL taper_release(se_taper%taper_add)
638
639 DEALLOCATE (se_taper)
640 END IF
641 END SUBROUTINE se_taper_release
642
643! **************************************************************************************************
644!> \brief Writes the semi-empirical type
645!> \param sep ...
646!> \param subsys_section ...
647!> \par History
648!> 04.2008 Teodoro Laino [tlaino] - University of Zurich: rewriting with
649!> support for the whole set of parameters
650! **************************************************************************************************
651 SUBROUTINE write_se_param(sep, subsys_section)
652
653 TYPE(semi_empirical_type), POINTER :: sep
654 TYPE(section_vals_type), POINTER :: subsys_section
655
656 CHARACTER(LEN=1), DIMENSION(0:3), PARAMETER :: orb_lab = (/"S", "P", "D", "F"/)
657 CHARACTER(LEN=2), DIMENSION(0:3), PARAMETER :: z_lab = (/"ZS", "ZP", "ZD", "ZF"/)
658 CHARACTER(LEN=3), DIMENSION(0:3), PARAMETER :: zeta_lab = (/"ZSN", "ZPN", "ZDN", "ZFN"/)
659 CHARACTER(LEN=5), DIMENSION(0:3), PARAMETER :: &
660 beta_lab = (/"BETAS", "BETAP", "BETAD", "BETAF"/)
661 CHARACTER(LEN=default_string_length) :: i_string, name
662 INTEGER :: i, l, natorb, ngauss, nr, output_unit, &
663 typ, z
664 LOGICAL :: defined
665 REAL(kind=dp) :: acoul, alp, app, asp, ass, de, eheat, &
666 eisol, gp2, gpp, gsp, gss, hsp, udd, &
667 uff, upp, uss, zeff
668 CHARACTER(LEN=3), DIMENSION(0:3), PARAMETER :: u_lab = (/"USS", "UPP", "UDD", "UFF"/)
669
670 REAL(kind=dp), DIMENSION(0:3) :: u
671 REAL(kind=dp), DIMENSION(2) :: dpddg, ppddg
672 REAL(kind=dp), DIMENSION(:), POINTER :: beta, sexp
673 TYPE(cp_logger_type), POINTER :: logger
674
675 NULLIFY (logger)
676 logger => cp_get_default_logger()
677 IF (ASSOCIATED(sep) .AND. btest(cp_print_key_should_output(logger%iter_info, subsys_section, &
678 "PRINT%KINDS/SE_PARAMETERS"), cp_p_file)) THEN
679
680 output_unit = cp_print_key_unit_nr(logger, subsys_section, "PRINT%KINDS/SE_PARAMETERS", &
681 extension=".Log")
682
683 IF (output_unit > 0) THEN
684 CALL get_se_param(sep, name=name, typ=typ, defined=defined, &
685 z=z, zeff=zeff, natorb=natorb, eheat=eheat, beta=beta, &
686 sto_exponents=sexp, uss=uss, upp=upp, udd=udd, uff=uff, &
687 alp=alp, eisol=eisol, gss=gss, gsp=gsp, gpp=gpp, gp2=gp2, &
688 de=de, ass=ass, asp=asp, app=app, hsp=hsp, ppddg=ppddg, &
689 acoul=acoul, nr=nr, dpddg=dpddg, ngauss=ngauss)
690
691 u(0) = uss
692 u(1) = upp
693 u(2) = udd
694 u(3) = uff
695
696 SELECT CASE (typ)
697 CASE DEFAULT
698 cpabort("Semiempirical method unknown")
699 CASE (do_method_am1)
700 WRITE (unit=output_unit, fmt="(/,A,T35,A,T67,A14)") &
701 " Semi empirical parameters: ", "Austin Model 1 (AM1)", trim(name)
702 CASE (do_method_rm1)
703 WRITE (unit=output_unit, fmt="(/,A,T35,A,T67,A14)") &
704 " Semi empirical parameters: ", "Recife Model 1 (RM1)", trim(name)
705 CASE (do_method_pm3)
706 WRITE (unit=output_unit, fmt="(/,A,T35,A,T67,A14)") &
707 " Semi empirical parameters: ", "Parametric Method 3 (PM3) ", trim(name)
708 CASE (do_method_pnnl)
709 WRITE (unit=output_unit, fmt="(/,A,T35,A,T67,A14)") &
710 " Semi empirical parameters: ", "PNNL method ", trim(name)
711 CASE (do_method_pm6)
712 WRITE (unit=output_unit, fmt="(/,A,T35,A,T67,A14)") &
713 " Semi empirical parameters: ", "Parametric Method 6 (PM6) ", trim(name)
714 CASE (do_method_pm6fm)
715 WRITE (unit=output_unit, fmt="(/,A,T35,A,T67,A14)") &
716 " Semi empirical parameters: ", "Parametric Method 6 (PM6-FM) ", trim(name)
717 CASE (do_method_pdg)
718 WRITE (unit=output_unit, fmt="(/,A,T35,A,T67,A14)") &
719 " Semi empirical parameters: ", "PDDG/PM3 ", trim(name)
720 CASE (do_method_mndo)
721 WRITE (unit=output_unit, fmt="(/,A,T35,A,T67,A14)") &
722 " Semi empirical parameters: ", "MNDO ", trim(name)
723 CASE (do_method_mndod)
724 WRITE (unit=output_unit, fmt="(/,A,T35,A,T67,A14)") &
725 " Semi empirical parameters: ", "MNDOD", trim(name)
726 END SELECT
727
728 ! If defined print all its semi-empirical parameters
729 IF (defined) THEN
730 WRITE (unit=output_unit, fmt="(T16,A,T71,F10.2)") &
731 "Effective core charge:", zeff
732 WRITE (unit=output_unit, fmt="(T16,A,T71,I10)") &
733 "Number of orbitals:", natorb, &
734 "Basis set expansion (STO-NG)", ngauss
735 WRITE (unit=output_unit, fmt="(T16,A,T66,F15.5)") &
736 "Atomic heat of formation [kcal/mol]:", eheat*kcalmol
737 DO l = 0, 3
738 IF (abs(beta(l)) > 0._dp) THEN
739 WRITE (unit=output_unit, fmt="(T16,A,I2)") "Parameters for Shell: ", l
740 WRITE (unit=output_unit, fmt="(T22,A5,T30,A,T64,F17.4)") &
741 adjustr(z_lab(l)), "- "//"Slater Exponent for "//orb_lab(l)//" [A]: ", sexp(l)
742 WRITE (unit=output_unit, fmt="(T22,A5,T30,A,T64,F17.4)") &
743 adjustr(u_lab(l)), "- "//"One Center Energy for "//orb_lab(l)//" [eV]: ", u(l)*evolt
744 WRITE (unit=output_unit, fmt="(T22,A5,T30,A,T64,F17.4)") &
745 adjustr(beta_lab(l)), "- "//"Beta Parameter for "//orb_lab(l)//" [eV]: ", beta(l)*evolt
746 WRITE (unit=output_unit, fmt="(T22,A5,T30,A,T64,F17.4)") &
747 adjustr(zeta_lab(l)), "- "//"Internal Exponent for "//orb_lab(l)//" [a.u.]: ", sep%zn(l)
748 END IF
749 END DO
750 WRITE (unit=output_unit, fmt="(/,T16,A)") "Additional Parameters (Derived or Fitted):"
751 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
752 adjustr("ALP"), "- "//"Alpha Parameter for Core [A^-1]: ", alp/angstrom
753 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
754 adjustr("EISOL"), "- "//"Atomic Energy (Calculated) [eV]: ", eisol*evolt
755 ! One center Two electron Integrals
756 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
757 adjustr("GSS"), "- "//"One Center Integral (SS ,SS ) [eV]: ", gss*evolt
758 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
759 adjustr("GSP"), "- "//"One Center Integral (SS ,PP ) [eV]: ", gsp*evolt
760 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
761 adjustr("GPP"), "- "//"One Center Integral (PP ,PP ) [eV]: ", gpp*evolt
762 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
763 adjustr("GP2"), "- "//"One Center Integral (PP*,PP*) [eV]: ", gp2*evolt
764 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
765 adjustr("HSP"), "- "//"One Center Integral (SP ,SP ) [eV]: ", hsp*evolt
766 ! Slater Condon Parameters
767 IF (sep%dorb) THEN
768 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
769 adjustr("F0DD"), "- "//"Slater Condon Parameter F0DD [eV]: ", sep%f0dd
770 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
771 adjustr("F2DD"), "- "//"Slater Condon Parameter F2DD [eV]: ", sep%f2dd
772 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
773 adjustr("F4DD"), "- "//"Slater Condon Parameter F4DD [eV]: ", sep%f4dd
774 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
775 adjustr("FOSD"), "- "//"Slater Condon Parameter FOSD [eV]: ", sep%f0sd
776 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
777 adjustr("G2SD"), "- "//"Slater Condon Parameter G2SD [eV]: ", sep%g2sd
778 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
779 adjustr("F0PD"), "- "//"Slater Condon Parameter F0PD [eV]: ", sep%f0pd
780 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
781 adjustr("F2PD"), "- "//"Slater Condon Parameter F2PD [eV]: ", sep%f2pd
782 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
783 adjustr("G1PD"), "- "//"Slater Condon Parameter G1PD [eV]: ", sep%g1pd
784 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
785 adjustr("G3PD"), "- "//"Slater Condon Parameter G3PD [eV]: ", sep%g3pd
786 END IF
787 ! Charge Separation
788 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
789 adjustr("DD2"), "- "//"Charge Separation SP, L=1 [bohr]: ", sep%cs(2)
790 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
791 adjustr("DD3"), "- "//"Charge Separation PP, L=2 [bohr]: ", sep%cs(3)
792 IF (sep%dorb) THEN
793 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
794 adjustr("DD4"), "- "//"Charge Separation SD, L=2 [bohr]: ", sep%cs(4)
795 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
796 adjustr("DD5"), "- "//"Charge Separation PD, L=1 [bohr]: ", sep%cs(5)
797 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
798 adjustr("DD6"), "- "//"Charge Separation DD, L=2 [bohr]: ", sep%cs(6)
799 END IF
800 ! Klopman-Ohno Terms
801 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
802 adjustr("PO1"), "- "//"Klopman-Ohno term, SS, L=0 [bohr]: ", sep%ko(1)
803 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
804 adjustr("PO2"), "- "//"Klopman-Ohno term, SP, L=1 [bohr]: ", sep%ko(2)
805 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
806 adjustr("PO3"), "- "//"Klopman-Ohno term, PP, L=2 [bohr]: ", sep%ko(3)
807 IF (sep%dorb) THEN
808 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
809 adjustr("PO4"), "- "//"Klopman-Ohno term, SD, L=2 [bohr]: ", sep%ko(4)
810 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
811 adjustr("PO5"), "- "//"Klopman-Ohno term, PD, L=1 [bohr]: ", sep%ko(5)
812 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
813 adjustr("PO6"), "- "//"Klopman-Ohno term, DD, L=2 [bohr]: ", sep%ko(6)
814 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
815 adjustr("PO7"), "- "//"Klopman-Ohno term, PP, L=0 [bohr]: ", sep%ko(7)
816 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
817 adjustr("PO8"), "- "//"Klopman-Ohno term, DD, L=0 [bohr]: ", sep%ko(8)
818 END IF
819 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
820 adjustr("PO9"), "- "//"Klopman-Ohno term, CORE [bohr]: ", sep%ko(9)
821 SELECT CASE (typ)
823 IF (typ == do_method_pnnl) THEN
824 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
825 adjustr("ASS"), "- "//" SS polarization [au]: ", sep%ass
826 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
827 adjustr("ASP"), "- "//" SP polarization [au]: ", sep%asp
828 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
829 adjustr("APP"), "- "//" PP polarization[au]: ", sep%app
830 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
831 adjustr("DE"), "- "//" Dispersion Parameter [eV]: ", sep%de*evolt
832 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
833 adjustr("ACOUL"), "- "//" Slater parameter: ", sep%acoul
834 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,I12)") &
835 adjustr("NR"), "- "//" Slater parameter: ", sep%nr
836 ELSEIF ((typ == do_method_am1 .OR. typ == do_method_rm1) .AND. sep%z == 5) THEN
837 ! Standard case
838 DO i = 1, SIZE(sep%bfn1, 1)
839 i_string = cp_to_string(i)
840 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
841 adjustr("FN1"//trim(adjustl(i_string))//"_ALL"), &
842 "- "//"Core-Core VDW, Multiplier [a.u.]: ", sep%bfn1(i, 1)
843 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
844 adjustr("FN2"//trim(adjustl(i_string))//"_ALL"), &
845 "- "//"Core-Core VDW, Exponent [a.u.]: ", sep%bfn2(i, 1)
846 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
847 adjustr("FN3"//trim(adjustl(i_string))//"_ALL"), &
848 "- "//"Core-Core VDW, Position [a.u.]: ", sep%bfn3(i, 1)
849 END DO
850 ! Special Case : Hydrogen
851 DO i = 1, SIZE(sep%bfn1, 1)
852 i_string = cp_to_string(i)
853 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
854 adjustr("FN1"//trim(adjustl(i_string))//"_H"), &
855 "- "//"Core-Core VDW, Multiplier [a.u.]: ", sep%bfn1(i, 2)
856 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
857 adjustr("FN2"//trim(adjustl(i_string))//"_H"), &
858 "- "//"Core-Core VDW, Exponent [a.u.]: ", sep%bfn2(i, 2)
859 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
860 adjustr("FN3"//trim(adjustl(i_string))//"_H"), &
861 "- "//"Core-Core VDW, Position [a.u.]: ", sep%bfn3(i, 2)
862 END DO
863 ! Special Case : Carbon
864 DO i = 1, SIZE(sep%bfn1, 1)
865 i_string = cp_to_string(i)
866 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
867 adjustr("FN1"//trim(adjustl(i_string))//"_C"), &
868 "- "//"Core-Core VDW, Multiplier [a.u.]: ", sep%bfn1(i, 3)
869 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
870 adjustr("FN2"//trim(adjustl(i_string))//"_C"), &
871 "- "//"Core-Core VDW, Exponent [a.u.]: ", sep%bfn2(i, 3)
872 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
873 adjustr("FN3"//trim(adjustl(i_string))//"_C"), &
874 "- "//"Core-Core VDW, Position [a.u.]: ", sep%bfn3(i, 3)
875 END DO
876 ! Special Case : Halogens
877 DO i = 1, SIZE(sep%bfn1, 1)
878 i_string = cp_to_string(i)
879 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
880 adjustr("FN1"//trim(adjustl(i_string))//"_HALO"), &
881 "- "//"Core-Core VDW, Multiplier [a.u.]: ", sep%bfn1(i, 4)
882 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
883 adjustr("FN2"//trim(adjustl(i_string))//"_HALO"), &
884 "- "//"Core-Core VDW, Exponent [a.u.]: ", sep%bfn2(i, 4)
885 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
886 adjustr("FN3"//trim(adjustl(i_string))//"_HALO"), &
887 "- "//"Core-Core VDW, Position [a.u.]: ", sep%bfn3(i, 4)
888 END DO
889 ELSE
890 DO i = 1, SIZE(sep%fn1, 1)
891 i_string = cp_to_string(i)
892 ! Skip the printing of params that are zero..
893 IF (sep%fn1(i) == 0.0_dp .AND. sep%fn2(i) == 0.0_dp .AND. sep%fn3(i) == 0.0_dp) cycle
894 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
895 adjustr("FN1"//trim(adjustl(i_string))), &
896 "- "//"Core-Core VDW, Multiplier [a.u.]: ", sep%fn1(i)
897 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
898 adjustr("FN2"//trim(adjustl(i_string))), &
899 "- "//"Core-Core VDW, Exponent [a.u.]: ", sep%fn2(i)
900 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T69,F12.4)") &
901 adjustr("FN3"//trim(adjustl(i_string))), &
902 "- "//"Core-Core VDW, Position [a.u.]: ", sep%fn3(i)
903 END DO
904 END IF
905 END SELECT
906 ELSE
907 WRITE (unit=output_unit, fmt="(T55,A)") "Parameters are not defined"
908 END IF
909
910 ! Additional Parameters not common to all semi-empirical methods
911 SELECT CASE (typ)
912 CASE (do_method_pdg)
913 WRITE (unit=output_unit, fmt="(T16,A11,T30,A,T52,F14.10,T67,F14.10)") &
914 adjustr("d_PDDG"), "- "//"Exponent [A^-1]:", dpddg/angstrom, &
915 adjustr("P_PDDG"), "- "//"Parameter [eV]:", ppddg*evolt
916 END SELECT
917 END IF
918 CALL cp_print_key_finished_output(output_unit, logger, subsys_section, &
919 "PRINT%KINDS/SE_PARAMETERS")
920 END IF
921 END SUBROUTINE write_se_param
922
923END MODULE semi_empirical_types
subroutine, public deallocate_sto_basis_set(sto_basis_set)
...
various routines to log and control the output. The idea is that decisions about where to log should ...
type(cp_logger_type) function, pointer, public cp_get_default_logger()
returns the default logger
routines to handle the output, The idea is to remove the decision of wheter to output and what to out...
integer function, public cp_print_key_unit_nr(logger, basis_section, print_key_path, extension, middle_name, local, log_filename, ignore_should_output, file_form, file_position, file_action, file_status, do_backup, on_file, is_new_file, mpi_io, fout)
...
subroutine, public cp_print_key_finished_output(unit_nr, logger, basis_section, print_key_path, local, ignore_should_output, on_file, mpi_io)
should be called after you finish working with a unit obtained with cp_print_key_unit_nr,...
integer, parameter, public cp_p_file
integer function, public cp_print_key_should_output(iteration_info, basis_section, print_key_path, used_print_key, first_time)
returns what should be done with the given property if btest(res,cp_p_store) then the property should...
collects all constants needed in input so that they can be used without circular dependencies
integer, parameter, public do_method_pdg
integer, parameter, public do_method_pnnl
integer, parameter, public do_se_is_kdso_d
integer, parameter, public do_method_rm1
integer, parameter, public do_method_pm3
integer, parameter, public do_method_mndo
integer, parameter, public do_method_mndod
integer, parameter, public do_method_am1
integer, parameter, public do_se_is_slater
integer, parameter, public do_method_pm6fm
integer, parameter, public do_method_pm6
objects that represent the structure of input sections and the data contained in an input section
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
integer, parameter, public default_string_length
Definition kinds.F:57
integer, parameter, public sp
Definition kinds.F:33
Multipole structure: for multipole (fixed and induced) in FF based MD.
integer, parameter, public do_multipole_quadrupole
integer, parameter, public do_multipole_dipole
integer, parameter, public do_multipole_charge
integer, parameter, public do_multipole_none
Definition of physical constants:
Definition physcon.F:68
real(kind=dp), parameter, public kcalmol
Definition physcon.F:171
real(kind=dp), parameter, public evolt
Definition physcon.F:183
real(kind=dp), parameter, public angstrom
Definition physcon.F:144
Manages a pool of grids (to be used for example as tmp objects), but can also be used to instantiate ...
Definition of the type to handle the 1/R^3 residual integral part.
subroutine, public semi_empirical_expns3_release(expns3)
Deallocate the semi-empirical type.
Definition of the semi empirical multipole integral expansions types.
subroutine, public semi_empirical_mpole_p_release(mpole)
Deallocate the semi-empirical mpole type.
Definition of the semi empirical parameter types.
subroutine, public write_se_param(sep, subsys_section)
Writes the semi-empirical type.
subroutine, public semi_empirical_create(sep)
Allocate semi-empirical type.
subroutine, public rotmat_release(rotmat)
Releases rotmat type.
subroutine, public se_taper_release(se_taper)
Releases the taper type used in SE calculations.
subroutine, public setup_se_int_control_type(se_int_control, shortrange, do_ewald_r3, do_ewald_gks, integral_screening, max_multipole, pc_coulomb_int)
Setup the Semiempirical integral control type.
subroutine, public get_se_param(sep, name, typ, defined, z, zeff, natorb, eheat, beta, sto_exponents, uss, upp, udd, uff, alp, eisol, gss, gsp, gpp, gp2, acoul, nr, de, ass, asp, app, hsp, gsd, gpd, gdd, ppddg, dpddg, ngauss)
Get info from the semi-empirical type.
subroutine, public rotmat_create(rotmat)
Creates rotmat type.
subroutine, public se_taper_create(se_taper, integral_screening, do_ewald, taper_cou, range_cou, taper_exc, range_exc, taper_scr, range_scr, taper_lrc, range_lrc)
Creates the taper type used in SE calculations.
subroutine, public semi_empirical_release(sep)
Deallocate the semi-empirical type.
Definition of the semi empirical parameter types.
Definition taper_types.F:12
subroutine, public taper_create(taper, rc, range)
Creates taper type.
Definition taper_types.F:44
subroutine, public taper_release(taper)
Releases taper type.
Definition taper_types.F:65
type of a logger, at the moment it contains just a print level starting at which level it should be l...
Manages a pool of grids (to be used for example as tmp objects), but can also be used to instantiate ...
Semi-empirical integral multipole expansion type - pointer type.
Store the value of the tapering function and possibly its derivative for screened integrals.
Taper type use in semi-empirical calculations.