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
 
  294    st%fromScratch = .
true. 
 
  299    st%d%ispin = space%ispin
 
  304    if (st%d%ispin /= 
unpolarized .and. kpoints%use_time_reversal) 
then 
  305      message(1) = 
"Time reversal symmetry is only implemented for unpolarized spins." 
  306      message(2) = 
"Use KPointsUseTimeReversal = no." 
  338      write(
message(1), 
'(a,i5,a)') 
"Input: '", ntot, 
"' is not a valid value for TotalStates." 
  360      write(
message(1), 
'(a,i5,a)') 
"Input: '", nempty, 
"' is not a valid value for ExtraStates." 
  361      message(2) = 
'(0 <= ExtraStates)' 
  365    if (ntot > 0 .and. nempty > 0) 
then 
  366      message(1) = 
'You cannot set TotalStates and ExtraStates at the same time.' 
  381    if (nempty_percent < 0) 
then 
  382      write(
message(1), 
'(a,f8.6,a)') 
"Input: '", nempty_percent, &
 
  383        "' should be a percentage value x (where x is parts in hundred) larger or equal 0" 
  387    if (nempty > 0 .and. nempty_percent > 0) 
then 
  388      message(1) = 
'You cannot set ExtraStates and ExtraStatesInPercent at the same time.' 
  404    call parse_variable(namespace, 
'ExtraStatesToConverge', nempty, nempty_conv)
 
  406      write(
message(1), 
'(a,i5,a)') 
"Input: '", nempty_conv, 
"' is not a valid value for ExtraStatesToConverge." 
  407      message(2) = 
'(0 <= ExtraStatesToConverge)' 
  411    if (nempty_conv > nempty) 
then 
  412      message(1) = 
'You cannot set ExtraStatesToConverge to a higher value than ExtraStates.' 
  419    st%val_charge = valence_charge
 
  421    st%qtot = -(st%val_charge + excess_charge)
 
  424      write(
message(1),
'(a,f12.6,a)') 
'Total charge = ', st%qtot, 
' < 0' 
  425      message(2) = 
'Check Species and ExcessCharge.' 
  429    select case (st%d%ispin)
 
  432      st%nst = int(st%qtot/2)
 
  433      if (st%nst*2 < st%qtot) st%nst = st%nst + 1
 
  435      st%d%spin_channels = 1
 
  438      st%nst = int(st%qtot/2)
 
  439      if (st%nst*2 < st%qtot) st%nst = st%nst + 1
 
  441      st%d%spin_channels = 2
 
  444      st%nst = int(st%qtot)
 
  445      if (st%nst < st%qtot) st%nst = st%nst + 1
 
  447      st%d%spin_channels = 2
 
  451      if (ntot < st%nst) 
then 
  452        message(1) = 
'TotalStates is smaller than the number of states required by the system.' 
  459    if (nempty_percent > 0) 
then 
  460      nempty = ceiling(nempty_percent * st%nst / 100)
 
  463    st%nst_conv = st%nst + nempty_conv
 
  464    st%nst = st%nst + nempty
 
  465    if (st%nst == 0) 
then 
  466      message(1) = 
"Cannot run with number of states = zero." 
  486      default = max(
accel%warp_size, 32)
 
  495    call parse_variable(namespace, 
'StatesBlockSize', default, st%block_size)
 
  496    if (st%block_size < 1) 
then 
  497      call messages_write(
"The variable 'StatesBlockSize' must be greater than 0.")
 
  501    st%block_size = min(st%block_size, st%nst)
 
  502    conf%target_states_block_size = st%block_size
 
  504    safe_allocate(st%eigenval(1:st%nst, 1:st%nik))
 
  505    st%eigenval = huge(st%eigenval)
 
  509    if (.not. kpoints%gamma_only()) 
then 
  522    call parse_variable(namespace, 
'OnlyUserDefinedInitialStates', .false., st%only_userdef_istates)
 
  525    safe_allocate(st%occ     (1:st%nst, 1:st%nik))
 
  530      safe_allocate(st%user_def_states(1:st%d%dim, 1:st%nst, 1:st%nik))
 
  532      st%user_def_states(1:st%d%dim, 1:st%nst, 1:st%nik) = 
'undefined' 
  535    if (st%d%ispin == 
spinors) 
then 
  536      safe_allocate(st%spin(1:3, 1:st%nst, 1:st%nik))
 
  563    if (st%smear%photodop) 
then 
  564      if (nempty == 0) 
then 
  565        write(
message(1), 
'(a,i5,a)') 
"PhotoDoping requires to specify ExtraStates." 
  566        message(2) = 
'(0 == ExtraStates)' 
  574    safe_allocate(st%node(1:st%nst))
 
  575    st%node(1:st%nst) = 0
 
  578    st%parallel_in_states = .false.
 
  583    if (st%modelmbparticles%nparticle > 0) 
then 
  585      safe_allocate(st%mmb_nspindown(1:st%modelmbparticles%ntype_of_particle, 1:st%nst))
 
  586      st%mmb_nspindown(:,:) = -1
 
  587      safe_allocate(st%mmb_iyoung(1:st%modelmbparticles%ntype_of_particle, 1:st%nst))
 
  588      st%mmb_iyoung(:,:) = -1
 
  589      safe_allocate(st%mmb_proj(1:st%nst))
 
  601    call parse_variable(namespace, 
'SymmetrizeDensity', kpoints%use_symmetries, st%symmetrize_density)
 
  631    integer,         
intent(out) :: nik
 
  632    integer,         
intent(out) :: dim
 
  633    integer,         
intent(out) :: nst
 
  634    integer,         
intent(out) :: ierr
 
  636    character(len=256) :: lines(3)
 
  637    character(len=20)   :: char
 
  647      read(lines(1), *) char, nst
 
  648      read(lines(2), *) char, dim
 
  649      read(lines(3), *) char, nik
 
  669    real(real64),         
intent(in)    :: excess_charge
 
  672    integer :: ik, ist, ispin, nspin, ncols, nrows, el_per_state, icol, start_pos, spin_n
 
  674    real(real64) :: rr, charge
 
  675    logical :: integral_occs, unoccupied_states
 
  676    real(real64), 
allocatable :: read_occs(:, :)
 
  677    real(real64) :: charge_in_block
 
  690    call parse_variable(namespace, 
'RestartFixedOccupations', .
true., st%restart_fixed_occ)
 
  761    integral_occs = .
true.
 
  763    occ_fix: 
if (
parse_block(namespace, 
'Occupations', blk) == 0) 
then 
  765      st%fixed_occ = .
true.
 
  768      if (ncols > st%nst) 
then 
  773      if (nrows /= st%nik) 
then 
  774        call messages_input_error(namespace, 
"Occupations", 
"Wrong number of rows in block Occupations.")
 
  777      do ik = 1, st%nik - 1
 
  780            "All rows in block Occupations must have the same number of columns.")
 
  791      safe_allocate(read_occs(1:ncols, 1:st%nik))
 
  797          charge_in_block = charge_in_block + read_occs(icol, ik) * st%kweights(ik)
 
  802      select case (st%d%ispin)
 
  811      start_pos = nint((st%qtot - charge_in_block)/spin_n)
 
  813      if (start_pos + ncols > st%nst) 
then 
  814        message(1) = 
