17#include "./base/base_uses.f90"
23 CHARACTER(len=*),
PARAMETER,
PRIVATE :: moduleN =
'qs_energy_types'
26 REAL(kind=
dp) :: core = 0.0_dp, &
27 core_overlap = 0.0_dp, &
28 core_overlap0 = 0.0_dp, &
31 dispersion = 0.0_dp, &
32 dispersion_sc = 0.0_dp, &
39 exc_aux_fit = 0.0_dp, &
41 exc1_aux_fit = 0.0_dp, &
43 hartree_1c = 0.0_dp, &
46 image_charge = 0.0_dp, &
54 efield_core = 0.0_dp, &
55 s2_restraint = 0.0_dp, &
57 sccs_hartree = 0.0_dp, &
67 nonscf_correction = 0.0_dp, &
72 singles_corr = 0.0_dp, &
74 excited_state = 0.0_dp, &
79 surf_dipole = 0.0_dp, &
80 embed_corr = 0.0_dp, &
81 xtb_xb_inter = 0.0_dp, &
82 xtb_nonbonded = 0.0_dp
83 REAL(kind=
dp),
DIMENSION(:),
POINTER :: ddapc_restraint => null()
109 CHARACTER(len=*),
PARAMETER :: routinen =
'allocate_qs_energy'
113 CALL timeset(routinen, handle)
120 CALL timestop(handle)
135 IF (
ASSOCIATED(
qs_energy%ddapc_restraint))
THEN
140 CALL cp_abort(__location__, &
141 "The qs_energy pointer is not associated "// &
142 "and cannot be deallocated")
201 IF (.NOT.
ASSOCIATED(
qs_energy%ddapc_restraint))
THEN
206 CALL cp_abort(__location__, &
207 "The qs_energy pointer is not associated "// &
208 "and cannot be initialised")
Add the DFT+U contribution to the Hamiltonian matrix.
Defines the basic variable types.
integer, parameter, public dp
Routines to calculate MP2 energy.
compute mulliken charges we (currently) define them as c_i = 1/2 [ (PS)_{ii} + (SP)_{ii} ]
subroutine, public init_qs_energy(qs_energy)
Initialise a Quickstep energy data structure.
subroutine, public deallocate_qs_energy(qs_energy)
Deallocate a Quickstep energy data structure.
subroutine, public allocate_qs_energy(qs_energy)
Allocate and/or initialise a Quickstep energy data structure.
Perform a QUICKSTEP wavefunction optimization (single point)