20#define RESTART_FILE 'dipoles' 
   32  use, 
intrinsic :: iso_fortran_env
 
   64    class(*),        
intent(inout) :: system
 
   65    logical,         
intent(in)    :: from_scratch
 
   71      message(1) = 
"CalculationMode = static_pol not implemented for multi-system calculations" 
   82    type(electrons_t),    
intent(inout) :: sys
 
   83    logical,              
intent(in)    :: fromScratch
 
   86    integer :: iunit, ios, i_start, ii, jj, is, isign, ierr, read_count, verbosity
 
   87    real(real64) :: e_field, e_field_saved
 
   88    real(real64), 
allocatable :: Vpsl_save(:), trrho(:), dipole(:, :, :)
 
   89    real(real64), 
allocatable :: elf(:,:), lr_elf(:,:), elfd(:,:), lr_elfd(:,:)
 
   90    real(real64), 
allocatable :: lr_rho(:,:), lr_rho2(:,:), gs_rho(:,:), tmp_rho(:,:)
 
   91    real(real64) :: center_dipole(1:sys%space%dim), diag_dipole(1:sys%space%dim), ionic_dipole(1:sys%space%dim), &
 
   92      print_dipole(1:sys%space%dim)
 
   93    type(born_charges_t) :: born_charges
 
   94    logical :: calc_born, start_density_is_zero_field, write_restart_densities, calc_diagonal, verbose
 
   95    logical :: diagonal_done, center_written, fromScratch_local, field_written
 
   96    character(len=MAX_PATH_LEN) :: fname, dir_name
 
   97    character(len=120) :: line(1)
 
   98    character :: sign_char
 
   99    type(restart_t) :: gs_restart, restart_load, restart_dump
 
  103    if (sys%hm%pcm%run_pcm) 
then 
  107    if (sys%kpoints%use_symmetries) 
then 
  108      call messages_experimental(
"KPoints symmetries with CalculationMode = em_resp", namespace=sys%namespace)
 
  116      call states_elec_load(gs_restart, sys%namespace, sys%space, sys%st, sys%gr, sys%kpoints, ierr)
 
  119      message(1) = 
"Unable to read wavefunctions." 
  124    if (sys%space%is_periodic()) 
then 
  125      message(1) = 
"Electric field cannot be applied to a periodic system (currently)." 
  130    message(1) = 
'Info: Setting up Hamiltonian.' 
  132    call v_ks_h_setup(sys%namespace, sys%space, sys%gr, sys%ions, sys%ext_partners, sys%st, sys%ks, &
 
  133      sys%hm, calc_eigenval = .false.) 
 
  136    safe_allocate(dipole(1:sys%space%dim, 1:sys%space%dim, 1:2))
 
  140    center_written = .false.
 
  141    diagonal_done = .false.
 
  142    field_written = .false.
 
  146    if (.not. fromscratch) 
then 
  158        read(iunit, fmt=*, iostat = ios) e_field_saved
 
  159        field_written = (ios == 0)
 
  161        read(iunit, fmt=*, iostat = ios) (center_dipole(jj), jj = 1, sys%space%dim)
 
  162        center_written = (ios == 0)
 
  165          read(iunit, fmt=*, iostat = ios) ((dipole(ii, jj, isign), jj = 1, sys%space%dim), isign = 1, 2)
 
  167          i_start = i_start + 1
 
  170        read(iunit, fmt=*, iostat = ios) (diag_dipole(jj), jj = 1, sys%space%dim)
 
  171        diagonal_done = (ios == 0)
 
  177      if (field_written .and. abs(e_field_saved - e_field) > 1e-15_real64) 
then 
  178        message(1) = 
"Saved dipoles are from a different electric field, cannot use them." 
  180        center_written = .false.
 
  181        diagonal_done = .false.
 
  185      read_count = (i_start - 1) * 2
 
  186      if (center_written) read_count = read_count + 1
 
  187      if (diagonal_done)  read_count = read_count + 1
 
  188      write(
message(1),
'(a,i1,a)') 
"Using ", read_count, 
" dipole(s) from file." 
  192    if (sys%outp%what(option__output__density) .or. &
 
  193      sys%outp%what(option__output__pol_density)) 