"To balance charge, the first column in block Occupations is taken to refer to state" 
  815        write(
message(2),
'(a,i6,a)') 
"number ", start_pos, 
" but there are too many columns for the number of states." 
  816        write(
message(3),
'(a,i6,a)') 
"Solution: set ExtraStates = ", start_pos + ncols - st%nst
 
  821        do ist = 1, start_pos
 
  822          st%occ(ist, ik) = el_per_state
 
  827        do ist = start_pos + 1, start_pos + ncols
 
  828          st%occ(ist, ik) = read_occs(ist - start_pos, ik)
 
  829          integral_occs = integral_occs .and. &
 
  830            abs((st%occ(ist, ik) - el_per_state) * st%occ(ist, ik))  <=  
m_epsilon 
  835        do ist = start_pos + ncols + 1, st%nst
 
  842      safe_deallocate_a(read_occs)
 
  845      st%fixed_occ = .false.
 
  846      integral_occs = .false.
 
  853      st%qtot = -(st%val_charge + excess_charge)
 
  856      if (st%d%nspin == 2) nspin = 2
 
  858      do ik = 1, st%nik, nspin
 
  861          do ispin = ik, ik + nspin - 1
 
  862            st%occ(ist, ispin) = min(rr, -(st%val_charge + excess_charge) - charge)
 
  863            charge = charge + st%occ(ist, ispin)
 
  882    if (st%fixed_occ) 
then 
  883      call parse_variable(namespace, 
'RestartReorderOccs', .false., st%restart_reorder_occs)
 
  885      st%restart_reorder_occs = .false.
 
  888    call smear_init(st%smear, namespace, st%d%ispin, st%fixed_occ, integral_occs, kpoints)
 
  890    unoccupied_states = (st%d%ispin /= 
spinors .and. st%nst*2 > st%qtot) .or. (st%d%ispin == 
spinors .and. st%nst > st%qtot)
 
  893      if (.not. unoccupied_states) 
then 
  894        call messages_write(
'Smearing needs unoccupied states (via ExtraStates or TotalStates) to be useful.')
 
  902      charge = charge + sum(st%occ(ist, 1:st%nik) * st%kweights(1:st%nik))
 
  904    if (abs(charge - st%qtot) > 1e-6_real64) 
then 
  905      message(1) = 
"Initial occupations do not integrate to total charge." 
  906      write(
message(2), 
'(6x,f12.6,a,f12.6)') charge, 
' != ', st%qtot
 
  933    st%fixed_spins = .false.
 
  934    if (st%d%ispin /= 
spinors) 
then 
  973    spin_fix: 
if (
parse_block(namespace, 
'InitialSpins', blk) == 0) 
then 
  981      st%fixed_spins = .
true.
 
  983        st%spin(:, :, i) = st%spin(:, :, 1)
 
  996    class(
mesh_t),          
intent(in)      :: mesh
 
  997    type(
type_t), 
optional, 
intent(in)      :: wfs_type
 
  998    logical,      
optional, 
intent(in)      :: skip(:)
 
  999    logical,      
optional, 
intent(in)      :: packed
 
 1003    if (
present(wfs_type)) 
then 
 1005      st%wfs_type = wfs_type
 
 1033    type(
mesh_t),                  
intent(in)    :: mesh
 
 1034    logical, 
optional,             
intent(in)    :: verbose
 
 1035    logical, 
optional,             
intent(in)    :: skip(:)
 
 1036    logical, 
optional,             
intent(in)    :: packed
 
 1038    integer :: ib, iqn, ist, istmin, istmax
 
 1039    logical :: same_node, verbose_, packed_
 
 1040    integer, 
allocatable :: bstart(:), bend(:)
 
 1044    safe_allocate(bstart(1:st%nst))
 
 1045    safe_allocate(bend(1:st%nst))
 
 1046    safe_allocate(st%group%iblock(1:st%nst))
 
 1055    if (
present(skip)) 
then 
 1057        if (.not. skip(ist)) 
then 
 1065    if (
present(skip)) 
then 
 1066      do ist = st%nst, istmin, -1
 
 1067        if (.not. skip(ist)) 
then 
 1074    if (
present(skip) .and. verbose_) 
then 
 1084    st%group%nblocks = 0
 
 1086    do ist = istmin, istmax
 
 1089      st%group%iblock(ist) = st%group%nblocks + 1
 
 1092      if (st%parallel_in_states .and. ist /= istmax) 
then 
 1095        same_node = (st%node(ist + 1) == st%node(ist))
 
 1098      if (ib == st%block_size .or. ist == istmax .or. .not. same_node) 
then 
 1100        st%group%nblocks = st%group%nblocks + 1
 
 1101        bend(st%group%nblocks) = ist
 
 1102        if (ist /= istmax) bstart(st%group%nblocks + 1) = ist + 1
 
 1106    safe_allocate(st%group%psib(1:st%group%nblocks, st%d%kpt%start:st%d%kpt%end))
 
 1108    safe_allocate(st%group%block_is_local(1:st%group%nblocks, 1:st%nik))
 
 1109    st%group%block_is_local = .false.
 
 1110    st%group%block_start  = -1
 
 1111    st%group%block_end    = -2  
 
 1113    do ib = 1, st%group%nblocks
 
 1114      if (bstart(ib) >= st%st_start .and. bend(ib) <= st%st_end) 
then 
 1115        if (st%group%block_start == -1) st%group%block_start = ib
 
 1116        st%group%block_end = ib
 
 1117        do iqn = st%d%kpt%start, st%d%kpt%end
 
 1118          st%group%block_is_local(ib, iqn) = .
true.
 
 1121            call dwfs_elec_init(st%group%psib(ib, iqn), st%d%dim, bstart(ib), bend(ib), mesh%np_part, iqn, &
 
 1122              special=.
true., packed=packed_)
 
 1124            call zwfs_elec_init(st%group%psib(ib, iqn), st%d%dim, bstart(ib), bend(ib), mesh%np_part, iqn, &
 
 1125              special=.
true., packed=packed_)
 
 1132    safe_allocate(st%group%block_range(1:st%group%nblocks, 1:2))
 
 1133    safe_allocate(st%group%block_size(1:st%group%nblocks))
 
 1135    st%group%block_range(1:st%group%nblocks, 1) = bstart(1:st%group%nblocks)
 
 1136    st%group%block_range(1:st%group%nblocks, 2) = bend(1:st%group%nblocks)
 
 1137    st%group%block_size(1:st%group%nblocks) = bend(1:st%group%nblocks) - bstart(1:st%group%nblocks) + 1
 
 1139    st%group%block_initialized = .
true.
 
 1141    safe_allocate(st%group%block_node(1:st%group%nblocks))
 
 1143    assert(
allocated(st%node))
 
 1144    assert(all(st%node >= 0) .and. all(st%node < st%mpi_grp%size))
 
 1146    do ib = 1, st%group%nblocks
 
 1147      st%group%block_node(ib) = st%node(st%group%block_range(ib, 1))
 
 1148      assert(st%group%block_node(ib) == st%node(st%group%block_range(ib, 2)))
 
 1154      do ib = 1, st%group%nblocks
 
 1160        if (st%group%block_size(ib) > 0) 
