(git:374b731)
Loading...
Searching...
No Matches
qs_dftb_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 DFTB parameter types.
10!> \author JGH (24.02.2007)
11! **************************************************************************************************
13
14 USE kinds, ONLY: default_string_length,&
15 dp
16#include "./base/base_uses.f90"
17
18 IMPLICIT NONE
19
20 PRIVATE
21
22! *** Global parameters ***
23
24 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'qs_dftb_types'
25
26! **************************************************************************************************
28 ! PRIVATE
29 CHARACTER(LEN=default_string_length) :: typ
30 CHARACTER(LEN=default_string_length) :: name
31 LOGICAL :: defined
32 INTEGER :: z !atomic number
33 REAL(kind=dp) :: zeff !effective core charge
34 INTEGER :: natorb !number of orbitals
35 INTEGER :: lmax !max angular momentum
36 REAL(kind=dp), DIMENSION(0:3) :: skself !orbital energy
37 REAL(kind=dp), DIMENSION(0:3) :: occupation !free atom occupation
38 REAL(kind=dp), DIMENSION(0:3) :: eta !orbital hardness
39 REAL(kind=dp) :: energy !free atom energy
40 REAL(kind=dp) :: cutoff !cutoff radius for f matrix
41 REAL(kind=dp) :: xi, di !London parameter
42 REAL(kind=dp) :: rcdisp !cutoff radius for vdW
43 REAL(kind=dp) :: dudq !DFTB3 hardness derivative
44 END TYPE qs_dftb_atom_type
45
46! **************************************************************************************************
48 REAL(kind=dp) :: dgrd ! grid spacing
49 INTEGER :: ngrd ! number of grid points
50 INTEGER :: ngrdcut ! grid cutoff
51 INTEGER :: llm ! number of interactions (l,l,m)
52 INTEGER :: n_urpoly ! order of polynomial
53 REAL(kind=dp) :: urep_cut ! cutoff for repulsive pot.
54 REAL(kind=dp), DIMENSION(10) :: urep ! coefficients for repulsive
55 ! potential in polynomial form
56 INTEGER :: spdim ! number of points for
57 ! spline representation
58 REAL(kind=dp) :: s_cut ! left-hand cutoff
59 REAL(kind=dp), DIMENSION(3) :: srep ! coefficients for extrapolation
60 REAL(kind=dp), DIMENSION(:, :), POINTER :: spxr ! spline points
61 REAL(kind=dp), DIMENSION(:, :), POINTER :: scoeff ! spline coefficients
62 REAL(kind=dp), DIMENSION(2) :: surr ! coefficients for last point
63 REAL(kind=dp), DIMENSION(:, :), POINTER :: fmat ! Slater-Koster table (Hamiltonian)
64 REAL(kind=dp), DIMENSION(:, :), POINTER :: smat ! Slater-Koster table (overlap)
65 ! van der Waals parameter
66 REAL(kind=dp) :: xij, dij ! standard LJ parameters
67 REAL(kind=dp) :: x0ij ! Evdw(x0) = 0
68 REAL(kind=dp) :: a, b, c ! Short range polynomial coeffs
70
71! *** Public data types ***
72
75
76CONTAINS
77
78! **************************************************************************************************
79!> \brief ...
80!> \param pairpot ...
81! **************************************************************************************************
82 SUBROUTINE qs_dftb_pairpot_init(pairpot)
83 TYPE(qs_dftb_pairpot_type), DIMENSION(:, :), &
84 POINTER :: pairpot
85
86 INTEGER :: i, j
87
88 IF (ASSOCIATED(pairpot)) THEN
89 DO i = 1, SIZE(pairpot, 1)
90 DO j = 1, SIZE(pairpot, 2)
91 NULLIFY (pairpot(i, j)%spxr, pairpot(i, j)%scoeff, &
92 pairpot(i, j)%smat, pairpot(i, j)%fmat)
93 END DO
94 END DO
95 END IF
96
97 END SUBROUTINE qs_dftb_pairpot_init
98
99! **************************************************************************************************
100!> \brief ...
101!> \param pairpot ...
102!> \param ngrd ...
103!> \param llm ...
104!> \param spdim ...
105! **************************************************************************************************
106 SUBROUTINE qs_dftb_pairpot_create(pairpot, ngrd, llm, spdim)
107 TYPE(qs_dftb_pairpot_type) :: pairpot
108 INTEGER, INTENT(IN) :: ngrd, llm, spdim
109
110 pairpot%ngrd = ngrd
111 pairpot%spdim = spdim
112 pairpot%llm = llm
113
114 IF (spdim > 0) THEN
115 ALLOCATE (pairpot%spxr(spdim, 2))
116
117 ALLOCATE (pairpot%scoeff(spdim, 4))
118 END IF
119
120 ALLOCATE (pairpot%fmat(ngrd, llm))
121
122 ALLOCATE (pairpot%smat(ngrd, llm))
123
124 END SUBROUTINE qs_dftb_pairpot_create
125
126! **************************************************************************************************
127!> \brief ...
128!> \param pairpot ...
129! **************************************************************************************************
130 SUBROUTINE qs_dftb_pairpot_release(pairpot)
131 TYPE(qs_dftb_pairpot_type), DIMENSION(:, :), &
132 POINTER :: pairpot
133
134 INTEGER :: i, j, n1, n2
135
136 IF (ASSOCIATED(pairpot)) THEN
137 n1 = SIZE(pairpot, 1)
138 n2 = SIZE(pairpot, 2)
139 DO i = 1, n1
140 DO j = 1, n2
141 IF (ASSOCIATED(pairpot(i, j)%spxr)) THEN
142 DEALLOCATE (pairpot(i, j)%spxr)
143 END IF
144 IF (ASSOCIATED(pairpot(i, j)%scoeff)) THEN
145 DEALLOCATE (pairpot(i, j)%scoeff)
146 END IF
147 IF (ASSOCIATED(pairpot(i, j)%smat)) THEN
148 DEALLOCATE (pairpot(i, j)%smat)
149 END IF
150 IF (ASSOCIATED(pairpot(i, j)%fmat)) THEN
151 DEALLOCATE (pairpot(i, j)%fmat)
152 END IF
153 END DO
154 END DO
155 DEALLOCATE (pairpot)
156 END IF
157
158 END SUBROUTINE qs_dftb_pairpot_release
159
160END MODULE qs_dftb_types
161
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
Definition of the DFTB parameter types.
subroutine, public qs_dftb_pairpot_init(pairpot)
...
subroutine, public qs_dftb_pairpot_create(pairpot, ngrd, llm, spdim)
...
subroutine, public qs_dftb_pairpot_release(pairpot)
...