then 
  194      if (i_start > 2 .and. calc_diagonal) 
then 
  196        diagonal_done = .false.
 
  201    if (i_start == 1) 
then 
  203      iunit = 
restart_open(restart_dump, restart_file, status=
'replace')
 
  204      write(line(1), fmt=
'(e20.12)') e_field
 
  207        message(1) = 
"Unsuccessful write of electric field." 
  211      center_written = .false.
 
  215    safe_allocate(vpsl_save(1:sys%gr%np))
 
  216    vpsl_save = sys%hm%ep%Vpsl
 
  219    safe_allocate(trrho(1:sys%gr%np))
 
  220    safe_allocate(gs_rho(1:sys%gr%np, 1:sys%st%d%nspin))
 
  221    safe_allocate(tmp_rho(1:sys%gr%np, 1:sys%st%d%nspin))
 
  226    call scf_init(scfv, sys%namespace, sys%gr, sys%ions, sys%st, sys%mc, sys%hm, sys%space)
 
  227    call born_charges_init(born_charges, sys%namespace, sys%ions%natoms, sys%st%val_charge, &
 
  228      sys%st%qtot, sys%space%dim)
 
  232    sys%hm%ep%vpsl(1:sys%gr%np) = vpsl_save(1:sys%gr%np)
 
  233    call sys%hm%update(sys%gr, sys%namespace, sys%space, sys%ext_partners)
 
  236    write(
message(2), 
'(a)') 
'Info: Calculating dipole moment for zero field.' 
  238    call scf_run(scfv, sys%namespace, sys%space, sys%mc, sys%gr, sys%ions, sys%ext_partners, sys%st, &
 
  239      sys%ks, sys%hm, verbosity = verbosity)
 
  241    gs_rho(1:sys%gr%np, 1:sys%st%d%nspin) = sys%st%rho(1:sys%gr%np, 1:sys%st%d%nspin)
 
  243    do is = 1, sys%st%d%spin_channels
 
  244      trrho(1:sys%gr%np) = trrho(1:sys%gr%np) + gs_rho(1:sys%gr%np, is)
 
  248    do jj = 1, sys%space%dim
 
  249      center_dipole(jj) = 
dmf_moment(sys%gr, trrho, jj, 1)
 
  253    if (.not. center_written) 
then 
  254      iunit = 
restart_open(restart_dump, restart_file, position=
'append')
 
  255      write(line(1), fmt=
'(6e20.12)') (center_dipole(jj), jj = 1, sys%space%dim)
 
  258        message(1) = 
"Unsuccessful write of center dipole." 
  265      ionic_dipole(1:sys%space%dim) = sys%ions%dipole()
 
  266      print_dipole(1:sys%space%dim) = center_dipole(1:sys%space%dim) + ionic_dipole(1:sys%space%dim)
 
  267      call output_dipole(print_dipole, sys%space%dim, namespace=sys%namespace)
 
  270    do ii = i_start, sys%space%dim
 
  273        write(
message(2), 
'(a,f6.4,5a)') 
'Info: Calculating dipole moment for field ', &
 
  280        sys%hm%ep%vpsl(1:sys%gr%np) = vpsl_save(1:sys%gr%np) + (-1)**isign * sys%gr%x(1:sys%gr%np, ii) * e_field
 
  281        call sys%hm%update(sys%gr, sys%namespace, sys%space, sys%ext_partners)
 
  289        write(dir_name,
'(a)') 
"field_"//
index2axis(ii)//sign_char
 
  290        fromscratch_local = fromscratch
 
  292        if (.not. fromscratch) 
