37 use,
intrinsic :: iso_fortran_env
109 real(real64) :: total(3,3) =
m_zero
110 real(real64) :: kinetic(3,3) =
m_zero
111 real(real64) :: Hartree(3,3) =
m_zero
112 real(real64) :: xc(3,3) =
m_zero
114 real(real64) :: ps_nl(3,3) =
m_zero
115 real(real64) :: ion_ion(3,3) =
m_zero
116 real(real64) :: vdw(3,3) =
m_zero
117 real(real64) :: hubbard(3,3) =
m_zero
119 real(real64) :: kinetic_sumrule
120 real(real64) :: hartree_sumrule
135 type(states_elec_dim_t) :: d
138 logical :: only_userdef_istates
140 type(states_elec_group_t) :: group
141 integer :: block_size
145 logical :: pack_states
151 character(len=1024),
allocatable :: user_def_states(:,:,:)
157 real(real64),
allocatable :: rho(:,:)
158 real(real64),
allocatable :: rho_core(:)
160 real(real64),
allocatable :: current(:, :, :)
161 real(real64),
allocatable :: current_para(:, :, :)
162 real(real64),
allocatable :: current_dia(:, :, :)
163 real(real64),
allocatable :: current_mag(:, :, :)
164 real(real64),
allocatable :: current_kpt(:,:,:)
169 real(real64),
allocatable :: frozen_rho(:, :)
170 real(real64),
allocatable :: frozen_tau(:, :)
171 real(real64),
allocatable :: frozen_gdens(:,:,:)
172 real(real64),
allocatable :: frozen_ldens(:,:)
174 logical :: uniform_occ
176 real(real64),
allocatable :: eigenval(:,:)
178 logical :: restart_fixed_occ
179 logical :: restart_reorder_occs
180 real(real64),
allocatable :: occ(:,:)
181 real(real64),
allocatable :: kweights(:)
184 logical,
private :: fixed_spins
186 real(real64),
allocatable :: spin(:, :, :)
189 real(real64) :: val_charge
191 type(stress_t) :: stress_tensors
193 logical :: fromScratch
194 type(smear_t) :: smear
197 type(modelmb_particle_t) :: modelmbparticles
198 integer,
allocatable :: mmb_nspindown(:,:)
199 integer,
allocatable :: mmb_iyoung(:,:)
200 real(real64),
allocatable :: mmb_proj(:)
202 logical :: parallel_in_states = .false.
213 logical :: scalapack_compatible
217 integer :: st_start, st_end
218 integer,
allocatable :: node(:)
221 integer,
allocatable :: st_kpt_task(:,:)
224 logical :: symmetrize_density
225 integer :: randomization
226 integer :: orth_method = 0
228 real(real64) :: cl_states_mem
240 integer,
public,
parameter :: &
284 real(real64),
intent(in) :: valence_charge
287 real(real64) :: excess_charge, nempty_percent
288 integer :: nempty, ntot, default
289 integer :: nempty_conv
291 real(real64),
parameter :: tol = 1e-13_real64
300 st%d%ispin = space%ispin
305 if (st%d%ispin /=
unpolarized .and. kpoints%use_time_reversal)
then
306 message(1) =
"Time reversal symmetry is only implemented for unpolarized spins."
307 message(2) =
"Use KPointsUseTimeReversal = no."
339 write(
message(1),
'(a,i5,a)')
"Input: '", ntot,
"' is not a valid value for TotalStates."
361 write(
message(1),
'(a,i5,a)')
"Input: '", nempty,
"' is not a valid value for ExtraStates."
362 message(2) =
'(0 <= ExtraStates)'
366 if (ntot > 0 .and. nempty > 0)
then
367 message(1) =
'You cannot set TotalStates and ExtraStates at the same time.'
382 if (nempty_percent < 0)
then
383 write(
message(1),
'(a,f8.6,a)')
"Input: '", nempty_percent, &
384 "' should be a percentage value x (where x is parts in hundred) larger or equal 0"
388 if (nempty > 0 .and. nempty_percent > 0)
then
389 message(1) =
'You cannot set ExtraStates and ExtraStatesInPercent at the same time.'
407 call parse_variable(namespace,
'ExtraStatesToConverge', nempty, nempty_conv)
409 write(
message(1),
'(a,i5,a)')
"Input: '", nempty_conv,
"' is not a valid value for ExtraStatesToConverge."
410 message(2) =
'(0 <= ExtraStatesToConverge)'
414 if (nempty_conv > nempty)
then
415 message(1) =
'You cannot set ExtraStatesToConverge to a higher value than ExtraStates.'
422 st%val_charge = valence_charge
424 st%qtot = -(st%val_charge + excess_charge)
427 write(
message(1),
'(a,f12.6,a)')
'Total charge = ', st%qtot,
' < 0'
428 message(2) =
'Check Species and ExcessCharge.'
432 select case (st%d%ispin)
435 st%nst = nint(st%qtot/2)
436 if (st%nst*2 - st%qtot < -tol) st%nst = st%nst + 1
438 st%d%spin_channels = 1
441 st%nst = nint(st%qtot/2)
442 if (st%nst*2 - st%qtot < -tol) st%nst = st%nst + 1
444 st%d%spin_channels = 2
447 st%nst = nint(st%qtot)
448 if (st%nst - st%qtot < -tol) st%nst = st%nst + 1
450 st%d%spin_channels = 2
454 if (ntot < st%nst)
then
455 message(1) =
'TotalStates is smaller than the number of states required by the system.'
462 if (nempty_percent > 0)
then
463 nempty = ceiling(nempty_percent * st%nst / 100)
466 st%nst_conv = st%nst + nempty_conv
467 st%nst = st%nst + nempty
468 if (st%nst == 0)
then
469 message(1) =
"Cannot run with number of states = zero."
489 default = max(
accel%warp_size, 32)
498 call parse_variable(namespace,
'StatesBlockSize', default, st%block_size)
499 if (st%block_size < 1)
then
500 call messages_write(
"The variable 'StatesBlockSize' must be greater than 0.")
504 st%block_size = min(st%block_size, st%nst)
505 conf%target_states_block_size = st%block_size
507 safe_allocate(st%eigenval(1:st%nst, 1:st%nik))
508 st%eigenval = huge(st%eigenval)
512 if (.not. kpoints%gamma_only())
then
525 call parse_variable(namespace,
'OnlyUserDefinedInitialStates', .false., st%only_userdef_istates)
528 safe_allocate(st%occ (1:st%nst, 1:st%nik))
533 safe_allocate(st%user_def_states(1:st%d%dim, 1:st%nst, 1:st%nik))
535 st%user_def_states(1:st%d%dim, 1:st%nst, 1:st%nik) =
'undefined'
538 if (st%d%ispin ==
spinors)
then
539 safe_allocate(st%spin(1:3, 1:st%nst, 1:st%nik))
566 if (st%smear%photodop)
then
567 if (nempty == 0)
then
568 write(
message(1),
'(a,i5,a)')
"PhotoDoping requires to specify ExtraStates."
569 message(2) =
'(0 == ExtraStates)'
577 safe_allocate(st%node(1:st%nst))
578 st%node(1:st%nst) = 0
581 st%parallel_in_states = .false.
586 if (st%modelmbparticles%nparticle > 0)
then
588 safe_allocate(st%mmb_nspindown(1:st%modelmbparticles%ntype_of_particle, 1:st%nst))
589 st%mmb_nspindown(:,:) = -1
590 safe_allocate(st%mmb_iyoung(1:st%modelmbparticles%ntype_of_particle, 1:st%nst))
591 st%mmb_iyoung(:,:) = -1
592 safe_allocate(st%mmb_proj(1:st%nst))
604 call parse_variable(namespace,
'SymmetrizeDensity', kpoints%use_symmetries, st%symmetrize_density)
634 integer,
intent(out) :: nik
635 integer,
intent(out) :: dim
636 integer,
intent(out) :: nst
637 integer,
intent(out) :: ierr
639 character(len=256) :: lines(3)
640 character(len=20) :: char
650 read(lines(1), *) char, nst
651 read(lines(2), *) char, dim
652 read(lines(3), *) char, nik
672 real(real64),
intent(in) :: excess_charge
675 integer :: ik, ist, ispin, nspin, ncols, nrows, el_per_state, icol, start_pos, spin_n
677 real(real64) :: rr, charge
678 logical :: integral_occs, unoccupied_states
679 real(real64),
allocatable :: read_occs(:, :)
680 real(real64) :: charge_in_block
693 call parse_variable(namespace,
'RestartFixedOccupations', .
true., st%restart_fixed_occ)
764 integral_occs = .
true.
766 occ_fix:
if (
parse_block(namespace,
'Occupations', blk) == 0)
then
768 st%fixed_occ = .
true.
771 if (ncols > st%nst)
then
776 if (nrows /= st%nik)
then
777 call messages_input_error(namespace,
"Occupations",
"Wrong number of rows in block Occupations.")
780 do ik = 1, st%nik - 1
783 "All rows in block Occupations must have the same number of columns.")
794 safe_allocate(read_occs(1:ncols, 1:st%nik))
800 charge_in_block = charge_in_block + read_occs(icol, ik) * st%kweights(ik)
805 select case (st%d%ispin)
814 start_pos = nint((st%qtot - charge_in_block)/spin_n)
816 if (start_pos + ncols > st%nst)
then
817 message(1) =
"To balance charge, the first column in block Occupations is taken to refer to state"
818 write(
message(2),
'(a,i6,a)')
"number ", start_pos,
" but there are too many columns for the number of states."
819 write(
message(3),
'(a,i6,a)')
"Solution: set ExtraStates = ", start_pos + ncols - st%nst
824 do ist = 1, start_pos
825 st%occ(ist, ik) = el_per_state
830 do ist = start_pos + 1, start_pos + ncols
831 st%occ(ist, ik) = read_occs(ist - start_pos, ik)
832 integral_occs = integral_occs .and. &
833 abs((st%occ(ist, ik) - el_per_state) * st%occ(ist, ik)) <=
m_epsilon
838 do ist = start_pos + ncols + 1, st%nst
845 safe_deallocate_a(read_occs)
848 st%fixed_occ = .false.
849 integral_occs = .false.
856 st%qtot = -(st%val_charge + excess_charge)
859 if (st%d%nspin == 2) nspin = 2
861 do ik = 1, st%nik, nspin
864 do ispin = ik, ik + nspin - 1
865 st%occ(ist, ispin) = min(rr, -(st%val_charge + excess_charge) - charge)
866 charge = charge + st%occ(ist, ispin)
885 if (st%fixed_occ)
then
886 call parse_variable(namespace,
'RestartReorderOccs', .false., st%restart_reorder_occs)
888 st%restart_reorder_occs = .false.
891 call smear_init(st%smear, namespace, st%d%ispin, st%fixed_occ, integral_occs, kpoints)
893 unoccupied_states = (st%d%ispin /=
spinors .and. st%nst*2 > st%qtot) .or. (st%d%ispin ==
spinors .and. st%nst > st%qtot)
896 if (.not. unoccupied_states)
then
897 call messages_write(
'Smearing needs unoccupied states (via ExtraStates or TotalStates) to be useful.')
905 charge = charge + sum(st%occ(ist, 1:st%nik) * st%kweights(1:st%nik))
907 if (abs(charge - st%qtot) > 1e-6_real64)
then
908 message(1) =
"Initial occupations do not integrate to total charge."
909 write(
message(2),
'(6x,f12.6,a,f12.6)') charge,
' != ', st%qtot
936 st%fixed_spins = .false.
937 if (st%d%ispin /=
spinors)
then
976 spin_fix:
if (
parse_block(namespace,
'InitialSpins', blk) == 0)
then
984 st%fixed_spins = .
true.
986 st%spin(:, :, i) = st%spin(:, :, 1)
999 class(
mesh_t),
intent(in) :: mesh
1000 type(
type_t),
optional,
intent(in) :: wfs_type
1001 logical,
optional,
intent(in) :: skip(:)
1002 logical,
optional,
intent(in) :: packed
1006 if (
present(wfs_type))
then
1008 st%wfs_type = wfs_type
1036 type(
mesh_t),
intent(in) :: mesh
1037 logical,
optional,
intent(in) :: verbose
1038 logical,
optional,
intent(in) :: skip(:)
1039 logical,
optional,
intent(in) :: packed
1041 integer :: ib, iqn, ist, istmin, istmax
1042 logical :: same_node, verbose_, packed_
1043 integer,
allocatable :: bstart(:), bend(:)
1047 safe_allocate(bstart(1:st%nst))
1048 safe_allocate(bend(1:st%nst))
1049 safe_allocate(st%group%iblock(1:st%nst))
1058 if (
present(skip))
then
1060 if (.not. skip(ist))
then
1068 if (
present(skip))
then
1069 do ist = st%nst, istmin, -1
1070 if (.not. skip(ist))
then
1077 if (
present(skip) .and. verbose_)
then
1087 st%group%nblocks = 0
1089 do ist = istmin, istmax
1092 st%group%iblock(ist) = st%group%nblocks + 1
1095 if (st%parallel_in_states .and. ist /= istmax)
then
1098 same_node = (st%node(ist + 1) == st%node(ist))
1101 if (ib == st%block_size .or. ist == istmax .or. .not. same_node)
then
1103 st%group%nblocks = st%group%nblocks + 1
1104 bend(st%group%nblocks) = ist
1105 if (ist /= istmax) bstart(st%group%nblocks + 1) = ist + 1
1109 safe_allocate(st%group%psib(1:st%group%nblocks, st%d%kpt%start:st%d%kpt%end))
1111 safe_allocate(st%group%block_is_local(1:st%group%nblocks, 1:st%nik))
1112 st%group%block_is_local = .false.
1113 st%group%block_start = -1
1114 st%group%block_end = -2
1116 do ib = 1, st%group%nblocks
1117 if (bstart(ib) >= st%st_start .and. bend(ib) <= st%st_end)
then
1118 if (st%group%block_start == -1) st%group%block_start = ib
1119 st%group%block_end = ib
1120 do iqn = st%d%kpt%start, st%d%kpt%end
1121 st%group%block_is_local(ib, iqn) = .
true.
1124 call dwfs_elec_init(st%group%psib(ib, iqn), st%d%dim, bstart(ib), bend(ib), mesh%np_part, iqn, &
1125 special=.
true., packed=packed_)
1127 call zwfs_elec_init(st%group%psib(ib, iqn), st%d%dim, bstart(ib), bend(ib), mesh%np_part, iqn, &
1128 special=.
true., packed=packed_)
1135 safe_allocate(st%group%block_range(1:st%group%nblocks, 1:2))
1136 safe_allocate(st%group%block_size(1:st%group%nblocks))
1138 st%group%block_range(1:st%group%nblocks, 1) = bstart(1:st%group%nblocks)
1139 st%group%block_range(1:st%group%nblocks, 2) = bend(1:st%group%nblocks)
1140 st%group%block_size(1:st%group%nblocks) = bend(1:st%group%nblocks) - bstart(1:st%group%nblocks) + 1
1142 st%group%block_initialized = .
true.
1144 safe_allocate(st%group%block_node(1:st%group%nblocks, 1:st%nik))
1145 st%group%block_node = 0
1147 assert(
allocated(st%node))
1148 assert(all(st%node >= 0) .and. all(st%node < st%mpi_grp%size))
1150 do iqn = st%d%kpt%start, st%d%kpt%end
1151 do ib = st%group%block_start, st%group%block_end
1152 st%group%block_node(ib, iqn) = st%st_kpt_mpi_grp%rank
1161 do ib = 1, st%group%nblocks
1167 if (st%group%block_size(ib) > 0)
then
1197 safe_deallocate_a(bstart)
1198 safe_deallocate_a(bend)
1219 type(
grid_t),
intent(in) :: gr
1221 real(real64) :: fsize
1225 safe_allocate(st%rho(1:gr%np_part, 1:st%d%nspin))
1228 fsize = gr%np_part*8.0_real64*st%block_size
1240 class(
space_t),
intent(in) :: space
1241 class(
mesh_t),
intent(in) :: mesh
1245 if (.not.
allocated(st%current))
then
1246 safe_allocate(st%current(1:mesh%np_part, 1:space%dim, 1:st%d%nspin))
1250 if (.not.
allocated(st%current_para))
then
1251 safe_allocate(st%current_para(1:mesh%np_part, 1:space%dim, 1:st%d%nspin))
1255 if (.not.
allocated(st%current_dia))
then
1256 safe_allocate(st%current_dia(1:mesh%np_part, 1:space%dim, 1:st%d%nspin))
1260 if (.not.
allocated(st%current_mag))
then
1261 safe_allocate(st%current_mag(1:mesh%np_part, 1:space%dim, 1:st%d%nspin))
1265 if (.not.
allocated(st%current_kpt))
then
1266 safe_allocate(st%current_kpt(1:mesh%np,1:space%dim,st%d%kpt%start:st%d%kpt%end))
1344 default = option__statesorthogonalization__cholesky_serial
1345#ifdef HAVE_SCALAPACK
1347 default = option__statesorthogonalization__cholesky_parallel
1351 call parse_variable(namespace,
'StatesOrthogonalization', default, st%orth_method)
1372 call parse_variable(namespace,
'StatesCLDeviceMemory', -512.0_real64, st%cl_states_mem)
1381 subroutine states_elec_copy(stout, stin, exclude_wfns, exclude_eigenval, special)
1384 logical,
optional,
intent(in) :: exclude_wfns
1385 logical,
optional,
intent(in) :: exclude_eigenval
1386 logical,
optional,
intent(in) :: special
1388 logical :: exclude_wfns_
1397 safe_allocate_source_a(stout%kweights, stin%kweights)
1398 stout%nik = stin%nik
1401 if (stin%modelmbparticles%nparticle > 0)
then
1402 safe_allocate_source_a(stout%mmb_nspindown, stin%mmb_nspindown)
1403 safe_allocate_source_a(stout%mmb_iyoung, stin%mmb_iyoung)
1404 safe_allocate_source_a(stout%mmb_proj, stin%mmb_proj)
1407 stout%wfs_type = stin%wfs_type
1408 stout%nst = stin%nst
1409 stout%block_size = stin%block_size
1410 stout%orth_method = stin%orth_method
1412 stout%cl_states_mem = stin%cl_states_mem
1413 stout%pack_states = stin%pack_states
1416 stout%only_userdef_istates = stin%only_userdef_istates
1418 if (.not. exclude_wfns_)
then
1419 safe_allocate_source_a(stout%rho, stin%rho)
1422 stout%uniform_occ = stin%uniform_occ
1425 safe_allocate_source_a(stout%eigenval, stin%eigenval)
1426 safe_allocate_source_a(stout%occ, stin%occ)
1427 safe_allocate_source_a(stout%spin, stin%spin)
1432 stout%group%nblocks = stin%group%nblocks
1434 safe_allocate_source_a(stout%user_def_states, stin%user_def_states)
1436 safe_allocate_source_a(stout%current, stin%current)
1437 safe_allocate_source_a(stout%current_kpt, stin%current_kpt)
1438 safe_allocate_source_a(stout%rho_core, stin%rho_core)
1439 safe_allocate_source_a(stout%frozen_rho, stin%frozen_rho)
1440 safe_allocate_source_a(stout%frozen_tau, stin%frozen_tau)
1441 safe_allocate_source_a(stout%frozen_gdens, stin%frozen_gdens)
1442 safe_allocate_source_a(stout%frozen_ldens, stin%frozen_ldens)
1444 stout%fixed_occ = stin%fixed_occ
1445 stout%restart_fixed_occ = stin%restart_fixed_occ
1447 stout%fixed_spins = stin%fixed_spins
1449 stout%qtot = stin%qtot
1450 stout%val_charge = stin%val_charge
1454 stout%parallel_in_states = stin%parallel_in_states
1456 call mpi_grp_copy(stout%dom_st_kpt_mpi_grp, stin%dom_st_kpt_mpi_grp)
1457 call mpi_grp_copy(stout%st_kpt_mpi_grp, stin%st_kpt_mpi_grp)
1458 call mpi_grp_copy(stout%dom_st_mpi_grp, stin%dom_st_mpi_grp)
1459 safe_allocate_source_a(stout%node, stin%node)
1460 safe_allocate_source_a(stout%st_kpt_task, stin%st_kpt_task)
1462#ifdef HAVE_SCALAPACK
1468 stout%scalapack_compatible = stin%scalapack_compatible
1470 stout%lnst = stin%lnst
1471 stout%st_start = stin%st_start
1472 stout%st_end = stin%st_end
1476 stout%symmetrize_density = stin%symmetrize_density
1480 stout%packed = stin%packed
1482 stout%randomization = stin%randomization
1498 if (st%modelmbparticles%nparticle > 0)
then
1499 safe_deallocate_a(st%mmb_nspindown)
1500 safe_deallocate_a(st%mmb_iyoung)
1501 safe_deallocate_a(st%mmb_proj)
1508 safe_deallocate_a(st%user_def_states)
1510 safe_deallocate_a(st%rho)
1511 safe_deallocate_a(st%eigenval)
1513 safe_deallocate_a(st%current)
1514 safe_deallocate_a(st%current_para)
1515 safe_deallocate_a(st%current_dia)
1516 safe_deallocate_a(st%current_mag)
1517 safe_deallocate_a(st%current_kpt)
1518 safe_deallocate_a(st%rho_core)
1519 safe_deallocate_a(st%frozen_rho)
1520 safe_deallocate_a(st%frozen_tau)
1521 safe_deallocate_a(st%frozen_gdens)
1522 safe_deallocate_a(st%frozen_ldens)
1523 safe_deallocate_a(st%occ)
1524 safe_deallocate_a(st%spin)
1525 safe_deallocate_a(st%kweights)
1528#ifdef HAVE_SCALAPACK
1534 safe_deallocate_a(st%node)
1535 safe_deallocate_a(st%st_kpt_task)
1537 if (st%parallel_in_states)
then
1538 safe_deallocate_a(st%ap%schedule)
1550 class(
mesh_t),
intent(in) :: mesh
1552 integer,
optional,
intent(in) :: ist_start_
1553 integer,
optional,
intent(in) :: ist_end_
1554 integer,
optional,
intent(in) :: ikpt_start_
1555 integer,
optional,
intent(in) :: ikpt_end_
1556 logical,
optional,
intent(in) :: normalized
1559 integer :: ist, ik, id, ist_start, ist_end, jst, ikpt_start, ikpt_end
1560 complex(real64) :: alpha, beta
1561 real(real64),
allocatable :: dpsi(:, :)
1562 complex(real64),
allocatable :: zpsi(:, :), zpsi2(:)
1563 integer :: ikpoint, ip
1566 logical :: normalized_
1577 safe_allocate(dpsi(1:mesh%np, 1:st%d%dim))
1579 safe_allocate(zpsi(1:mesh%np, 1:st%d%dim))
1582 select case (st%d%ispin)
1585 do ik = ikpt_start, ikpt_end
1586 ikpoint = st%d%get_kpoint_index(ik)
1587 do ist = ist_start, ist_end
1591 pre_shift = mesh%pv%xlocal-1, &
1592 post_shift = mesh%pv%np_global - mesh%pv%xlocal - mesh%np + 1, &
1593 normalized = normalized)
1595 if(mesh%parallel_in_domains)
then
1601 call dmf_random(mesh, dpsi(:, 1), normalized = normalized)
1606 zpsi(ip,1) = cmplx(dpsi(ip,1),
m_zero, real64)
1615 pre_shift = mesh%pv%xlocal-1, &
1616 post_shift = mesh%pv%np_global - mesh%pv%xlocal - mesh%np + 1, &
1617 normalized = normalized)
1619 if(mesh%parallel_in_domains)
then
1625 call zmf_random(mesh, zpsi(:, 1), normalized = normalized)
1637 if (st%fixed_spins)
then
1639 do ik = ikpt_start, ikpt_end
1640 ikpoint = st%d%get_kpoint_index(ik)
1641 do ist = ist_start, ist_end
1645 pre_shift = mesh%pv%xlocal-1, &
1646 post_shift = mesh%pv%np_global - mesh%pv%xlocal - mesh%np + 1, &
1647 normalized = normalized)
1649 if(mesh%parallel_in_domains)
then
1655 call dmf_random(mesh, dpsi(:, 1), normalized = normalized)
1659 zpsi(ip,1) = cmplx(dpsi(ip,1),
m_zero, real64)
1665 pre_shift = mesh%pv%xlocal-1, &
1666 post_shift = mesh%pv%np_global - mesh%pv%xlocal - mesh%np + 1, &
1667 normalized = normalized)
1669 if(mesh%parallel_in_domains)
then
1675 call zmf_random(mesh, zpsi(:, 1), normalized = normalized)
1688 safe_allocate(zpsi2(1:mesh%np))
1689 do jst = ist_start, ist - 1
1691 zpsi(1:mesh%np, 1) = zpsi(1:mesh%np, 1) -
zmf_dotp(mesh, zpsi(:, 1), zpsi2)*zpsi2(1:mesh%np)
1693 safe_deallocate_a(zpsi2)
1696 zpsi(1:mesh%np, 2) = zpsi(1:mesh%np, 1)
1700 if (abs(alpha) >
m_zero)
then
1701 beta = cmplx(st%spin(1, ist, ik) / abs(alpha), st%spin(2, ist, ik) / abs(alpha), real64)
1703 zpsi(1:mesh%np, 1) = alpha*zpsi(1:mesh%np, 1)
1704 zpsi(1:mesh%np, 2) = beta*zpsi(1:mesh%np, 2)
1709 do ik = ikpt_start, ikpt_end
1710 do ist = ist_start, ist_end
1714 pre_shift = mesh%pv%xlocal-1, &
1715 post_shift = mesh%pv%np_global - mesh%pv%xlocal - mesh%np + 1, &
1716 normalized = .false.)
1718 if(mesh%parallel_in_domains)
then
1724 call zmf_random(mesh, zpsi(:, id), normalized = .false.)
1739 safe_deallocate_a(dpsi)
1740 safe_deallocate_a(zpsi)
1751 class(
mesh_t),
intent(in) :: mesh
1752 logical,
optional,
intent(in) :: compute_spin
1756 real(real64) :: charge
1757 complex(real64),
allocatable :: zpsi(:, :)
1762 st%nik, st%nst, st%kweights)
1769 charge = charge + sum(st%occ(ist, 1:st%nik) * st%kweights(1:st%nik))
1771 if (abs(charge-st%qtot) > 1e-6_real64)
then
1772 message(1) =
'Occupations do not integrate to total charge.'
1773 write(
message(2),
'(6x,f12.8,a,f12.8)') charge,
' != ', st%qtot
1776 message(1) =
"There don't seem to be any electrons at all!"
1786 safe_allocate(zpsi(1:mesh%np, st%d%dim))
1787 do ik = st%d%kpt%start, st%d%kpt%end
1788 do ist = st%st_start, st%st_end
1790 st%spin(1:3, ist, ik) =
state_spin(mesh, zpsi)
1793 safe_deallocate_a(zpsi)
1795 if (st%parallel_in_states .or. st%d%kpt%parallel)
then
1810 real(real64),
optional,
intent(in) :: alt_eig(st%st_start:, st%d%kpt%start:)
1819 do ik = st%d%kpt%start, st%d%kpt%end
1820 if (
present(alt_eig))
then
1821 tot = tot + st%kweights(ik) * sum(st%occ(st%st_start:st%st_end, ik) * &
1822 alt_eig(st%st_start:st%st_end, ik))
1824 tot = tot + st%kweights(ik) * sum(st%occ(st%st_start:st%st_end, ik) * &
1825 st%eigenval(st%st_start:st%st_end, ik))
1829 if (st%parallel_in_states .or. st%d%kpt%parallel)
call comm_allreduce(st%st_kpt_mpi_grp, tot)
1841 logical :: default_scalapack_compatible
1852 st%parallel_in_states = .false.
1855 call mpi_grp_init(st%dom_st_kpt_mpi_grp, mc%dom_st_kpt_comm)
1859 default_scalapack_compatible =
calc_mode_par%scalapack_compat() .and. .not. st%d%kpt%parallel
1873 call parse_variable(namespace,
'ScaLAPACKCompatible', default_scalapack_compatible, st%scalapack_compatible)
1875#ifdef HAVE_SCALAPACK
1876 if (default_scalapack_compatible .neqv. st%scalapack_compatible)
then
1877 call messages_experimental(
'Setting ScaLAPACKCompatible to other than default', namespace=namespace)
1880 if (st%scalapack_compatible)
then
1887 st%scalapack_compatible = .false.
1896 if (st%nst < st%mpi_grp%size)
then
1897 message(1) =
"Have more processors than necessary"
1898 write(
message(2),
'(i4,a,i4,a)') st%mpi_grp%size,
" processors and ", st%nst,
" states."
1902 call distributed_init(st%dist, st%nst, st%mpi_grp%comm,
"states", scalapack_compat = st%scalapack_compatible)
1904 st%parallel_in_states = st%dist%parallel
1907 st%st_start = st%dist%start
1908 st%st_end = st%dist%end
1909 st%lnst = st%dist%nlocal
1910 st%node(1:st%nst) = st%dist%node(1:st%nst)
1927 kinetic_energy_density, paramagnetic_current, density_gradient, density_laplacian, &
1928 gi_kinetic_energy_density, st_end)
1932 logical,
intent(in) :: nlcc
1933 real(real64),
contiguous,
optional,
target,
intent(out) :: kinetic_energy_density(:,:)
1934 real(real64),
contiguous,
optional,
target,
intent(out) :: paramagnetic_current(:,:,:)
1935 real(real64),
contiguous,
optional,
intent(out) :: density_gradient(:,:,:)
1936 real(real64),
contiguous,
optional,
intent(out) :: density_laplacian(:,:)
1937 real(real64),
contiguous,
optional,
intent(out) :: gi_kinetic_energy_density(:,:)
1938 integer,
optional,
intent(in) :: st_end
1940 real(real64),
pointer,
contiguous :: jp(:, :, :)
1941 real(real64),
pointer,
contiguous :: tau(:, :)
1942 complex(real64),
allocatable :: wf_psi(:,:), gwf_psi(:,:,:), wf_psi_conj(:,:), lwf_psi(:,:)
1943 real(real64),
allocatable :: abs_wf_psi(:,:), abs_gwf_psi(:,:)
1944 complex(real64),
allocatable :: psi_gpsi(:,:)
1945 complex(real64) :: c_tmp
1946 integer :: is, ik, ist, i_dim, st_dim, ii, st_end_
1947 real(real64) :: ww, kpoint(gr%der%dim)
1948 logical :: something_to_do
1956 something_to_do =
present(kinetic_energy_density) .or.
present(gi_kinetic_energy_density) .or. &
1957 present(paramagnetic_current) .or.
present(density_gradient) .or.
present(density_laplacian)
1958 assert(something_to_do)
1960 safe_allocate( wf_psi(1:gr%np_part, 1:st%d%dim))
1961 safe_allocate( wf_psi_conj(1:gr%np_part, 1:st%d%dim))
1962 safe_allocate(gwf_psi(1:gr%np, 1:gr%der%dim, 1:st%d%dim))
1963 safe_allocate(abs_wf_psi(1:gr%np, 1:st%d%dim))
1964 safe_allocate(abs_gwf_psi(1:gr%np, 1:st%d%dim))
1965 safe_allocate(psi_gpsi(1:gr%np, 1:st%d%dim))
1966 if (
present(density_laplacian))
then
1967 safe_allocate(lwf_psi(1:gr%np, 1:st%d%dim))
1971 if (
present(kinetic_energy_density)) tau => kinetic_energy_density
1974 if (
present(paramagnetic_current)) jp => paramagnetic_current
1978 if (
present(gi_kinetic_energy_density))
then
1980 safe_allocate(jp(1:gr%np, 1:gr%der%dim, 1:st%d%nspin))
1982 if (.not.
present(kinetic_energy_density))
then
1983 safe_allocate(tau(1:gr%np, 1:st%d%nspin))
1987 if (
associated(tau)) tau =
m_zero
1988 if (
associated(jp)) jp =
m_zero
1989 if (
present(density_gradient)) density_gradient(:,:,:) =
m_zero
1990 if (
present(density_laplacian)) density_laplacian(:,:) =
m_zero
1991 if (
present(gi_kinetic_energy_density)) gi_kinetic_energy_density =
m_zero
1993 do ik = st%d%kpt%start, st%d%kpt%end
1995 kpoint(1:gr%der%dim) = kpoints%get_point(st%d%get_kpoint_index(ik))
1996 is = st%d%get_spin_index(ik)
1998 do ist = st%st_start, st_end_
1999 ww = st%kweights(ik)*st%occ(ist, ik)
2005 do st_dim = 1, st%d%dim
2010 do st_dim = 1, st%d%dim
2011 call zderivatives_grad(gr%der, wf_psi(:,st_dim), gwf_psi(:,:,st_dim), set_bc = .false.)
2015 if (
present(density_laplacian))
then
2016 do st_dim = 1, st%d%dim
2017 call zderivatives_lapl(gr%der, wf_psi(:,st_dim), lwf_psi(:,st_dim), ghost_update = .false., set_bc = .false.)
2022 wf_psi_conj(1:gr%np, 1:st%d%dim) = conjg(wf_psi(1:gr%np,1:st%d%dim))
2023 abs_wf_psi(1:gr%np, 1:st%d%dim) = real(wf_psi_conj(1:gr%np, 1:st%d%dim) * wf_psi(1:gr%np, 1:st%d%dim), real64)
2025 if (
present(density_laplacian))
then
2026 density_laplacian(1:gr%np, is) = density_laplacian(1:gr%np, is) + &
2027 ww *
m_two*real(wf_psi_conj(1:gr%np, 1) * lwf_psi(1:gr%np, 1), real64)
2028 if (st%d%ispin ==
spinors)
then
2029 density_laplacian(1:gr%np, 2) = density_laplacian(1:gr%np, 2) + &
2030 ww *
m_two*real(wf_psi_conj(1:gr%np, 2) * lwf_psi(1:gr%np, 2), real64)
2033 c_tmp = ww*(lwf_psi(ii, 1) * wf_psi_conj(ii, 2) + wf_psi(ii, 1) * conjg(lwf_psi(ii, 2)))
2034 density_laplacian(ii, 3) = density_laplacian(ii, 3) + real(c_tmp, real64)
2035 density_laplacian(ii, 4) = density_laplacian(ii, 4) + aimag(c_tmp)
2040 if (
associated(tau))
then
2041 tau(1:gr%np, is) = tau(1:gr%np, is) &
2042 + ww * sum(kpoint(1:gr%der%dim)**2) * abs_wf_psi(1:gr%np, 1)
2043 if (st%d%ispin ==
spinors)
then
2044 tau(1:gr%np, 2) = tau(1:gr%np, 2) &
2045 + ww * sum(kpoint(1:gr%der%dim)**2) * abs_wf_psi(1:gr%np, 2)
2049 c_tmp = ww * sum(kpoint(1:gr%der%dim)**2) * wf_psi(ii, 1) * wf_psi_conj(ii, 2)
2050 tau(ii, 3) = tau(ii, 3) + real(c_tmp, real64)
2051 tau(ii, 4) = tau(ii, 4) + aimag(c_tmp)
2056 do i_dim = 1, gr%der%dim
2059 psi_gpsi(1:gr%np, 1:st%d%dim) = wf_psi_conj(1:gr%np, 1:st%d%dim) &
2060 * gwf_psi(1:gr%np,i_dim,1:st%d%dim)
2061 abs_gwf_psi(1:gr%np, 1:st%d%dim) = real(conjg(gwf_psi(1:gr%np, i_dim, 1:st%d%dim)) &
2062 * gwf_psi(1:gr%np, i_dim, 1:st%d%dim), real64)
2064 if (
present(density_gradient))
then
2065 density_gradient(1:gr%np, i_dim, is) = density_gradient(1:gr%np, i_dim, is) &
2066 + ww *
m_two * real(psi_gpsi(1:gr%np, 1), real64)
2067 if (st%d%ispin ==
spinors)
then
2068 density_gradient(1:gr%np, i_dim, 2) = density_gradient(1:gr%np, i_dim, 2) &
2069 + ww *
m_two*real(psi_gpsi(1:gr%np, 2), real64)
2072 c_tmp = ww * (gwf_psi(ii, i_dim, 1) * wf_psi_conj(ii, 2) + wf_psi(ii, 1) * conjg(gwf_psi(ii, i_dim, 2)))
2073 density_gradient(ii, i_dim, 3) = density_gradient(ii, i_dim, 3) + real(c_tmp, real64)
2074 density_gradient(ii, i_dim, 4) = density_gradient(ii, i_dim, 4) + aimag(c_tmp)
2079 if (
present(density_laplacian))
then
2080 call lalg_axpy(gr%np, ww*
m_two, abs_gwf_psi(:,1), density_laplacian(:,is))
2081 if (st%d%ispin ==
spinors)
then
2082 call lalg_axpy(gr%np, ww*
m_two, abs_gwf_psi(:,2), density_laplacian(:,2))
2085 c_tmp =
m_two * ww * gwf_psi(ii, i_dim, 1) * conjg(gwf_psi(ii, i_dim, 2))
2086 density_laplacian(ii, 3) = density_laplacian(ii, 3) + real(c_tmp, real64)
2087 density_laplacian(ii, 4) = density_laplacian(ii, 4) + aimag(c_tmp)
2095 if (
associated(jp))
then
2097 jp(1:gr%np, i_dim, is) = jp(1:gr%np, i_dim, is) + &
2098 ww*(aimag(psi_gpsi(1:gr%np, 1)) - abs_wf_psi(1:gr%np, 1)*kpoint(i_dim))
2099 if (st%d%ispin ==
spinors)
then
2100 jp(1:gr%np, i_dim, 2) = jp(1:gr%np, i_dim, 2) + &
2101 ww*( aimag(psi_gpsi(1:gr%np, 2)) - abs_wf_psi(1:gr%np, 2)*kpoint(i_dim))
2104 c_tmp = -ww*
m_half*
m_zi*(gwf_psi(ii, i_dim, 1)*wf_psi_conj(ii, 2) - wf_psi(ii, 1)*conjg(gwf_psi(ii, i_dim, 2)) &
2105 -
m_two *
m_zi*wf_psi(ii, 1)*wf_psi_conj(ii, 2)*kpoint(i_dim))
2106 jp(ii, i_dim, 3) = jp(ii, i_dim, 3) + real(c_tmp, real64)
2107 jp(ii, i_dim, 4) = jp(ii, i_dim, 4) + aimag(c_tmp)
2116 if (
associated(tau))
then
2117 tau(1:gr%np, is) = tau(1:gr%np, is) + ww*(abs_gwf_psi(1:gr%np,1) &
2118 -
m_two*aimag(psi_gpsi(1:gr%np, 1))*kpoint(i_dim))
2119 if (st%d%ispin ==
spinors)
then
2120 tau(1:gr%np, 2) = tau(1:gr%np, 2) + ww*(abs_gwf_psi(1:gr%np, 2) &
2121 -
m_two*aimag(psi_gpsi(1:gr%np, 2))*kpoint(i_dim))
2124 c_tmp = ww * ( gwf_psi(ii, i_dim, 1)*conjg(gwf_psi(ii, i_dim, 2)) &
2125 +
m_zi * (gwf_psi(ii,i_dim,1)*wf_psi_conj(ii, 2) &
2126 - wf_psi(ii, 1)*conjg(gwf_psi(ii,i_dim,2)))*kpoint(i_dim))
2127 tau(ii, 3) = tau(ii, 3) + real(c_tmp, real64)
2128 tau(ii, 4) = tau(ii, 4) + aimag(c_tmp)
2138 safe_deallocate_a(wf_psi_conj)
2139 safe_deallocate_a(abs_wf_psi)
2140 safe_deallocate_a(abs_gwf_psi)
2141 safe_deallocate_a(psi_gpsi)
2143 if (.not.
present(gi_kinetic_energy_density))
then
2144 if (.not.
present(paramagnetic_current))
then
2145 safe_deallocate_p(jp)
2147 if (.not.
present(kinetic_energy_density))
then
2148 safe_deallocate_p(tau)
2152 if (st%parallel_in_states .or. st%d%kpt%parallel)
call reduce_all(st%st_kpt_mpi_grp)
2157 if (st%symmetrize_density)
then
2158 do is = 1, st%d%nspin
2159 if (
associated(tau))
then
2163 if (
present(density_laplacian))
then
2167 if (
associated(jp))
then
2171 if (
present(density_gradient))
then
2178 if (
allocated(st%rho_core) .and. nlcc .and. (
present(density_laplacian) .or.
present(density_gradient)))
then
2180 wf_psi(ii, 1) = st%rho_core(ii)/st%d%spin_channels
2185 if (
present(density_gradient))
then
2188 do is = 1, st%d%spin_channels
2189 density_gradient(1:gr%np, 1:gr%der%dim, is) = density_gradient(1:gr%np, 1:gr%der%dim, is) + &
2190 real(gwf_psi(1:gr%np, 1:gr%der%dim,1))
2195 if (
present(density_laplacian))
then
2198 do is = 1, st%d%spin_channels
2199 density_laplacian(1:gr%np, is) = density_laplacian(1:gr%np, is) + real(lwf_psi(1:gr%np, 1))
2206 if (
allocated(st%frozen_tau) .and. .not.
present(st_end))
then
2209 if (
allocated(st%frozen_gdens) .and. .not.
present(st_end))
then
2210 do is = 1, st%d%nspin
2211 call lalg_axpy(gr%np, gr%der%dim,
m_one, st%frozen_gdens(:,:,is), density_gradient(:,:,is))
2214 if (
allocated(st%frozen_tau) .and. .not.
present(st_end))
then
2215 call lalg_axpy(gr%np, st%d%nspin,
m_one, st%frozen_ldens, density_laplacian)
2218 safe_deallocate_a(wf_psi)
2219 safe_deallocate_a(gwf_psi)
2220 safe_deallocate_a(lwf_psi)
2224 if (
present(gi_kinetic_energy_density))
then
2225 do is = 1, st%d%nspin
2226 assert(
associated(tau))
2227 gi_kinetic_energy_density(1:gr%np, is) = tau(1:gr%np, is)
2230 assert(
associated(jp))
2231 if (st%d%ispin /=
spinors)
then
2232 do is = 1, st%d%nspin
2235 if (st%rho(ii, is) < 1.0e-7_real64) cycle
2236 gi_kinetic_energy_density(ii, is) = &
2237 gi_kinetic_energy_density(ii, is) - sum(jp(ii,1:gr%der%dim, is)**2)/st%rho(ii, is)
2243 gi_kinetic_energy_density(ii, 1) = gi_kinetic_energy_density(ii, 1) &
2244 - sum(jp(ii,1:gr%der%dim, 1)**2)/(safe_tol(st%rho(ii, 1),
m_epsilon))
2245 gi_kinetic_energy_density(ii, 2) = gi_kinetic_energy_density(ii, 2) &
2246 - sum(jp(ii,1:gr%der%dim, 2)**2)/(safe_tol(st%rho(ii, 2),
m_epsilon))
2247 gi_kinetic_energy_density(ii, 3) = &
2248 gi_kinetic_energy_density(ii, 3) - sum(jp(ii,1:gr%der%dim, 3)**2 + jp(ii,1:gr%der%dim, 4)**2) &
2249 /(safe_tol((st%rho(ii, 3)**2 + st%rho(ii, 4)**2),
m_epsilon))*st%rho(ii, 3)
2250 gi_kinetic_energy_density(ii, 4) = &
2251 gi_kinetic_energy_density(ii, 4) + sum(jp(ii,1:gr%der%dim, 3)**2 + jp(ii,1:gr%der%dim, 4)**2) &
2252 /(safe_tol((st%rho(ii, 3)**2 + st%rho(ii, 4)**2),
m_epsilon))*st%rho(ii, 4)
2258 if (.not.
present(kinetic_energy_density))
then
2259 safe_deallocate_p(tau)
2261 if (.not.
present(paramagnetic_current))
then
2262 safe_deallocate_p(jp)
2277 if (
associated(tau))
call comm_allreduce(grp, tau, dim = (/gr%np, st%d%nspin/))
2279 if (
present(density_laplacian))
call comm_allreduce(grp, density_laplacian, dim = (/gr%np, st%d%nspin/))
2281 do is = 1, st%d%nspin
2282 if (
associated(jp))
call comm_allreduce(grp, jp(:, :, is), dim = (/gr%np, gr%der%dim/))
2284 if (
present(density_gradient))
then
2285 call comm_allreduce(grp, density_gradient(:, :, is), dim = (/gr%np, gr%der%dim/))
2299 type(
mesh_t),
intent(in) :: mesh
2300 complex(real64),
intent(in) :: f1(:, :)
2301 real(real64) :: spin(1:3)
2303 complex(real64) :: z
2307 z =
zmf_dotp(mesh, f1(:, 1) , f1(:, 2))
2309 spin(1) =
m_two*real(z, real64)
2310 spin(2) =
m_two*aimag(z)
2322 integer,
intent(in) :: ist
2336 integer,
intent(in) :: ist
2337 integer,
intent(in) :: ik
2342 ik >= st%d%kpt%start .and. ik <= st%d%kpt%end
2352 class(
mesh_t),
intent(in) :: mesh
2358 memory = memory + real64*real(mesh%np_part_global, real64) *st%d%dim*real(st%nst, real64) *st%d%kpt%nglobal
2368 logical,
optional,
intent(in) :: copy
2371 integer(int64) :: max_mem, mem
2383 if (accel_is_enabled())
then
2384 max_mem = accel_global_memory_size()
2386 if (st%cl_states_mem > m_one)
then
2387 max_mem = int(st%cl_states_mem, int64)*(1024_8)**2
2388 else if (st%cl_states_mem < 0.0_real64)
then
2389 max_mem = max_mem + int(st%cl_states_mem, int64)*(1024_8)**2
2391 max_mem = int(st%cl_states_mem*real(max_mem, real64) , int64)
2394 max_mem = huge(max_mem)
2398 qnloop:
do iqn = st%d%kpt%start, st%d%kpt%end
2399 do ib = st%group%block_start, st%group%block_end
2401 mem = mem + st%group%psib(ib, iqn)%pack_total_size()
2403 if (mem > max_mem)
then
2404 call messages_write(
'Not enough CL device memory to store all states simultaneously.', new_line = .
true.)
2405 call messages_write(
'Only ')
2406 call messages_write(ib - st%group%block_start)
2407 call messages_write(
' of ')
2408 call messages_write(st%group%block_end - st%group%block_start + 1)
2409 call messages_write(
' blocks will be stored in device memory.', new_line = .
true.)
2410 call messages_warning()
2414 call st%group%psib(ib, iqn)%do_pack(copy)
2426 logical,
optional,
intent(in) :: copy
2435 do iqn = st%d%kpt%start, st%d%kpt%end
2436 do ib = st%group%block_start, st%group%block_end
2437 if (st%group%psib(ib, iqn)%is_packed())
call st%group%psib(ib, iqn)%do_unpack(copy)
2450 type(namespace_t),
intent(in) :: namespace
2454 call messages_print_with_emphasis(msg=
"States", namespace=namespace)
2456 write(message(1),
'(a,f12.3)')
'Total electronic charge = ', st%qtot
2457 write(message(2),
'(a,i8)')
'Number of states = ', st%nst
2458 write(message(3),
'(a,i8)')
'States block-size = ', st%block_size
2459 call messages_info(3, namespace=namespace)
2461 call messages_print_with_emphasis(namespace=namespace)
2476 do iqn = st%d%kpt%start, st%d%kpt%end
2477 do ib = st%group%block_start, st%group%block_end
2478 call batch_set_zero(st%group%psib(ib, iqn))
2488 integer pure function states_elec_block_min(st, ib) result(range)
2490 integer,
intent(in) :: ib
2492 range = st%group%block_range(ib, 1)
2498 integer pure function states_elec_block_max(st, ib) result(range)
2500 integer,
intent(in) :: ib
2502 range = st%group%block_range(ib, 2)
2508 integer pure function states_elec_block_size(st, ib) result(size)
2510 integer,
intent(in) :: ib
2512 size = st%group%block_size(ib)
2520 type(namespace_t),
intent(in) :: namespace
2521 integer,
intent(out) :: n_pairs
2522 integer,
intent(out) :: n_occ(:)
2523 integer,
intent(out) :: n_unocc(:)
2524 logical,
allocatable,
intent(out) :: is_included(:,:,:)
2526 logical,
intent(out) :: is_frac_occ
2528 integer :: ik, ist, ast, n_filled, n_partially_filled, n_half_filled
2529 character(len=80) :: nst_string, default, wfn_list
2530 real(real64) :: energy_window
2534 is_frac_occ = .false.
2536 call occupied_states(st, namespace, ik, n_filled, n_partially_filled, n_half_filled)
2537 if (n_partially_filled > 0 .or. n_half_filled > 0) is_frac_occ = .
true.
2538 n_occ(ik) = n_filled + n_partially_filled + n_half_filled
2539 n_unocc(ik) = st%nst - n_filled
2552 call parse_variable(namespace,
'CasidaKSEnergyWindow', -m_one, energy_window, units_inp%energy)
2575 safe_allocate(is_included(maxval(n_occ), minval(n_occ) + 1:st%nst , st%nik))
2576 is_included(:,:,:) = .false.
2578 if (energy_window < m_zero)
then
2579 write(nst_string,
'(i6)') st%nst
2580 write(default,
'(a,a)')
"1-", trim(adjustl(nst_string))
2581 call parse_variable(namespace,
'CasidaKohnShamStates', default, wfn_list)
2583 write(message(1),
'(a,a)')
"Info: States that form the basis: ", trim(wfn_list)
2584 call messages_info(1, namespace=namespace)
2589 do ast = n_occ(ik) + 1, st%nst
2590 if (loct_isinstringlist(ast, wfn_list))
then
2591 do ist = 1, n_occ(ik)
2592 if (loct_isinstringlist(ist, wfn_list))
then
2593 n_pairs = n_pairs + 1
2594 is_included(ist, ast, ik) = .
true.
2603 write(message(1),
'(a,f12.6,a)')
"Info: including transitions with energy < ", &
2604 units_from_atomic(units_out%energy, energy_window), trim(units_abbrev(units_out%energy))
2605 call messages_info(1, namespace=namespace)
2610 do ast = n_occ(ik) + 1, st%nst
2611 do ist = 1, n_occ(ik)
2612 if (st%eigenval(ast, ik) - st%eigenval(ist, ik) < energy_window)
then
2613 n_pairs = n_pairs + 1
2614 is_included(ist, ast, ik) = .
true.
2642 subroutine occupied_states(st, namespace, ik, n_filled, n_partially_filled, n_half_filled, &
2643 filled, partially_filled, half_filled)
2645 type(namespace_t),
intent(in) :: namespace
2646 integer,
intent(in) :: ik
2647 integer,
intent(out) :: n_filled, n_partially_filled, n_half_filled
2648 integer,
optional,
intent(out) :: filled(:), partially_filled(:), half_filled(:)
2654 if (
present(filled)) filled(:) = 0
2655 if (
present(partially_filled)) partially_filled(:) = 0
2656 if (
present(half_filled)) half_filled(:) = 0
2658 n_partially_filled = 0
2661 select case (st%d%ispin)
2664 if (abs(st%occ(ist, ik) - m_two) < m_min_occ)
then
2665 n_filled = n_filled + 1
2666 if (
present(filled)) filled(n_filled) = ist
2667 else if (abs(st%occ(ist, ik) - m_one) < m_min_occ)
then
2668 n_half_filled = n_half_filled + 1
2669 if (
present(half_filled)) half_filled(n_half_filled) = ist
2670 else if (st%occ(ist, ik) > m_min_occ)
then
2671 n_partially_filled = n_partially_filled + 1
2672 if (
present(partially_filled)) partially_filled(n_partially_filled) = ist
2673 else if (abs(st%occ(ist, ik)) > m_min_occ)
then
2674 write(message(1),*)
'Internal error in occupied_states: Illegal occupation value ', st%occ(ist, ik)
2675 call messages_fatal(1, namespace=namespace)
2678 case (spin_polarized, spinors)
2680 if (abs(st%occ(ist, ik)-m_one) < m_min_occ)
then
2681 n_filled = n_filled + 1
2682 if (
present(filled)) filled(n_filled) = ist
2683 else if (st%occ(ist, ik) > m_min_occ)
then
2684 n_partially_filled = n_partially_filled + 1
2685 if (
present(partially_filled)) partially_filled(n_partially_filled) = ist
2686 else if (abs(st%occ(ist, ik)) > m_min_occ)
then
2687 write(message(1),*)
'Internal error in occupied_states: Illegal occupation value ', st%occ(ist, ik)
2688 call messages_fatal(1, namespace=namespace)
2700 type(multicomm_t),
intent(in) :: mc
2703 call distributed_init(this%d%kpt, this%nik, mc%group_comm(p_strategy_kpoints),
"k-points")
2718 if (.not.
allocated(st%st_kpt_task))
then
2719 safe_allocate(st%st_kpt_task(0:st%st_kpt_mpi_grp%size-1, 1:4))
2722 st%st_kpt_task(0:st%st_kpt_mpi_grp%size-1, :) = 0
2723 st%st_kpt_task(st%st_kpt_mpi_grp%rank, :) = [st%st_start, st%st_end, st%d%kpt%start, st%d%kpt%end]
2725 if (st%parallel_in_states .or. st%d%kpt%parallel)
then
2726 call comm_allreduce(st%st_kpt_mpi_grp, st%st_kpt_task)
2737 type(kpoints_t),
intent(in) :: kpoints
2738 type(namespace_t),
intent(in) :: namespace
2741 type(states_elec_dim_t),
pointer :: dd
2748 st%nik = kpoints_number(kpoints)
2750 if (dd%ispin == spin_polarized) st%nik = 2*st%nik
2752 safe_allocate(st%kweights(1:st%nik))
2755 ik = dd%get_kpoint_index(iq)
2756 st%kweights(iq) = kpoints%get_weight(ik)
2768 call io_mkdir(
'debug/', namespace)
2769 iunit = io_open(
'debug/kpoints', namespace, action =
'write')
2770 call kpoints%write_info(iunit=iunit, absolute_coordinates = .
true.)
2771 call io_close(iunit)
2785 class(mesh_t),
intent(in) :: gr
2786 real(real64) :: dipole(1:gr%box%dim)
2789 real(real64) :: e_dip(1:gr%box%dim, this%d%spin_channels)
2793 do ispin = 1, this%d%spin_channels
2794 call dmf_dipole(gr, this%rho(:, ispin), e_dip(:, ispin))
2797 dipole(:) = sum(e_dip(:, 1:this%d%spin_channels), 2)
2805#include "states_elec_inc.F90"
2808#include "complex.F90"
2809#include "states_elec_inc.F90"
initialize a batch with existing memory
constant times a vector plus a vector
Prints out to iunit a message in the form: ["InputVariable" = value] where "InputVariable" is given b...
pure logical function, public accel_is_enabled()
type(accel_t), public accel
This module implements batches of mesh functions.
This module implements common operations on batches of mesh functions.
This module provides the BLACS processor grid.
subroutine, public blacs_proc_grid_init(this, mpi_grp, procdim)
Initializes a blacs context from an MPI communicator with topological information.
subroutine, public blacs_proc_grid_end(this)
subroutine, public blacs_proc_grid_copy(cin, cout)
Module implementing boundary conditions in Octopus.
This module handles the calculation mode.
type(calc_mode_par_t), public calc_mode_par
Singleton instance of parallel calculation mode.
integer, parameter, public p_strategy_states
parallelization in states
This module calculates the derivatives (gradients, Laplacians, etc.) of a function.
subroutine, public zderivatives_grad(der, ff, op_ff, ghost_update, set_bc, to_cartesian)
apply the gradient to a mesh function
subroutine, public zderivatives_lapl(der, ff, op_ff, ghost_update, set_bc, factor)
apply the Laplacian to a mesh function
subroutine, public distributed_end(this)
subroutine, public distributed_nullify(this, total)
subroutine, public distributed_init(this, total, comm, tag, scalapack_compat)
Distribute N instances across M processes of communicator comm
subroutine, public distributed_copy(in, out)
@Brief Create a copy of a distributed instance
integer, parameter, public unpolarized
Parameters...
integer, parameter, public spinors
integer, parameter, public spin_polarized
real(real64), parameter, public m_two
real(real64), parameter, public m_zero
real(real64), parameter, public m_fourth
complex(real64), parameter, public m_zi
real(real64), parameter, public m_epsilon
type(conf_t), public conf
Global instance of Octopus configuration.
real(real64), parameter, public m_half
real(real64), parameter, public m_one
This module implements the underlying real-space grid.
subroutine, public dgrid_symmetrize_vector_field(gr, field, suppress_warning)
subroutine, public dgrid_symmetrize_scalar_field(gr, field, suppress_warning)
logical pure function, public kpoints_point_is_gamma(this, ik)
This module is intended to contain "only mathematical" functions and procedures.
integer pure function, public pad_pow2(size)
create array size, which is padded to powers of 2
This module defines functions over batches of mesh functions.
subroutine, public zmesh_batch_exchange_points(mesh, aa, forward_map, backward_map)
This functions exchanges points of a mesh according to a certain map. Two possible maps can be given....
subroutine, public dmesh_batch_exchange_points(mesh, aa, forward_map, backward_map)
This functions exchanges points of a mesh according to a certain map. Two possible maps can be given....
This module defines various routines, operating on mesh functions.
subroutine, public zmf_random(mesh, ff, pre_shift, post_shift, seed, normalized)
This subroutine fills a function with random values.
subroutine, public dmf_random(mesh, ff, pre_shift, post_shift, seed, normalized)
This subroutine fills a function with random values.
subroutine, public zmf_normalize(mesh, dim, psi, norm)
Normalize a mesh function psi.
This module defines the meshes, which are used in Octopus.
subroutine, public messages_not_implemented(feature, namespace)
subroutine, public messages_warning(no_lines, all_nodes, namespace)
subroutine, public messages_obsolete_variable(namespace, name, rep)
character(len=256), dimension(max_lines), public message
to be output by fatal, warning
subroutine, public messages_fatal(no_lines, only_root_writes, namespace)
subroutine, public messages_input_error(namespace, var, details, row, column)
subroutine, public messages_experimental(name, namespace)
subroutine, public messages_info(no_lines, iunit, debug_only, stress, all_nodes, namespace)
general module for modelmb particles
subroutine, public modelmb_particles_end(this)
subroutine, public modelmb_particles_init(this, namespace, space)
==============================================================
subroutine, public modelmb_particles_copy(modelmb_out, modelmb_in)
subroutine mpi_grp_copy(mpi_grp_out, mpi_grp_in)
type(mpi_comm), parameter, public mpi_comm_undefined
used to indicate a communicator has not been initialized
subroutine mpi_grp_init(grp, comm)
Initialize MPI group instance.
This module handles the communicators for the various parallelization strategies.
logical pure function, public multicomm_strategy_is_parallel(mc, level)
subroutine, public multicomm_all_pairs_copy(apout, apin)
logical pure function, public multicomm_have_slaves(this)
subroutine, public multicomm_create_all_pairs(mpi_grp, ap)
This routine uses the one-factorization (or near-one-factorization of a complete graph to construct a...
logical function, public parse_is_defined(namespace, name)
integer function, public parse_block(namespace, name, blk, check_varinfo_)
subroutine, public profiling_out(label)
Increment out counter and sum up difference between entry and exit time.
subroutine, public profiling_in(label, exclude)
Increment in counter and save entry time.
subroutine, public restart_read(restart, iunit, lines, nlines, ierr)
subroutine, public restart_close(restart, iunit)
Close a file previously opened with restart_open.
integer function, public restart_open(restart, filename, status, position, silent)
Open file "filename" found inside the current restart directory. Depending on the type of restart,...
subroutine, public smear_fill_occupations(this, eigenvalues, occupations, nik, nst)
subroutine, public smear_find_fermi_energy(this, namespace, eigenvalues, occupations, qtot, nik, nst, kweights)
subroutine, public smear_copy(to, from)
integer, parameter, public smear_fixed_occ
subroutine, public smear_init(this, namespace, ispin, fixed_occ, integral_occs, kpoints)
logical pure function, public smear_is_semiconducting(this)
subroutine, public states_set_complex(st)
pure logical function, public states_are_complex(st)
pure logical function, public states_are_real(st)
This module handles spin dimensions of the states and the k-point distribution.
subroutine, public states_elec_dim_copy(dout, din)
subroutine, public states_elec_dim_end(dim)
This module handles groups of electronic batches and their parallel distribution.
subroutine, public states_elec_group_copy(d, group_in, group_out, copy_data, special)
make a copy of a group
subroutine, public states_elec_group_end(this, d)
finalize the local blocks of wave functions and release local arrays
real(real64) function, public states_elec_wfns_memory(st, mesh)
return the memory usage of a states_elec_t object
integer pure function, public states_elec_block_max(st, ib)
return index of last state in block ib
subroutine zstates_elec_generate_random_vector(mesh, st, vector, normalized, reset_seed)
Generate a random vector.
subroutine, public states_elec_null(st)
subroutine, public states_elec_distribute_nodes(st, namespace, mc)
@Brief. Distribute states over the processes for states parallelization
subroutine, public states_elec_fermi(st, namespace, mesh, compute_spin)
calculate the Fermi level for the states in this object
logical function, public state_kpt_is_local(st, ist, ik)
check whether a given state (ist, ik) is on the local node
subroutine, public states_elec_calc_quantities(gr, st, kpoints, nlcc, kinetic_energy_density, paramagnetic_current, density_gradient, density_laplacian, gi_kinetic_energy_density, st_end)
calculated selected quantities
real(real64) function, dimension(1:gr%box%dim) states_elec_calculate_dipole(this, gr)
calculate the expectation value of the dipole moment of electrons
subroutine, public states_elec_densities_init(st, gr)
subroutine, public states_elec_end(st)
finalize the states_elec_t object
subroutine zstates_elec_get_state1(st, mesh, idim, ist, iqn, psi)
Write one component (dim) of a wave function into a state_elec_t object.
subroutine, public states_elec_deallocate_wfns(st)
Deallocates the KS wavefunctions defined within a states_elec_t structure.
subroutine, public states_elec_allocate_wfns(st, mesh, wfs_type, skip, packed)
Allocates the KS wavefunctions defined within a states_elec_t structure.
subroutine zstates_elec_get_points1(st, start_point, end_point, iqn, psi)
Returns the value of all the states for given k-point in the range of points [start_point:end_point].
subroutine states_elec_read_initial_occs(st, namespace, excess_charge, kpoints)
Reads from the input file the initial occupations, if the block "Occupations" is present....
subroutine, public states_elec_init(st, namespace, space, valence_charge, kpoints)
Initialize a new states_elec_t object.
subroutine zstates_elec_set_state1(st, mesh, idim, ist, iqn, psi)
get one dimension of local wave function for given k-point and states index from a states_elec_t obje...
real(real64) function, public states_elec_eigenvalues_sum(st, alt_eig)
function to calculate the eigenvalues sum using occupations as weights
integer, parameter, public par_independent
Method used to generate random states.
subroutine dstates_elec_generate_random_vector(mesh, st, vector, normalized, reset_seed)
Generate a random vector.
subroutine, public occupied_states(st, namespace, ik, n_filled, n_partially_filled, n_half_filled, filled, partially_filled, half_filled)
return information about occupied orbitals in many-body state
subroutine dstates_elec_get_state2(st, mesh, ist, iqn, psi)
Write a wave function into a state_elec_t object.
subroutine zstates_elec_set_state2(st, mesh, ist, iqn, psi)
get local wave function for given k-point and states index from a states_elec_t object
subroutine zstates_elec_get_state2(st, mesh, ist, iqn, psi)
Write a wave function into a state_elec_t object.
subroutine dstates_elec_get_points1(st, start_point, end_point, iqn, psi)
Returns the value of all the states for given k-point in the range of points [start_point:end_point].
integer pure function, public states_elec_block_size(st, ib)
return number of states in block ib
subroutine, public kpoints_distribute(this, mc)
distribute k-points over the nodes in the corresponding communicator
integer, parameter, public par_dependent
subroutine states_elec_pack(st, copy)
pack the batches in this states object
subroutine, public states_elec_choose_kpoints(st, kpoints, namespace)
double up k-points for SPIN_POLARIZED calculations
subroutine zstates_elec_get_state3(st, mesh, iqn, psi)
get local wave functions for given k-point from a states_elec_t object
logical function, public state_is_local(st, ist)
check whether a given state (ist) is on the local node
subroutine dstates_elec_set_state1(st, mesh, idim, ist, iqn, psi)
get one dimension of local wave function for given k-point and states index from a states_elec_t obje...
subroutine, public states_elec_exec_init(st, namespace, mc)
Further initializations.
subroutine dstates_elec_set_state4(st, mesh, psi)
set all local wave functions in a states_elec_t object
subroutine dstates_elec_set_state3(st, mesh, iqn, psi)
set local wave functions for given k-point in a states_elec_t object
subroutine states_elec_write_info(st, namespace)
write information about the states object
subroutine states_elec_init_block(st, mesh, verbose, skip, packed)
Initializes the data components in st that describe how the states are distributed in blocks:
real(real64) function, dimension(1:3) state_spin(mesh, f1)
calculate the spin vector for a spinor wave function f1
subroutine states_elec_kpoints_distribution(st)
Assign the start and end indices for states and kpoints, for "st_kpt_mpi_grp" communicator.
subroutine zstates_elec_get_state4(st, mesh, psi)
get all local wave functions from a states_elec_t object
subroutine, public states_elec_copy(stout, stin, exclude_wfns, exclude_eigenval, special)
make a (selective) copy of a states_elec_t object
subroutine, public states_elec_generate_random(st, mesh, kpoints, ist_start_, ist_end_, ikpt_start_, ikpt_end_, normalized)
randomize states
subroutine dstates_elec_get_state1(st, mesh, idim, ist, iqn, psi)
Write one component (dim) of a wave function into a state_elec_t object.
subroutine dstates_elec_set_state2(st, mesh, ist, iqn, psi)
get local wave function for given k-point and states index from a states_elec_t object
subroutine zstates_elec_set_state4(st, mesh, psi)
set all local wave functions in a states_elec_t object
subroutine states_elec_read_initial_spins(st, namespace)
Reads, if present, the "InitialSpins" block.
subroutine dstates_elec_get_state3(st, mesh, iqn, psi)
get local wave functions for given k-point from a states_elec_t object
subroutine dstates_elec_get_points2(st, start_point, end_point, psi)
Returns the value of all the states in the range of points [start_point:end_point].
integer pure function, public states_elec_block_min(st, ib)
return index of first state in block ib
subroutine states_elec_unpack(st, copy)
unpack the batches in this states object
subroutine, public states_elec_look(restart, nik, dim, nst, ierr)
Reads the 'states' file in the restart directory, and finds out the nik, dim, and nst contained in it...
subroutine dstates_elec_get_state4(st, mesh, psi)
get all local wave functions from a states_elec_t object
subroutine, public states_elec_count_pairs(st, namespace, n_pairs, n_occ, n_unocc, is_included, is_frac_occ)
number of occupied-unoccupied pairs for Casida
subroutine, public states_elec_allocate_current(st, space, mesh)
subroutine, public states_elec_set_zero(st)
expclicitely set all wave functions in the states to zero
subroutine zstates_elec_set_state3(st, mesh, iqn, psi)
set local wave functions for given k-point in a states_elec_t object
subroutine zstates_elec_get_points2(st, start_point, end_point, psi)
Returns the value of all the states in the range of points [start_point:end_point].
type(type_t), public type_float
type(type_t), public type_cmplx
brief This module defines the class unit_t which is used by the unit_systems_oct_m module.
This module defines the unit system, used for input and output.
type(unit_t), public unit_megabytes
For large amounts of data (natural code units are bytes)
subroutine, public zwfs_elec_init(this, dim, st_start, st_end, np, ik, special, packed)
initialize an empty wfs_elec_t object
subroutine, public dwfs_elec_init(this, dim, st_start, st_end, np, ik, special, packed)
initialize an empty wfs_elec_t object
subroutine reduce_all(grp)
subroutine print_kpoints_debug
Class defining batches of mesh functions.
Distribution of N instances over mpi_grpsize processes, for the local rank mpi_grprank....
Extension of space that contains the knowledge of the spin dimension.
Description of the grid, containing information on derivatives, stencil, and symmetries.
Describes mesh distribution to nodes.
This is defined even when running serial.
An all-pairs communication schedule for a given group.
Stores all communicators and groups.
abstract class for states
The states_elec_t class contains all electronic wave functions.