From 0cebfcf64fbb39c3a09bcc7bfecbc64c283f79ee Mon Sep 17 00:00:00 2001 From: Philipp Ruessmann <p.ruessmann@fz-juelich.de> Date: Wed, 1 Dec 2021 16:39:58 +0100 Subject: [PATCH] Change default NPAN_LOGPANELFAC for impurity code to behave as host code also add test option write_tmat_all and make KKRimp and KKRhost compile simultaneously --- source/KKRhost/tmat_newsolver.F90 | 6 +- source/KKRimp/calctmat_bauernew.f90 | 14 ++- source/KKRimp/convol.f | 4 +- source/KKRimp/ecoub.f | 4 +- source/KKRimp/epotinb.f | 4 +- source/KKRimp/espcb.f | 4 +- source/KKRimp/etotb1.f90 | 4 +- source/KKRimp/initldau.F | 4 +- source/KKRimp/interpolatecell.f90 | 13 ++- source/KKRimp/kkrflex.F90 | 26 ++--- source/KKRimp/mixstr.f90 | 4 +- source/KKRimp/rhocore.f90 | 4 +- source/KKRimp/rhototb.f90 | 4 +- source/KKRimp/rites.f90 | 4 +- source/KKRimp/type_config.f90 | 145 +++++++++++++--------------- source/KKRimp/vintras.f90 | 4 +- source/KKRimp/vxcdrv.f90 | 4 +- source/KKRimp/wrmoms.f90 | 4 +- source/common/runoptions.F90 | 4 + 19 files changed, 134 insertions(+), 126 deletions(-) diff --git a/source/KKRhost/tmat_newsolver.F90 b/source/KKRhost/tmat_newsolver.F90 index 2cfac3cb4..5a1f7356e 100644 --- a/source/KKRhost/tmat_newsolver.F90 +++ b/source/KKRhost/tmat_newsolver.F90 @@ -45,7 +45,7 @@ contains #endif use :: mod_datatypes, only: dp use :: mod_runoptions, only: calc_exchange_couplings, disable_tmat_sratrick, formatted_file, stop_1b, & - write_BdG_tests, write_pkkr_operators, write_rhoq_input, set_cheby_nospeedup, decouple_spin_cheby, calc_wronskian + write_BdG_tests, write_pkkr_operators, write_rhoq_input, set_cheby_nospeedup, decouple_spin_cheby, calc_wronskian, write_tmat_all use :: mod_constants, only: czero, cone, cvlight use :: global_variables, only: ntotd, ncleb, nrmaxd, mmaxd, nspind, nspotd, iemxd, lmmaxd, korbit use :: mod_wunfiles, only: t_params @@ -583,15 +583,13 @@ contains #ifdef CPP_OMP !$omp critical #endif -#ifdef CPP_BdG - if (write_BdG_tests) then + if (write_tmat_all) then write (filename, '(A,I0.3,A,I0.3,A)') 'tmat_atom_', i1, '_energ_', ie, '.dat' open (888888, file=trim(filename), form='formatted') write (888888, '(A,I9,A,I9,A,2ES15.7)') '# dimension: lmmaxd=', lmmaxd, ' lmmaxd=', lmmaxd, ' ; ERYD=', eryd write (888888, '(2ES25.16)') tmatll(:, :) close (888888) end if -#endif #ifdef CPP_OMP !$omp end critical #endif diff --git a/source/KKRimp/calctmat_bauernew.f90 b/source/KKRimp/calctmat_bauernew.f90 index ac0e6fc01..b0c3d136d 100644 --- a/source/KKRimp/calctmat_bauernew.f90 +++ b/source/KKRimp/calctmat_bauernew.f90 @@ -527,6 +527,16 @@ if ( .not. config_testflag('nosph') .or. nsra==5 ) then end do end if + + +if (config_testflag('write_tmat_all')) then + write (filename, '(A,I0.3,A,I0.3,A)') 'tmat_atom_', iatom, '_energ_', ie, '.dat' + open (888888, file=trim(filename), form='formatted') + write (888888, '(A,I9,A,I9,A,2ES15.7)') '# dimension: lmmaxd=', lmsize, ' lmmaxd=', lmsize, ' ; ERYD=', eryd + write (888888, '(2ES25.16)') tmat%tmat(:, :) + close (888888) +end if + !####################################################### ! If spin-orbit coupling is used the left solution of the ! Hamiltonian is non-trivial and needs to be calculated explicitly @@ -563,8 +573,8 @@ if ((kspinorbit==1).and.calcleft) then ! ------------> watch out here changed the order for left and right solution <----------- jlk_index, hlk2, jlk2, hlk, jlk, GMATPREFACTOR, '1', '1', '0', use_sratrick, tmattemp) if (nsra==2) then - wavefunction%RLLleft(lmsize+1:,:,:,1)=wavefunction%RLLleft(lmsize+1:,:,:,1)/(cvlight) - wavefunction%SLLleft(lmsize+1:,:,:,1)=wavefunction%SLLleft(lmsize+1:,:,:,1)/(cvlight) + wavefunction%RLLleft(lmsize+1:,:,:,1) = wavefunction%RLLleft(lmsize+1:,:,:,1)/(cvlight) + wavefunction%SLLleft(lmsize+1:,:,:,1) = wavefunction%SLLleft(lmsize+1:,:,:,1)/(cvlight) end if if ( config_testflag('tmatdebug') ) then diff --git a/source/KKRimp/convol.f b/source/KKRimp/convol.f index b3883bdd4..d8bee24e7 100644 --- a/source/KKRimp/convol.f +++ b/source/KKRimp/convol.f @@ -4,7 +4,7 @@ !> !> Calculate convolution of potential with shapefunction. !------------------------------------------------------------------------------- - MODULE MOD_CONVOL + MODULE mod_convol_kkrimp CONTAINS !------------------------------------------------------------------------------- !> Summary: Driver routine for the convolution module @@ -191,4 +191,4 @@ C COPY THE PART INSIDE THE MT SPHERE RETURN END SUBROUTINE - END MODULE MOD_CONVOL + END MODULE mod_convol_kkrimp diff --git a/source/KKRimp/ecoub.f b/source/KKRimp/ecoub.f index 8b7f9cee2..21d8f3b89 100644 --- a/source/KKRimp/ecoub.f +++ b/source/KKRimp/ecoub.f @@ -4,7 +4,7 @@ !> Calculate the electrostatic potential-energies without the !> electron-nuclear interaction in the cell itself. !------------------------------------------------------------------------------- - MODULE MOD_ECOUB + MODULE mod_ecoub_kkrimp CONTAINS !------------------------------------------------------------------------------- !> Summary: Coulomb hartree energy @@ -250,4 +250,4 @@ c 9010 FORMAT (10x,' generalized madelung pot. for atom',1x,i3,1x, + ': ',1p,d14.6) END SUBROUTINE - END MODULE MOD_ECOUB + END MODULE mod_ecoub_kkrimp diff --git a/source/KKRimp/epotinb.f b/source/KKRimp/epotinb.f index a58771547..a54ac0dd1 100644 --- a/source/KKRimp/epotinb.f +++ b/source/KKRimp/epotinb.f @@ -4,7 +4,7 @@ !> !> Calculate the energy of the input potential: Int V(r) rho(r) d^3r !> --------------------------------------------------- - MODULE MOD_EPOTINB + MODULE mod_epotinb_kkrimp CONTAINS !------------------------------------------------------------------------------- !> Summary: Calculates energy of the input potential @@ -226,4 +226,4 @@ c 90 CONTINUE ! IATOM = 1,NATYP END SUBROUTINE - END MODULE MOD_EPOTINB + END MODULE mod_epotinb_kkrimp diff --git a/source/KKRimp/espcb.f b/source/KKRimp/espcb.f index 6d44e021b..7ca475d20 100644 --- a/source/KKRimp/espcb.f +++ b/source/KKRimp/espcb.f @@ -5,7 +5,7 @@ !> Calculate the core contribution of the single particle energies !> l and spin dependent. !------------------------------------------------------------------------------- - MODULE MOD_ESPCB + MODULE mod_espcb_kkrimp CONTAINS !------------------------------------------------------------------------------- !> Summary: Collects single-particle core energy @@ -95,4 +95,4 @@ c 30 CONTINUE 40 CONTINUE END SUBROUTINE - END MODULE MOD_ESPCB + END MODULE mod_espcb_kkrimp diff --git a/source/KKRimp/etotb1.f90 b/source/KKRimp/etotb1.f90 index 61691dffb..325ff6738 100644 --- a/source/KKRimp/etotb1.f90 +++ b/source/KKRimp/etotb1.f90 @@ -4,7 +4,7 @@ !> !> Calculate the total energy of the cluster. !------------------------------------------------------------------------------- -MODULE MOD_ETOTB1 +MODULE mod_etotb1_kkrimp CONTAINS !------------------------------------------------------------------------------- !> Summary: Collects total energy of cluster @@ -186,4 +186,4 @@ MODULE MOD_ETOTB1 99021 FORMAT (3X,' including LDA+U correction :',F15.8) 99022 FORMAT (3X,70('-')) END SUBROUTINE -END MODULE MOD_ETOTB1 +END MODULE mod_etotb1_kkrimp diff --git a/source/KKRimp/initldau.F b/source/KKRimp/initldau.F index bf7bf5550..dee70d056 100644 --- a/source/KKRimp/initldau.F +++ b/source/KKRimp/initldau.F @@ -1,5 +1,5 @@ C*==initldau.f processed by SPAG 6.05Rc at 15:27 on 7 Mar 2003 - MODULE mod_initldau + MODULE mod_initldau_kkrimp CONTAINS !------------------------------------------------------------------------------- @@ -497,4 +497,4 @@ C END FUNCTION GAUNTC1 - END MODULE mod_initldau + END MODULE mod_initldau_kkrimp diff --git a/source/KKRimp/interpolatecell.f90 b/source/KKRimp/interpolatecell.f90 index fdaf125f8..a8cb8b1dd 100644 --- a/source/KKRimp/interpolatecell.f90 +++ b/source/KKRimp/interpolatecell.f90 @@ -111,9 +111,16 @@ if ( config%rmin< -1.0D-10 ) then rmin=cell%rmesh(2) ! because cell%rmesh(1) is always 0! end if -rval=0 -fac=config%npan_logfac !4.0D0/3.0D0 -ishift=0 +rval = 0 +if (config%npan_logfac<0) then + ! this is the same behavior as in the host code + ! this is also the (new) default bahavior + fac = (rmax/rmin)**(1.d0/config%npan_log) +else + ! old behavior: read npan_logfac from config.cfg (old default was 2) + fac = config%npan_logfac !4.0D0/3.0D0 +end if +ishift = 0 ! the old mesh has a discontinuity where the non-spherical mesh is set to diff --git a/source/KKRimp/kkrflex.F90 b/source/KKRimp/kkrflex.F90 index 29225bbac..8b5a851c8 100644 --- a/source/KKRimp/kkrflex.F90 +++ b/source/KKRimp/kkrflex.F90 @@ -28,28 +28,28 @@ program kkrflex use mod_gauntharmonics, only: gauntharmonics_set ! use mod_gauntharmonics_test, only: gauntharmonics_set_test use mod_calctmat - use mod_rhocore + use mod_rhocore_kkrimp use mod_gauntshape, only: gen_gauntshape use arrayparams, only: arrayparams_set use mod_energyloop - use mod_rhototb + use mod_rhototb_kkrimp use mod_preconditioning use mod_mpienergy, only: mpienergy_distribute use mod_vinters2010 - use mod_vintras - use mod_convol - use MOD_MIXSTR + use mod_vintras_kkrimp + use mod_convol_kkrimp + use mod_mixstr_kkrimp use mod_mixbroyden - use mod_vxcdrv, only: vxcdrv - use mod_rites - use mod_epotinb - use mod_ESPCB - use mod_ECOUB - use mod_etotb1 - use mod_wrmoms + use mod_vxcdrv_kkrimp, only: vxcdrv + use mod_rites_kkrimp + use mod_epotinb_kkrimp + use mod_espcb_kkrimp + use mod_ecoub_kkrimp + use mod_etotb1_kkrimp + use mod_wrmoms_kkrimp use mod_calcforce use mod_utrafo - use mod_initldau ! lda+u + use mod_initldau_kkrimp ! lda+u use mod_calcwldau ! lda+u use mod_averagewldau ! lda+u diff --git a/source/KKRimp/mixstr.f90 b/source/KKRimp/mixstr.f90 index 97b113c9f..b80f3482a 100644 --- a/source/KKRimp/mixstr.f90 +++ b/source/KKRimp/mixstr.f90 @@ -1,4 +1,4 @@ - MODULE MOD_MIXSTR + MODULE mod_mixstr_kkrimp CONTAINS ! c 13.10.95 *************************************************************** !------------------------------------------------------------------------------- @@ -187,4 +187,4 @@ 9050 FORMAT (' ITERATION',I4,' average rms-error : v+ + v- = ', & 1p,d11.4) END SUBROUTINE - END MODULE + END MODULE mod_mixstr_kkrimp diff --git a/source/KKRimp/rhocore.f90 b/source/KKRimp/rhocore.f90 index d1c952c22..b48686479 100644 --- a/source/KKRimp/rhocore.f90 +++ b/source/KKRimp/rhocore.f90 @@ -1,4 +1,4 @@ -MODULE MOD_RHOCORE +MODULE mod_rhocore_kkrimp CONTAINS !------------------------------------------------------------------------------------ @@ -157,4 +157,4 @@ MODULE MOD_RHOCORE END SUBROUTINE RHOCORE -END MODULE MOD_RHOCORE +END MODULE mod_rhocore_kkrimp diff --git a/source/KKRimp/rhototb.f90 b/source/KKRimp/rhototb.f90 index 60f769225..d41d333da 100644 --- a/source/KKRimp/rhototb.f90 +++ b/source/KKRimp/rhototb.f90 @@ -1,4 +1,4 @@ -MODULE MOD_RHOTOTB +MODULE mod_rhototb_kkrimp CONTAINS !------------------------------------------------------------------------- @@ -224,4 +224,4 @@ MODULE MOD_RHOTOTB END SUBROUTINE RHOTOTB -END MODULE MOD_RHOTOTB +END MODULE mod_rhototb_kkrimp diff --git a/source/KKRimp/rites.f90 b/source/KKRimp/rites.f90 index 292314b86..ffc523f9a 100644 --- a/source/KKRimp/rites.f90 +++ b/source/KKRimp/rites.f90 @@ -1,4 +1,4 @@ -MODULE MOD_RITES +MODULE mod_rites_kkrimp CONTAINS !--------------------------------------------------------------------- !> Summary: Writes the potential file @@ -250,4 +250,4 @@ MODULE MOD_RITES 9060 FORMAT (10i5) 9070 FORMAT (1p,4d20.13) END SUBROUTINE - END MODULE MOD_RITES + END MODULE mod_rites_kkrimp diff --git a/source/KKRimp/type_config.f90 b/source/KKRimp/type_config.f90 index 367da2a5f..03e8ba662 100644 --- a/source/KKRimp/type_config.f90 +++ b/source/KKRimp/type_config.f90 @@ -8,83 +8,72 @@ !------------------------------------------------------------------------------------ module type_config -! ------------------------- -! test and run flags -! ------------------------- -integer, parameter :: dim_flags = 20 !! dimension of testflag and runflag array -character(len=20),dimension(dim_flags) :: testflag = '' !! testflag array -character(len=20),dimension(dim_flags) :: runflag = '' !! runflag array - -TYPE :: CONFIG_TYPE - -! ------------------------- -! selfconsistency -! ------------------------- - integer :: icst = 4 !! number of born iterations - integer :: ins = 1 !! non-spherical calculation =1 full pot, =0 asa - integer :: kvrel = 1 !! option for the scalar relativistic approximation (=1 sets nsra to 2) - integer :: nsra = 2 !! option for the scalar relativistic approximation (=2 for sra) - integer :: nspin = 2 !! number of spins - integer :: kte = 1 !! -! integer :: kxc = 2 - character(len=20) :: modeexcorr = 'LDA' !! exchange correlation mode - integer :: kshape = 1 !! = ins - integer :: kspinorbit = 0 !! spin-orbit coupling - integer :: ncoll = 0 !! non-collinear calculation - ! changed default value to save the first 20 wavefunctions. This needs up to - ! 1GB of additional memory, which should usually be available. By using the - ! keyword 'WAVEFUNC_RECALC_THRESHHOLD' in the inputcard this can be modified. - !integer :: wavefunc_recalc_threshhold=0 - integer :: wavefunc_recalc_threshhold=20 !! Number of stored wavefunctions -! ------------------------- -! -! ------------------------- - integer :: npan_log = 40 !! number of panels in the log region - integer :: npan_eq = 40 !! number of panels in the equidistant region - integer :: ncheb = 16 !! probably number of chebyshev nodes - double precision :: npan_logfac = 2.0D0 !! factor for the generation of the log mesh -real(kind=8) :: rmin = -1.0D0 !! first point of the new radial mesh -real(kind=8) :: rlogpan = 1.0D0 !! radius of the log panel - - - INTEGER :: SCFSTEPS = 1 !! number of iterations -! ------------------------- -! switch for the calculation of different properties -! ------------------------- - - integer :: calcforce= 0 !! calculate the force - integer :: calcorbitalmoment= 0 !! calculate the orbital moments - integer :: calcJijmat = 0 !! calculate the magnetic exchange interactions - - - integer :: hfield_apply_niter=0 !! number of iterations for a magnetic field (should only be used to force a spin splitting) - real(kind=8) :: hfield=0.0D0 !! magnitude of the magnetic field - - integer :: hfield_apply_niter2=0 !! number of iterations for a asymmetric magnetic field - real(kind=8) :: hfield2(2)=0.0D0 !! asymmetric magnetic field for the two spin channels - - -! ------------------------- -! mixing -! ------------------------- -integer :: imix = 2 !! mixing scheme, imix=2 (straight), 3 (broy1), 4 (broy2), 5 (anderson) -integer :: NSIMPLEMIXFIRST = 0 !! number of initial simple mixing steps -integer :: IMIXSPIN = 0 !! spin mixing (0 straight, 1 broyden) -real(kind=8) :: SPINMIXFAC = 1.0D0 !! spin mixing factor -integer :: spinmixbound=99999 - -real(kind=8) :: mixfac = 0.1 !! mixing factor -real(kind=8) :: fcm = 2.0 !! -real(kind=8) :: qbound = 1d-8 !! -real(kind=8) :: qbound_ldau = 1d-4 !! qbound for mixing of ldau potential (see calcwldau) -integer :: itdbry = 40 !! number of iterations which are used for the broyden mixing -! ------------------------- -! lattice relaxation -! ------------------------- -integer :: lattice_relax = 0 !! - - - - END TYPE CONFIG_TYPE + ! ------------------------- + ! test and run flags + ! ------------------------- + integer, parameter :: dim_flags = 20 !! dimension of testflag and runflag array + character(len=20),dimension(dim_flags) :: testflag = '' !! testflag array + character(len=20),dimension(dim_flags) :: runflag = '' !! runflag array + + TYPE :: config_type + + ! ------------------------- + ! selfconsistency + ! ------------------------- + integer :: icst = 4 !! number of born iterations + integer :: ins = 1 !! non-spherical calculation =1 full pot, =0 asa + integer :: kvrel = 1 !! option for the scalar relativistic approximation (=1 sets nsra to 2) + integer :: nsra = 2 !! option for the scalar relativistic approximation (=2 for sra) + integer :: nspin = 2 !! number of spins + integer :: kte = 1 !! + character(len=20) :: modeexcorr = 'LDA' !! exchange correlation mode + integer :: kshape = 1 !! = ins + integer :: kspinorbit = 0 !! spin-orbit coupling + integer :: ncoll = 0 !! non-collinear calculation + ! changed default value to save the first 20 wavefunctions. This needs up to + ! 1GB of additional memory, which should usually be available. By using the + ! keyword 'WAVEFUNC_RECALC_THRESHHOLD' in the inputcard this can be modified. + integer :: wavefunc_recalc_threshhold=20 !! Number of stored wavefunctions + ! ------------------------- + ! + ! ------------------------- + integer :: npan_log = 40 !! number of panels in the log region + integer :: npan_eq = 40 !! number of panels in the equidistant region + integer :: ncheb = 16 !! probably number of chebyshev nodes + real(kind=8) :: npan_logfac = -1.0D0 !! factor for the generation of the log mesh (-1 defaults to the same behavior as in the host code) + real(kind=8) :: rmin = -1.0D0 !! first point of the new radial mesh + real(kind=8) :: rlogpan = 1.0D0 !! radius of the log panel + + ! ------------------------- + ! switch for the calculation of different properties + ! ------------------------- + integer :: calcforce= 0 !! calculate the force + integer :: calcorbitalmoment= 0 !! calculate the orbital moments + integer :: calcJijmat = 0 !! calculate the magnetic exchange interaction + integer :: hfield_apply_niter=0 !! number of iterations for a magnetic field (should only be used to force a spin splitting) + real(kind=8) :: hfield=0.0D0 !! magnitude of the magnetic field + integer :: hfield_apply_niter2=0 !! number of iterations for a asymmetric magnetic field + real(kind=8) :: hfield2(2)=0.0D0 !! asymmetric magnetic field for the two spin channels + + ! ------------------------- + ! mixing + ! ------------------------- + integer :: SCFSTEPS = 1 !! number of iterations + integer :: imix = 2 !! mixing scheme, imix=2 (straight), 3 (broy1), 4 (broy2), 5 (anderson) + integer :: NSIMPLEMIXFIRST = 0 !! number of initial simple mixing steps + integer :: IMIXSPIN = 0 !! spin mixing (0 straight, 1 broyden) + real(kind=8) :: SPINMIXFAC = 1.0D0 !! spin mixing factor + integer :: spinmixbound = 99999 !! + real(kind=8) :: mixfac = 0.1 !! mixing factor + real(kind=8) :: fcm = 2.0 !! + real(kind=8) :: qbound = 1d-8 !! + real(kind=8) :: qbound_ldau = 1d-4 !! qbound for mixing of ldau potential (see calcwldau) + integer :: itdbry = 40 !! number of iterations which are used for the broyden mixing + ! ------------------------- + ! lattice relaxation + ! ------------------------- + integer :: lattice_relax = 0 !! + + END TYPE config_type end module type_config diff --git a/source/KKRimp/vintras.f90 b/source/KKRimp/vintras.f90 index 1ae9d420a..5fc4ba0da 100644 --- a/source/KKRimp/vintras.f90 +++ b/source/KKRimp/vintras.f90 @@ -1,4 +1,4 @@ -module mod_vintras +module mod_vintras_kkrimp contains @@ -201,4 +201,4 @@ contains end subroutine vintras -end module mod_vintras +end module mod_vintras_kkrimp diff --git a/source/KKRimp/vxcdrv.f90 b/source/KKRimp/vxcdrv.f90 index cb6d9389d..360076322 100644 --- a/source/KKRimp/vxcdrv.f90 +++ b/source/KKRimp/vxcdrv.f90 @@ -6,7 +6,7 @@ !> appropriate subroutines depending on the type of exchange correlation potential !> indicated in the `inputcard` !------------------------------------------------------------------------------------ - MODULE MOD_VXCDRV + MODULE mod_vxcdrv_kkrimp CONTAINS ! call vxcdrv(energyparts%exc,config%kte,config%kxc,nspin,natom,density, & ! vpot_out, cell,config%kshape,gauntshape, shapefun,lmaxd, & @@ -165,4 +165,4 @@ END SUBROUTINE VXCDRV - END MODULE MOD_VXCDRV + END MODULE mod_vxcdrv_kkrimp diff --git a/source/KKRimp/wrmoms.f90 b/source/KKRimp/wrmoms.f90 index 073c1a047..bab7d3ba9 100644 --- a/source/KKRimp/wrmoms.f90 +++ b/source/KKRimp/wrmoms.f90 @@ -3,7 +3,7 @@ !> Author: !> Write charges and magnetic and orbital moments to file. The output is l-decomposed !------------------------------------------------------------------------------------ - MODULE MOD_WRMOMS + MODULE mod_wrmoms_kkrimp CONTAINS !------------------------------------------------------------------------------- @@ -154,4 +154,4 @@ 99006 FORMAT (' m_orb spin dn spin up') END SUBROUTINE WRMOMS - END MODULE MOD_WRMOMS + END MODULE mod_wrmoms_kkrimp diff --git a/source/common/runoptions.F90 b/source/common/runoptions.F90 index c254f4d60..47a17bf93 100644 --- a/source/common/runoptions.F90 +++ b/source/common/runoptions.F90 @@ -121,6 +121,7 @@ module mod_runoptions logical :: nosmallcomp = .false. !! set small component of the wavefunction to zero logical :: use_broyden_spinmix = .false. !! use broyden spin mixing for noncollinear angles logical :: write_angles_alliter= .false. !! write out noncollinear angles for all iterations + logical :: write_tmat_all= .false. !! write out the tmat for all atoms and energies !some old run and test options have been removed: ! 'atptshft': replaced by presence or absence of IVSHIFT in inputcard @@ -243,6 +244,7 @@ module mod_runoptions call set_runoption(calc_wronskian , '<calc_wronskian>' , '<wronskian>') call set_runoption(use_broyden_spinmix , '<use_broyden_spinmix>' , '<bryspinmix>') call set_runoption(write_angles_alliter , '<write_angles_alliter>') + call set_runoption(write_tmat_all , '<write_tmat_all>') end subroutine read_runoptions @@ -786,6 +788,7 @@ module mod_runoptions call mpi_bcast(calc_wronskian , 1, mpi_logical, master, mpi_comm_world, ierr) call mpi_bcast(use_broyden_spinmix , 1, mpi_logical, master, mpi_comm_world, ierr) call mpi_bcast(write_angles_alliter , 1, mpi_logical, master, mpi_comm_world, ierr) + call mpi_bcast(write_tmat_all , 1, mpi_logical, master, mpi_comm_world, ierr) end subroutine bcast_runoptions #endif @@ -901,6 +904,7 @@ module mod_runoptions write(iounit, '(A35,1x,1L,3x,A)') '<calc_wronskian>=', calc_wronskian, "calculate the wronskian relations of first and second kind for the wavefunctions (see PhD Bauer pp 48)" write(iounit, '(A35,1x,1L,3x,A)') '<use_broyden_spinmix>=', use_broyden_spinmix, "use broyden spin mixing for noncollinear angles" write(iounit, '(A35,1x,1L,3x,A)') '<write_angles_alliter>=', write_angles_alliter, "write out noncollinear angles for all iterations" + write(iounit, '(A35,1x,1L,3x,A)') '<write_tmat_all>=', write_tmat_all, "write out the tmat for all energies and all atoms" end subroutine print_runoptions -- GitLab