29  use, 
intrinsic :: iso_fortran_env
 
   74    type(restart_t),             
intent(in)    :: restart
 
   75    type(namespace_t),           
intent(in)    :: namespace
 
   76    class(space_t),              
intent(in)    :: space
 
   77    type(states_elec_t), 
target, 
intent(inout) :: st
 
   78    class(mesh_t),               
intent(in)    :: mesh
 
   79    type(kpoints_t),             
intent(in)    :: kpoints
 
   80    logical,           
optional, 
intent(in)    :: is_complex
 
   81    logical,           
optional, 
intent(in)    :: packed
 
   83    integer :: nkpt, dim, nst, ierr
 
   84    real(real64), 
allocatable :: new_occ(:,:)
 
   91      message(1) = 
"Unable to read states information." 
   95    if (st%parallel_in_states) 
then 
   96      message(1) = 
"Internal error: cannot use states_elec_look_and_load when parallel in states." 
  101    safe_allocate(new_occ(1:nst, 1:st%nik))
 
  103    new_occ(1:min(nst, st%nst),:) = st%occ(1:min(nst, st%nst),:)
 
  104    safe_deallocate_a(st%occ)
 
  105    call move_alloc(new_occ, st%occ)
 
  115    safe_deallocate_a(st%node)
 
  116    safe_allocate(st%node(1:st%nst))
 
  119    safe_deallocate_a(st%eigenval)
 
  120    safe_allocate(st%eigenval(1:st%nst, 1:st%nik))
 
  121    st%eigenval = huge(st%eigenval)
 
  123    if (
present(is_complex)) 
then 
  134    if (st%d%ispin == 
spinors) 
then 
  135      safe_allocate(st%spin(1:3, 1:st%nst, 1:st%nik))
 
  142      message(1) = 
"Unable to read wavefunctions." 
  151  subroutine states_elec_dump(restart, space, st, mesh, kpoints, ierr, iter, lr, st_start_writing, verbose)
 
  152    type(restart_t),      
intent(in)  :: restart
 
  153    class(space_t),       
intent(in)  :: space
 
  154    type(states_elec_t),  
intent(in)  :: st
 
  155    class(mesh_t),        
intent(in)  :: mesh
 
  156    type(kpoints_t),      
intent(in)  :: kpoints
 
  157    integer,              
intent(out) :: ierr
 
  158    integer,    
optional, 
intent(in)  :: iter
 
  160    type(lr_t), 
optional, 
intent(in)  :: lr
 
  161    integer,    
optional, 
intent(in)  :: st_start_writing
 
  162    logical,    
optional, 
intent(in)  :: verbose
 
  164    integer :: iunit_wfns, iunit_occs, iunit_states
 
  165    integer :: err, err2(2), ik, idir, ist, idim, itot
 
  167    character(len=MAX_PATH_LEN) :: filename
 
  168    character(len=300) :: lines(3)
 
  169    logical :: lr_wfns_are_associated, should_write, verbose_
 
  170    real(real64)   :: kpoint(space%dim)
 
  171    real(real64),  
allocatable :: dpsi(:), rff_global(:)
 
  172    complex(real64),  
allocatable :: zpsi(:), zff_global(:)
 
  186      message(1) = 
"Info: Writing states." 
  192    if (
present(lr)) 
then 
  193      lr_wfns_are_associated = (
allocated(lr%ddl_psi) .and. 
states_are_real(st)) .or. &
 
  195      assert(lr_wfns_are_associated)
 
  202    write(lines(1), 
'(a20,1i10)')  
'nst=                ', st%nst
 
  203    write(lines(2), 
'(a20,1i10)')  
'dim=                ', st%d%dim
 
  204    write(lines(3), 
'(a20,1i10)')  
'nik=                ', st%nik
 
  206    if (err /= 0) ierr = ierr + 1
 
  211    lines(1) = 
'#     #k-point            #st            #dim    filename' 
  213      lines(2) = 
'%Real_Wavefunctions' 
  215      lines(2) = 
'%Complex_Wavefunctions' 
  218    if (err /= 0) ierr = ierr + 2
 
  222    lines(1) = 
'# occupations | eigenvalue[a.u.] | Im(eigenvalue) [a.u.] | k-points | k-weights | filename | ik | ist | idim' 
  223    lines(2) = 