then 
  295            call states_elec_load(restart_load, sys%namespace, sys%space, sys%st, sys%gr, sys%kpoints, ierr)
 
  297          call v_ks_h_setup(sys%namespace, sys%space, sys%gr, sys%ions, sys%ext_partners, sys%st, sys%ks, sys%hm)
 
  298          if (ierr /= 0) fromscratch_local = .
true.
 
  302        if (fromscratch_local) 
then 
  303          if (start_density_is_zero_field) 
then 
  304            sys%st%rho(1:sys%gr%np, 1:sys%st%d%nspin) = gs_rho(1:sys%gr%np, 1:sys%st%d%nspin)
 
  305            call v_ks_h_setup(sys%namespace, sys%space, sys%gr, sys%ions, sys%ext_partners, sys%st, sys%ks, sys%hm)
 
  307            call lcao_run(sys%namespace, sys%space, sys%gr, sys%ions, sys%ext_partners, sys%st, sys%ks, &
 
  308              sys%hm, lmm_r = scfv%lmm_r)
 
  313        call scf_run(scfv, sys%namespace, sys%space, sys%mc, sys%gr, sys%ions, sys%ext_partners, sys%st, &
 
  314          sys%ks, sys%hm, verbosity = verbosity)
 
  317        do is = 1, sys%st%d%spin_channels
 
  318          trrho(1:sys%gr%np) = trrho(1:sys%gr%np) + sys%st%rho(1:sys%gr%np, is)
 
  322        do jj = 1, sys%space%dim
 
  323          dipole(ii, jj, isign) = 
dmf_moment(sys%gr, trrho, jj, 1)
 
  327          print_dipole(1:sys%space%dim) = dipole(ii, 1:sys%space%dim, isign) + ionic_dipole(1:sys%space%dim)
 
  328          call output_dipole(print_dipole, sys%space%dim, namespace=sys%namespace)
 
  333        if (write_restart_densities) 
then 
  336            call states_elec_dump(restart_dump, sys%space, sys%st, sys%gr, sys%kpoints, ierr)
 
  340            message(1) = 
'Unable to write states wavefunctions.' 
  347      iunit = 
restart_open(restart_dump, restart_file, position=
'append')
 
  348      write(line(1), 
'(6e20.12)') ((dipole(ii, jj, isign), jj = 1, sys%space%dim), isign = 1, 2)
 
  351        message(1) = 
"Unsuccessful write of dipole." 
  357    if (.not. diagonal_done .and. calc_diagonal) 
then 
  359      write(
message(2), 
'(a,f6.4,3a, f6.4, 3a)') 
'Info: Calculating dipole moment for field ', &
 
  366      sys%hm%ep%vpsl(1:sys%gr%np) = vpsl_save(1:sys%gr%np) &
 
  367        - (sys%gr%x(1:sys%gr%np, 2) + sys%gr%x(1:sys%gr%np, 3)) * e_field
 
  368      call sys%hm%update(sys%gr, sys%namespace, sys%space, sys%ext_partners)
 
  376      fromscratch_local = fromscratch
 
  378      if (.not. fromscratch) 
then 
  381          call states_elec_load(restart_load, sys%namespace, sys%space, sys%st, sys%gr, sys%kpoints, ierr)
 
  383        call v_ks_h_setup(sys%namespace, sys%space, sys%gr, sys%ions, sys%ext_partners, sys%st, sys%ks, sys%hm)
 
  384        if (ierr /= 0) fromscratch_local = .
true.
 
  388      if (fromscratch_local) 
then 
  389        if (start_density_is_zero_field) 
then 
  390          sys%st%rho(1:sys%gr%np, 1:sys%st%d%nspin) = gs_rho(1:sys%gr%np, 1:sys%st%d%nspin)
 
  391          call v_ks_h_setup(sys%namespace, sys%space, sys%gr, sys%ions, sys%ext_partners, sys%st, sys%ks, sys%hm)
 
  393          call lcao_run(sys%namespace, sys%space, sys%gr, sys%ions, sys%ext_partners, sys%st, sys%ks, &
 
  394            sys%hm, lmm_r = scfv%lmm_r)
 
  399      call scf_run(scfv, sys%namespace, sys%space, sys%mc, sys%gr, sys%ions, sys%ext_partners, sys%st, &
 
  400        sys%ks, sys%hm, verbosity = verbosity)
 
  403      do is = 1, sys%st%d%spin_channels
 
  404        trrho(1:sys%gr%np) = trrho(1:sys%gr%np) + sys%st%rho(1:sys%gr%np, is)
 
  408      do jj = 1, sys%space%dim
 
  409        diag_dipole(jj) = 