then 
 1190    safe_deallocate_a(bstart)
 
 1191    safe_deallocate_a(bend)
 
 1212    type(
grid_t),                
intent(in)    :: gr
 
 1214    real(real64) :: fsize
 
 1218    safe_allocate(st%rho(1:gr%np_part, 1:st%d%nspin))
 
 1221    fsize = gr%np_part*8.0_real64*st%block_size
 
 1233    class(
space_t),      
intent(in)    :: space
 
 1234    class(
mesh_t),       
intent(in)    :: mesh
 
 1238    if (.not. 
allocated(st%current)) 
then 
 1239      safe_allocate(st%current(1:mesh%np_part, 1:space%dim, 1:st%d%nspin))
 
 1243    if (.not. 
allocated(st%current_para)) 
then 
 1244      safe_allocate(st%current_para(1:mesh%np_part, 1:space%dim, 1:st%d%nspin))
 
 1248    if (.not. 
allocated(st%current_dia)) 
then 
 1249      safe_allocate(st%current_dia(1:mesh%np_part, 1:space%dim, 1:st%d%nspin))
 
 1253    if (.not. 
allocated(st%current_mag)) 
then 
 1254      safe_allocate(st%current_mag(1:mesh%np_part, 1:space%dim, 1:st%d%nspin))
 
 1258    if (.not. 
allocated(st%current_kpt)) 
then 
 1259      safe_allocate(st%current_kpt(1:mesh%np,1:space%dim,st%d%kpt%start:st%d%kpt%end))
 
 1337    default = option__statesorthogonalization__cholesky_serial
 
 1338#ifdef HAVE_SCALAPACK 
 1340      default = option__statesorthogonalization__cholesky_parallel
 
 1344    call parse_variable(namespace, 
'StatesOrthogonalization', default, st%orth_method)
 
 1365    call parse_variable(namespace, 
'StatesCLDeviceMemory', -512.0_real64, st%cl_states_mem)
 
 1374  subroutine states_elec_copy(stout, stin, exclude_wfns, exclude_eigenval, special)
 
 1377    logical, 
optional,           
intent(in)    :: exclude_wfns
 
 1378    logical, 
optional,           
intent(in)    :: exclude_eigenval
 
 1379    logical, 
optional,           
intent(in)    :: special
 
 1381    logical :: exclude_wfns_
 
 1390    safe_allocate_source_a(stout%kweights, stin%kweights)
 
 1391    stout%nik = stin%nik
 
 1394    if (stin%modelmbparticles%nparticle > 0) 
then 
 1395      safe_allocate_source_a(stout%mmb_nspindown, stin%mmb_nspindown)
 
 1396      safe_allocate_source_a(stout%mmb_iyoung, stin%mmb_iyoung)
 
 1397      safe_allocate_source_a(stout%mmb_proj, stin%mmb_proj)
 
 1400    stout%wfs_type    = stin%wfs_type
 
 1401    stout%nst         = stin%nst
 
 1402    stout%block_size  = stin%block_size
 
 1403    stout%orth_method = stin%orth_method
 
 1405    stout%cl_states_mem  = stin%cl_states_mem
 
 1406    stout%pack_states    = stin%pack_states
 
 1409    stout%only_userdef_istates = stin%only_userdef_istates
 
 1411    if (.not. exclude_wfns_) 
then 
 1412      safe_allocate_source_a(stout%rho, stin%rho)
 
 1415    stout%uniform_occ = stin%uniform_occ
 
 1418      safe_allocate_source_a(stout%eigenval, stin%eigenval)
 
 1419      safe_allocate_source_a(stout%occ, stin%occ)
 
 1420      safe_allocate_source_a(stout%spin, stin%spin)
 
 1425    stout%group%nblocks = stin%group%nblocks
 
 1427    safe_allocate_source_a(stout%user_def_states, stin%user_def_states)
 
 1429    safe_allocate_source_a(stout%current, stin%current)
 
 1430    safe_allocate_source_a(stout%current_kpt, stin%current_kpt)
 
 1431    safe_allocate_source_a(stout%rho_core, stin%rho_core)
 
 1432    safe_allocate_source_a(stout%frozen_rho, stin%frozen_rho)
 
 1433    safe_allocate_source_a(stout%frozen_tau, stin%frozen_tau)
 
 1434    safe_allocate_source_a(stout%frozen_gdens, stin%frozen_gdens)
 
 1435    safe_allocate_source_a(stout%frozen_ldens, stin%frozen_ldens)
 
 1437    stout%fixed_occ = stin%fixed_occ
 
 1438    stout%restart_fixed_occ = stin%restart_fixed_occ
 
 1440    stout%fixed_spins = stin%fixed_spins
 
 1442    stout%qtot       = stin%qtot
 
 1443    stout%val_charge = stin%val_charge
 
 1447    stout%parallel_in_states = stin%parallel_in_states
 
 1449    call mpi_grp_copy(stout%dom_st_kpt_mpi_grp, stin%dom_st_kpt_mpi_grp)
 
 1450    call mpi_grp_copy(stout%st_kpt_mpi_grp, stin%st_kpt_mpi_grp)
 
 1451    call mpi_grp_copy(stout%dom_st_mpi_grp, stin%dom_st_mpi_grp)
 
 1452    safe_allocate_source_a(stout%node, stin%node)
 
 1453    safe_allocate_source_a(stout%st_kpt_task, stin%st_kpt_task)
 
 1455#ifdef HAVE_SCALAPACK 
 1461    stout%scalapack_compatible = stin%scalapack_compatible
 
 1463    stout%lnst       = stin%lnst
 
 1464    stout%st_start   = stin%st_start
 
 1465    stout%st_end     = stin%st_end
 
 1469    stout%symmetrize_density = stin%symmetrize_density
 
 1473    stout%packed = stin%packed
 
 1475    stout%randomization = stin%randomization
 
 1491    if (st%modelmbparticles%nparticle > 0) 
then 
 1492      safe_deallocate_a(st%mmb_nspindown)
 
 1493      safe_deallocate_a(st%mmb_iyoung)
 
 1494      safe_deallocate_a(st%mmb_proj)
 
 1501    safe_deallocate_a(st%user_def_states)
 
 1503    safe_deallocate_a(st%rho)
 
 1504    safe_deallocate_a(st%eigenval)
 
 1506    safe_deallocate_a(st%current)
 
 1507    safe_deallocate_a(st%current_para)
 
 1508    safe_deallocate_a(st%current_dia)
 
 1509    safe_deallocate_a(st%current_mag)
 
 1510    safe_deallocate_a(st%current_kpt)
 
 1511    safe_deallocate_a(st%rho_core)
 
 1512    safe_deallocate_a(st%frozen_rho)
 
 1513    safe_deallocate_a(st%frozen_tau)
 
 1514    safe_deallocate_a(st%frozen_gdens)
 
 1515    safe_deallocate_a(st%frozen_ldens)
 
 1516    safe_deallocate_a(st%occ)
 
 1517    safe_deallocate_a(st%spin)
 
 1518    safe_deallocate_a(st%kweights)
 
 1521#ifdef HAVE_SCALAPACK 
 1527    safe_deallocate_a(st%node)
 
 1528    safe_deallocate_a(st%st_kpt_task)
 
 1530    if (st%parallel_in_states) 
then 
 1531      safe_deallocate_a(st%ap%schedule)
 
 1543    class(
mesh_t),          
intent(in)    :: mesh
 
 1545    integer, 
optional,      
intent(in)    :: ist_start_
 
 1546    integer, 
optional,      
intent(in)    :: ist_end_
 
 1547    integer, 
