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 :: &
53 xc_vdw_t, &
55
56 type xc_vdw_t
57 private
58 integer, public :: vdw_correction = -1
59 logical :: self_consistent = .false.
60 type(vdw_ts_t), public :: vdw_ts
61 type(dftd3_calc) :: vdw_d3
62 real(real64), public, allocatable :: forces(:, :)
63
64 real(real64), public :: stress(3, 3)
65
66 contains
67 procedure :: init => xc_vdw_init
68 procedure :: calc => xc_vdw_calc
69 procedure :: d3_version => xc_vdw_octopus_input_to_version
70 procedure :: end => xc_vdw_end
71 end type xc_vdw_t
72
74 ! No reason for this to be int64, but options are appended with this
75 ! precision when parsed.
76 integer(int64), parameter :: d3_lib_options(5) = [&
77 option__vdwcorrection__vdw_d2, &
78 option__vdwcorrection__vdw_d3_zero_damping, &
79 option__vdwcorrection__vdw_d3_bj, &
80 option__vdwcorrection__vdw_d3m_zero_damping, &
81 option__vdwcorrection__vdw_d3m_bj &
82 ]
83
84contains
85
87 subroutine xc_vdw_init(this, namespace, space, gr, xc, ions, x_id, c_id)
88 class(xc_vdw_t), intent(inout) :: this
89 type(namespace_t), intent(in) :: namespace
90 class(space_t), intent(in) :: space
91 type(grid_t), intent(in) :: gr
92 type(xc_t), intent(inout) :: xc
93 type(ions_t), intent(in) :: ions
94 integer, intent(in) :: x_id, c_id
95
96 integer :: iatom
97 type(dftd3_input) :: d3_input
98 character(len=20) :: d3func_def, d3func
99
100 push_sub(xc_vdw_init)
101
102 if (in_family(xc%family, [xc_family_libvdwxc])) then
103 call libvdwxc_set_geometry(xc%functional(func_c,1)%libvdwxc, namespace, space, gr)
104 end if
105
106 !%Variable VDWCorrection
107 !%Type integer
108 !%Default no
109 !%Section Hamiltonian::XC
110 !%Description
111 !% (Experimental) This variable selects which van der Waals
112 !% correction to apply to the correlation functional.
113 !%Option none 0
114 !% No correction is applied.
115 !%Option vdw_ts 1
116 !% The scheme of Tkatchenko and Scheffler, Phys. Rev. Lett. 102
117 !% 073005 (2009).
118 !%Option vdw_d2 2
119 !% DFT-D2 corrections, equivalent to specifying version = 2 in the DFTD3 library.
120 !%Option vdw_d3_zero_damping 3
121 !% DFT-D3 corrections, damping the dispersion contribution to zero for short ranges.
122 !% This is equivalent to specifying version = 3 in the DFTD3 library.
123 !% For more details, see [J. Chem. Phys. 132, 154104 (2010)](https://doi.org/10.1063/1.3382344).
124 !%Option vdw_d3_bj 4
125 !% DFT-D3 with Becke-Johnson finite-damping, variant 2. In Octopus 15.0 and older, this was only option with the DFT-D3 library, and was
126 !% specified with "vdw_d3".
127 !% This is equivalent to specifying version = 4 in the DFTD3 library.
128 !% For more details, see [Effect of the damping function in dispersion corrected density functional theory](https://doi.org/10.1002/jcc.21759).
129 !%Option vdw_d3m_zero_damping 5
130 !% DFT-D3 corrections, damping the dispersion contribution to zero for short ranges. This uses the modified damping function and parameters
131 !% of Sherrill and coworkers. For more details see [J. Phys. Chem. Lett. 2016, 7, 12, 2197–2203](https://doi.org/10.1021/acs.jpclett.6b00780)
132 !% This is equivalent to specifying version = 5 in the DFTD3 library.
133 !%Option vdw_d3m_bj 6
134 !% DFT-D3 with Becke-Johnson finite-damping, and the modified parameters of Sherrill and coworkers.
135 !% For more details see [J. Phys. Chem. Lett. 2016, 7, 12, 2197–2203](https://doi.org/10.1021/acs.jpclett.6b00780)
136 !% This is equivalent to specifying version = 6 in the DFTD3 library.
137 !%End
138 call parse_variable(namespace, 'VDWCorrection', option__vdwcorrection__none, this%vdw_correction)
139
140 if (this%vdw_correction == option__vdwcorrection__none) then
141 this%self_consistent = .false.
142 pop_sub(xc_vdw_init)
143 return
144 endif
145
146 call messages_experimental('VDWCorrection')
147
148 if( this%vdw_correction == option__vdwcorrection__vdw_ts) then
149 !%Variable VDWSelfConsistent
150 !%Type logical
151 !%Default yes
152 !%Section Hamiltonian::XC
153 !%Description
154 !% This variable controls whether the VDW correction is applied
155 !% self-consistently, the default, or just as a correction to
156 !% the total energy. This option only works with vdw_ts.
157 !%End
158 call parse_variable(namespace, 'VDWSelfConsistent', .true., this%self_consistent)
159
160 call vdw_ts_init(this%vdw_ts, namespace, ions)
162 ! DFTD3 library
163 else
164 this%self_consistent = .false.
165
166 if (space%dim /= 3) then
167 call messages_write('xc_vdw_d3 can only be used in 3-dimensional systems')
168 call messages_fatal(namespace=namespace)
169 end if
170
171 do iatom = 1, ions%natoms
172 if (.not. ions%atom(iatom)%species%represents_real_atom()) then
173 call messages_write('xc_vdw_d3 is not implemented when non-atomic species are present')
174 call messages_fatal(namespace=namespace)
175 end if
176 end do
177
178 d3func_def = ''
179
180 ! The list of valid values can be found in 'external_libs/dftd3/core.f90'.
181 ! For the moment I include the most common ones.
182 if (x_id == option__xcfunctional__gga_x_b88 .and. c_id*libxc_c_index == option__xcfunctional__gga_c_lyp) then
183 d3func_def = 'b-lyp'
184 end if
185 if (x_id == option__xcfunctional__gga_x_pbe .and. c_id*libxc_c_index == option__xcfunctional__gga_c_pbe) then
186 d3func_def = 'pbe'
187 end if
188 if (x_id == option__xcfunctional__gga_x_pbe_sol .and. c_id*libxc_c_index == option__xcfunctional__gga_c_pbe_sol) then
189 d3func_def = 'pbesol'
190 end if
191 if (c_id*libxc_c_index == option__xcfunctional__hyb_gga_xc_b3lyp) then
192 d3func_def = 'b3-lyp'
193 end if
194 if (c_id*libxc_c_index == option__xcfunctional__hyb_gga_xc_pbeh) then
195 d3func_def = 'pbe0'
196 end if
197
198 !%Variable VDWD3Functional
199 !%Type string
200 !%Section Hamiltonian::XC
201 !%Description
202 !% (Experimental) You can use this variable to override the
203 !% parametrization used by the DFT-D3 van deer Waals
204 !% correction. Normally you need not set this variable, as the
205 !% proper value will be selected by Octopus (if available).
206 !%
207 !% This variable takes a string value, the valid values can
208 !% be found in the source file 'external_libs/dftd3/core.f90'.
209 !% For example you can use:
210 !%
211 !% VDWD3Functional = 'pbe'
212 !%
213 !%End
214 if (parse_is_defined(namespace, 'VDWD3Functional')) call messages_experimental('VDWD3Functional')
215 call parse_variable(namespace, 'VDWD3Functional', d3func_def, d3func)
216
217 if (d3func == '') then
218 call messages_write('Cannot find a matching parametrization of DFT-D3 for the current')
219 call messages_new_line()
220 call messages_write('XCFunctional. Please select a different XCFunctional, or select a')
221 call messages_new_line()
222 call messages_write('functional for DFT-D3 using the <tt>VDWD3Functional</tt> variable.')
223 call messages_fatal(namespace=namespace)
224 end if
225
226 if (space%periodic_dim /= 0 .and. space%periodic_dim /= 3) then
227 call messages_write('For partially periodic systems, the xc_vdw_d3 interaction is assumed')
228 call messages_new_line()
229 call messages_write('to be periodic in three dimensions.')
230 call messages_warning(namespace=namespace)
231 end if
232
233 call dftd3_init(this%vdw_d3, d3_input, trim(conf%share)//'/dftd3/pars.dat')
234 call dftd3_set_functional(this%vdw_d3, func = d3func, version = this%d3_version(), tz = .false.)
235 endif
236
237 pop_sub(xc_vdw_init)
238 end subroutine xc_vdw_init
239
240
242 function xc_vdw_octopus_input_to_version(this) result(d3_version)
243 class(xc_vdw_t), intent(in) :: this
244
245 integer :: d3_version
246
248
249 select case (this%vdw_correction)
250 case (option__vdwcorrection__vdw_d2)
251 d3_version = 2
252 case (option__vdwcorrection__vdw_d3_zero_damping)
253 d3_version = 3
254 case (option__vdwcorrection__vdw_d3_bj)
255 d3_version = 4
256 case (option__vdwcorrection__vdw_d3m_zero_damping)
257 d3_version = 5
258 case (option__vdwcorrection__vdw_d3m_bj)
259 d3_version = 6
260 case default
261 assert(.false.)
262 end select
263
265
267
268
269 ! ---------------------------------------------------------
270 subroutine xc_vdw_end(this)
271 class(xc_vdw_t), intent(inout) :: this
272
273 push_sub(xc_vdw_end)
274
275 select case (this%vdw_correction)
276 case (option__vdwcorrection__vdw_ts)
277 call vdw_ts_end(this%vdw_ts)
278 end select
279
280 pop_sub(xc_vdw_end)
281 end subroutine xc_vdw_end
282
283 ! ---------------------------------------------------------
284 subroutine xc_vdw_calc(this, namespace, space, latt, atom, natoms, pos, gr, st, energy, vxc)
285 class(xc_vdw_t), intent(inout) :: this
286 type(namespace_t), intent(in) :: namespace
287 type(space_t), intent(in) :: space
288 type(lattice_vectors_t), intent(in) :: latt
289 type(atom_t), intent(in) :: atom(:)
290 integer, intent(in) :: natoms
291 real(real64), intent(in) :: pos(1:space%dim,1:natoms)
292 type(grid_t), intent(in) :: gr
293 type(states_elec_t), intent(inout) :: st
294 real(real64), intent(out) :: energy
295 real(real64), contiguous, intent(inout) :: vxc(:,:)
296
297 integer :: ispin, iatom, idir
298 real(real64), allocatable :: vxc_vdw(:)
299 integer, allocatable :: atnum(:)
300 real(real64) :: rlattice(3, 3)
301 ! For non-periodic directions, we make the length of the box very large
302 real(real64), parameter :: aperiodic_scaling = 1000.0_real64
303
304 energy = m_zero
305 if (this%vdw_correction == option__vdwcorrection__none) return
306
307 push_sub(xc_vdw_calc)
308
309 assert(space%dim == 3)
310
311 safe_allocate(vxc_vdw(1:gr%np))
312 safe_allocate(this%forces(1:space%dim, 1:natoms))
313
314 if(this%vdw_correction == option__vdwcorrection__vdw_ts) then
315 vxc_vdw = m_zero
316 call vdw_ts_calculate(this%vdw_ts, namespace, space, latt, atom, natoms, pos, &
317 gr, st%d%nspin, st%rho, energy, vxc_vdw, this%forces)
318 this%stress = m_zero
319
320 elseif(any(this%vdw_correction == d3_lib_options)) then
321
322 safe_allocate(atnum(1:natoms))
323
324 atnum = [(nint(atom(iatom)%species%get_z()), iatom=1, natoms)]
325
326 if (space%is_periodic()) then
327 ! DFTD3 treats interactions as 3D periodic. In the case of
328 ! mixed-periodicity, we set the length of the periodic lattice along
329 ! the non-periodic dimensions to be much larger than the system
330 ! size, such that for all practical purposes the system is treated
331 ! as isolated.
332 rlattice = latt%rlattice(1:3, 1:3)
333 if (space%periodic_dim < 3) then
334 message(1) = "Info: Using DFT-D3 van der Walls corrections for a system with mixed-periodicity,"
335 message(2) = " but DFTD3 treats system as fully periodic. Octopus will set the DFT-D3"
336 message(3) = " lattice vectors along non-periodic dimensions to a suitably large value."
337 call messages_info(3, namespace=namespace)
338
339 do idir = space%periodic_dim + 1, 3
340 rlattice(idir,idir) = (maxval(abs(pos(idir,:))) + m_one)*aperiodic_scaling
341 end do
342 end if
343 call dftd3_pbc_dispersion(this%vdw_d3, pos, atnum, rlattice, energy, this%forces, &
344 this%stress)
345 else
346 call dftd3_dispersion(this%vdw_d3, pos, atnum, energy, this%forces)
347 this%stress = m_zero
348 end if
349
350 safe_deallocate_a(atnum)
351
352 else
353 assert(.false.)
354 endif
355
356 if (this%self_consistent) then
357 do ispin = 1, st%d%nspin
358 call lalg_axpy(gr%np, m_one, vxc_vdw, vxc(:, ispin))
359 end do
360 end if
361
362 safe_deallocate_a(vxc_vdw)
364 pop_sub(xc_vdw_calc)
365 end subroutine xc_vdw_calc
366
367end module xc_vdw_oct_m
368
369!! Local Variables:
370!! mode: f90
371!! coding: utf-8
372!! 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
integer, parameter, private libxc_c_index
Definition: species.F90:276
Tkatchenko-Scheffler pairwise method for van der Waals (vdW, dispersion) interactions.
Definition: vdw_ts.F90:119
subroutine, public vdw_ts_init(this, namespace, ions)
Definition: vdw_ts.F90:173
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:267
subroutine, public vdw_ts_end(this)
Definition: vdw_ts.F90:249
integer, parameter, public xc_family_libvdwxc
integer, parameter, public func_c
Definition: xc.F90:114
pure logical function, public in_family(family, xc_families)
Definition: xc.F90:620
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:364
subroutine xc_vdw_init(this, namespace, space, gr, xc, ions, x_id, c_id)
Initialize a xc_vdw_t instance.
Definition: xc_vdw.F90:181
integer function xc_vdw_octopus_input_to_version(this)
Map Octopus''s VDWCORRECTION input option to the DFTD3 library''s input option "version".
Definition: xc_vdw.F90:336
integer(int64), dimension(5), parameter, public d3_lib_options
VDWCORRECTION options that correspond to the DFT-D3 library.
Definition: xc_vdw.F90:169
subroutine xc_vdw_calc(this, namespace, space, latt, atom, natoms, pos, gr, st, energy, vxc)
Definition: xc_vdw.F90:378
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)