dmf_moment(sys%gr, trrho, jj, 1)
 
  413        print_dipole(1:sys%space%dim) = diag_dipole(1:sys%space%dim) + ionic_dipole(1:sys%space%dim)
 
  414        call output_dipole(print_dipole, sys%space%dim, namespace=sys%namespace)
 
  418      iunit = 
restart_open(restart_dump, restart_file, position=
'append')
 
  419      write(line(1), fmt=
'(3e20.12)') (diag_dipole(jj), jj = 1, sys%space%dim)
 
  422        message(1) = 
"Unsuccessful write of dipole." 
  427      if (write_restart_densities) 
then 
  430          call states_elec_dump(restart_dump, sys%space, sys%st, sys%gr, sys%kpoints, ierr)
 
  434          message(1) = 
'Unable to write states wavefunctions.' 
  441    if (.not. fromscratch) 
call restart_end(restart_load)
 
  446    safe_deallocate_a(vpsl_save)
 
  447    safe_deallocate_a(trrho)
 
  448    safe_deallocate_a(gs_rho)
 
  449    safe_deallocate_a(tmp_rho)
 
  450    safe_deallocate_a(dipole)
 
  472      if (e_field <= 
m_zero) 
then 
  473        write(
message(1), 
'(a,e14.6,a)') 
"Input: '", e_field, 
"' is not a valid EMStaticElectricField." 
  474        message(2) = 
'(Must have EMStaticElectricField > 0)' 
  479      call parse_variable(sys%namespace, 
'EMCalcbornCharges', .false., calc_born)
 
  480      if (calc_born) 
call messages_experimental(
"Calculation of born effective charges", namespace=sys%namespace)
 
  493      call parse_variable(sys%namespace, 
'EMStartDensityIsZeroField', .
true., start_density_is_zero_field)
 
  514      call parse_variable(sys%namespace, 
'EMWriteRestartDensities', .
true., write_restart_densities)
 
  551      if (sys%outp%what(option__output__density) .or. &
 
  552        sys%outp%what(option__output__pol_density)) 
then 
  553        safe_allocate(lr_rho(1:sys%gr%np, 1:sys%st%d%nspin))
 
  554        safe_allocate(lr_rho2(1:sys%gr%np, 1:sys%st%d%nspin))
 
  557      if (sys%outp%what(option__output__elf)) 
then 
  558        safe_allocate(    elf(1:sys%gr%np, 1:sys%st%d%nspin))
 
  559        safe_allocate( lr_elf(1:sys%gr%np, 1:sys%st%d%nspin))
 
  560        safe_allocate(   elfd(1:sys%gr%np, 1:sys%st%d%nspin))
 
  561        safe_allocate(lr_elfd(1:sys%gr%np, 1:sys%st%d%nspin))
 
  577        do iatom = 1, sys%ions%natoms
 
  580            born_charges%charge(ii, 1:sys%space%dim, iatom) = sys%ions%tot_force(:, iatom)
 
  582            born_charges%charge(ii, 1:sys%space%dim, iatom) = &
 
  583              (sys%ions%tot_force(:, iatom) - born_charges%charge(ii, 1:sys%space%dim, iatom)) &
 
  585            born_charges%charge(ii, ii, iatom) = born_charges%charge(ii, ii, iatom) + sys%ions%charge(iatom)
 
  594      if (sys%outp%what(option__output__density) .or. &
 
  595        sys%outp%what(option__output__pol_density)) 