optional,      
intent(in)    :: ikpt_start_
 
 1548    integer, 
optional,      
intent(in)    :: ikpt_end_
 
 1549    logical, 
optional,      
intent(in)    :: normalized
 
 1552    integer :: ist, ik, id, ist_start, ist_end, jst, ikpt_start, ikpt_end
 
 1553    complex(real64)   :: alpha, beta
 
 1554    real(real64), 
allocatable :: dpsi(:,  :)
 
 1555    complex(real64), 
allocatable :: zpsi(:,  :), zpsi2(:)
 
 1556    integer :: ikpoint, ip
 
 1559    logical :: normalized_
 
 1570    safe_allocate(dpsi(1:mesh%np, 1:st%d%dim))
 
 1572      safe_allocate(zpsi(1:mesh%np, 1:st%d%dim))
 
 1575    select case (st%d%ispin)
 
 1578      do ik = ikpt_start, ikpt_end
 
 1579        ikpoint = st%d%get_kpoint_index(ik)
 
 1580        do ist = ist_start, ist_end
 
 1584                pre_shift = mesh%pv%xlocal-1, &
 
 1585                post_shift = mesh%pv%np_global - mesh%pv%xlocal - mesh%np + 1, &
 
 1586                normalized = normalized)
 
 1588              if(mesh%parallel_in_domains) 
then 
 1594              call dmf_random(mesh, dpsi(:, 1), normalized = normalized)
 
 1599                zpsi(ip,1) = cmplx(dpsi(ip,1), 
m_zero, real64)
 
 1608                pre_shift = mesh%pv%xlocal-1, &
 
 1609                post_shift = mesh%pv%np_global - mesh%pv%xlocal - mesh%np + 1, &
 
 1610                normalized = normalized)
 
 1612              if(mesh%parallel_in_domains) 
then 
 1618              call zmf_random(mesh, zpsi(:, 1), normalized = normalized)
 
 1630      if (st%fixed_spins) 
then 
 1632        do ik = ikpt_start, ikpt_end
 
 1633          ikpoint = st%d%get_kpoint_index(ik)
 
 1634          do ist = ist_start, ist_end
 
 1638                  pre_shift = mesh%pv%xlocal-1, &
 
 1639                  post_shift = mesh%pv%np_global - mesh%pv%xlocal - mesh%np + 1, &
 
 1640                  normalized = normalized)
 
 1642                if(mesh%parallel_in_domains) 
then 
 1648                call dmf_random(mesh, dpsi(:, 1), normalized = normalized)
 
 1652                zpsi(ip,1) = cmplx(dpsi(ip,1), 
m_zero, real64)
 
 1658                  pre_shift = mesh%pv%xlocal-1, &
 
 1659                  post_shift = mesh%pv%np_global - mesh%pv%xlocal - mesh%np + 1, &
 
 1660                  normalized = normalized)
 
 1662                if(mesh%parallel_in_domains) 
then 
 1668                call zmf_random(mesh, zpsi(:, 1), normalized = normalized)
 
 1681            safe_allocate(zpsi2(1:mesh%np))
 
 1682            do jst = ist_start, ist - 1
 
 1684              zpsi(1:mesh%np, 1) = zpsi(1:mesh%np, 1) - 
zmf_dotp(mesh, zpsi(:, 1), zpsi2)*zpsi2(1:mesh%np)
 
 1686            safe_deallocate_a(zpsi2)
 
 1689            zpsi(1:mesh%np, 2) = zpsi(1:mesh%np, 1)
 
 1693            if (abs(alpha) > 
m_zero) 
then 
 1694              beta = cmplx(st%spin(1, ist, ik) / abs(alpha), st%spin(2, ist, ik) / abs(alpha), real64)
 
 1696            zpsi(1:mesh%np, 1) = alpha*zpsi(1:mesh%np, 1)
 
 1697            zpsi(1:mesh%np, 2) = beta*zpsi(1:mesh%np, 2)
 
 1702        do ik = ikpt_start, ikpt_end
 
 1703          do ist = ist_start, ist_end
 
 1707                  pre_shift = mesh%pv%xlocal-1, &
 
 1708                  post_shift = mesh%pv%np_global - mesh%pv%xlocal - mesh%np + 1, &
 
 1709                  normalized = .false.)
 
 1711                if(mesh%parallel_in_domains) 
then 
 1717                call zmf_random(mesh, zpsi(:, id), normalized = .false.)
 
 1732    safe_deallocate_a(dpsi)
 
 1733    safe_deallocate_a(zpsi)
 
 1744    class(
mesh_t),       
intent(in)    :: mesh
 
 1745    logical, 
optional,   
intent(in)    :: compute_spin
 
 1749    real(real64)       :: charge
 
 1750    complex(real64), 
allocatable :: zpsi(:, :)
 
 1755      st%nik, st%nst, st%kweights)
 
 1762      charge = charge + sum(st%occ(ist, 1:st%nik) * st%kweights(1:st%nik))
 
 1764    if (abs(charge-st%qtot) > 1e-6_real64) 
then 
 1765      message(1) = 
'Occupations do not integrate to total charge.' 
 1766      write(
message(2), 
'(6x,f12.8,a,f12.8)') charge, 
' != ', st%qtot
 
 1769        message(1) = 
"There don't seem to be any electrons at all!" 
 1779      safe_allocate(zpsi(1:mesh%np, st%d%dim))
 
 1780      do ik = st%d%kpt%start, st%d%kpt%end
 
 1781        do ist = st%st_start, st%st_end
 
 1783          st%spin(1:3, ist, ik) = 
state_spin(mesh, zpsi)
 
 1786      safe_deallocate_a(zpsi)
 
 1788      if (st%parallel_in_states .or. st%d%kpt%parallel) 
then 
 1803    real(real64),      
optional, 
intent(in) :: alt_eig(st%st_start:, st%d%kpt%start:)
 
 1812    do ik = st%d%kpt%start, st%d%kpt%end
 
 1813      if (
present(alt_eig)) 
then 
 1814        tot = tot + st%kweights(ik) * sum(st%occ(st%st_start:st%st_end, ik) * &
 
 1815          alt_eig(st%st_start:st%st_end, ik))
 
 1817        tot = tot + st%kweights(ik) * sum(st%occ(st%st_start:st%st_end, ik) * &
 
 1818          st%eigenval(st%st_start:st%st_end, ik))
 
 1822    if (st%parallel_in_states .or. st%d%kpt%parallel) 
call comm_allreduce(st%st_kpt_mpi_grp, tot)
 
 1834    logical :: default_scalapack_compatible
 
 1845    st%parallel_in_states = .false.
 
 1848    call mpi_grp_init(st%dom_st_kpt_mpi_grp, mc%dom_st_kpt_comm)
 
 1852    default_scalapack_compatible = 
calc_mode_par%scalapack_compat() .and. .not. st%d%kpt%parallel
 
 1866    call parse_variable(namespace, 
'ScaLAPACKCompatible', default_scalapack_compatible, st%scalapack_compatible)
 
 1868#ifdef HAVE_SCALAPACK 
 1869    if (default_scalapack_compatible .neqv. st%scalapack_compatible) 
then 
 1870      call messages_experimental(
'Setting ScaLAPACKCompatible to other than default', namespace=namespace)
 
 1873    if (st%scalapack_compatible) 
then 
 1880    st%scalapack_compatible = .false.
 
 1889      if (st%nst < st%mpi_grp%size) 
