Octopus
orbitalbasis.F90
Go to the documentation of this file.
1!! Copyright (C) 2016 N. Tancogne-Dejean
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#include "global.h"
19
21 use accel_oct_m
24 use debug_oct_m
26 use global_oct_m
27 use io_oct_m
28 use ions_oct_m
29 use, intrinsic :: iso_fortran_env
31 use math_oct_m
33 use mesh_oct_m
38 use parser_oct_m
43 use types_oct_m
44
45 implicit none
46
47 private
48
49 public :: &
57
59 private
60 type(orbitalset_t), allocatable, public :: orbsets(:)
61
62 integer, public :: norbsets = 0
63 integer, public :: maxnorbs = 0
64 integer, public :: max_np = 0
65 integer, public :: size = 0
66 integer, allocatable, public :: global2os(:,:)
67 integer, allocatable :: os2global(:,:)
68
69 integer(int64) :: truncation
70 real(real64) :: threshold = 0.01_real64
71
72 logical, public :: normalize = .true.
73 logical, public :: use_submesh = .false.
74 logical, public :: orthogonalization = .false.
75
76 character(len=256), public :: debugdir
77
78 logical, public :: combine_j_orbitals
79 end type orbitalbasis_t
80
81contains
82
83 subroutine orbitalbasis_init(this, namespace, periodic_dim)
84 type(orbitalbasis_t), intent(inout) :: this
85 type(namespace_t), intent(in) :: namespace
86 integer, intent(in) :: periodic_dim
87
88 push_sub(orbitalbasis_init)
89
90 !%Variable AOTruncation
91 !%Type flag
92 !%Default ao_full
93 !%Section Atomic Orbitals
94 !%Description
95 !% This option determines how Octopus will truncate the orbitals used for DFT+U.
96 !% Except for the full method, the other options are only there to get a quick idea.
97 !%Option ao_full bit(0)
98 !% The full size of the orbitals used. The radius is controled by variable AOThreshold.
99 !%Option ao_box bit(1)
100 !% The radius of the orbitals are restricted to the size of the simulation box.
101 !% This reduces the number of points used to discretize the orbitals.
102 !% This is mostly a debug option, and one should be aware that changing the size of the simulation box
103 !% will affect the result of the calculation. It is recommended to use ao_nlradius instead.
104 !%Option ao_nlradius bit(2)
105 !% The radius of the orbitals are restricted to the radius of the non-local part of the pseudopotential
106 !% of the corresponding atom.
107 !%End
108 call parse_variable(namespace, 'AOTruncation', option__aotruncation__ao_full, this%truncation)
109 call messages_print_var_option('AOTruncation', this%truncation, namespace=namespace)
110
111 !%Variable AOThreshold
112 !%Type float
113 !%Default 0.01
114 !%Section Atomic Orbitals
115 !%Description
116 !% Determines the threshold used to compute the radius of the atomic orbitals for DFT+U and for Wannier90.
117 !% This radius is computed by making sure that the
118 !% absolute value of the radial part of the atomic orbital is below the specified threshold.
119 !% This value should be converged to be sure that results do not depend on this value.
120 !% However increasing this value increases the number of grid points covered by the orbitals and directly affect performances.
121 !%End
122 call parse_variable(namespace, 'AOThreshold', 0.01_real64, this%threshold)
123 if (this%threshold <= m_zero) call messages_input_error(namespace, 'AOThreshold')
124 call messages_print_var_value('AOThreshold', this%threshold, namespace=namespace)
125
126 !%Variable AONormalize
127 !%Type logical
128 !%Default yes
129 !%Section Atomic Orbitals
130 !%Description
131 !% If set to yes, Octopus will normalize the atomic orbitals individually.
132 !% This variable is ignored is <tt>AOLoewdin</tt> is set to yes.
133 !%End
134 call parse_variable(namespace, 'AONormalize', .true., this%normalize)
135 call messages_print_var_value('AONormalize', this%normalize, namespace=namespace)
136
137 !%Variable AOSubmesh
138 !%Type logical
139 !%Section Atomic Orbitals
140 !%Description
141 !% If set to yes, Octopus will use submeshes to internally store the orbitals with
142 !% their phase instead of storing them on the mesh. This is usually slower for small
143 !% periodic systems, but becomes advantageous for large supercells.
144 !% Submeshes are not compatible with Loewdin orthogonalization.
145 !% For periodic systems, the default is set to no, whereas it is set to yes for isolated systems.
146 !%End
147 if (periodic_dim > 0) then
148 call parse_variable(namespace, 'AOSubmesh', .false., this%use_submesh)
149 else
150 call parse_variable(namespace, 'AOSubmesh', .true., this%use_submesh)
151 end if
152 call messages_print_var_value('AOSubmesh', this%use_submesh, namespace=namespace)
154 !%Variable AOLoewdin
155 !%Type logical
156 !%Default no
157 !%Section Atomic Orbitals
158 !%Description
159 !% This option determines if the atomic orbital basis is orthogonalized or not.
160 !% This is done for using the Loewdin orthogonalization scheme.
161 !% The default is set to no for the moment as this option is
162 !% not yet implemented for isolated systems, and seems to lead to important egg-box effect
163 !%End
164 call parse_variable(namespace, 'AOLoewdin', .false., this%orthogonalization)
165 call messages_print_var_value('AOLoewdin', this%orthogonalization, namespace=namespace)
166 if (this%orthogonalization) call messages_experimental("AOLoewdin")
167 if (this%orthogonalization) this%normalize = .false.
168
169 !%Variable AOCombineJOrbitals
170 !%Type logical
171 !%Default no
172 !%Section Atomic Orbitals
173 !%Description
174 !% By default, Octopus creates two sets of atomic orbitals for j-dependent pseudopotentials.
175 !% When doing ACBN0 functional, this leads to a Hubbard U for j=l-1/2 and one for j=l+1/2, unless
176 !% hubbard_j is specified in the species block.
177 !% By setting this variable to yes, one can instead define a single set of atomic orbitals that
178 !% contains both the j=l-1/2 and j=l+1/2 orbitals.
179 !% This is only relevant for spinor calculations with j-dependent pseudopotentials.
180 !%End
181 call parse_variable(namespace, 'AOCombineJOrbitals', .false., this%combine_j_orbitals)
182 call messages_print_var_value('AOCombineJOrbitals', this%combine_j_orbitals, namespace=namespace)
183
184
185 if (this%orthogonalization .and. this%use_submesh) then
186 call messages_not_implemented("AOLoewdin=yes with AOSubmesh=yes.")
187 end if
188
189 if (debug%info) then
190 write(this%debugdir, '(a)') 'debug/ao_basis'
191 call io_mkdir(this%debugdir, namespace)
192 end if
193
194 pop_sub(orbitalbasis_init)
195 end subroutine orbitalbasis_init
196
197
198 subroutine orbitalbasis_end(this)
199 type(orbitalbasis_t), intent(inout) :: this
200
201 integer :: ios
202
203 push_sub(orbitalbasis_end)
204
205 do ios = 1, this%norbsets
206 call orbitalset_end(this%orbsets(ios))
207 end do
208 safe_deallocate_a(this%orbsets)
209
210 safe_deallocate_a(this%global2os)
211 safe_deallocate_a(this%os2global)
212
213 pop_sub(orbitalbasis_end)
214 end subroutine orbitalbasis_end
215
216 ! ---------------------------------------------------------
220 subroutine orbitalbasis_set_nlmj_radius(this, mesh, os, hubbard_l, hubbard_j, norb)
221 type(orbitalbasis_t), intent(in) :: this
222 type(mesh_t), intent(in) :: mesh
223 type(orbitalset_t), intent(inout) :: os
224 integer, intent(in) :: hubbard_l
225 real(real64), intent(in) :: hubbard_j
226 integer, intent(out) :: norb
227
228 integer :: iorb, i, l, m, n
229 real(real64) :: j
230
231 norb = 0
232
234
235 do iorb = 1, os%spec%get_niwfs()
236 call os%spec%get_iwf_ilm(iorb, 1, i, l, m)
237 call os%spec%get_iwf_n(iorb, 1, n)
238 call os%spec%get_iwf_j(iorb, j)
239 if (l .eq. hubbard_l .and. is_close(hubbard_j, j)) then
240 norb = norb + 1
241 call orbitalset_set_jln(os, j, hubbard_l, n)
242 os%ii = i
243 if (os%spec%is_full()) os%ii = n
244 os%radius = atomic_orbital_get_radius(os%spec, mesh, iorb, 1, &
245 this%truncation, this%threshold)
246 end if
247 end do
249 end subroutine orbitalbasis_set_nlmj_radius
250
251
252#include "undef.F90"
253#include "real.F90"
254#include "orbitalbasis_inc.F90"
255
256#include "undef.F90"
257#include "complex.F90"
258#include "orbitalbasis_inc.F90"
259
260end module orbitalbasis_oct_m
Prints out to iunit a message in the form: ["InputVariable" = value] where "InputVariable" is given b...
Definition: messages.F90:180
real(real64) function, public atomic_orbital_get_radius(species, mesh, iorb, ispin, truncation, threshold)
type(debug_t), save, public debug
Definition: debug.F90:154
real(real64), parameter, public m_zero
Definition: global.F90:187
Definition: io.F90:114
subroutine, public io_mkdir(fname, namespace, parents)
Definition: io.F90:354
This module is intended to contain "only mathematical" functions and procedures.
Definition: math.F90:115
This module defines various routines, operating on mesh functions.
This module defines the meshes, which are used in Octopus.
Definition: mesh.F90:118
subroutine, public messages_not_implemented(feature, namespace)
Definition: messages.F90:1125
subroutine, public messages_input_error(namespace, var, details, row, column)
Definition: messages.F90:723
subroutine, public messages_experimental(name, namespace)
Definition: messages.F90:1097
subroutine, public orbitalbasis_end(this)
subroutine, public zorbitalbasis_build(this, namespace, ions, mesh, kpt, ndim, skip_s_orb, use_all_orb, verbose)
This routine is an interface for constructing the orbital basis.
subroutine, public dorbitalbasis_build(this, namespace, ions, mesh, kpt, ndim, skip_s_orb, use_all_orb, verbose)
This routine is an interface for constructing the orbital basis.
subroutine, public zorbitalbasis_build_empty(this, mesh, kpt, ndim, norbsets, map_os, verbose)
This routine constructd an empty orbital basis.
subroutine, public dorbitalbasis_build_empty(this, mesh, kpt, ndim, norbsets, map_os, verbose)
This routine constructd an empty orbital basis.
subroutine orbitalbasis_set_nlmj_radius(this, mesh, os, hubbard_l, hubbard_j, norb)
Loop over orbitals for a given l and j.
subroutine, public orbitalbasis_init(this, namespace, periodic_dim)
subroutine, public orbitalset_end(this)
Definition: orbitalset.F90:229
subroutine, public orbitalset_set_jln(this, jj, ll, nn)
Definition: orbitalset.F90:263
Describes mesh distribution to nodes.
Definition: mesh.F90:186
int true(void)