then 
  597        if (isign == 1 .and. ii == 2) 
then 
  598          tmp_rho(1:sys%gr%np, 1:sys%st%d%nspin) = sys%st%rho(1:sys%gr%np, 1:sys%st%d%nspin)
 
  604          lr_rho(1:sys%gr%np, 1:sys%st%d%nspin) = sys%st%rho(1:sys%gr%np, 1:sys%st%d%nspin)
 
  606          lr_rho2(1:sys%gr%np, 1:sys%st%d%nspin) = &
 
  607            -(sys%st%rho(1:sys%gr%np, 1:sys%st%d%nspin) + lr_rho(1:sys%gr%np, 1:sys%st%d%nspin) - &
 
  608            2 * gs_rho(1:sys%gr%np, 1:sys%st%d%nspin)) / e_field**2
 
  610          lr_rho(1:sys%gr%np, 1:sys%st%d%nspin) = &
 
  611            (sys%st%rho(1:sys%gr%np, 1:sys%st%d%nspin) - lr_rho(1:sys%gr%np, 1:sys%st%d%nspin)) / (
m_two*e_field)
 
  614          do is = 1, sys%st%d%nspin
 
  615            if (sys%outp%what(option__output__density)) 
then 
  617              write(fname, 
'(a,i1,2a)') 
'fd_density-sp', is, 
'-', 
index2axis(ii)
 
  619                sys%namespace, sys%space, sys%gr, lr_rho(:, is), fn_unit, ierr, pos=sys%ions%pos, atoms=sys%ions%atom)
 
  623              do jj = ii, sys%space%dim
 
  626                  sys%namespace, sys%space, sys%gr, lr_rho2(:, is), fn_unit, ierr, pos=sys%ions%pos, atoms=sys%ions%atom)
 
  630            if (sys%outp%what(option__output__pol_density)) 
then 
  631              do jj = ii, sys%space%dim
 
  635                  sys%namespace, sys%space, sys%gr, -sys%gr%x(:, jj) * lr_rho(:, is), &
 
  636                  fn_unit, ierr, pos=sys%ions%pos, atoms=sys%ions%atom)
 
  639                write(fname, 
'(a,i1,6a)') 
'beta_density-sp', is, 
'-', 
index2axis(ii), &
 
  642                  sys%namespace, sys%space, sys%gr, -sys%gr%x(:, jj) * lr_rho2(:, is), &
 
  643                  fn_unit, ierr, pos=sys%ions%pos, atoms=sys%ions%atom)
 
  652      if (sys%outp%what(option__output__elf)) 
then 
  655          call elf_calc(sys%space, sys%st, sys%gr, sys%kpoints, elf, elfd)
 
  657          call elf_calc(sys%space, sys%st, sys%gr, sys%kpoints, lr_elf, lr_elfd)
 
  660          lr_elf(1:sys%gr%np, 1:sys%st%d%nspin) = &
 
  661            ( lr_elf(1:sys%gr%np, 1:sys%st%d%nspin) -  elf(1:sys%gr%np, 1:sys%st%d%nspin)) / (
m_two * e_field)
 
  662          lr_elfd(1:sys%gr%np, 1:sys%st%d%nspin) = &
 
  663            (lr_elfd(1:sys%gr%np, 1:sys%st%d%nspin) - elfd(1:sys%gr%np, 1:sys%st%d%nspin)) / (
m_two * e_field)
 
  666          do is = 1, sys%st%d%nspin
 
  667            write(fname, 
'(a,i1,2a)') 
'lr_elf-sp', is, 
'-', 
index2axis(ii)
 
  669              sys%namespace, sys%space, sys%gr, lr_elf(:, is), 
unit_one, ierr, pos=sys%ions%pos, atoms=sys%ions%atom)
 
  670            write(fname, 
'(a,i1,2a)') 
'lr_elf_D-sp', is, 
'-', 
index2axis(ii)
 
  672              sys%namespace, sys%space, sys%gr, lr_elfd(:, is), 