'%Occupations_Eigenvalues_K-Points' 
  225    if (err /= 0) ierr = ierr + 4
 
  229      safe_allocate(dpsi(1:mesh%np))
 
  230      safe_allocate(rff_global(1:mesh%np_global))
 
  232      safe_allocate(zpsi(1:mesh%np))
 
  233      safe_allocate(zff_global(1:mesh%np_global))
 
  240      kpoint(1:space%dim) = &
 
  241        kpoints%get_point(st%d%get_kpoint_index(ik), absolute_coordinates = .
true.)
 
  244        do idim = 1, st%d%dim
 
  246          write(filename,
'(i10.10)') itot
 
  248          write(lines(1), 
'(i8,a,i8,a,i8,3a)') ik, 
' | ', ist, 
' | ', idim, 
' | "', trim(filename), 
'"' 
  250          if (err /= 0) err2(1) = err2(1) + 1
 
  252          write(lines(1), 
'(e23.16,a,e23.16)') st%occ(ist,ik), 
' | ', st%eigenval(ist, ik)
 
  253          write(lines(1), 
'(a,a,e23.16)') trim(lines(1)), 
' | ', 
m_zero 
  254          do idir = 1, space%dim
 
  255            write(lines(1), 
'(a,a,e23.16)') trim(lines(1)), 
' | ', kpoint(idir)
 
  257          write(lines(1), 
'(a,a,e23.16,a,i10.10,3(a,i8))') trim(lines(1)), &
 
  258            ' | ', st%kweights(ik), 
' | ', itot, 
' | ', ik, 
' | ', ist, 
' | ', idim
 
  260          if (err /= 0) err2(1) = err2(1) + 1
 
  262          should_write = st%st_start <= ist .and. ist <= st%st_end
 
  263          if (should_write .and. 
present(st_start_writing)) 
then 
  264            if (ist < st_start_writing) should_write = .false.
 
  267          if (should_write) 
then 
  268            if (.not. 
present(lr)) 
then 
  269              if (st%d%kpt%start <= ik .and. ik <= st%d%kpt%end) 
then 
  281              if (st%d%kpt%start <= ik .and. ik <= st%d%kpt%end) 
then 
  284                    lr%ddl_psi(:, idim, ist, ik), err, root = root)
 
  287                    lr%zdl_psi(:, idim, ist, ik), err, root = root)
 
  293            if (err /= 0) err2(2) = err2(2) + 1
 
  300    if (err2(1) /= 0) ierr = ierr + 8
 
  301    if (err2(2) /= 0) ierr = ierr + 16
 
  303    safe_deallocate_a(dpsi)
 
  304    safe_deallocate_a(zpsi)
 
  305    safe_deallocate_a(rff_global)
 
  306    safe_deallocate_a(zff_global)
 
  310    if (err /= 0) ierr = ierr + 32
 
  312    if (err /= 0) ierr = ierr + 64
 
  313    if (
present(iter)) 
then 
  314      write(lines(1),
'(a,i7)') 
'Iter = ', iter
 
  316      if (err /= 0) ierr = ierr + 128
 
  323      message(1) = 
"Info: Finished writing states." 
  340  subroutine states_elec_load(restart, namespace, space, st, mesh, kpoints, ierr, iter, lr, lowest_missing, label, verbose, skip)
 
  343    class(
space_t),             
intent(in)    :: space
 
  345    class(
mesh_t),              
intent(in)    :: mesh
 
  347    integer,                    
intent(out)   :: ierr
 
  348    integer,          
optional, 
intent(out)   :: iter
 
  349    type(
lr_t),       
optional, 
intent(inout) :: lr
 
  350    integer,          
optional, 
intent(out)   :: lowest_missing(:, :)
 
  351    character(len=*), 
optional, 
intent(in)    :: label
 
  352    logical,          
optional, 
intent(in)    :: verbose
 
  353    logical,          
optional, 
intent(in)    :: skip(:)
 
  355    integer              :: states_elec_file, wfns_file, occ_file, err, ik, ist, idir, idim
 
  356    integer              :: idone, iread, ntodo
 
  357    character(len=12)    :: filename
 
  358    character(len=1)     :: char
 
  359    logical, 
allocatable :: filled(:, :, :)
 
  360    character(len=256)   :: lines(3), label_
 
  361    character(len=50)    :: str
 
  363    real(real64)         :: my_occ, imev, my_kweight
 
  364    logical              :: read_occ, lr_allocated, verbose_
 
  365    logical              :: integral_occs
 
  366    real(real64), 
