Electron Hamiltonian class
The electronic Hamiltonian is derived from the abstract Hamiltonian.
type, extends(hamiltonian_abst_t) :: hamiltonian_elec_t
! Components are public by default
!> The Hamiltonian must know what are the "dimensions" of the spaces,
!! in order to be able to operate on the states.
type(space_t), private :: space
type(states_elec_dim_t) :: d
type(hamiltonian_elec_base_t) :: hm_base
type(energy_t), allocatable :: energy
type(absorbing_boundaries_t) :: abs_boundaries !< absorbing boundaries
FLOAT, allocatable :: vhartree(:) !< Hartree potential
FLOAT, allocatable :: vxc(:,:) !< XC potential
FLOAT, allocatable :: vhxc(:,:) !< XC potential + Hartree potential + Berry potential
FLOAT, allocatable :: vtau(:,:) !< Derivative of e_XC w.r.t. tau
FLOAT, allocatable :: vberry(:,:) !< Berry phase potential from external E_field
type(derivatives_t), pointer, private :: der !< pointer to derivatives
type(ions_t), pointer :: ions
FLOAT :: exx_coef !< how much of EXX to mix
type(poisson_t) :: psolver !< Poisson solver
!> The self-induced vector potential and magnetic field
logical :: self_induced_magnetic
FLOAT, allocatable :: a_ind(:, :)
FLOAT, allocatable :: b_ind(:, :)
integer :: theory_level !< copied from sys%ks
type(xc_t), pointer :: xc !< pointer to xc object
type(epot_t) :: ep !< handles the external potential
type(pcm_t) :: pcm !< handles pcm variables
!> absorbing boundaries
logical, private :: adjoint
!> Mass of the particle (in most cases, mass = 1, electron mass)
FLOAT, private :: mass
!> anisotropic scaling factor for the mass: different along x,y,z etc...
FLOAT, private :: mass_scaling(MAX_DIM)
!> There may be an "inhomogeneous", "source", or "forcing" term (useful for the OCT formalism)
logical, private :: inh_term
type(states_elec_t) :: inh_st
!> There may also be a exchange-like term, similar to the one necessary for time-dependent
!! Hartree Fock, also useful only for the OCT equations
type(oct_exchange_t) :: oct_exchange
type(scissor_t) :: scissor
FLOAT :: current_time
logical, private :: apply_packed !< This is initialized by the StatesPack variable.
!> For the LDA+U
type(lda_u_t) :: lda_u
integer :: lda_u_level
logical, public :: time_zero
type(exchange_operator_t), public :: exxop
type(kpoints_t), pointer, public :: kpoints => null()
type(partner_list_t) :: external_potentials !< List with all the external potentials
FLOAT, allocatable, public :: v_ext_pot(:) !< the potential comming from external potentials
FLOAT, allocatable, public :: v_static(:) !< static scalar potential
type(ion_electron_local_potential_t) :: v_ie_loc !< Ion-electron local potential interaction
type(nlcc_t) :: nlcc !< Ion-electron NLCC interaction
type(magnetic_constrain_t) :: magnetic_constrain
!> The possible kick
type(kick_t) :: kick
contains
procedure :: update_span => hamiltonian_elec_span
procedure :: dapply => dhamiltonian_elec_apply
procedure :: zapply => zhamiltonian_elec_apply
procedure :: dmagnus_apply => dhamiltonian_elec_magnus_apply
procedure :: zmagnus_apply => zhamiltonian_elec_magnus_apply
procedure :: is_hermitian => hamiltonian_elec_hermitian
end type hamiltonian_elec_t
It contains the ‘physical’ quantities, such as
- information about the dimensionality,
- the contributions to the potential,
- a pointer to the ions,
- electronic mass,
- etc.
and an instance of hamiltonian_elec_base_t
, which bundles some lower level variables.
The separation of quantities into these two classes is mostly historic, and currently has no deeper systematics.
type hamiltonian_elec_base_t
private
integer :: nspin
FLOAT :: mass !< Needed to compute the magnetic terms, if the mass is not one.
FLOAT :: rashba_coupling
type(nl_operator_t), pointer, public :: kinetic
type(projector_matrix_t), allocatable, public :: projector_matrices(:)
FLOAT, allocatable, public :: potential(:, :)
FLOAT, allocatable, public :: Impotential(:, :)
FLOAT, allocatable, public :: uniform_magnetic_field(:)
FLOAT, allocatable, public :: uniform_vector_potential(:)
FLOAT, allocatable, public :: vector_potential(:, :)
integer, public :: nprojector_matrices
logical, public :: apply_projector_matrices
logical, public :: has_non_local_potential
integer :: full_projection_size
integer, public :: max_npoints
integer, public :: total_points
integer :: max_nprojs
logical :: projector_mix
CMPLX, allocatable, public :: projector_phases(:, :, :, :)
integer, allocatable, public :: projector_to_atom(:)
integer :: nregions
integer, public :: nphase
integer, allocatable :: regions(:)
type(accel_mem_t) :: potential_accel
type(accel_mem_t) :: impotential_accel
type(accel_mem_t), public :: vtau_accel
type(accel_mem_t) :: buff_offsets
type(accel_mem_t) :: buff_matrices
type(accel_mem_t) :: buff_maps
type(accel_mem_t) :: buff_scals
type(accel_mem_t) :: buff_position
type(accel_mem_t) :: buff_pos
type(accel_mem_t) :: buff_invmap
type(accel_mem_t), public :: buff_projector_phases
type(accel_mem_t) :: buff_mix
CMPLX, allocatable, public :: phase(:, :)
CMPLX, allocatable, public :: phase_corr(:,:)
CMPLX, allocatable, public :: phase_spiral(:,:)
type(accel_mem_t), public :: buff_phase
type(accel_mem_t), public :: buff_phase_spiral
integer, public :: buff_phase_qn_start
logical :: projector_self_overlap !< if .true. some projectors overlap with themselves
FLOAT, pointer, public :: spin(:,:,:)
end type hamiltonian_elec_base_t
The method for application of the Hamiltonian, is implemented as a wrapper routine, which checks the compatibility of the supplied wave functions, and then calls the batched version of the routine.
This batched routine now takes care of the actual application of the various terms of the Hamiltonian. The different terms to be applied
can be selected using the optional terms
argument.
The Hamiltonian is only allowed to modify the wave functions. The reason why also the initial state psib
has intent(INOUT)
is that the Hamiltonian can pack the wave functions, if requested.