unit_one, ierr, pos=sys%ions%pos, atoms=sys%ions%atom)
 
  684      real(real64) :: alpha(sys%space%dim, sys%space%dim)
 
  685      complex(real64) :: beta(sys%space%dim, sys%space%dim, sys%space%dim)
 
  686      integer :: iunit, idir
 
  688      real(real64) :: freq_factor(3)
 
  694      if ((sys%outp%what(option__output__density) .or. &
 
  695        sys%outp%what(option__output__pol_density)) .and. calc_diagonal) 
then 
  696        lr_rho2(1:sys%gr%np, 1:sys%st%d%nspin) = &
 
  697          -(sys%st%rho(1:sys%gr%np, 1:sys%st%d%nspin) - lr_rho(1:sys%gr%np, 1:sys%st%d%nspin) &
 
  698          - tmp_rho(1:sys%gr%np, 1:sys%st%d%nspin) + gs_rho(1:sys%gr%np, 1:sys%st%d%nspin)) / e_field**2
 
  700        do is = 1, sys%st%d%nspin
 
  701          if (sys%outp%what(option__output__density)) 
then 
  703            write(fname, 
'(a,i1,a)') 
'fd2_density-sp', is, 
'-y-z' 
  705              sys%namespace, sys%space, sys%gr, lr_rho2(:, is), fn_unit, ierr, pos=sys%ions%pos, atoms=sys%ions%atom)
 
  708          if (sys%outp%what(option__output__pol_density)) 
then 
  710            write(fname, 
'(a,i1,a)') 
'beta_density-sp', is, 
'-x-y-z' 
  712              sys%namespace, sys%space, sys%gr, -sys%gr%x(:, 1) * lr_rho2(:, is), &
 
  713              fn_unit, ierr, pos=sys%ions%pos, atoms=sys%ions%atom)
 
  722        alpha(1:sys%space%dim, 1:sys%space%dim) = (dipole(1:sys%space%dim, 1:sys%space%dim, 1) - &
 
  723          dipole(1:sys%space%dim, 1:sys%space%dim, 2)) / (
m_two * e_field)
 
  727        do idir = 1, sys%space%dim
 
  728          beta(1:sys%space%dim, idir, idir) = &
 
  729            -(dipole(idir, 1:sys%space%dim, 1) + dipole(idir, 1:sys%space%dim, 2) - &
 
  730            m_two * center_dipole(1:sys%space%dim)) / e_field**2
 
  731          beta(idir, 1:sys%space%dim, idir) = beta(1:sys%space%dim, idir, idir)
 
  732          beta(idir, idir, 1:sys%space%dim) = beta(1:sys%space%dim, idir, idir)
 
  735        if (calc_diagonal) 
then 
  736          beta(1, 2, 3) = -(diag_dipole(1) - dipole(2, 1, 1) - dipole(3, 1, 1) + center_dipole(1)) / e_field**2
 
  741        beta(2, 3, 1) = beta(1, 2, 3)
 
  742        beta(3, 1, 2) = beta(1, 2, 3)
 
  743        beta(3, 2, 1) = beta(1, 2, 3)
 
  744        beta(1, 3, 2) = beta(1, 2, 3)
 
  745        beta(2, 1, 3) = beta(1, 2, 3)
 
  759      if (sys%outp%what(option__output__density) .or. &
 
  760        sys%outp%what(option__output__pol_density)) 
then 
  761        safe_deallocate_a(lr_rho)
 
  762        safe_deallocate_a(lr_rho2)
 
  765      if (sys%outp%what(option__output__elf)) 
then 
  766        safe_deallocate_a(lr_elf)
 
  767        safe_deallocate_a(elf)
 
  768        safe_deallocate_a(lr_elfd)
 
  769        safe_deallocate_a(elfd)
 
subroutine init_(fromscratch)
 
subroutine, public born_charges_end(this)
 
subroutine, public born_output_charges(this, atom, charge, natoms, namespace, dim, dirname, write_real)
 