allocatable   :: dpsi(:)
 
  367    complex(real64), 
allocatable   :: zpsi(:), zpsil(:)
 
  368    character(len=256), 
allocatable :: restart_file(:, :, :)
 
  369    logical,            
allocatable :: restart_file_present(:, :, :)
 
  370    real(real64)         :: kpoint(space%dim), read_kpoint(space%dim)
 
  373    integer, 
allocatable :: lowest_missing_tmp(:, :)
 
  380    if (
present(lowest_missing)) lowest_missing = 1
 
  381    if (
present(iter)) iter = 0
 
  383    if (
present(skip)) 
then 
  384      assert(ubound(skip, dim = 1) == st%nst)
 
  397    if (
present(label)) 
then 
  400      if (
present(lr)) 
then 
  401        label_ = 
" for linear response" 
  407    message(1) = 
'Info: Reading states' 
  408    if (len(trim(label_)) > 0) 
then 
  414    if (.not. 
present(lr)) 
then 
  415      st%fromScratch = .false. 
 
  421    integral_occs = .
true. 
 
  422    if (st%restart_fixed_occ) 
then 
  424      st%fixed_occ = .
true.
 
  426      read_occ = .not. st%fixed_occ
 
  429    if (.not. 
present(lr)) 
then 
  430      st%eigenval(:, :) = 
m_zero 
  434    if (.not. 
present(lr) .and. read_occ) 
then 
  440    if (
present(lr)) 
then 
  441      lr_allocated = (
allocated(lr%ddl_psi) .and. 
states_are_real(st)) .or. &
 
  451    call restart_read(restart, states_elec_file, lines, 3, err)
 
  455      read(lines(2), *) str, idim
 
  456      read(lines(3), *) str, ik
 
  457      if (idim == 2 .and. st%d%dim == 1) 
then 
  458        write(
message(1),
'(a)') 
'Incompatible restart information: saved calculation is spinors, this one is not.' 
  462      if (idim == 1 .and. st%d%dim == 2) 
then 
  463        write(
message(1),
'(a)') 
'Incompatible restart information: this calculation is spinors, saved one is not.' 
  467      if (ik < st%nik) 
then 
  468        write(
message(1),
'(a)') 
'Incompatible restart information: not enough k-points.' 
  469        write(
message(2),
'(2(a,i6))') 
'Expected ', st%nik, 
' > Read ', ik
 
  484      read(lines(2), 
'(a)') str
 
  485      if (str(2:8) == 
'Complex') 
then 
  486        message(1) = 
"Cannot read real states from complex wavefunctions." 
  489      else if (str(2:5) /= 
'Real') 
then 
  490        message(1) = 
"Restart file 'wfns' does not specify real/complex; cannot check compatibility." 
  498    if (err /= 0) ierr = ierr - 2**7
 
  511      safe_allocate(dpsi(1:mesh%np))
 
  513      safe_allocate(zpsi(1:mesh%np))
 
  516    safe_allocate(restart_file(1:st%d%dim, st%st_start:st%st_end, 1:st%nik))
 
  517    safe_allocate(restart_file_present(1:st%d%dim, st%st_start:st%st_end, 1:st%nik))
 
  518    restart_file_present = .false.
 
  526        read(lines(1), 
'(a)') char
 
  527        if (char == 
'%') 
then 
  531          read(lines(1), *) ik, char, ist, char, idim, char, filename
 
  540      if (ist >= st%st_start .and. ist <= st%st_end .and. &
 
  541        ik >= st%d%kpt%start .and. ik <= st%d%kpt%end) 
then 
  543        restart_file(idim, ist, ik) = trim(filename)
 
  544        restart_file_present(idim, ist, ik) = .
true.
 
  548      if (.not. 
present(lr)) 
then  
  552          read(lines(1), *) my_occ, char, st%eigenval(ist, ik), char, imev, char, &
 
  553            (read_kpoint(idir), char, idir = 1, space%dim), my_kweight
 
  557          if (ist >= st%st_start .and. ist <= st%st_end .and. &
 
  558            ik >= st%d%kpt%start .and. ik <= st%d%kpt%end) 
then 
  559            restart_file_present(idim, ist, ik) = .false.
 
  564        kpoint(1:space%dim) = &
 
  565          kpoints%get_point(st%d%get_kpoint_index(ik), absolute_coordinates = .
true.)
 
  567        if (any(abs(kpoint(1:space%dim) - read_kpoint(1:space%dim)) > 1e-12_real64)) 
