(git:374b731)
Loading...
Searching...
No Matches
qs_tddfpt2_soc_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!--------------------------------------------------------------------------------------------------!
10 USE cp_fm_types, ONLY: cp_fm_release,&
12 USE dbcsr_api, ONLY: dbcsr_p_type,&
13 dbcsr_release
14 USE kinds, ONLY: dp
20
21 IMPLICIT NONE
22
23 PUBLIC :: soc_env_type, soc_env_create, &
26
27 PRIVATE
28
29 !! Helper copied from xas_tdp_types
30 TYPE grid_atom_p_type
31 TYPE(grid_atom_type), POINTER :: grid_atom => null()
32 END TYPE grid_atom_p_type
33
34 TYPE harmonics_atom_p_type
35 TYPE(harmonics_atom_type), POINTER :: harmonics_atom => null()
36 END TYPE harmonics_atom_p_type
37
38!*************************************************************************************************
39! \brief: This structure contains the static matrices for the soc-correction
40! \param dbcsr_soc: the ZORA-operator within the ao-basis
41! \param dipmat: the dipole-operator within the ao-basis
42! \paramn evals_a: spin-conservin/singlet excitation energies
43! \param evals_b: spin-filp/triplet exciation energies
44! \param a_coeff: spin-conservin/singlet excitation vector
45! \param b_coeff: spin-filp/triplet exciation vectors
46! \param soc_evals: SOC-Corrected eigenvalues
47! \param soc_osc: ozillatorstrength of soc-corrected excitations
48!*************************************************************************************************
50 !! a :: singlet or spin-conserving b :: triplet or spin flip
51 TYPE(dbcsr_p_type), DIMENSION(:), POINTER :: orb_soc => null()
52 TYPE(dbcsr_p_type), DIMENSION(:), POINTER :: dipmat_ao => null()
53 TYPE(dbcsr_p_type), DIMENSION(:), POINTER :: dipmat => null()
54 REAL(dp), POINTER, DIMENSION(:) :: evals_a => null(), &
55 evals_b => null()
56 TYPE(cp_fm_type), DIMENSION(:, :), ALLOCATABLE :: cds
57 TYPE(cp_fm_type), DIMENSION(:), ALLOCATABLE :: sc, ediff
58 TYPE(cp_fm_type) :: a_coeff = cp_fm_type(), &
59 b_coeff = cp_fm_type()
60 REAL(dp), ALLOCATABLE, DIMENSION(:) :: soc_evals, &
61 soc_osc
62 END TYPE
63
64! ************************************************************************************************
65! \bief: an environment type analog to the xas_atom_env in xas_tdp_types:343
66! All unused parameters have been droped
67! \param nspins: number of spins
68! \param grid_atom_set:
69! \param harmonics_atom_set:
70! \param orb_sphi_so contains the coefficient for direct contraction from so to sgf, for the orb basis
71!*************************************************************************************************
73 INTEGER :: nspins = -1
74 TYPE(grid_atom_p_type), DIMENSION(:), POINTER :: grid_atom_set => null()
75 TYPE(harmonics_atom_p_type), DIMENSION(:), POINTER :: harmonics_atom_set => null()
76 TYPE(cp_2d_r_p_type), DIMENSION(:), POINTER :: orb_sphi_so => null()
77 TYPE(dbcsr_p_type), DIMENSION(:, :), POINTER :: soc_pp => null()
78 END TYPE
79
80CONTAINS
81
82! **************************************************************************************************
83!> \brief ...
84!> \param soc_env ...
85! **************************************************************************************************
86 SUBROUTINE soc_env_create(soc_env)
87 TYPE(soc_env_type), TARGET :: soc_env
88
89 NULLIFY (soc_env%orb_soc)
90 NULLIFY (soc_env%evals_a)
91 NULLIFY (soc_env%evals_b)
92 NULLIFY (soc_env%dipmat, soc_env%dipmat_ao)
93
94 END SUBROUTINE soc_env_create
95
96! **************************************************************************************************
97!> \brief ...
98!> \param soc_env ...
99! **************************************************************************************************
100 SUBROUTINE soc_env_release(soc_env)
101 TYPE(soc_env_type), TARGET :: soc_env
102
103 INTEGER :: i, j
104
105 IF (ASSOCIATED(soc_env%orb_soc)) THEN
106 DO i = 1, SIZE(soc_env%orb_soc)
107 CALL dbcsr_release(soc_env%orb_soc(i)%matrix)
108 DEALLOCATE (soc_env%orb_soc(i)%matrix)
109 END DO
110 DEALLOCATE (soc_env%orb_soc)
111 END IF
112
113 CALL cp_fm_release(soc_env%a_coeff)
114 CALL cp_fm_release(soc_env%b_coeff)
115 IF (ASSOCIATED(soc_env%evals_a)) NULLIFY (soc_env%evals_a)
116 IF (ASSOCIATED(soc_env%evals_b)) NULLIFY (soc_env%evals_b)
117 IF (ASSOCIATED(soc_env%dipmat)) THEN
118 DO i = 1, SIZE(soc_env%dipmat)
119 CALL dbcsr_release(soc_env%dipmat(i)%matrix)
120 DEALLOCATE (soc_env%dipmat(i)%matrix)
121 END DO
122 DEALLOCATE (soc_env%dipmat)
123 END IF
124 IF (ASSOCIATED(soc_env%dipmat_ao)) THEN
125 DO i = 1, SIZE(soc_env%dipmat_ao)
126 CALL dbcsr_release(soc_env%dipmat_ao(i)%matrix)
127 DEALLOCATE (soc_env%dipmat_ao(i)%matrix)
128 END DO
129 DEALLOCATE (soc_env%dipmat_ao)
130 END IF
131 IF (ALLOCATED(soc_env%soc_evals)) DEALLOCATE (soc_env%soc_evals)
132 IF (ALLOCATED(soc_env%soc_osc)) DEALLOCATE (soc_env%soc_osc)
133 IF (ALLOCATED(soc_env%CdS)) THEN
134 DO i = 1, SIZE(soc_env%CdS, 1)
135 DO j = 1, SIZE(soc_env%CdS, 2)
136 CALL cp_fm_release(soc_env%CdS(i, j))
137 END DO
138 END DO
139 DEALLOCATE (soc_env%CdS)
140 END IF
141 IF (ALLOCATED(soc_env%SC)) THEN
142 DO i = 1, SIZE(soc_env%SC)
143 CALL cp_fm_release(soc_env%SC(i))
144 CALL cp_fm_release(soc_env%ediff(i))
145 END DO
146 DEALLOCATE (soc_env%SC, soc_env%ediff)
147 END IF
148
149 END SUBROUTINE soc_env_release
150
151! ************************************************************************************************
152!*************************************************************************************************
153
154! **************************************************************************************************
155!> \brief ...
156!> \param soc_atom_env ...
157! **************************************************************************************************
158 SUBROUTINE soc_atom_create(soc_atom_env)
159 TYPE(soc_atom_env_type), POINTER :: soc_atom_env
160
161 ALLOCATE (soc_atom_env)
162
163 soc_atom_env%nspins = 1
164 NULLIFY (soc_atom_env%grid_atom_set)
165 NULLIFY (soc_atom_env%harmonics_atom_set)
166 NULLIFY (soc_atom_env%orb_sphi_so)
167 NULLIFY (soc_atom_env%soc_pp)
168
169 END SUBROUTINE soc_atom_create
170
171! **************************************************************************************************
172!> \brief ...
173!> \param soc_atom_env ...
174! **************************************************************************************************
175 SUBROUTINE soc_atom_release(soc_atom_env)
176 TYPE(soc_atom_env_type), POINTER :: soc_atom_env
177
178 INTEGER :: i
179
180 IF (ASSOCIATED(soc_atom_env%grid_atom_set)) THEN
181 DO i = 1, SIZE(soc_atom_env%grid_atom_set)
182 IF (ASSOCIATED(soc_atom_env%grid_atom_set(i)%grid_atom)) THEN
183 CALL deallocate_grid_atom(soc_atom_env%grid_atom_set(i)%grid_atom)
184 END IF
185 END DO
186 DEALLOCATE (soc_atom_env%grid_atom_set)
187 END IF
188
189 IF (ASSOCIATED(soc_atom_env%harmonics_atom_set)) THEN
190 DO i = 1, SIZE(soc_atom_env%harmonics_atom_set)
191 IF (ASSOCIATED(soc_atom_env%harmonics_atom_set(i)%harmonics_atom)) THEN
192 CALL deallocate_harmonics_atom(soc_atom_env%harmonics_atom_set(i)%harmonics_atom)
193 END IF
194 END DO
195 DEALLOCATE (soc_atom_env%harmonics_atom_set)
196 END IF
197
198 IF (ASSOCIATED(soc_atom_env%orb_sphi_so)) THEN
199 DO i = 1, SIZE(soc_atom_env%orb_sphi_so)
200 IF (ASSOCIATED(soc_atom_env%orb_sphi_so(i)%array)) THEN
201 DEALLOCATE (soc_atom_env%orb_sphi_so(i)%array)
202 END IF
203 END DO
204 DEALLOCATE (soc_atom_env%orb_sphi_so)
205 END IF
206
207 IF (ASSOCIATED(soc_atom_env%soc_pp)) CALL dbcsr_deallocate_matrix_set(soc_atom_env%soc_pp)
208
209 !Clean-up libint
211
212 DEALLOCATE (soc_atom_env)
213
214 END SUBROUTINE soc_atom_release
215
216END MODULE qs_tddfpt2_soc_types
various utilities that regard array of different kinds: output, allocation,... maybe it is not a good...
DBCSR operations in CP2K.
represent a full matrix distributed on many processors
Definition cp_fm_types.F:15
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
Interface to the Libint-Library or a c++ wrapper.
subroutine, public cp_libint_static_cleanup()
subroutine, public deallocate_grid_atom(grid_atom)
Deallocate a Gaussian-type orbital (GTO) basis set data set.
subroutine, public deallocate_harmonics_atom(harmonics)
Deallocate the spherical harmonics set for the atom grid.
subroutine, public soc_env_create(soc_env)
...
subroutine, public soc_atom_release(soc_atom_env)
...
subroutine, public soc_atom_create(soc_atom_env)
...
subroutine, public soc_env_release(soc_env)
...
represent a pointer to a 2d array
represent a full matrix