Octopus
rkb_projector.F90
Go to the documentation of this file.
1!! Copyright (C) 2002-2006 M. Marques, A. Castro, A. Rubio, G. Bertsch
2!!
3!! This program is free software; you can redistribute it and/or modify
4!! it under the terms of the GNU General Public License as published by
5!! the Free Software Foundation; either version 2, or (at your option)
6!! any later version.
7!!
8!! This program is distributed in the hope that it will be useful,
9!! but WITHOUT ANY WARRANTY; without even the implied warranty of
10!! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
11!! GNU General Public License for more details.
12!!
13!! You should have received a copy of the GNU General Public License
14!! along with this program; if not, write to the Free Software
15!! Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
16!! 02110-1301, USA.
17!!
18
19#include "global.h"
20
22 use debug_oct_m
23 use global_oct_m
24 use mesh_oct_m
26 use mpi_oct_m
29 use ps_oct_m
32
33 implicit none
34
35 private
36 public :: &
43
48 private
49 integer :: n_s
50 integer, public :: n_c
51 complex(real64), allocatable :: bra(:, :)
52 complex(real64), public, allocatable :: ket(:, :, :, :)
53 real(real64), public, allocatable :: f(:, :, :)
54 end type rkb_projector_t
55
56
57contains
58
59 ! ---------------------------------------------------------
60 subroutine rkb_projector_init(rkb_p, sm, spec, l, lm, so_strength)
61 type(rkb_projector_t), intent(inout) :: rkb_p
62 type(submesh_t), intent(in) :: sm
63 class(pseudopotential_t), intent(in) :: spec
64 integer, intent(in) :: l, lm
65 real(real64), intent(in) :: so_strength
66
67 integer :: i
68
69 push_sub(rkb_projector_init)
70
71 rkb_p%n_s = sm%np
72 rkb_p%n_c = spec%ps%projectors_per_l(l+1)
73 assert(mod(rkb_p%n_c, 2) == 0)
74 assert(spec%ps%relativistic_treatment == proj_j_dependent)
75
76 !Allocate memory
77 safe_allocate(rkb_p%bra(1:rkb_p%n_s, 1:rkb_p%n_c))
78 safe_allocate(rkb_p%ket(1:rkb_p%n_s, 1:rkb_p%n_c, 1:2, 1:2))
79 safe_allocate(rkb_p%f(1:rkb_p%n_c, 1:2, 1:2))
80
81 ! Build projectors
82 ! He only need P^{m,m}, P^{m+1,m}, and P^{m-1,m}, for l+1/2 and for l-1/2.
83 ! If we use Vanderbilt-type multi-projector per l, we repeat this for each pair of (l+1/2,l-1/2) projectors.
84 ! For instead ONCVPSP uses 2 projector per l, so rkb_p%n_c is 4
85 do i = 1, rkb_p%n_c
86 call pseudopotential_nl_projector(spec, rkb_p%n_s, sm%rel_x, sm%r, l, lm, i, rkb_p%ket(:, i, 1, 1))
87 rkb_p%bra(:, i) = conjg(rkb_p%ket(:, i, 1, 1))
88 rkb_p%ket(:, i, 2, 2) = rkb_p%ket(:, i, 1, 1)
89
90 if (lm /= l) then
91 call pseudopotential_nl_projector(spec, rkb_p%n_s, sm%rel_x, sm%r, l, lm+1, i, rkb_p%ket(:, i, 2, 1))
92 else
93 rkb_p%ket(:, i, 2, 1) = m_z0
94 end if
95 if (lm /= -l) then
96 call pseudopotential_nl_projector(spec, rkb_p%n_s, sm%rel_x, sm%r, l, lm-1, i, rkb_p%ket(:, i, 1, 2))
97 else
98 rkb_p%ket(:, i, 1, 2) = m_z0
99 end if
100 end do
101
102 ! The l- and m-dependent prefactors are included in the KB energies
103 ! See Eq. B.7 in the thesis of M. Oliveira
104 do i = 0, rkb_p%n_c/2-1
105 rkb_p%f(i*2+1, 1, 1) = real(l + so_strength*lm + 1, real64) ! S_{\up\up}
106 rkb_p%f(i*2+1, 2, 1) = so_strength*sqrt(real((l + lm + 1)*(l - lm), real64)) ! S_{\down\up}
107 rkb_p%f(i*2+1, 1, 2) = so_strength*sqrt(real((l - lm + 1)*(l + lm), real64)) ! S_{\up\down}
108 rkb_p%f(i*2+1, 2, 2) = real(l - so_strength*lm + 1, real64) ! S_{\down\down}
109 rkb_p%f(i*2+2, 1, 1) = real(l - so_strength*lm, real64) ! S_{\up\up}
110 rkb_p%f(i*2+2, 2, 1) = -so_strength*sqrt(real((l + lm + 1)*(l - lm), real64)) ! S_{\down\up}
111 rkb_p%f(i*2+2, 1, 2) = -so_strength*sqrt(real((l - lm + 1)*(l + lm), real64)) ! S_{\up\down}
112 rkb_p%f(i*2+2, 2, 2) = real(l + so_strength*lm, real64) ! S_{\down\down}
113 end do
114 rkb_p%f = rkb_p%f/real(2*l + 1, real64)
115
116 ! Multiply by the KB energies
117 do i = 1, rkb_p%n_c
118 rkb_p%f(i, :, :) = rkb_p%f(i, :, :) * spec%ps%h(l, i, i)
119 end do
120
121 pop_sub(rkb_projector_init)
122 end subroutine rkb_projector_init
123
124 ! ---------------------------------------------------------
125 subroutine rkb_projector_end(rkb_p)
126 type(rkb_projector_t), intent(inout) :: rkb_p
127
128 push_sub(rkb_projector_end)
129
130 safe_deallocate_a(rkb_p%bra)
131 safe_deallocate_a(rkb_p%ket)
132 safe_deallocate_a(rkb_p%f)
133
134 pop_sub(rkb_projector_end)
135 end subroutine rkb_projector_end
136
137 ! ---------------------------------------------------------
138 subroutine rkb_project(mesh, sm, rkb_p, psi, ppsi)
139 type(mesh_t), intent(in) :: mesh
140 type(submesh_t), intent(in) :: sm
141 type(rkb_projector_t), intent(in) :: rkb_p
142 complex(real64), intent(in) :: psi(:, :)
143 complex(real64), intent(inout) :: ppsi(:, :)
145 complex(real64) :: uvpsi(1:2, 1:rkb_p%n_c)
147 push_sub(rkb_project)
148
149 call rkb_project_bra(mesh, sm, rkb_p, psi, uvpsi)
150 call mesh%allreduce(uvpsi)
151
152 call rkb_project_ket(rkb_p, uvpsi, ppsi)
154 pop_sub(rkb_project)
155 end subroutine rkb_project
156
157 ! ---------------------------------------------------------
159 subroutine rkb_project_bra(mesh, sm, rkb_p, psi, uvpsi)
160 type(mesh_t), intent(in) :: mesh
161 type(submesh_t), intent(in) :: sm
162 type(rkb_projector_t), intent(in) :: rkb_p
163 complex(real64), intent(in) :: psi(:, :)
164 complex(real64), intent(out) :: uvpsi(:,:)
165
166 integer :: idim, n_s, is, ic
167
168 complex(real64), allocatable :: bra(:, :)
169
170#ifndef HAVE_OPENMP
171 push_sub(rkb_project_bra)
172#endif
173
174 call profiling_in("RKB_PROJECT_BRA")
175
176 uvpsi(1:2, 1:rkb_p%n_c) = m_zero
177
178 n_s = rkb_p%n_s
179
180 if (mesh%use_curvilinear) then
181 safe_allocate(bra(1:n_s, 1:rkb_p%n_c))
182 do ic = 1, rkb_p%n_c
183 bra(1:n_s, ic) = rkb_p%bra(1:n_s, ic)*mesh%vol_pp(sm%map(1:n_s))
184 do idim = 1, 2
185 do is = 1, n_s
186 uvpsi(idim, ic) = uvpsi(idim, ic) + psi(is, idim)*bra(is, ic)
187 end do
188 end do
189 end do
190 safe_deallocate_a(bra)
191 else
192 do ic = 1, rkb_p%n_c
193 do idim = 1, 2
194 do is = 1, n_s
195 uvpsi(idim, ic) = uvpsi(idim, ic) + psi(is, idim)*rkb_p%bra(is, ic)
196 end do
197 end do
198 end do
199 end if
200
201 uvpsi(1:2, 1:rkb_p%n_c) = uvpsi(1:2, 1:rkb_p%n_c)*mesh%volume_element
202
203 safe_deallocate_a(bra)
204
205 call profiling_out("RKB_PROJECT_BRA")
206
207#ifndef HAVE_OPENMP
208 pop_sub(rkb_project_bra)
209#endif
210 end subroutine rkb_project_bra
211
212 ! ---------------------------------------------------------
214 subroutine rkb_project_ket(rkb_p, uvpsi, psi)
215 type(rkb_projector_t), intent(in) :: rkb_p
216 complex(real64), intent(in) :: uvpsi(:, :)
217 complex(real64), intent(inout) :: psi(:, :)
219 integer :: idim, jdim, n_s, is, ic
220 complex(real64) :: aa
221 complex(real64) :: weight(2,2,rkb_p%n_c)
222
223#ifndef HAVE_OPENMP
224 push_sub(rkb_project_ket)
225#endif
226
227 call profiling_in("RKB_PROJECT_KET")
228
229 n_s = rkb_p%n_s
230
231 ! Weight the projectors
232 do jdim = 1, 2
233 do ic = 1, rkb_p%n_c
234 do idim = 1, 2
235 weight(jdim, idim, ic) = rkb_p%f(ic, jdim, idim)*uvpsi(idim, ic)
236 end do
237 end do
238 end do
239
240 do ic = 1, rkb_p%n_c
241 do jdim = 1, 2
242 do is = 1, n_s
243 aa = m_z0
244 do idim = 1, 2
245 aa = aa + weight(jdim, idim, ic)*rkb_p%ket(is, ic, jdim, idim)
246 end do
247 psi(is, jdim) = psi(is, jdim) + aa
248 end do
249 end do
250 end do
251
252 call profiling_out("RKB_PROJECT_KET")
253
254#ifndef HAVE_OPENMP
255 pop_sub(rkb_project_ket)
256#endif
257 end subroutine rkb_project_ket
258
259end module rkb_projector_oct_m
260
261!! Local Variables:
262!! mode: f90
263!! coding: utf-8
264!! End:
double sqrt(double __x) __attribute__((__nothrow__
real(real64), parameter, public m_zero
Definition: global.F90:188
complex(real64), parameter, public m_z0
Definition: global.F90:198
This module defines the meshes, which are used in Octopus.
Definition: mesh.F90:118
subroutine, public profiling_out(label)
Increment out counter and sum up difference between entry and exit time.
Definition: profiling.F90:623
subroutine, public profiling_in(label, exclude)
Increment in counter and save entry time.
Definition: profiling.F90:552
Definition: ps.F90:114
integer, parameter, public proj_j_dependent
Fully-relativistic j-dependent pseudopotentials.
Definition: ps.F90:173
subroutine, public pseudopotential_nl_projector(spec, np, x, r, l, lm, i, uV)
This routine returns the non-local projector, built using spherical harmonics.
subroutine, public rkb_project_bra(mesh, sm, rkb_p, psi, uvpsi)
THREADSAFE.
subroutine, public rkb_projector_init(rkb_p, sm, spec, l, lm, so_strength)
subroutine, public rkb_project_ket(rkb_p, uvpsi, psi)
THREADSAFE.
subroutine, public rkb_projector_end(rkb_p)
subroutine, public rkb_project(mesh, sm, rkb_p, psi, ppsi)
Describes mesh distribution to nodes.
Definition: mesh.F90:186
The rkb_projector data type holds the KB projectors build with total angular momentum eigenfunctions....
A submesh is a type of mesh, used for the projectors in the pseudopotentials It contains points on a ...
Definition: submesh.F90:175