then 
  570            write(
message(1),
'(a,i6)') 
'Incompatible restart information: k-point mismatch for ik ', ik
 
  571            write(
message(2),
'(a,99f18.12)') 
'  Expected : ', kpoint(1:space%dim)
 
  572            write(
message(3),
'(a,99f18.12)') 
'  Read     : ', read_kpoint(1:space%dim)
 
  575          if (ist >= st%st_start .and. ist <= st%st_end .and. &
 
  576            ik >= st%d%kpt%start .and. ik <= st%d%kpt%end) 
then 
  577            restart_file_present(idim, ist, ik) = .false.
 
  582          st%occ(ist, ik) = my_occ
 
  583          integral_occs = integral_occs .and. &
 
  584            abs((st%occ(ist, ik) - st%smear%el_per_state) * st%occ(ist, ik))  <=  
m_epsilon 
  589    if (
present(iter)) 
then 
  594        read(lines(1), *) filename, filename, iter
 
  605    safe_allocate(filled(1:st%d%dim, st%st_start:st%st_end, st%d%kpt%start:st%d%kpt%end))
 
  608    if (
present(lowest_missing)) lowest_missing = st%nst + 1
 
  613      ntodo = st%lnst*st%d%kpt%nlocal*st%d%dim
 
  617    do ik = st%d%kpt%start, st%d%kpt%end
 
  618      do ist = st%st_start, st%st_end
 
  619        if (
present(skip)) 
then 
  623        do idim = 1, st%d%dim
 
  625          if (.not. restart_file_present(idim, ist, ik)) 
then 
  626            if (
present(lowest_missing)) 
then 
  627              lowest_missing(idim, ik) = min(lowest_missing(idim, ik), ist)
 
  639            if (.not. 
present(lr)) 
then 
  642              call lalg_copy(mesh%np, dpsi, lr%ddl_psi(:, idim, ist, ik))
 
  645            if (.not. 
present(lr)) 
then 
  648              call lalg_copy(mesh%np, zpsi, lr%zdl_psi(:, idim, ist, ik))
 
  654            filled(idim, ist, ik) = .
true.
 
  656          else if (
present(lowest_missing)) 
then 
  657            lowest_missing(idim, ik) = min(lowest_missing(idim, ik), ist)
 
  669    safe_deallocate_a(dpsi)
 
  670    safe_deallocate_a(zpsi)
 
  671    safe_deallocate_a(zpsil)
 
  672    safe_deallocate_a(restart_file)
 
  673    safe_deallocate_a(restart_file_present)
 
  679    if (st%parallel_in_states .or. st%d%kpt%parallel) 
then 
  681      call st%st_kpt_mpi_grp%allreduce(iread_tmp, iread, 1, mpi_integer, mpi_sum)
 
  684    if (st%d%kpt%parallel) 
then 
  686      if (
present(lowest_missing)) 
then 
  687        safe_allocate(lowest_missing_tmp(1:st%d%dim, 1:st%nik))
 
  688        lowest_missing_tmp = lowest_missing
 
  689        call st%d%kpt%mpi_grp%allreduce(lowest_missing_tmp(1,1), lowest_missing(1,1), st%d%dim*st%nik, &
 
  690          mpi_integer, mpi_min)
 
  691        safe_deallocate_a(lowest_missing_tmp)
 
  695    if (st%restart_fixed_occ .and. iread == st%nst * st%nik * st%d%dim) 
then 
  698      call smear_init(st%smear, namespace, st%d%ispin, fixed_occ = .
true., integral_occs = integral_occs, kpoints = kpoints)
 
  701    if (.not. 
present(lr) .and. .not. 
present(skip)) 
call fill_random()
 
  704    safe_deallocate_a(filled)
 
  706    if (ierr == 0 .and. iread /= st%nst * st%nik * st%d%dim) 
then 
  714      if (.not. 
present(lr)) 
then 
  715        write(str, 
'(a,i5)') 
'Reading states.' 
  717        write(str, 
'(a,i5)') 
'Reading states information for linear response.' 
  720      if (.not. 
present(skip)) 
then 
  721        write(
message(1),
'(a,i6,a,i6,a)') 
'Only ', iread,
' files out of ', &
 
  722          st%nst * st%nik * st%d%dim, 