then 
 1890        message(1) = 
"Have more processors than necessary" 
 1891        write(
message(2),
'(i4,a,i4,a)') st%mpi_grp%size, 
" processors and ", st%nst, 
" states." 
 1895      call distributed_init(st%dist, st%nst, st%mpi_grp%comm, 
"states", scalapack_compat = st%scalapack_compatible)
 
 1897      st%parallel_in_states = st%dist%parallel
 
 1900      st%st_start = st%dist%start
 
 1901      st%st_end   = st%dist%end
 
 1902      st%lnst     = st%dist%nlocal
 
 1903      st%node(1:st%nst) = st%dist%node(1:st%nst)
 
 1920    kinetic_energy_density, paramagnetic_current, density_gradient, density_laplacian, &
 
 1921    gi_kinetic_energy_density, st_end)
 
 1925    logical,                 
intent(in)    :: nlcc
 
 1926    real(real64), 
optional, 
target, 
intent(out)   :: kinetic_energy_density(:,:)
 
 1927    real(real64), 
optional, 
target, 
intent(out)   :: paramagnetic_current(:,:,:)
 
 1928    real(real64), 
optional,         
intent(out)   :: density_gradient(:,:,:)
 
 1929    real(real64), 
contiguous, 
optional,         
intent(out)   :: density_laplacian(:,:)
 
 1930    real(real64), 
optional,         
intent(out)   :: gi_kinetic_energy_density(:,:)
 
 1931    integer, 
optional,       
intent(in)    :: st_end
 
 1933    real(real64), 
pointer :: jp(:, :, :)
 
 1934    real(real64), 
pointer :: tau(:, :)
 
 1935    complex(real64), 
allocatable :: wf_psi(:,:), gwf_psi(:,:,:), wf_psi_conj(:,:), lwf_psi(:,:)
 
 1936    real(real64), 
allocatable :: abs_wf_psi(:,:), abs_gwf_psi(:,:)
 
 1937    complex(real64), 
allocatable :: psi_gpsi(:,:)
 
 1938    complex(real64)   :: c_tmp
 
 1939    integer :: is, ik, ist, i_dim, st_dim, ii, st_end_
 
 1940    real(real64)   :: ww, kpoint(gr%der%dim)
 
 1941    logical :: something_to_do
 
 1949    something_to_do = 
present(kinetic_energy_density) .or. 
present(gi_kinetic_energy_density) .or. &
 
 1950      present(paramagnetic_current) .or. 
present(density_gradient) .or. 
present(density_laplacian)
 
 1951    assert(something_to_do)
 
 1953    safe_allocate( wf_psi(1:gr%np_part, 1:st%d%dim))
 
 1954    safe_allocate( wf_psi_conj(1:gr%np_part, 1:st%d%dim))
 
 1955    safe_allocate(gwf_psi(1:gr%np, 1:gr%der%dim, 1:st%d%dim))
 
 1956    safe_allocate(abs_wf_psi(1:gr%np, 1:st%d%dim))
 
 1957    safe_allocate(abs_gwf_psi(1:gr%np, 1:st%d%dim))
 
 1958    safe_allocate(psi_gpsi(1:gr%np, 1:st%d%dim))
 
 1959    if (
present(density_laplacian)) 
then 
 1960      safe_allocate(lwf_psi(1:gr%np, 1:st%d%dim))
 
 1964    if (
present(kinetic_energy_density)) tau => kinetic_energy_density
 
 1967    if (
present(paramagnetic_current)) jp => paramagnetic_current
 
 1971    if (
present(gi_kinetic_energy_density)) 
then 
 1973        safe_allocate(jp(1:gr%np, 1:gr%der%dim, 1:st%d%nspin))
 
 1975      if (.not. 
present(kinetic_energy_density)) 
then 
 1976        safe_allocate(tau(1:gr%np, 1:st%d%nspin))
 
 1980    if (
associated(tau)) tau = 
m_zero 
 1981    if (
associated(jp)) jp = 
m_zero 
 1982    if (
present(density_gradient)) density_gradient(:,:,:) = 
m_zero 
 1983    if (
present(density_laplacian)) density_laplacian(:,:) = 
m_zero 
 1984    if (
present(gi_kinetic_energy_density)) gi_kinetic_energy_density = 
m_zero 
 1986    do ik = st%d%kpt%start, st%d%kpt%end
 
 1988      kpoint(1:gr%der%dim) = kpoints%get_point(st%d%get_kpoint_index(ik))
 
 1989      is = st%d%get_spin_index(ik)
 
 1991      do ist = st%st_start, st_end_
 
 1992        ww = st%kweights(ik)*st%occ(ist, ik)
 
 1998        do st_dim = 1, st%d%dim
 
 2003        do st_dim = 1, st%d%dim
 
 2004          call zderivatives_grad(gr%der, wf_psi(:,st_dim), gwf_psi(:,:,st_dim), set_bc = .false.)
 
 2008        if (
present(density_laplacian)) 
then 
 2009          do st_dim = 1, st%d%dim
 
 2010            call zderivatives_lapl(gr%der, wf_psi(:,st_dim), lwf_psi(:,st_dim), ghost_update = .false., set_bc = .false.)
 
 2015        wf_psi_conj(1:gr%np, 1:st%d%dim) = conjg(wf_psi(1:gr%np,1:st%d%dim))
 
 2016        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)
 
 2018        if (
present(density_laplacian)) 
then 
 2019          density_laplacian(1:gr%np, is) = density_laplacian(1:gr%np, is) + &
 
 2020            ww * 
m_two*real(wf_psi_conj(1:gr%np, 1) * lwf_psi(1:gr%np, 1), real64)
 
 2021          if (st%d%ispin == 
spinors) 
then 
 2022            density_laplacian(1:gr%np, 2) = density_laplacian(1:gr%np, 2) + &
 
 2023              ww * 
m_two*real(wf_psi_conj(1:gr%np, 2) * lwf_psi(1:gr%np, 2), real64)
 
 2026              c_tmp = ww*(lwf_psi(ii, 1) * wf_psi_conj(ii, 2) + wf_psi(ii, 1) * conjg(lwf_psi(ii, 2)))
 
 2027              density_laplacian(ii, 3) = density_laplacian(ii, 3) + real(c_tmp, real64)
 
 2028              density_laplacian(ii, 4) = density_laplacian(ii, 4) + aimag(c_tmp)
 
 2033        if (
associated(tau)) 
then 
 2034          tau(1:gr%np, is) = tau(1:gr%np, is) &
 
 2035            + ww * sum(kpoint(1:gr%der%dim)**2) * abs_wf_psi(1:gr%np, 1)
 
 2036          if (st%d%ispin == 
spinors) 
then 
 2037            tau(1:gr%np, 2) = tau(1:gr%np, 2) &
 
 2038              + ww * sum(kpoint(1:gr%der%dim)**2) * abs_wf_psi(1:gr%np, 2)
 
 2042              c_tmp = ww * sum(kpoint(1:gr%der%dim)**2) * wf_psi(ii, 1) * wf_psi_conj(ii, 2)
 
 2043              tau(ii, 3) = tau(ii, 3) + real(c_tmp, real64)
 
 2044              tau(ii, 4) = tau(ii, 4) + aimag(c_tmp)
 
 2049        do i_dim = 1, gr%der%dim
 
 2052          psi_gpsi(1:gr%np, 1:st%d%dim) = wf_psi_conj(1:gr%np, 1:st%d%dim) &
 
 2053            * gwf_psi(1:gr%np,i_dim,1:st%d%dim)
 
 2054          abs_gwf_psi(1:gr%np, 1:st%d%dim) = real(conjg(gwf_psi(1:gr%np, i_dim, 1:st%d%dim)) &
 
 2055            * gwf_psi(1:gr%np, i_dim, 1:st%d%dim), real64)
 
 2057          if (
present(density_gradient)) 
then 
 2058            density_gradient(1:gr%np, i_dim, is) = density_gradient(1:gr%np, i_dim, is) &
 
 2059              + ww * 
