(git:374b731)
Loading...
Searching...
No Matches
qs_linres_nmr_epr_common_utils.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 given the response wavefunctions obtained by the application
10!> of the (rxp), p, and ((dk-dl)xp) operators,
11!> here the current density vector (jx, jy, jz)
12!> is computed for the 3 directions of the magnetic field (Bx, By, Bz)
13!> \par History
14!> created 02-2006 [MI]
15!> \author MI
16! **************************************************************************************************
18 USE kinds, ONLY: dp
19 USE mathconstants, ONLY: gaussi
21 USE pw_methods, ONLY: pw_transfer
23 USE pw_types, ONLY: pw_c1d_gs_type
24#include "./base/base_uses.f90"
25
26 IMPLICIT NONE
27
28 PRIVATE
29
30 ! *** Public subroutines ***
31 PUBLIC :: mult_g_ov_g2_grid
32
33 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'qs_linres_nmr_epr_common_utils'
34
35CONTAINS
36
37! **************************************************************************************************
38!> \brief Given the current density on the PW grid in reciprcal space
39!> (obtained by FFT), calculate the integral
40!> \int_{r}[ ((r-r') x j(r))/|r-r'|^3 ] = Bind(r')
41!> which in reciprcal space reads (for G/=0)
42!> i G/|G|^2 x J(G)
43!> \param pw_pool ...
44!> \param rho_gspace ...
45!> \param funcG_times_rho ...
46!> \param idir ...
47!> \param my_chi ...
48!> \author MI
49!> \note
50!> The G=0 component is not comnputed here, but can be evaluated
51!> through the susceptibility and added to the shift in a second time
52!>
53!> This method would not work for a non periodic system
54!> It should be generalized like the calculation of Hartree
55! **************************************************************************************************
56 SUBROUTINE mult_g_ov_g2_grid(pw_pool, rho_gspace, funcG_times_rho, idir, my_chi)
57
58 TYPE(pw_pool_type), POINTER :: pw_pool
59 TYPE(pw_c1d_gs_type), INTENT(IN) :: rho_gspace
60 TYPE(pw_c1d_gs_type), INTENT(INOUT) :: funcg_times_rho
61 INTEGER, INTENT(IN) :: idir
62 REAL(dp), INTENT(IN) :: my_chi
63
64 INTEGER :: handle, ig, ng
65 REAL(dp) :: g2
66 TYPE(pw_c1d_gs_type) :: influence_fn
67 TYPE(pw_grid_type), POINTER :: grid
68 CHARACTER(len=*), PARAMETER :: routinen = 'mult_G_ov_G2_grid'
69
70 CALL timeset(routinen, handle)
71
72 CALL pw_pool%create_pw(influence_fn)
73
74 grid => influence_fn%pw_grid
75 DO ig = grid%first_gne0, grid%ngpts_cut_local
76 g2 = grid%gsq(ig)
77 influence_fn%array(ig) = gaussi*grid%g(idir, ig)/g2
78 END DO ! ig
79 IF (grid%have_g0) influence_fn%array(1) = 0.0_dp
80
81 CALL pw_transfer(rho_gspace, funcg_times_rho)
82
83 ng = SIZE(grid%gsq)
84 funcg_times_rho%array(1:ng) = funcg_times_rho%array(1:ng)*influence_fn%array(1:ng)
85 IF (grid%have_g0) funcg_times_rho%array(1) = my_chi
86
87 CALL pw_pool%give_back_pw(influence_fn)
88
89 CALL timestop(handle)
90
91 END SUBROUTINE mult_g_ov_g2_grid
92
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
Definition of mathematical constants and functions.
complex(kind=dp), parameter, public gaussi
Manages a pool of grids (to be used for example as tmp objects), but can also be used to instantiate ...
given the response wavefunctions obtained by the application of the (rxp), p, and ((dk-dl)xp) operato...
subroutine, public mult_g_ov_g2_grid(pw_pool, rho_gspace, funcg_times_rho, idir, my_chi)
Given the current density on the PW grid in reciprcal space (obtained by FFT), calculate the integral...
Manages a pool of grids (to be used for example as tmp objects), but can also be used to instantiate ...