' could be read.' 
  724        write(
message(1),
'(a,i6,a,i6,a)') 
'Only ', iread,
' files out of ', &
 
  725          st%nst * st%nik * st%d%dim, 
' were loaded.' 
  732    message(1) = 
'Info: States reading done.' 
  741    subroutine fill_random() !< put 
random function in orbitals that could not be read.
 
  744      do ik = st%d%kpt%start, st%d%kpt%end
 
  746        do ist = st%st_start, st%st_end
 
  747          do idim = 1, st%d%dim
 
  748            if (filled(idim, ist, ik)) cycle
 
  760    logical function index_is_wrong() !< .
true. if the index (idim, ist, ik) is not present in st structure...
 
  763      if (idim > st%d%dim .or. idim < 1 .or.   &
 
  764        ist   > st%nst   .or. ist  < 1 .or.   &
 
  765        ik    > st%nik .or. ik   < 1) 
then 
  779    class(
space_t),       
intent(in)    :: space
 
  781    class(
mesh_t),        
intent(in)    :: mesh
 
  782    integer,              
intent(out)   :: ierr
 
  783    integer,    
optional, 
intent(in)    :: iter
 
  785    integer :: iunit, isp, err, err2(2)
 
  786    character(len=80) :: filename
 
  787    character(len=300) :: lines(2)
 
  799      message(1) = 
"Debug: Writing density restart." 
  807    lines(1) = 
'#     #spin    #nspin    filename' 
  808    lines(2) = 
'%densities' 
  810    if (err /= 0) ierr = ierr + 1
 
  813    do isp = 1, st%d%nspin
 
  814      if (st%d%nspin == 1) 
then 
  815        write(filename, fmt=
'(a)') 
'density' 
  817        write(filename, fmt=
'(a,i1)') 
'density-sp', isp
 
  819      write(lines(1), 
'(i8,a,i8,a)') isp, 
' | ', st%d%nspin, 
' | "'//trim(adjustl(filename))//
'"' 
  821      if (err /= 0) err2(1) = err2(1) + 1
 
  824      if (err /= 0) err2(2) = err2(2) + 1
 
  827    if (err2(1) /= 0) ierr = ierr + 2
 
  828    if (err2(2) /= 0) ierr = ierr + 4
 
  832    if (err /= 0) ierr = ierr + 8
 
  833    if (
present(iter)) 
then 
  834      write(lines(1),
'(a,i7)') 
'Iter = ', iter
 
  836      if (err /= 0) ierr = ierr + 16
 
  843      message(1) = 
"Debug: Writing density restart done." 
  854    class(
space_t),       
intent(in)    :: space
 
  856    class(
mesh_t),        
intent(in)    :: mesh
 
  857    integer,              
intent(out)   :: ierr
 
  859    integer              :: err, err2, isp
 
  860    character(len=12)    :: filename
 
  873      message(1) = 
"Debug: Reading density restart." 
  885    do isp = 1, st%d%nspin
 
  886      if (st%d%nspin == 1) 
then 
  887        write(filename, fmt=
'(a)') 
'density' 
  889        write(filename, fmt=
'(a,i1)') 
'density-sp', isp
 
  895      if (err /= 0) err2 = err2 + 1
 
  898    if (err2 /= 0) ierr = ierr + 1
 
  901      message(1) = 
"Debug: Reading density restart done." 
  910    class(
space_t),       
intent(in)    :: space
 
  912    class(
mesh_t),        
intent(in)    :: mesh
 
  913    integer,              
intent(out)   :: ierr
 
  915    integer :: isp, err, err2(2), idir
 
  916    character(len=80) :: filename
 
  922    assert(
allocated(st%frozen_rho))
 
  930      message(1) = 
"Debug: Writing frozen densities restart." 
  937    do isp = 1, st%d%nspin
 
  938      if (st%d%nspin == 1) 
then 
  939        write(filename, fmt=
'(a)') 
'frozen_rho' 
  941        write(filename, fmt=
'(a,i1)') 
'frozen_rho-sp', isp
 
  945      if (err /= 0) err2(2) = err2(2) + 1
 
  947      if (
allocated(st%frozen_tau)) 
then 
  948        if (st%d%nspin == 1) 
then 
  949          write(filename, fmt=
'(a)') 
'frozen_tau' 
  951          write(filename, fmt=
'(a,i1)') 
'frozen_tau-sp', isp
 
  954        if (err /= 0) err2 = err2 + 1
 
  957      if (
allocated(st%frozen_gdens)) 
then 
  958        do idir = 1, space%dim
 
  959          if (st%d%nspin == 1) 