m_two * real(psi_gpsi(1:gr%np, 1), real64)
 
 2060            if (st%d%ispin == 
spinors) 
then 
 2061              density_gradient(1:gr%np, i_dim, 2) = density_gradient(1:gr%np, i_dim, 2)  &
 
 2062                + ww * 
m_two*real(psi_gpsi(1:gr%np, 2), real64)
 
 2065                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)))
 
 2066                density_gradient(ii, i_dim, 3) = density_gradient(ii, i_dim, 3) + real(c_tmp, real64)
 
 2067                density_gradient(ii, i_dim, 4) = density_gradient(ii, i_dim, 4) + aimag(c_tmp)
 
 2072          if (
present(density_laplacian)) 
then 
 2073            call lalg_axpy(gr%np, ww*
m_two, abs_gwf_psi(:,1), density_laplacian(:,is))
 
 2074            if (st%d%ispin == 
spinors) 
then 
 2075              call lalg_axpy(gr%np, ww*
m_two, abs_gwf_psi(:,2), density_laplacian(:,2))
 
 2078                c_tmp = 
m_two * ww * gwf_psi(ii, i_dim, 1) * conjg(gwf_psi(ii, i_dim, 2))
 
 2079                density_laplacian(ii, 3) = density_laplacian(ii, 3) + real(c_tmp, real64)
 
 2080                density_laplacian(ii, 4) = density_laplacian(ii, 4) + aimag(c_tmp)
 
 2088          if (
associated(jp)) 
then 
 2090              jp(1:gr%np, i_dim, is) = jp(1:gr%np, i_dim, is) + &
 
 2091                ww*(aimag(psi_gpsi(1:gr%np, 1)) - abs_wf_psi(1:gr%np, 1)*kpoint(i_dim))
 
 2092              if (st%d%ispin == 
spinors) 
then 
 2093                jp(1:gr%np, i_dim, 2) = jp(1:gr%np, i_dim, 2) + &
 
 2094                  ww*( aimag(psi_gpsi(1:gr%np, 2)) - abs_wf_psi(1:gr%np, 2)*kpoint(i_dim))
 
 2097                  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)) &
 
 2098                    - 
m_two * 
m_zi*wf_psi(ii, 1)*wf_psi_conj(ii, 2)*kpoint(i_dim))
 
 2099                  jp(ii, i_dim, 3) = jp(ii, i_dim, 3) + real(c_tmp, real64)
 
 2100                  jp(ii, i_dim, 4) = jp(ii, i_dim, 4) + aimag(c_tmp)
 
 2109          if (
associated(tau)) 
then 
 2110            tau(1:gr%np, is) = tau(1:gr%np, is) + ww*(abs_gwf_psi(1:gr%np,1) &
 
 2111              - 
m_two*aimag(psi_gpsi(1:gr%np, 1))*kpoint(i_dim))
 
 2112            if (st%d%ispin == 
spinors) 
then 
 2113              tau(1:gr%np, 2) = tau(1:gr%np, 2) + ww*(abs_gwf_psi(1:gr%np, 2) &
 
 2114                - 
m_two*aimag(psi_gpsi(1:gr%np, 2))*kpoint(i_dim))
 
 2117                c_tmp = ww * ( gwf_psi(ii, i_dim, 1)*conjg(gwf_psi(ii, i_dim, 2))  &
 
 2118                  + 
m_zi * (gwf_psi(ii,i_dim,1)*wf_psi_conj(ii, 2)    &
 
 2119                  - wf_psi(ii, 1)*conjg(gwf_psi(ii,i_dim,2)))*kpoint(i_dim))
 
 2120                tau(ii, 3) = tau(ii, 3) + real(c_tmp, real64)
 
 2121                tau(ii, 4) = tau(ii, 4) + aimag(c_tmp)
 
 2131    safe_deallocate_a(wf_psi_conj)
 
 2132    safe_deallocate_a(abs_wf_psi)
 
 2133    safe_deallocate_a(abs_gwf_psi)
 
 2134    safe_deallocate_a(psi_gpsi)
 
 2136    if (.not. 
present(gi_kinetic_energy_density)) 
then 
 2137      if (.not. 
present(paramagnetic_current)) 
then 
 2138        safe_deallocate_p(jp)
 
 2140      if (.not. 
present(kinetic_energy_density)) 
then 
 2141        safe_deallocate_p(tau)
 
 2145    if (st%parallel_in_states .or. st%d%kpt%parallel) 
call reduce_all(st%st_kpt_mpi_grp)
 
 2150    if (st%symmetrize_density) 