subroutine, public born_charges_init(this, namespace, natoms, val_charge, qtot, dim)
 
subroutine, public elf_calc(space, st, gr, kpoints, elf, de)
(time-dependent) electron localization function, (TD)ELF.
 
subroutine, public out_hyperpolarizability(box, beta, freq_factor, converged, dirname, namespace)
Ref: David M Bishop, Rev Mod Phys 62, 343 (1990) beta generalized to lack of Kleinman symmetry.
 
character(len= *), parameter, public em_resp_fd_dir
 
real(real64), parameter, public m_two
 
real(real64), parameter, public m_zero
 
subroutine, public dio_function_output(how, dir, fname, namespace, space, mesh, ff, unit, ierr, pos, atoms, grp, root)
 
subroutine, public io_close(iunit, grp)
 
subroutine, public io_mkdir(fname, namespace, parents)
 
integer function, public io_open(file, namespace, action, status, form, position, die, recl, grp)
 
subroutine, public lcao_run(namespace, space, gr, ions, ext_partners, st, ks, hm, st_start, lmm_r)
 
This module defines various routines, operating on mesh functions.
 
real(real64) function, public dmf_moment(mesh, ff, idir, order)
This function calculates the "order" moment of the function ff.
 
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_experimental(name, namespace)
 
logical function mpi_grp_is_root(grp)
 
type(mpi_grp_t), public mpi_world
 
This module implements the basic mulsisystem class, a container system for other systems.
 
subroutine, public restart_close(restart, iunit)
Close a file previously opened with restart_open.
 
integer, parameter, public restart_gs
 
integer, parameter, public restart_em_resp_fd
 
subroutine, public restart_init(restart, namespace, data_type, type, mc, ierr, mesh, dir, exact)
Initializes a restart object.
 
integer, parameter, public restart_type_dump
 
subroutine, public restart_write(restart, iunit, lines, nlines, ierr)
 
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 restart_open_dir(restart, dirname, ierr)
Change the restart directory to dirname, where "dirname" is a subdirectory of the base restart direct...
 
integer, parameter, public restart_type_load
 
subroutine, public restart_end(restart)
 
subroutine, public restart_close_dir(restart)
Change back to the base directory. To be called after restart_open_dir.
 
subroutine, public scf_mix_clear(scf)
 
subroutine, public scf_run(scf, namespace, space, mc, gr, ions, ext_partners, st, ks, hm, outp, verbosity, iters_done, restart_load, restart_dump)
 
integer, parameter, public verb_full
 
integer, parameter, public verb_compact
 
subroutine, public scf_init(scf, namespace, gr, ions, st, mc, hm, space)
 
subroutine, public scf_end(scf)
 
pure logical function, public states_are_real(st)
 
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.
 
This module handles reading and writing restart information for the states_elec_t.
 
subroutine, public states_elec_dump(restart, space, st, mesh, kpoints, ierr, iter, lr, st_start_writing, verbose)
 
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 static_pol_run_legacy(sys, fromScratch)
 
subroutine, public static_pol_run(system, from_scratch)
 
brief This module defines the class unit_t which is used by the unit_systems_oct_m module.
 
character(len=20) pure function, public units_abbrev(this)
 
This module defines the unit system, used for input and output.
 
type(unit_system_t), public units_out
 
type(unit_system_t), public units_inp
the units systems for reading and writing
 
type(unit_t), public unit_one
some special units required for particular quantities
 
This module is intended to contain simple general-purpose utility functions and procedures.
 
subroutine, public output_tensor(tensor, ndim, unit, write_average, iunit, namespace)
 
subroutine, public output_dipole(dipole, ndim, iunit, namespace)
 
character pure function, public index2axis(idir)
 
subroutine, public v_ks_h_setup(namespace, space, gr, ions, ext_partners, st, ks, hm, calc_eigenval, calc_current)
 
subroutine output_init_()
 
subroutine output_cycle_()
 
Class describing the electron system.
 
Container class for lists of system_oct_m::system_t.