then 
  960            write(filename, fmt=
'(a,i1)') 
'frozen_gdens-dir', idir
 
  962            write(filename, fmt=
'(a,i1,a,i1)') 
'frozen_tau-dir', idir, 
'-', isp
 
  965          if (err /= 0) err2 = err2 + 1
 
  969      if (
allocated(st%frozen_ldens)) 
then 
  970        if (st%d%nspin == 1) 
then 
  971          write(filename, fmt=
'(a)') 
'frozen_ldens' 
  973          write(filename, fmt=
'(a,i1)') 
'frozen_ldens-sp', isp
 
  976        if (err /= 0) err2 = err2 + 1
 
  980    if (err2(1) /= 0) ierr = ierr + 2
 
  981    if (err2(2) /= 0) ierr = ierr + 4
 
  986      message(1) = 
"Debug: Writing frozen densities restart done." 
  997    class(
space_t),       
intent(in)    :: space
 
  999    class(
mesh_t),        
intent(in)    :: mesh
 
 1000    integer,              
intent(out)   :: ierr
 
 1002    integer              :: err, err2, isp, idir
 
 1003    character(len=80)    :: filename
 
 1007    assert(
allocated(st%frozen_rho))
 
 1017    if (
debug%info) 
then 
 1018      message(1) = 
"Debug: Reading densities restart." 
 1023    do isp = 1, st%d%nspin
 
 1024      if (st%d%nspin == 1) 
then 
 1025        write(filename, fmt=
'(a)') 
'frozen_rho' 
 1027        write(filename, fmt=
'(a,i1)') 
'frozen_rho-sp', isp
 
 1030      if (err /= 0) err2 = err2 + 1
 
 1032      if (
allocated(st%frozen_tau)) 
then 
 1033        if (st%d%nspin == 1) 
then 
 1034          write(filename, fmt=
'(a)') 
'frozen_tau' 
 1036          write(filename, fmt=
'(a,i1)') 
'frozen_tau-sp', isp
 
 1039        if (err /= 0) err2 = err2 + 1
 
 1042      if (
allocated(st%frozen_gdens)) 
then 
 1043        do idir = 1, space%dim
 
 1044          if (st%d%nspin == 1) 
then 
 1045            write(filename, fmt=
'(a,i1)') 
'frozen_gdens-dir', idir
 
 1047            write(filename, fmt=
'(a,i1,a,i1)') 
'frozen_tau-dir', idir, 
'-', isp
 
 1050          if (err /= 0) err2 = err2 + 1
 
 1054      if (
allocated(st%frozen_ldens)) 
then 
 1055        if (st%d%nspin == 1) 
then 
 1056          write(filename, fmt=
'(a)') 
'frozen_ldens' 
 1058          write(filename, fmt=
'(a,i1)') 
'frozen_ldens-sp', isp
 
 1061        if (err /= 0) err2 = err2 + 1
 
 1065    if (err2 /= 0) ierr = ierr + 1
 
 1067    if (
debug%info) 
then 
 1068      message(1) = 
"Debug: Reading frozen densities restart done." 
 1080    class(
mesh_t),       
intent(in)    :: mesh
 
 1082    class(
space_t),      
intent(in)    :: space
 
 1086    integer :: ip, id, is, ik, nstates, state_from, ierr, ncols
 
 1087    integer :: ib, idim, inst, inik, normalize
 
 1088    real(real64) :: xx(space%dim), rr, psi_re, psi_im
 
 1089    character(len=150) :: filename
 
 1090    complex(real64), 
allocatable :: zpsi(:, :)
 
 1092    integer, 
parameter ::           &
 
 1093      state_from_formula  = 1,      &
 
 1094      state_from_file     = -10010, &
 
 1095      normalize_yes       = 1,      &
 
 1147    if (
parse_block(namespace, 
'UserDefinedStates', blk) == 0) 
then 
 1154      safe_allocate(zpsi(1:mesh%np, 1:st%d%dim))
 
 1160        if (ncols  <  5 .or. ncols > 6) 
then 
 1161          message(1) = 
'Each line in the UserDefinedStates block must have' 
 1162          message(2) = 