then 
 2151      do is = 1, st%d%nspin
 
 2152        if (
associated(tau)) 
then 
 2156        if (
present(density_laplacian)) 
then 
 2160        if (
associated(jp)) 
then 
 2164        if (
present(density_gradient)) 
then 
 2171    if (
allocated(st%rho_core) .and. nlcc .and. (
present(density_laplacian) .or. 
present(density_gradient))) 
then 
 2173        wf_psi(ii, 1) = st%rho_core(ii)/st%d%spin_channels
 
 2178      if (
present(density_gradient)) 
then 
 2181        do is = 1, st%d%spin_channels
 
 2182          density_gradient(1:gr%np, 1:gr%der%dim, is) = density_gradient(1:gr%np, 1:gr%der%dim, is) + &
 
 2183            real(gwf_psi(1:gr%np, 1:gr%der%dim,1))
 
 2188      if (
present(density_laplacian)) 
then 
 2191        do is = 1, st%d%spin_channels
 
 2192          density_laplacian(1:gr%np, is) = density_laplacian(1:gr%np, is) + real(lwf_psi(1:gr%np, 1))
 
 2199    if (
allocated(st%frozen_tau) .and. .not. 
present(st_end)) 
then 
 2202    if (
allocated(st%frozen_gdens) .and. .not. 
present(st_end)) 
then 
 2203      do is = 1, st%d%nspin
 
 2204        call lalg_axpy(gr%np, gr%der%dim, 
m_one, st%frozen_gdens(:,:,is), density_gradient(:,:,is))
 
 2207    if (
allocated(st%frozen_tau) .and. .not. 
present(st_end)) 
then 
 2208      call lalg_axpy(gr%np, st%d%nspin, 
m_one, st%frozen_ldens, density_laplacian)
 
 2211    safe_deallocate_a(wf_psi)
 
 2212    safe_deallocate_a(gwf_psi)
 
 2213    safe_deallocate_a(lwf_psi)
 
 2217    if (
present(gi_kinetic_energy_density)) 
then 
 2218      do is = 1, st%d%nspin
 
 2219        assert(
associated(tau))
 
 2220        gi_kinetic_energy_density(1:gr%np, is) = tau(1:gr%np, is)
 
 2223        assert(
associated(jp))
 
 2224        if (st%d%ispin /= 
spinors) 
then 
 2225          do is = 1, st%d%nspin
 
 2228              if (st%rho(ii, is) < 1.0e-7_real64) cycle
 
 2229              gi_kinetic_energy_density(ii, is) = &
 
 2230                gi_kinetic_energy_density(ii, is) - sum(jp(ii,1:gr%der%dim, is)**2)/st%rho(ii, is)
 
 2236            gi_kinetic_energy_density(ii, 1) = gi_kinetic_energy_density(ii, 1) &
 
 2237              - sum(jp(ii,1:gr%der%dim, 1)**2)/(safe_tol(st%rho(ii, 1),
m_epsilon))
 
 2238            gi_kinetic_energy_density(ii, 2) = gi_kinetic_energy_density(ii, 2) &
 
 2239              - sum(jp(ii,1:gr%der%dim, 2)**2)/(safe_tol(st%rho(ii, 2),
m_epsilon))
 
 2240            gi_kinetic_energy_density(ii, 3) = &
 
 2241              gi_kinetic_energy_density(ii, 3) - sum(jp(ii,1:gr%der%dim, 3)**2 + jp(ii,1:gr%der%dim, 4)**2) &
 
 2242              /(safe_tol((st%rho(ii, 3)**2 + st%rho(ii, 4)**2), 
m_epsilon))*st%rho(ii, 3)
 
 2243            gi_kinetic_energy_density(ii, 4) = &
 
 2244              gi_kinetic_energy_density(ii, 4) + sum(jp(ii,1:gr%der%dim, 3)**2 + jp(ii,1:gr%der%dim, 4)**2) &
 
 2245              /(safe_tol((st%rho(ii, 3)**2 + st%rho(ii, 4)**2), 
m_epsilon))*st%rho(ii, 4)
 
 2251    if (.not. 
present(kinetic_energy_density)) 
then 
 2252      safe_deallocate_p(tau)
 
 2254    if (.not. 
present(paramagnetic_current)) 
then 
 2255      safe_deallocate_p(jp)
 
 2270      if (
associated(tau)) 
call comm_allreduce(grp, tau, dim = (/gr%np, st%d%nspin/))
 
 2272      if (
present(density_laplacian)) 
call comm_allreduce(grp, density_laplacian, dim = (/gr%np, st%d%nspin/))
 
 2274      do is = 1, st%d%nspin
 
 2275        if (
associated(jp)) 
call comm_allreduce(grp, jp(:, :, is), dim = (/gr%np, gr%der%dim/))
 
 2277        if (
present(density_gradient)) 
then 
 2278          call comm_allreduce(grp, density_gradient(:, :, is), dim = (/gr%np, gr%der%dim/))
 
 2292    type(
mesh_t), 
intent(in) :: mesh
 
 2293    complex(real64),        
intent(in) :: f1(:, :)
 
 2294    real(real64)             :: spin(1:3)
 
 2296    complex(real64) :: z
 
 2300    z = 
zmf_dotp(mesh, f1(:, 1) , f1(:, 2))
 
 2302    spin(1) = 
m_two*real(z, real64)
 
 2303    spin(2) = 
m_two*aimag(z)
 
 2315    integer,             
intent(in) :: ist
 
 2329    integer,             
intent(in) :: ist
 
 2330    integer,             
intent(in) :: ik
 
 2335      ik >= st%d%kpt%start .and. ik <= st%d%kpt%end
 
 2345    class(
mesh_t),       
intent(in) :: mesh
 
 2351    memory = memory + real64*real(mesh%np_part_global, real64) *st%d%dim*real(st%nst, real64) *st%d%kpt%nglobal
 
 2361    logical,      
optional, 
intent(in)    :: copy
 
 2364    integer(int64) :: max_mem, mem
 
 2376    if (accel_is_enabled()) 
then 
 2377      max_mem = accel_global_memory_size()
 
 2379      if (st%cl_states_mem > m_one) 
then 
 2380        max_mem = int(st%cl_states_mem, int64)*(1024_8)**2
 
 2381      else if (st%cl_states_mem < 0.0_real64) 
then 
 2382        max_mem = max_mem + int(st%cl_states_mem, int64)*(1024_8)**2
 
 2384        max_mem = int(st%cl_states_mem*real(max_mem, real64) , int64)
 
 2387      max_mem = huge(max_mem)
 
 2391    qnloop: 
do iqn = st%d%kpt%start, st%d%kpt%end
 
 2392      do ib = st%group%block_start, st%group%block_end
 
 2394        mem = mem + st%group%psib(ib, iqn)%pack_total_size()
 
 2396        if (mem > max_mem) 
then 
 2397          call messages_write(
'Not enough CL device memory to store all states simultaneously.', new_line = .
true.)
 
 2398          call messages_write(
'Only ')
 
 2399          call messages_write(ib - st%group%block_start)
 
 2400          call messages_write(
' of ')
 
 2401          call messages_write(st%group%block_end - st%group%block_start + 1)
 
 2402          call messages_write(
' blocks will be stored in device memory.', new_line = .
true.)
 
 2403          call messages_warning()
 
 2407        call st%group%psib(ib, iqn)%do_pack(copy)
 
 2419    logical,      
optional, 
intent(in)    :: copy
 
 2428      do iqn = st%d%kpt%start, st%d%kpt%end
 
 2429        do ib = st%group%block_start, st%group%block_end
 
 2430          if (st%group%psib(ib, iqn)%is_packed()) 
call st%group%psib(ib, iqn)%do_unpack(copy)
 
 2443    type(namespace_t),       
intent(in) :: namespace
 
 2447    call messages_print_with_emphasis(msg=
"States", namespace=namespace)
 
 2449    write(message(1), 
'(a,f12.3)') 
'Total electronic charge  = ', st%qtot
 
 2450    write(message(2), 
'(a,i8)')    
'Number of states         = ', st%nst
 
 2451    write(message(3), 
'(a,i8)')    
'States block-size        = ', st%block_size
 
 2452    call messages_info(3, namespace=namespace)
 
 2454    call messages_print_with_emphasis(namespace=namespace)
 
 2469    do iqn = st%d%kpt%start, st%d%kpt%end
 
 2470      do ib = st%group%block_start, st%group%block_end
 
 2471        call batch_set_zero(st%group%psib(ib, iqn))
 
 2481  integer pure function states_elec_block_min(st, ib) result(range)
 
 2483    integer,                
intent(in) :: ib
 
 2485    range = st%group%block_range(ib, 1)
 
 2491  integer pure function states_elec_block_max(st, ib) result(range)
 
 2493    integer,                
intent(in) :: ib
 
 2495    range = st%group%block_range(ib, 2)
 
 2501  integer pure function states_elec_block_size(st, ib) result(size)
 
 2503    integer,           
intent(in) :: ib
 
 2505    size = st%group%block_size(ib)
 
 2513    type(namespace_t),    
intent(in)  :: namespace
 
 2514    integer,              
intent(out) :: n_pairs
 
 2515    integer,              
intent(out) :: n_occ(:)
 
 2516    integer,              
intent(out) :: n_unocc(:)
 
 2517    logical, 
allocatable, 
intent(out) :: is_included(:,:,:)
 
 2519    logical,              
