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