'five or six columns.' 
 1178              if (.not.(id == idim .and. is == inst .and. ik == inik )) cycle
 
 1184              select case (state_from)
 
 1185              case (state_from_formula)
 
 1188                  blk, ib - 1, 4, st%user_def_states(id, is, ik))
 
 1190                write(
message(1), 
'(a,3i5)') 
'Substituting state of orbital with k, ist, dim = ', ik, is, id
 
 1191                write(
message(2), 
'(2a)') 
'  with the expression:' 
 1192                write(
message(3), 
'(2a)') 
'  ',trim(st%user_def_states(id, is, ik))
 
 1198              case (state_from_file)
 
 1204                write(
message(1), 
'(a,3i5)') 
'Substituting state of orbital with k, ist, dim = ', ik, is, id
 
 1205                write(
message(2), 
'(2a)') 
'  with data from file:' 
 1206                write(
message(3), 
'(2a)') 
'  ',trim(filename)
 
 1212              if (.not.(st%st_start  <=  is .and. st%st_end >= is          &
 
 1213                .and. st%d%kpt%start  <=  ik .and. st%d%kpt%end >= ik)) cycle
 
 1215              select case (state_from)
 
 1217              case (state_from_formula)
 
 1226                  zpsi(ip, 1) = psi_re + 
m_zi * psi_im
 
 1229              case (state_from_file)
 
 1233                  message(1) = 
'Could not read the file!' 
 1234                  write(
message(2),
'(a,i1)') 
'Error code: ', ierr
 
 1239                message(1) = 
'Wrong entry in UserDefinedStates, column 4.' 
 1240                message(2) = 
'You may state "formula" or "file" here.' 
 1250              select case (normalize)
 
 1253              case (normalize_yes)
 
 1254                assert(st%d%dim == 1)
 
 1258                message(1) = 
'The sixth column in UserDefinedStates may either be' 
 1259                message(2) = 
'"normalize_yes" or "normalize_no"' 
 1269      safe_deallocate_a(zpsi)
 
 1287    integer,              
intent(out) :: ierr
 
 1289    integer :: iunit_spin
 
 1290    integer :: err, err2(2), ik, ist
 
 1291    character(len=300) :: lines(3)
 
 1307    lines(1) = 
'#     #k-point            #st       #spin(x) spin(y) spin(z)' 
 1309    if (err /= 0) ierr = ierr + 1
 
 1314        write(lines(1), 
'(i8,a,i8,3(a,f18.12))') ik, 
' | ', ist, 
' | ', &
 
 1315          st%spin(1,ist,ik), 
' | ', st%spin(2,ist,ik),
' | ', st%spin(3,ist,ik)
 
 1317        if (err /= 0) err2(1) = err2(1) + 1
 
 1322    if (err2(1) /= 0) ierr = ierr + 8
 
 1323    if (err2(2) /= 0) ierr = ierr + 16
 
 1344    integer,                    
intent(out)   :: ierr
 
 1346    integer              :: spin_file, err, ik, ist
 
 1347    character(len=256)   :: lines(3)
 
 1348    real(real64)         :: spin(3)
 
 1349    character(len=1)     :: char
 
 1368    if (err /= 0) ierr = ierr - 2**7
 
 1384      read(lines(1), 
'(a)') char
 
 1385      if (char == 
'%') 
then 
 1389        read(lines(1), *) ik, char, ist, char,  spin(1), char, spin(2), char, spin(3)
 
 1394      st%spin(1:3, ist, ik) = spin(1:3)
 
 1407    class(
space_t),             
intent(in)    :: space
 
 1408    type(
restart_t),            
intent(inout) :: restart
 
 1409    class(
mesh_t),              
intent(in)    :: mesh
 
 1411    character(len=*), 
optional, 
intent(in)    :: prefix
 
 1415    complex(real64), 
allocatable :: rotation_matrix(:,:), psi(:, :)
 
 1416    integer :: ist, jst, ncols, iqn
 
 1417    character(len=256) :: block_name
 
 1449      if (
parse_block(namespace, trim(block_name), blk) == 0) 
then 
 1450        if (st%parallel_in_states) 
then 
 1454          message(1) = 
"Number of rows in block " // trim(block_name) // 
" must equal number of states in this calculation." 
 1461        safe_allocate(rotation_matrix(1:stin%nst, 1:stin%nst))
 
 1462        safe_allocate(psi(1:mesh%np, 1:st%d%dim))
 
 1468          if (ncols /= stin%nst) 
