Octopus
xc_vdw.F90
Go to the documentation of this file.
1!! Copyright (C) 2002-2006 M. Marques, A. Castro, A. Rubio, G. Bertsch
2!! Copyright (C) 2023 . Tancogne-Dejean
3!!
4!! This program is free software; you can redistribute it and/or modify
5!! it under the terms of the GNU General Public License as published by
6!! the Free Software Foundation; either version 2, or (at your option)
7!! any later version.
8!!
9!! This program is distributed in the hope that it will be useful,
10!! but WITHOUT ANY WARRANTY; without even the implied warranty of
11!! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
12!! GNU General Public License for more details.
13!!
14!! You should have received a copy of the GNU General Public License
15!! along with this program; if not, write to the Free Software
16!! Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
17!! 02110-1301, USA.
18!!
19
20#include "global.h"
21
23module xc_vdw_oct_m
24 use atom_oct_m
25 use debug_oct_m
26 use global_oct_m
27 use grid_oct_m
28 use ions_oct_m
29 use, intrinsic :: iso_fortran_env
35 use parser_oct_m
37 use space_oct_m
41 use vdw_ts_oct_m
42 use xc_oct_m
45
46 ! from the dftd3 library
47 use dftd3_api
48
49 implicit none
50
51 private
52 public :: &
54
55 type xc_vdw_t
56 private
57 integer, public :: vdw_correction = -1
58 logical :: self_consistent = .false.
59 type(vdw_ts_t), public :: vdw_ts
60 type(dftd3_calc) :: vdw_d3
61 real(real64), public, allocatable :: forces(:, :)
62
63 real(real64), public :: stress(3, 3)
64
65 contains
66 procedure :: init => xc_vdw_init
67 procedure :: calc => xc_vdw_calc
68 procedure :: end => xc_vdw_end
69 end type xc_vdw_t
70
71contains
72
73 ! ---------------------------------------------------------
74 subroutine xc_vdw_init(this, namespace, space, gr, xc, ions, x_id, c_id)
75 class(xc_vdw_t), intent(inout) :: this
76 type(namespace_t), intent(in) :: namespace
77 class(space_t), intent(in) :: space
78 type(grid_t), intent(in) :: gr
79 type(xc_t), intent(inout) :: xc
80 type(ions_t), intent(in) :: ions
81 integer, intent(in) :: x_id, c_id
82
83 integer :: iatom
84 type(dftd3_input) :: d3_input
85 character(len=20) :: d3func_def, d3func
86
87 push_sub(xc_vdw_init)
88
89 if (in_family(xc%family, [xc_family_libvdwxc])) then
90 call libvdwxc_set_geometry(xc%functional(func_c,1)%libvdwxc, namespace, space, gr)
91 end if
92
93 !%Variable VDWCorrection
94 !%Type integer
95 !%Default no
96 !%Section Hamiltonian::XC
97 !%Description
98 !% (Experimental) This variable selects which van der Waals
99 !% correction to apply to the correlation functional.
100 !%Option none 0
101 !% No correction is applied.
102 !%Option vdw_ts 1
103 !% The scheme of Tkatchenko and Scheffler, Phys. Rev. Lett. 102
104 !% 073005 (2009).
105 !%Option vdw_d3 3
106 !% The DFT-D3 scheme of S. Grimme, J. Antony, S. Ehrlich, and
107 !% S. Krieg, J. Chem. Phys. 132, 154104 (2010).
108 !%End
109 call parse_variable(namespace, 'VDWCorrection', option__vdwcorrection__none, this%vdw_correction)
110
111 if (this%vdw_correction /= option__vdwcorrection__none) then
112 call messages_experimental('VDWCorrection')
113
114 select case (this%vdw_correction)
115 case (option__vdwcorrection__vdw_ts)
117 !%Variable VDWSelfConsistent
118 !%Type logical
119 !%Default yes
120 !%Section Hamiltonian::XC
121 !%Description
122 !% This variable controls whether the VDW correction is applied
123 !% self-consistently, the default, or just as a correction to
124 !% the total energy. This option only works with vdw_ts.
125 !%End
126 call parse_variable(namespace, 'VDWSelfConsistent', .true., this%self_consistent)
127
128 call vdw_ts_init(this%vdw_ts, namespace, ions)
129
130 case (option__vdwcorrection__vdw_d3)
131 this%self_consistent = .false.
132
133 if (space%dim /= 3) then
134 call messages_write('xc_vdw_d3 can only be used in 3-dimensional systems')
135 call messages_fatal(namespace=namespace)
136 end if
137
138 do iatom = 1, ions%natoms
139 if (.not. ions%atom(iatom)%species%represents_real_atom()) then
140 call messages_write('xc_vdw_d3 is not implemented when non-atomic species are present')
141 call messages_fatal(namespace=namespace)
142 end if
143 end do
144
145 d3func_def = ''
146
147 ! The list of valid values can be found in 'external_libs/dftd3/core.f90'.
148 ! For the moment I include the most common ones.
149 if (x_id == option__xcfunctional__gga_x_b88 .and. c_id*libxc_c_index == option__xcfunctional__gga_c_lyp) then
150 d3func_def = 'b-lyp'
151 end if
152 if (x_id == option__xcfunctional__gga_x_pbe .and. c_id*libxc_c_index == option__xcfunctional__gga_c_pbe) then
153 d3func_def = 'pbe'
154 end if
155 if (x_id == option__xcfunctional__gga_x_pbe_sol .and. c_id*libxc_c_index == option__xcfunctional__gga_c_pbe_sol) then
156 d3func_def = 'pbesol'
157 end if
158 if (c_id*libxc_c_index == option__xcfunctional__hyb_gga_xc_b3lyp) then
159 d3func_def = 'b3-lyp'
160 end if
161 if (c_id*libxc_c_index == option__xcfunctional__hyb_gga_xc_pbeh) then
162 d3func_def = 'pbe0'
163 end if
164
165 !%Variable VDWD3Functional
166 !%Type string
167 !%Section Hamiltonian::XC
168 !%Description
169 !% (Experimental) You can use this variable to override the
170 !% parametrization used by the DFT-D3 van deer Waals
171 !% correction. Normally you need not set this variable, as the
172 !% proper value will be selected by Octopus (if available).
173 !%
174 !% This variable takes a string value, the valid values can
175 !% be found in the source file 'external_libs/dftd3/core.f90'.
176 !% For example you can use:
177 !%
178 !% VDWD3Functional = 'pbe'
179 !%
180 !%End
181 if (parse_is_defined(namespace, 'VDWD3Functional')) call messages_experimental('VDWD3Functional')
182 call parse_variable(namespace, 'VDWD3Functional', d3func_def, d3func)
183
184 if (d3func == '') then
185 call messages_write('Cannot find a matching parametrization of DFT-D3 for the current')
186 call messages_new_line()
187 call messages_write('XCFunctional. Please select a different XCFunctional, or select a')
188 call messages_new_line()
189 call messages_write('functional for DFT-D3 using the <tt>VDWD3Functional</tt> variable.')
190 call messages_fatal(namespace=namespace)
191 end if
192
193 if (space%periodic_dim /= 0 .and. space%periodic_dim /= 3) then
194 call messages_write('For partially periodic systems, the xc_vdw_d3 interaction is assumed')
195 call messages_new_line()
196 call messages_write('to be periodic in three dimensions.')
197 call messages_warning(namespace=namespace)
198 end if
199
200 call dftd3_init(this%vdw_d3, d3_input, trim(conf%share)//'/dftd3/pars.dat')
201 call dftd3_set_functional(this%vdw_d3, func = d3func, version = 4, tz = .false.)
202
203 case default
204 assert(.false.)
205 end select
206
207 else
208 this%self_consistent = .false.
209 end if
210
211 pop_sub(xc_vdw_init)
212 end subroutine xc_vdw_init
213
214 ! ---------------------------------------------------------
215 subroutine xc_vdw_end(this)
216 class(xc_vdw_t), intent(inout) :: this
217
218 push_sub(xc_vdw_end)
219
220 select case (this%vdw_correction)
221 case (option__vdwcorrection__vdw_ts)
222 call vdw_ts_end(this%vdw_ts)
223 end select
224
225 pop_sub(xc_vdw_end)
226 end subroutine xc_vdw_end
227
228 ! ---------------------------------------------------------
229 subroutine xc_vdw_calc(this, namespace, space, latt, atom, natoms, pos, gr, st, energy, vxc)
230 class(xc_vdw_t), intent(inout) :: this
231 type(namespace_t), intent(in) :: namespace
232 type(space_t), intent(in) :: space
233 type(lattice_vectors_t), intent(in) :: latt
234 type(atom_t), intent(in) :: atom(:)
235 integer, intent(in) :: natoms
236 real(real64), intent(in) :: pos(1:space%dim,1:natoms)
237 type(grid_t), intent(in) :: gr
238 type(states_elec_t), intent(inout) :: st
239 real(real64), intent(out) :: energy
240 real(real64), intent(inout) :: vxc(:,:)
241
242 integer :: ispin, iatom, idir
243 real(real64), allocatable :: vxc_vdw(:)
244 integer, allocatable :: atnum(:)
245 real(real64) :: rlattice(3, 3)
246 ! For non-periodic directions, we make the length of the box very large
247 real(real64), parameter :: aperiodic_scaling = 1000.0_real64
248
249 energy = m_zero
250 if (this%vdw_correction == option__vdwcorrection__none) return
251
252 push_sub(xc_vdw_calc)
253
254 assert(space%dim == 3)
255
256 safe_allocate(vxc_vdw(1:gr%np))
257 safe_allocate(this%forces(1:space%dim, 1:natoms))
258
259 select case (this%vdw_correction)
260
261 case (option__vdwcorrection__vdw_ts)
262 vxc_vdw = m_zero
263 call vdw_ts_calculate(this%vdw_ts, namespace, space, latt, atom, natoms, pos, &
264 gr, st%d%nspin, st%rho, energy, vxc_vdw, this%forces)
265 this%stress = m_zero
266
267 case (option__vdwcorrection__vdw_d3)
268
269 safe_allocate(atnum(1:natoms))
270
271 atnum = [(nint(atom(iatom)%species%get_z()), iatom=1, natoms)]
272
273 if (space%is_periodic()) then
274 ! DFTD3 treats interactions as 3D periodic. In the case of
275 ! mixed-periodicity, we set the length of the periodic lattice along
276 ! the non-periodic dimensions to be much larger than the system
277 ! size, such that for all practical purposes the system is treated
278 ! as isolated.
279 rlattice = latt%rlattice(1:3, 1:3)
280 if (space%periodic_dim < 3) then
281 message(1) = "Info: Using DFT-D3 van der Walls corrections for a system with mixed-periodicity,"
282 message(2) = " but DFTD3 treats system as fully periodic. Octopus will set the DFT-D3"
283 message(3) = " lattice vectors along non-periodic dimensions to a suitably large value."
284 call messages_info(3, namespace=namespace)
285
286 do idir = space%periodic_dim + 1, 3
287 rlattice(idir,idir) = (maxval(abs(pos(idir,:))) + m_one)*aperiodic_scaling
288 end do
289 end if
290 call dftd3_pbc_dispersion(this%vdw_d3, pos, atnum, rlattice, energy, this%forces, &
291 this%stress)
292 else
293 call dftd3_dispersion(this%vdw_d3, pos, atnum, energy, this%forces)
294 this%stress = m_zero
295 end if
296
297 safe_deallocate_a(atnum)
298
299 case default
300 assert(.false.)
301 end select
302
303 if (this%self_consistent) then
304 do ispin = 1, st%d%nspin
305 call lalg_axpy(gr%np, m_one, vxc_vdw, vxc(:, ispin))
306 end do
307 end if
309 safe_deallocate_a(vxc_vdw)
310
311 pop_sub(xc_vdw_calc)
312 end subroutine xc_vdw_calc
313
314end module xc_vdw_oct_m
315
316!! Local Variables:
317!! mode: f90
318!! coding: utf-8
319!! End:
constant times a vector plus a vector
Definition: lalg_basic.F90:170
real(real64) function func(r1, rn, n, a)
Definition: logrid.F90:355
real(real64), parameter, public m_zero
Definition: global.F90:187
type(conf_t), public conf
Global instance of Octopus configuration.
Definition: global.F90:177
real(real64), parameter, public m_one
Definition: global.F90:188
This module implements the underlying real-space grid.
Definition: grid.F90:117
subroutine, public libvdwxc_set_geometry(this, namespace, space, mesh)
Definition: libvdwxc.F90:229
subroutine, public messages_warning(no_lines, all_nodes, namespace)
Definition: messages.F90:543
subroutine, public messages_info(no_lines, iunit, verbose_limit, stress, all_nodes, namespace)
Definition: messages.F90:624
subroutine, public messages_new_line()
Definition: messages.F90:1146
character(len=256), dimension(max_lines), public message
to be output by fatal, warning
Definition: messages.F90:160
subroutine, public messages_fatal(no_lines, only_root_writes, namespace)
Definition: messages.F90:420
subroutine, public messages_experimental(name, namespace)
Definition: messages.F90:1097
logical function, public parse_is_defined(namespace, name)
Definition: parser.F90:502
subroutine, public vdw_ts_init(this, namespace, ions)
Definition: vdw_ts.F90:170
subroutine, public vdw_ts_calculate(this, namespace, space, latt, atom, natoms, pos, mesh, nspin, density, energy, potential, force)
Calculate the potential for the Tatchenko-Scheffler vdW correction as described in Phys....
Definition: vdw_ts.F90:264
subroutine, public vdw_ts_end(this)
Definition: vdw_ts.F90:246
integer, parameter, public xc_family_libvdwxc
integer, parameter, public libxc_c_index
integer, parameter, public func_c
Definition: xc.F90:114
pure logical function, public in_family(family, xc_families)
Definition: xc.F90:604
A module that takes care of xc contribution from vdW interactions.
Definition: xc_vdw.F90:116
subroutine xc_vdw_end(this)
Definition: xc_vdw.F90:309
subroutine xc_vdw_init(this, namespace, space, gr, xc, ions, x_id, c_id)
Definition: xc_vdw.F90:168
subroutine xc_vdw_calc(this, namespace, space, latt, atom, natoms, pos, gr, st, energy, vxc)
Definition: xc_vdw.F90:323
Description of the grid, containing information on derivatives, stencil, and symmetries.
Definition: grid.F90:168
The states_elec_t class contains all electronic wave functions.
int true(void)