intent(out) :: is_frac_occ
 
 2521    integer :: ik, ist, ast, n_filled, n_partially_filled, n_half_filled
 
 2522    character(len=80) :: nst_string, default, wfn_list
 
 2523    real(real64) :: energy_window
 
 2527    is_frac_occ = .false.
 
 2529      call occupied_states(st, namespace, ik, n_filled, n_partially_filled, n_half_filled)
 
 2530      if (n_partially_filled > 0 .or. n_half_filled > 0) is_frac_occ = .
true.
 
 2531      n_occ(ik) = n_filled + n_partially_filled + n_half_filled
 
 2532      n_unocc(ik) = st%nst - n_filled
 
 2545    call parse_variable(namespace, 
'CasidaKSEnergyWindow', -m_one, energy_window, units_inp%energy)
 
 2568    safe_allocate(is_included(maxval(n_occ), minval(n_occ) + 1:st%nst , st%nik))
 
 2569    is_included(:,:,:) = .false.
 
 2571    if (energy_window < m_zero) 
then 
 2572      write(nst_string,
'(i6)') st%nst
 
 2573      write(default,
'(a,a)') 
"1-", trim(adjustl(nst_string))
 
 2574      call parse_variable(namespace, 
'CasidaKohnShamStates', default, wfn_list)
 
 2576      write(message(1),
'(a,a)') 
"Info: States that form the basis: ", trim(wfn_list)
 
 2577      call messages_info(1, namespace=namespace)
 
 2582        do ast = n_occ(ik) + 1, st%nst
 
 2583          if (loct_isinstringlist(ast, wfn_list)) 
then 
 2584            do ist = 1, n_occ(ik)
 
 2585              if (loct_isinstringlist(ist, wfn_list)) 
then 
 2586                n_pairs = n_pairs + 1
 
 2587                is_included(ist, ast, ik) = .
true.
 
 2596      write(message(1),
'(a,f12.6,a)') 
"Info: including transitions with energy < ", &
 
 2597        units_from_atomic(units_out%energy, energy_window), trim(units_abbrev(units_out%energy))
 
 2598      call messages_info(1, namespace=namespace)
 
 2603        do ast = n_occ(ik) + 1, st%nst
 
 2604          do ist = 1, n_occ(ik)
 
 2605            if (st%eigenval(ast, ik) - st%eigenval(ist, ik) < energy_window) 
then 
 2606              n_pairs = n_pairs + 1
 
 2607              is_included(ist, ast, ik) = .
true.
 
 2635  subroutine occupied_states(st, namespace, ik, n_filled, n_partially_filled, n_half_filled, &
 
 2636    filled, partially_filled, half_filled)
 
 2638    type(namespace_t),      
intent(in)  :: namespace
 
 2639    integer,                
intent(in)  :: ik
 
 2640    integer,                
intent(out) :: n_filled, n_partially_filled, n_half_filled
 
 2641    integer,      
optional, 
intent(out) :: filled(:), partially_filled(:), half_filled(:)
 
 2647    if (
present(filled))           filled(:) = 0
 
 2648    if (
present(partially_filled)) partially_filled(:) = 0
 
 2649    if (
present(half_filled))      half_filled(:) = 0
 
 2651    n_partially_filled = 0
 
 2654    select case (st%d%ispin)
 
 2657        if (abs(st%occ(ist, ik) - m_two) < m_min_occ) 
then 
 2658          n_filled = n_filled + 1
 
 2659          if (
present(filled)) filled(n_filled) = ist
 
 2660        else if (abs(st%occ(ist, ik) - m_one) < m_min_occ) 
then 
 2661          n_half_filled = n_half_filled + 1
 
 2662          if (
present(half_filled)) half_filled(n_half_filled) = ist
 
 2663        else if (st%occ(ist, ik) > m_min_occ) 
then 
 2664          n_partially_filled = n_partially_filled + 1
 
 2665          if (
present(partially_filled)) partially_filled(n_partially_filled) = ist
 
 2666        else if (abs(st%occ(ist, ik)) > m_min_occ) 
then 
 2667          write(message(1),*) 
'Internal error in occupied_states: Illegal occupation value ', st%occ(ist, ik)
 
 2668          call messages_fatal(1, namespace=namespace)
 
 2671    case (spin_polarized, spinors)
 
 2673        if (abs(st%occ(ist, ik)-m_one) < m_min_occ) 
then 
 2674          n_filled = n_filled + 1
 
 2675          if (
present(filled)) filled(n_filled) = ist
 
 2676        else if (st%occ(ist, ik) > m_min_occ) 
then 
 2677          n_partially_filled = n_partially_filled + 1
 
 2678          if (
present(partially_filled)) partially_filled(n_partially_filled) = ist
 
 2679        else if (abs(st%occ(ist, ik)) > m_min_occ) 
then 
 2680          write(message(1),*) 
'Internal error in occupied_states: Illegal occupation value ', st%occ(ist, ik)
 
 2681          call messages_fatal(1, namespace=namespace)
 
 2693    type(multicomm_t),       
intent(in)    :: mc
 
 2696    call distributed_init(this%d%kpt, this%nik, mc%group_comm(p_strategy_kpoints), 
"k-points")
 
 2711    if (.not. 
allocated(st%st_kpt_task)) 
then 
 2712      safe_allocate(st%st_kpt_task(0:st%st_kpt_mpi_grp%size-1, 1:4))
 
 2715    st%st_kpt_task(0:st%st_kpt_mpi_grp%size-1, :) = 0
 
 2716    st%st_kpt_task(st%st_kpt_mpi_grp%rank, :) = [st%st_start, st%st_end, st%d%kpt%start, st%d%kpt%end]
 
 2718    if (st%parallel_in_states .or. st%d%kpt%parallel) 
then 
 2719      call comm_allreduce(st%st_kpt_mpi_grp, st%st_kpt_task)
 
 2730    type(kpoints_t),             
intent(in)    :: kpoints
 
 2731    type(namespace_t),           
intent(in)    :: namespace
 
 2734    type(states_elec_dim_t), 
pointer :: dd
 
 2741    st%nik = kpoints_number(kpoints)
 
 2743    if (dd%ispin == spin_polarized) st%nik = 2*st%nik
 
 2745    safe_allocate(st%kweights(1:st%nik))
 
 2748      ik = dd%get_kpoint_index(iq)
 
 2749      st%kweights(iq) = kpoints%get_weight(ik)
 
 2761      call io_mkdir(
'debug/', namespace)
 
 2762      iunit = io_open(
'debug/kpoints', namespace, action = 
'write')
 
 2763      call kpoints%write_info(iunit=iunit, absolute_coordinates = .
true.)
 
 2764      call io_close(iunit)
 
 2778    class(mesh_t),        
intent(in) :: gr
 
 2779    real(real64)                     :: dipole(1:gr%box%dim)
 
 2782    real(real64) :: e_dip(1:gr%box%dim, this%d%spin_channels)
 
 2786    do ispin = 1, this%d%spin_channels
 
 2787      call dmf_dipole(gr, this%rho(:, ispin), e_dip(:, ispin))
 
 2790    dipole(:) = sum(e_dip(:, 1:this%d%spin_channels), 2)  
 
 2798#include "states_elec_inc.F90" 
 2801#include "complex.F90" 
 2802#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)
 
subroutine, public messages_info(no_lines, iunit, verbose_limit, stress, all_nodes, namespace)
 
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)
 
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.