then 
 1469            write(
message(1),
'(a,i6,a,i6,3a,i6,a)') 
"Number of columns (", ncols, 
") in row ", ist, 
" of block ", &
 
 1470              trim(block_name), 
" must equal number of states (", stin%nst, 
") read from gs restart." 
 1473          do jst = 1, stin%nst
 
 1480        do iqn = st%d%kpt%start, st%d%kpt%end
 
 1487          do ist = st%st_start, st%st_end
 
 1494        safe_deallocate_a(rotation_matrix)
 
 1495        safe_deallocate_a(psi)
 
Copies a vector x, to a vector y.
 
This module handles the calculation mode.
 
integer, parameter, public p_strategy_max
 
integer, parameter, public p_strategy_domains
parallelization in domains
 
type(debug_t), save, public debug
 
integer, parameter, public spinors
 
real(real64), parameter, public m_zero
 
complex(real64), parameter, public m_zi
 
real(real64), parameter, public m_epsilon
 
complex(real64), parameter, public m_z1
 
subroutine, public zio_function_input(filename, namespace, space, mesh, ff, ierr, map)
Reads a mesh function from file filename, and puts it into ff. If the map argument is passed,...
 
This module is intended to contain "only mathematical" functions and procedures.
 
This module defines various routines, operating on mesh functions.
 
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_print_with_emphasis(msg, iunit, namespace)
 
subroutine, public messages_not_implemented(feature, namespace)
 
character(len=512), private msg
 
subroutine, public messages_variable_is_block(namespace, name)
 
subroutine, public messages_warning(no_lines, all_nodes, namespace)
 
subroutine, public print_date(str)
 
subroutine, public messages_info(no_lines, iunit, verbose_limit, stress, all_nodes, namespace)
 
subroutine, public messages_new_line()
 
character(len=256), dimension(max_lines), public message
to be output by fatal, warning
 
subroutine, public messages_fatal(no_lines, only_root_writes, namespace)
 
logical function mpi_grp_is_root(grp)
 
type(mpi_grp_t), public mpi_world
 
This module handles the communicators for the various parallelization strategies.
 
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.
 
subroutine, public restart_write(restart, iunit, lines, nlines, ierr)
 
logical pure function, public restart_skip(restart)
Returns true if the restart information should neither be read nor written. This might happen because...
 
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_init(this, namespace, ispin, fixed_occ, integral_occs, kpoints)
 
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_end(st)
finalize the states_elec_t object
 
subroutine, public states_elec_allocate_wfns(st, mesh, wfs_type, skip, packed)
Allocates the KS wavefunctions defined within a states_elec_t structure.
 
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, 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...
 
This module handles reading and writing restart information for the states_elec_t.
 
subroutine, public states_elec_read_user_def_orbitals(mesh, namespace, space, st)
the routine reads formulas for user-defined wavefunctions from the input file and fills the respectiv...
 
subroutine, public states_elec_load_frozen(restart, space, st, mesh, ierr)
 
subroutine, public states_elec_dump(restart, space, st, mesh, kpoints, ierr, iter, lr, st_start_writing, verbose)
 
subroutine, public states_elec_look_and_load(restart, namespace, space, st, mesh, kpoints, is_complex, packed)
 
subroutine, public states_elec_transform(st, namespace, space, restart, mesh, kpoints, prefix)
 
subroutine, public states_elec_load(restart, namespace, space, st, mesh, kpoints, ierr, iter, lr, lowest_missing, label, verbose, skip)
returns in ierr: <0 => Fatal error, or nothing read =0 => read all wavefunctions >0 => could only rea...
 
subroutine, public states_elec_load_spin(restart, st, ierr)
returns in ierr: <0 => Fatal error, or nothing read =0 => read all wavefunctions >0 => could only rea...
 
subroutine, public states_elec_dump_frozen(restart, space, st, mesh, ierr)
 
subroutine, public states_elec_load_rho(restart, space, st, mesh, ierr)
 
subroutine, public states_elec_dump_rho(restart, space, st, mesh, ierr, iter)
 
subroutine, public states_elec_dump_spin(restart, st, ierr)
 
subroutine, public conv_to_c_string(str)
converts to c string
 
type(type_t), public type_float
 
type(type_t), public type_cmplx
 
logical function index_is_wrong()
 
Describes mesh distribution to nodes.
 
The states_elec_t class contains all electronic wave functions.