LCOV - code coverage report
Current view: top level - io - w_inpXML.f90 (source / functions) Hit Total Coverage
Test: FLEUR test coverage Lines: 0 251 0.0 %
Date: 2024-04-25 04:21:55 Functions: 0 1 0.0 %

          Line data    Source code
       1             : !--------------------------------------------------------------------------------
       2             : ! Copyright (c) 2016 Peter Grünberg Institut, Forschungszentrum Jülich, Germany
       3             : ! This file is part of FLEUR and available as free software under the conditions
       4             : ! of the MIT license as expressed in the LICENSE file in more detail.
       5             : !--------------------------------------------------------------------------------
       6             : 
       7             : MODULE m_winpXML
       8             : 
       9             : !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
      10             : !!!
      11             : !!!   XML input file generator
      12             : !!!
      13             : !!!   This subroutine is supposed to write out a file inp.xml
      14             : !!!   containing all required input data.
      15             : !!!                                         GM'16
      16             : !!!
      17             : !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
      18             : CONTAINS
      19           0 :    SUBROUTINE w_inpXML( &
      20             :       atoms, vacuum, input, stars, sliceplot, forcetheo, banddos, juPhon, &
      21           0 :       cell, sym, xcpot, noco,   mpinp, hybinp, kptsArray, kptsSelection, enpara, &
      22             :       gfinp, hub1inp, l_explicitIn, l_includeIn, filename, add_filename)
      23             : 
      24             :       use m_types_input
      25             :       use m_types_sym
      26             :       use m_types_stars
      27             :       use m_types_atoms
      28             :       use m_types_vacuum
      29             :       use m_types_kpts
      30             : 
      31             :       use m_types_mpinp
      32             :       use m_types_hybinp
      33             :       use m_types_gfinp
      34             :       use m_types_hub1inp
      35             :       use m_types_cell
      36             :       use m_types_banddos
      37             :       use m_types_sliceplot
      38             :       USE m_types_xcpot
      39             :       USE m_types_xcpot_inbuild_nofunction
      40             :       USE m_types_noco
      41             :       use m_types_enparaxml
      42             :       USE m_types_forcetheo
      43             :       USE m_types_juPhon
      44             : 
      45             :       USE m_juDFT
      46             :       USE m_constants
      47             :       USE m_xmlOutput
      48             : 
      49             :       IMPLICIT NONE
      50             : 
      51             : ! arguments
      52             : 
      53             :       TYPE(t_input), INTENT(IN)   :: input
      54             :       TYPE(t_sym), INTENT(IN)     :: sym
      55             :       TYPE(t_stars), INTENT(IN)   :: stars
      56             :       TYPE(t_atoms), INTENT(IN)   :: atoms
      57             :       TYPE(t_vacuum), INTENT(IN)   :: vacuum
      58             :       TYPE(t_kpts), INTENT(IN)     :: kptsArray(:)
      59             : 
      60             : 
      61             :       TYPE(t_mpinp), INTENT(IN)    :: mpinp
      62             :       TYPE(t_hybinp), INTENT(IN)   :: hybinp
      63             :       TYPE(t_cell), INTENT(IN)     :: cell
      64             :       TYPE(t_banddos), INTENT(IN)  :: banddos
      65             :       TYPE(t_juPhon), INTENT(IN)   :: juPhon
      66             :       TYPE(t_sliceplot), INTENT(IN):: sliceplot
      67             :       CLASS(t_xcpot), INTENT(IN)   :: xcpot
      68             :       TYPE(t_noco), INTENT(IN)     :: noco
      69             :       TYPE(t_gfinp), INTENT(IN)    :: gfinp
      70             :       TYPE(t_hub1inp), INTENT(IN)  :: hub1inp
      71             :       CLASS(t_enparaxml), INTENT(IN)   :: enpara
      72             :       CLASS(t_forcetheo), INTENT(IN):: forcetheo !nothing is done here so far....
      73             :       CHARACTER(LEN=40)          :: kptsSelection(3) ! 1: default selection, 2: alternative for band structures, alternative for GW
      74             :       LOGICAL, INTENT(IN)        :: l_explicitIn, l_includeIn(4)
      75             :       CHARACTER(LEN=*), INTENT(IN), OPTIONAL :: filename
      76             :       CHARACTER(LEN=*), INTENT(IN), OPTIONAL :: add_filename
      77             : 
      78             :       INTEGER          :: iSpecies, fileNum
      79             :       CHARACTER(len=8) :: name(10)
      80             :       INTEGER          :: numSpecies
      81           0 :       INTEGER          :: speciesRepAtomType(atoms%ntype)
      82           0 :       CHARACTER(len=20):: speciesNames(atoms%ntype)
      83             :       CHARACTER(LEN=50):: tempStringA, tempStringB
      84             :       LOGICAL          :: known_species
      85             : 
      86             : !+lda+u
      87             :       REAL u, j
      88             :       INTEGER l, i_u
      89           0 :       INTEGER uIndices(2, atoms%ntype)
      90             :       LOGICAL l_amf
      91             :       CHARACTER(len=3) ch_test
      92             :       NAMELIST /ldaU/ l, u, j, l_amf
      93             : !-lda+u
      94             : !+odim
      95             :       INTEGER MM, vM, m_cyl
      96             :       LOGICAL invs1, zrfs1
      97             :       INTEGER chi, rot
      98             :       LOGICAL d1, band
      99             :       NAMELIST /odim/ d1, MM, vM, m_cyl, chi, rot, invs1, zrfs1
     100             : !-odim
     101             : ! ..
     102             : ! ..  Local Variables
     103             :       REAL     :: zc, sumWeight, occ(2)
     104             :       INTEGER  ::nw, idsprs, n1, n2
     105             :       INTEGER ieq, i, k, na, n, ilo,iContour, iKpts
     106             :       REAL s3, ah, a, hs2, rest
     107             :       LOGICAL l_hyb, ldum
     108             :       INTEGER :: ierr
     109             : ! ..
     110             : !...  Local Arrays
     111             :       CHARACTER :: helpchar(atoms%ntype)
     112             :       CHARACTER(len=4) :: chntype
     113             :       CHARACTER(len=41) :: chform
     114             :       CHARACTER(len=100) :: line
     115             : 
     116             : !     added for HF and hybinp functionals
     117             :       REAL                  ::  aMix, omega
     118             :       INTEGER               :: idum
     119             :       CHARACTER(len=1)     ::  check
     120             : 
     121             :       CHARACTER(len=20) :: speciesName
     122             :       CHARACTER(len=150) :: format
     123             :       CHARACTER(len=20) :: mixingScheme
     124             :       CHARACTER(len=10) :: loType
     125             :       CHARACTER(len=10) :: bzIntMode
     126             :       LOGICAL ::   l_explicit, l_nocoOpt, l_gfOpt, l_include(4)
     127             :       INTEGER :: iAtomType, startCoreStates, endCoreStates
     128             :       CHARACTER(len=100) :: posString(3)
     129             :       CHARACTER(len=7) :: str
     130           0 :       REAL :: tempTaual(3, atoms%nat), scpos(3)
     131             :       REAL :: amatTemp(3, 3), bmatTemp(3, 3)
     132             : 
     133           0 :       l_include = l_includeIn .or. .not. present(filename)
     134           0 :       l_explicit = l_explicitIn .OR. .not. present(filename)
     135           0 :       l_nocoOpt = noco%l_noco .OR. juDFT_was_argument("-noco")
     136           0 :       l_gfOpt = gfinp%n>0 .OR. juDFT_was_argument("-greensf")
     137             : 
     138           0 :       band = .false.
     139           0 :       nw = 1
     140             : 
     141           0 :       IF (PRESENT(filename)) THEN
     142           0 :          filenum = 98
     143           0 :          OPEN (fileNum, file=TRIM(ADJUSTL(filename)), form='formatted', status='replace')
     144           0 :          WRITE (fileNum, '(a)') '<?xml version="1.0" encoding="UTF-8" standalone="no"?>'
     145           0 :          WRITE (fileNum, '(a)') '<fleurInput fleurInputVersion="'//TRIM(ADJUSTL(inputFileVersion_const))//'">'
     146             :       ELSE
     147           0 :          fileNum = getXMLOutputUnitNumber()
     148           0 :          CALL openXMLElementNoAttributes('inputData')
     149             :       END IF
     150             : 
     151           0 :       WRITE (fileNum, '(a)') '   <comment>'
     152           0 :       WRITE (fileNum, '(a6,10a)') '      ', input%comment
     153           0 :       WRITE (fileNum, '(a)') '   </comment>'
     154             : 
     155           0 :       WRITE (fileNum, '(a)') '   <calculationSetup>'
     156             : 
     157             : !      <cutoffs Kmax="3.60000" Gmax="11.000000" GmaxXC="9.200000" numbands="0"/>
     158             : 110   FORMAT('      <cutoffs Kmax="', f0.8, '" Gmax="', f0.8, '" GmaxXC="', f0.8, '" numbands="', i0, '"/>')
     159           0 :       WRITE (fileNum, 110) input%rkmax, input%gmax, xcpot%gmaxxc, input%gw_neigd
     160             : 
     161             : !      <scfLoop itmax="9" maxIterBroyd="99" imix="Anderson" alpha="0.05" precondParam="0.0" spinf="2.00"/>
     162             : 120   FORMAT('      <scfLoop itmax="', i0, '" minDistance="', f0.8, '" maxIterBroyd="', i0, '" imix="', a, '" alpha="', f0.8, '" precondParam="', f3.1, '" spinf="', f0.8, '"/>')
     163           0 :       SELECT CASE (input%imix)
     164             :       CASE (1)
     165           0 :          mixingScheme = 'straight'
     166             :       CASE (3)
     167           0 :          mixingScheme = 'Broyden1'
     168             :       CASE (5)
     169           0 :          mixingScheme = 'Broyden2'
     170             :       CASE (7)
     171           0 :          mixingScheme = 'Anderson'
     172             :       CASE DEFAULT
     173           0 :          mixingScheme = 'errorUnknownMixing'
     174             :       END SELECT
     175           0 :       WRITE (fileNum, 120) input%itmax, input%minDistance, input%maxiter, TRIM(mixingScheme), input%alpha, input%preconditioning_param, input%spinf
     176             : 
     177             : !      <coreElectrons ctail="T" frcor="F" kcrel="0" coretail_lmax="0" l_core_confpot="T"/>
     178             : 130   FORMAT('      <coreElectrons ctail="', l1, '" frcor="', l1, '" kcrel="', i0, '" coretail_lmax="', i0, '"/>')
     179           0 :       WRITE (fileNum, 130) input%ctail, input%frcor, input%kcrel, input%coretail_lmax
     180             : 
     181             :       SELECT TYPE (xcpot)
     182             :       CLASS IS (t_xcpot_inbuild_nf)
     183             :          !   <xcFunctional name="pbe" relativisticCorrections="F">
     184             : 135      FORMAT('      <xcFunctional name="', a, '" relativisticCorrections="', l1, '"/>')
     185           0 :          WRITE (fileNum, 135) trim(xcpot%get_name()), xcpot%relativistic_correction()
     186             :       END SELECT
     187             : 
     188             : !      <magnetism jspins="1" l_noco="F" l_J="F" swsp="F" lflip="F"/>
     189             : 140   FORMAT('      <magnetism jspins="', i0, '" l_noco="', l1, '" l_ss="', l1, '">')
     190             : 141   FORMAT('      <magnetism jspins="', i0, '"/>')
     191           0 :       IF(l_explicit.OR.l_nocoOpt) THEN
     192           0 :          WRITE (fileNum, 140) input%jspins, noco%l_noco, noco%l_ss
     193             : 162      FORMAT('         <qss>', f0.10, ' ', f0.10, ' ', f0.10, '</qss>')
     194           0 :          WRITE (fileNum, 162) noco%qss_inp
     195             : 164      FORMAT('         <mtNocoParams l_mperp="', l1, '" l_mtNocoPot="', l1,'" l_relaxSQA="', l1,'" mag_mixing_scheme="', i1, '" mix_RelaxWeightOffD="',f0.8,'" l_constrained="', l1,'" mix_constr="', f0.8,'"/>')
     196           0 :          WRITE (fileNum, 164) noco%l_mperp,any(noco%l_unrestrictMT), any(noco%l_alignMT), noco%mag_mixing_scheme, minval(noco%mix_RelaxWeightOffD), any(noco%l_constrained), noco%mix_b
     197             : 166      FORMAT('         <sourceFreeMag l_sourceFree="', l1, '" l_scaleMag="', l1, '" mag_scale="', f0.8,'"/>')
     198           0 :          WRITE (fileNum, 166) noco%l_sourceFree, noco%l_scaleMag, noco%mag_scale
     199           0 :          WRITE (fileNum, '(a)') '      </magnetism>'
     200             :       ELSE
     201           0 :          WRITE (fileNum, 141) input%jspins
     202             :       END IF
     203             : 
     204             :       !      <soc theta="0.00000" phi="0.00000" l_soc="F" spav="F" off="F" soc66="F"/>
     205             : 150   FORMAT('      <soc l_soc="', l1, '" theta="', f0.8, '" phi="', f0.8, '" spav="', l1, '"/>')
     206           0 :       WRITE (fileNum, 150) noco%l_soc, noco%theta_inp, noco%phi_inp, noco%l_spav
     207             : 
     208           0 :       IF (l_explicit .OR. hybinp%l_hybrid) THEN
     209             : 155      FORMAT('      <prodBasis gcutm="', f0.8, '" tolerance="', f0.8, '" ewaldlambda="', i0, '" lexp="', i0, '" bands="', i0, '" fftcut="', f0.8, '"/>')
     210           0 :          WRITE (fileNum, 155) mpinp%g_cutoff, mpinp%linear_dep_tol, hybinp%ewaldlambda, hybinp%lexp, hybinp%bands1, hybinp%fftcut
     211             :       END IF
     212             : 
     213             : 
     214             : !      <expertModes spex="0"  eig66="F" lpr="0" secvar="F" />
     215             : 180   FORMAT('      <expertModes spex="', i0, '" secvar="', l1, '"/>')
     216           0 :       WRITE (fileNum, 180) input%gw, input%secvar
     217             : 
     218             : !      <geometryOptimization l_f="F" xa="2.00000" thetad="330.00000" epsdisp="0.00001" epsforce="0.00001"/>
     219             : 190   FORMAT('      <geometryOptimization l_f="', l1, '" forcealpha="', f0.8, '" forcemix="', a, '" epsdisp="', f0.8, '" epsforce="', f0.8, '"/>')
     220           0 :       SELECT CASE (input%forcemix)
     221             :          CASE (0)
     222           0 :             mixingScheme = 'Straight'
     223             :          CASE (1)
     224           0 :             mixingScheme = 'CG'
     225             :          CASE (2)
     226           0 :             mixingScheme = 'BFGS'
     227             :          CASE DEFAULT
     228           0 :             mixingScheme = 'errorUnknownMixing'
     229             :       END SELECT
     230           0 :       WRITE (fileNum, 190) input%l_f, input%forcealpha, TRIM(mixingScheme), input%epsdisp, input%epsforce
     231             : 
     232           0 :       SELECT CASE (input%bz_integration)
     233             :          CASE (BZINT_METHOD_HIST)
     234           0 :             bzIntMode = 'hist'
     235             :          CASE (BZINT_METHOD_GAUSS)
     236           0 :             bzIntMode = 'gauss'
     237             :          CASE (BZINT_METHOD_TRIA)
     238           0 :             bzIntMode = 'tria'
     239             :          CASE (BZINT_METHOD_TETRA)
     240           0 :             bzIntMode = 'tetra'
     241             :          CASE DEFAULT
     242           0 :             CALL judft_error("Invalid brillouin zone integration mode",calledby="w_inpXML")
     243             :       END SELECT
     244             : 
     245             : !      <ldaU l_linMix="F" mixParam="0.05" spinf="1.0" />
     246             : 195   FORMAT('      <ldaU l_linMix="', l1, '" mixParam="', f0.6, '" spinf="', f0.6, '"/>')
     247           0 :       WRITE (fileNum, 195) input%ldauLinMix, input%ldauMixParam, input%ldauSpinf
     248             : 
     249           0 :       IF(atoms%n_hia>0 .OR. l_explicit) THEN
     250             : 196      FORMAT('      <ldaHIA itmaxHubbard1="', i0, '" minoccDistance="', f0.6, '" minmatDistance="', f0.6, '" beta="', f0.1, '" dftspinpol="', l1, '"/>')
     251           0 :          WRITE (fileNum, 196) hub1inp%itmax, hub1inp%minoccDistance, hub1inp%minmatDistance, hub1inp%beta, hub1inp%l_dftspinpol
     252             :       ENDIF
     253             : 
     254           0 :       IF(l_gfOpt) THEN
     255             : 205      FORMAT('      <greensFunction l_mperp="', l1,'">')
     256           0 :          WRITE(fileNum, 205) gfinp%l_mperp
     257             : 206      FORMAT('         <realAxis ne="', i0, '" ellow="', f0.8, '" elup="', f0.8, '"/>')
     258           0 :          WRITE(fileNum, 206) gfinp%ne, gfinp%ellow, gfinp%elup
     259           0 :          IF(gfinp%numberContours>0) THEN
     260           0 :             DO iContour = 1, gfinp%numberContours
     261           0 :                SELECT CASE(gfinp%contour(iContour)%shape)
     262             :                CASE(CONTOUR_RECTANGLE_CONST)
     263             : 207               FORMAT('         <contourRectangle n1="', i0, '" n2="', i0, '" n3="', i0, '" nmatsub="', i0,&
     264             :                          '" sigma="', f0.8, '" eb="', f0.8, '" label="', a,'"/>')
     265           0 :                   WRITE(fileNum, 207) gfinp%contour(iContour)%n1, gfinp%contour(iContour)%n2, gfinp%contour(iContour)%n3,&
     266           0 :                                       gfinp%contour(iContour)%nmatsub, gfinp%contour(iContour)%sigma, gfinp%contour(iContour)%eb,&
     267           0 :                                       gfinp%contour(iContour)%label
     268             :                CASE(CONTOUR_SEMICIRCLE_CONST)
     269             : 208               FORMAT('         <contourSemicircle n="', i0, '" eb="', f0.8, '" et="', f0.8, '" alpha="', f0.8, '" label="', a,'"/>')
     270           0 :                   WRITE(fileNum, 208) gfinp%contour(iContour)%ncirc, gfinp%contour(iContour)%eb, gfinp%contour(iContour)%et,&
     271           0 :                                       gfinp%contour(iContour)%alpha,gfinp%contour(iContour)%label
     272             :                CASE(CONTOUR_DOS_CONST)
     273             : 209               FORMAT('         <contourDOS n="', i0, '" sigma="', f0.8, '" eb="', f0.8, '" et="', f0.8, &
     274             :                          '" analytical_cont="', l1, '" l_fermi="', l1, '" label="', a,'"/>')
     275           0 :                   WRITE(fileNum, 209) gfinp%contour(iContour)%nDOS, gfinp%contour(iContour)%sigmaDOS, gfinp%contour(iContour)%eb,&
     276           0 :                                       gfinp%contour(iContour)%et, gfinp%contour(iContour)%l_anacont, gfinp%contour(iContour)%l_dosfermi,&
     277           0 :                                       gfinp%contour(iContour)%label
     278             :                CASE DEFAULT
     279           0 :                   CALL judft_error("Unknown green's function contour mode", calledby="w_inpXML")
     280             :                END SELECT
     281             :             ENDDO
     282             :          ELSE
     283             :             !Write out a default contour (Semicircle)
     284           0 :             WRITE(fileNum, 208) 128, -1.0, 0.0,1.0,"default"
     285             :          ENDIF
     286           0 :          WRITE(fileNum, '(a)') '      </greensFunction>'
     287             :       ENDIF
     288             : 
     289             : !
     290             : 
     291           0 :       WRITE (fileNum, '(a)') '   </calculationSetup>'
     292           0 :       WRITE (fileNum, '(a)') '   <cell>'
     293             : 
     294             : !      <bzIntegration valenceElectrons="8.00000" mode="hist" fermiSmearingEnergy="0.00100">
     295             : 200   FORMAT('      <bzIntegration valenceElectrons="', f0.8, '" mode="', a, '" fermiSmearingEnergy="', f0.8, '">')
     296           0 :       WRITE (fileNum, 200) input%zelec, TRIM(ADJUSTL(bzIntMode)), input%tkb
     297             : 
     298             : 210   FORMAT('         <kPointListSelection listName="', a, '"/>')
     299           0 :       WRITE (filenum, 210) TRIM(ADJUSTL(kptsSelection(1)))
     300             : 
     301             : !211   FORMAT('         <altKPointList listName="', a, '" purpose="', a, '"/>')
     302             : !      IF(kptsSelection(2).NE.'') THEN
     303             : !         WRITE (filenum, 211) TRIM(ADJUSTL(kptsSelection(2))), 'bands'
     304             : !      END IF
     305             : !      IF(kptsSelection(3).NE.'') THEN
     306             : !         WRITE (filenum, 211) TRIM(ADJUSTL(kptsSelection(3))), 'GW'
     307             : !      END IF
     308             : 
     309           0 :       if (l_include(1)) THEN
     310           0 :          WRITE (fileNum, '(a)') "         <kPointLists>"
     311           0 :          DO iKpts = 1, SIZE(kptsArray)
     312           0 :             CALL kptsArray(iKpts)%print_XML(fileNum)
     313             :          END DO
     314           0 :          WRITE (fileNum, '(a)') "         </kPointLists>"
     315             :       else
     316           0 :          WRITE (fileNum, '(a)') '         <!-- k-points included here -->'
     317           0 :          WRITE (fileNum, '(a)') '         <xi:include xmlns:xi="http://www.w3.org/2001/XInclude" href="'//TRIM(add_filename)//'kpts.xml"> </xi:include>'
     318             :       end if
     319           0 :       WRITE (fileNum, '(a)') '      </bzIntegration>'
     320             : 
     321             : !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     322             : !!! Note: Different options for the cell definition!
     323             : !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     324           0 :       if (l_include(2)) THEN
     325           0 :          call sym%print_xml(fileNum)
     326             :       else
     327           0 :          WRITE (fileNum, '(a)') '      <!-- symmetry operations included here -->'
     328           0 :          WRITE (fileNum, '(a)') '      <xi:include xmlns:xi="http://www.w3.org/2001/XInclude" href="'//TRIM(add_filename)//'sym.xml"> </xi:include>'
     329             :       end if
     330           0 :       IF (input%film) THEN
     331             : !      <xsd:attribute name="dVac" type="xsd:double" use="required"/>
     332             : !      <xsd:attribute name="dTilda" type="xsd:double" use="required"/>
     333             : !      <filmLattice ...>
     334             : 241      FORMAT('      <filmLattice scale="', f0.8, '" dVac="', f0.8, '" dTilda="', f0.8, '">')
     335           0 :          WRITE (fileNum, 241) 1.0, vacuum%dvac, cell%amat(3, 3)
     336             :          !       <bravaisMatrixFilm>
     337           0 :          WRITE (fileNum, '(a)') '         <bravaisMatrixFilm>'
     338             :       !            <row-1>0.00000 5.13000 </row-1>
     339             : 251      FORMAT('            <row-1>', f22.16, ' ', f22.16, '</row-1>')
     340           0 :          WRITE (fileNum, 251) cell%amat(:2, 1)
     341             :       !            <row-2>5.13000 0.00000 5.13000</row-2>
     342             : 252      FORMAT('            <row-2>', f22.16, ' ', f22.16, '</row-2>')
     343           0 :          WRITE (fileNum, 252) cell%amat(:2, 2)
     344           0 :          WRITE (fileNum, '(a)') '         </bravaisMatrixFilm>'
     345             :       ELSE
     346             : 242      FORMAT('      <bulkLattice scale="', f0.10, '">')
     347           0 : WRITE (fileNum, 242) 1.0
     348             : !         <bravaisMatrix>
     349           0 :    WRITE (fileNum, '(a)') '         <bravaisMatrix>'
     350             : !            <row-1>0.00000 5.13000 5.13000</row-1>
     351             : 250      FORMAT('            <row-1>', f22.16, ' ', f22.16, ' ', f22.16, '</row-1>')
     352           0 :    WRITE (fileNum, 250) cell%amat(:, 1)
     353             : !            <row-2>5.13000 0.00000 5.13000</row-2>
     354             : 260      FORMAT('            <row-2>', f22.16, ' ', f22.16, ' ', f22.16, '</row-2>')
     355           0 :    WRITE (fileNum, 260) cell%amat(:, 2)
     356             : !            <row-3>5.13000 5.13000 0.00000</row-3>
     357             : 270      FORMAT('            <row-3>', f22.16, ' ', f22.16, ' ', f22.16, '</row-3>')
     358           0 :    WRITE (fileNum, 270) cell%amat(:, 3)
     359           0 :    WRITE (fileNum, '(a)') '         </bravaisMatrix>'
     360             :    ENDIF
     361             : 
     362           0 :       IF (input%film) THEN
     363             : 268      FORMAT('         <vacuumEnergyParameters vacuum="', i0, '" spinUp="', f0.8, '" spinDown="', f0.8, '"/>')
     364           0 :          DO i = 1, vacuum%nvac
     365           0 :             WRITE (fileNum, 268) i, enpara%evac0(i, 1), enpara%evac0(i, input%jspins)
     366             :          END DO
     367             : 
     368           0 :          WRITE (fileNum, '(a)') '      </filmLattice>'
     369             :       ELSE
     370           0 :          WRITE (fileNum, '(a)') '      </bulkLattice>'
     371             :       END IF
     372           0 :       WRITE (fileNum, '(a)') '   </cell>'
     373             : 
     374           0 :       uIndices = -1
     375           0 :       DO i_u = 1, atoms%n_u
     376           0 :          IF (uIndices(1, atoms%lda_u(i_u)%atomType) .EQ. -1) uIndices(1, atoms%lda_u(i_u)%atomType) = i_u
     377           0 :          uIndices(2, atoms%lda_u(i_u)%atomType) = i_u
     378             :       END DO
     379             : 
     380             :       !Build list of species
     381           0 :       speciesNames = ''
     382           0 :       numSpecies = 0
     383           0 :       DO n = 1, atoms%ntype
     384           0 :          known_species = ANY(trim(atoms%speciesname(n)) == speciesNames(:numSpecies))
     385           0 :          if (.not. known_species) THEN
     386           0 :             numSpecies = numSpecies + 1
     387           0 :             speciesNames(numSpecies) = trim(atoms%speciesname(n))
     388           0 :             speciesRepAtomType(numSpecies) = n
     389             :          end if
     390             :       enddo
     391             : 
     392           0 :       if (.not. l_include(3)) then
     393           0 :          open (99, file=TRIM(add_filename)//'species.xml')
     394           0 :          WRITE (fileNum, '(a)') '      <!-- species included here -->'
     395           0 :          WRITE (fileNum, '(a)') '      <xi:include xmlns:xi="http://www.w3.org/2001/XInclude" href="'//TRIM(add_filename)//'species.xml"> </xi:include>'
     396           0 :          fileNum = 99
     397             :       endif
     398             : 
     399           0 :       WRITE (fileNum, '(a)') '   <atomSpecies>'
     400           0 :       DO iSpecies = 1, numSpecies
     401           0 :          iAtomType = speciesRepAtomType(iSpecies)
     402           0 :          IF (iAtomType .EQ. -1) THEN
     403             :             EXIT
     404             :          END IF
     405             : !      <species name="Si-1" element="Si" atomicNumber="14" coreStates="4" magMom="0.0" flipSpin="F">
     406             : 300      FORMAT('      <species name="', a, '" element="', a, '" atomicNumber="', i0, '">')
     407           0 :          speciesName = TRIM(ADJUSTL(speciesNames(iSpecies)))
     408           0 :          WRITE (fileNum, 300) TRIM(ADJUSTL(speciesName)), TRIM(ADJUSTL(namat_const(atoms%nz(iAtomType)))), atoms%nz(iAtomType)
     409             : 
     410             : !         <mtSphere radius="2.160000" gridPoints="521" logIncrement="0.022000"/>
     411             : 310      FORMAT('         <mtSphere radius="', f0.8, '" gridPoints="', i0, '" logIncrement="', f0.8, '"/>')
     412           0 :          WRITE (fileNum, 310) atoms%rmt(iAtomType), atoms%jri(iAtomType), atoms%dx(iAtomType)
     413             : 
     414             : !         <atomicCutoffs lmax="8" lnonsphr="6"/>
     415             : 320      FORMAT('         <atomicCutoffs lmax="', i0, '" lnonsphr="', i0, '"/>')
     416           0 :          WRITE (fileNum, 320) atoms%lmax(iAtomType), atoms%lnonsph(iAtomType)
     417             : 
     418           0 :          WRITE (fileNum, '(a)') '         <electronConfig flipSpins="F">'
     419             : !         <coreConfig>[He] (2s1/2) (2p1/2) (2p3/2)</coreConfig>
     420             : 322      FORMAT('            <coreConfig>', a, '</coreConfig>')
     421           0 :          WRITE (fileNum, 322) TRIM(ADJUSTL(atoms%econf(iAtomType)%coreconfig))
     422             : 323      FORMAT('            <valenceConfig>', a, '</valenceConfig>')
     423           0 :          IF (len_TRIM(atoms%econf(iAtomType)%valenceconfig) > 1) THEN
     424           0 :             WRITE (fileNum, 323) TRIM(ADJUSTL(atoms%econf(iAtomType)%valenceconfig))
     425             :          END IF
     426           0 :          DO i = 1, MERGE(atoms%econf(iAtomType)%num_states, atoms%econf(iAtomType)%num_core_states, (len_TRIM(atoms%econf(iAtomType)%valenceconfig) > 1))
     427           0 :             occ = atoms%econf(iAtomType)%occupation(i, :)
     428           0 :             IF (ABS(occ(1) - occ(2)) > 1E-5 .OR. ABS(occ(1) - ABS(atoms%econf(iAtomType)%kappa(i))) > 1E-5) THEN
     429             :                !State not fully occupied
     430             : 325            FORMAT('            <stateOccupation state="', a, '" spinUp="', f0.8, '" spinDown="', f0.8, '"/>')
     431           0 :                str = atoms%econf(iAtomType)%get_state_string(i)
     432           0 :                WRITE (fileNum, 325) str, occ(1), occ(2)
     433             :             END IF
     434             :          END DO
     435           0 :          WRITE (fileNum, '(a)') '         </electronConfig>'
     436             : 
     437             :          !IF (ALL(enpara%qn_el(0:3,iAtomType,1).ne.0)) THEN
     438             : !!         <energyParameters s="3" p="3" d="3" f="4"/>
     439             : 321      FORMAT('         <energyParameters s="', i0, '" p="', i0, '" d="', i0, '" f="', i0, '"/>')
     440           0 :          WRITE (fileNum, 321) enpara%qn_el(0:3, iAtomType, 1)
     441             :          !END IF
     442           0 :          IF (l_explicit .OR. hybinp%l_hybrid) THEN
     443             : 315         FORMAT('         <prodBasis lcutm="', i0, '" lcutwf="', i0, '" select="', a, '"/>')
     444           0 :             line = ''
     445           0 :             WRITE (line, '(i0,1x,i0,1x,i0,1x,i0)') hybinp%select1(1:4, iAtomType)
     446           0 :             WRITE (fileNum, 315) hybinp%lcutm1(iAtomType), hybinp%lcutwf(iAtomType), TRIM(ADJUSTL(line))
     447             :          END IF
     448             : 
     449           0 :          IF (l_explicit) THEN
     450             : 328         FORMAT('         <modInitDen flipSpinPhi="', f0.8, '" flipSpinTheta="', f0.8, '" flipSpinScale="', l1, '"/>')
     451           0 :             WRITE (fileNum, 328) atoms%flipSpinPhi(iAtomType), atoms%flipSpinTheta(iAtomType), atoms%flipSpinScale(iAtomType)
     452             :          END IF
     453             : 
     454           0 :          IF (uIndices(1, iAtomType) .NE. -1) THEN
     455             : !         <ldaU l="2" U="5.5" J="0.9" l_amf="F"/>
     456           0 :             DO i_u = uIndices(1, iAtomType), uIndices(2, iAtomType)
     457             : 326            FORMAT('         <ldaU l="', i0, '" U="', f0.5, '" J="', f0.5, '" l_amf="', l1, '"/>')
     458           0 :                WRITE (fileNum, 326) atoms%lda_u(i_u)%l, atoms%lda_u(i_u)%u, atoms%lda_u(i_u)%j, atoms%lda_u(i_u)%l_amf
     459             :             END DO
     460             :          END IF
     461             : 
     462           0 :          IF(l_gfOpt) THEN
     463           0 :             WRITE (fileNum,316) .TRUE., "default",0,"calc"
     464           0 :             WRITE (fileNum,318) .FALSE.,.FALSE.,.FALSE.,.FALSE.
     465           0 :             WRITE (fileNum, '(a)') '         </greensfCalculation>'
     466             : 316         FORMAT('         <greensfCalculation l_sphavg="', l1, '" label="', a, '" nshells="', i0, '" kkintgrCutoff="', a, '">')
     467             : 318         FORMAT('            <diagElements s="', l1, '" p="', l1, '" d="', l1, '" f="', l1, '"/>')
     468             :          ENDIF
     469             : 
     470           0 :          DO ilo = 1, atoms%nlo(iAtomType)
     471             : !         <lo type="HELO" l="0" n="4"/>
     472           0 :             l = atoms%llo(ilo, iAtomType)
     473           0 :             n = enpara%qn_ello(ilo, iAtomType, 1)
     474           0 :             loType = 'SCLO'
     475           0 :             IF (n .LT. 0) THEN
     476           0 :                loType = 'HELO'
     477             :             END IF
     478           0 :             n = ABS(n)
     479             : 324         FORMAT('         <lo type="', a, '" l="', i0, '" n="', i0, '" eDeriv="', i0, '"/>')
     480           0 :             WRITE (fileNum, 324) TRIM(ADJUSTL(loType)), l, n, atoms%ulo_der(ilo, iAtomType)
     481             :          END DO
     482             : 
     483           0 :          WRITE (fileNum, '(a)') '      </species>'
     484             :       END DO
     485           0 :       WRITE (fileNum, '(a)') '   </atomSpecies>'
     486             : 
     487           0 :       if (.not. l_include(3)) then
     488           0 :          close (99)
     489           0 :          fileNum = 98
     490             :       endif
     491             : 
     492           0 :       if (.not. l_include(4)) then
     493           0 :          open (99, file=TRIM(add_filename)//'atoms.xml')
     494           0 :          WRITE (fileNum, '(a)') '      <!-- atoms group included here -->'
     495           0 :          WRITE (fileNum, '(a)') '      <xi:include xmlns:xi="http://www.w3.org/2001/XInclude" href="'//TRIM(add_filename)//'atoms.xml"> </xi:include>'
     496           0 :          fileNum = 98
     497             :       endif
     498             : 
     499           0 :       WRITE (fileNum, '(a)') '   <atomGroups>'
     500           0 :       na = 0
     501           0 :       DO iAtomType = 1, atoms%ntype
     502             : !      <atomGroup species="Si-1">
     503             : 330      FORMAT('      <atomGroup species="', a, '">')
     504           0 :          speciesName = TRIM(ADJUSTL(atoms%speciesName(iAtomType)))
     505           0 :          WRITE (fileNum, 330) TRIM(ADJUSTL(speciesName))
     506             : 
     507           0 :          DO ieq = 1, atoms%neq(iAtomType)
     508           0 :             na = na + 1
     509           0 :             tempTaual(1, na) = atoms%taual(1, na)
     510           0 :             tempTaual(2, na) = atoms%taual(2, na)
     511           0 :             tempTaual(3, na) = atoms%taual(3, na)
     512           0 :             scpos = 1.0
     513           0 :             DO i = 2, 40
     514           0 :                rest = ABS(i*tempTaual(1, na) - NINT(i*tempTaual(1, na)))
     515           0 :                IF ((scpos(1) .EQ. 1.0) .AND. (rest .LT. (i*0.000001))) scpos(1) = real(i)
     516           0 :                rest = ABS(i*tempTaual(2, na) - NINT(i*tempTaual(2, na)))
     517           0 :                IF ((scpos(2) .EQ. 1.0) .AND. (rest .LT. (i*0.000001))) scpos(2) = real(i)
     518           0 :                IF (.not. input%film) THEN
     519           0 :                   rest = ABS(i*tempTaual(3, na) - NINT(i*tempTaual(3, na)))
     520           0 :                   IF ((scpos(3) .EQ. 1.0) .AND. (rest .LT. (i*0.000001))) scpos(3) = real(i)
     521             :                END IF
     522             :             END DO
     523           0 :             DO i = 1, 2
     524           0 :                tempTaual(i, na) = tempTaual(i, na)*scpos(i)
     525             :             END DO
     526           0 :             IF (.not. input%film) tempTaual(3, na) = tempTaual(3, na)*scpos(3)
     527           0 :             IF (input%film) THEN
     528           0 :                tempTaual(3, na) = cell%amat(3, 3)*tempTaual(3, na)
     529             :             END IF
     530           0 :             IF (input%film) THEN
     531             : !         <filmPos> x/myConstant  y/myConstant  1/myConstant</filmPos>
     532             : 340            FORMAT('         <filmPos label="', a20, '">', a, ' ', a, ' ', a, '</filmPos>')
     533           0 :                posString(:) = ''
     534           0 :                DO i = 1, 2
     535           0 :                   IF ((scpos(i) .NE. 1.0) .AND. (tempTaual(i, na) .NE. 0.0)) THEN
     536           0 :                      WRITE (posString(i), '(f0.3,a1,f0.3)') tempTaual(i, na), '/', scpos(i)
     537             :                   ELSE
     538           0 :                      WRITE (posString(i), '(f0.10)') tempTaual(i, na)
     539             :                   END IF
     540             :                END DO
     541           0 :                WRITE (posString(3), '(f0.10)') tempTaual(3, na)
     542           0 :                WRITE (fileNum, 340) TRIM(ADJUSTL(atoms%label(na))), &
     543           0 :                   TRIM(ADJUSTL(posString(1))), TRIM(ADJUSTL(posString(2))), TRIM(ADJUSTL(posString(3)))
     544             :             ELSE
     545             : !         <relPos> x/myConstant  y/myConstant  z/myConstant</relPos>
     546             : 350            FORMAT('         <relPos label="', a20, '">', a, ' ', a, ' ', a, '</relPos>')
     547           0 :                posString(:) = ''
     548           0 :                DO i = 1, 3
     549           0 :                   IF ((scpos(i) .NE. 1.0) .AND. (tempTaual(i, na) .NE. 0.0)) THEN
     550           0 :                      WRITE (posString(i), '(f0.3,a1,f0.3)') tempTaual(i, na), '/', scpos(i)
     551             :                   ELSE
     552           0 :                      WRITE (posString(i), '(f0.10)') tempTaual(i, na)
     553             :                   END IF
     554             :                END DO
     555           0 :                WRITE (fileNum, 350) TRIM(ADJUSTL(atoms%label(na))), &
     556           0 :                   TRIM(ADJUSTL(posString(1))), TRIM(ADJUSTL(posString(2))), TRIM(ADJUSTL(posString(3)))
     557             :             END IF
     558             :          END DO
     559             : !         <force calculate="F" relaxX="T" relaxY="T" relaxZ="T"/>
     560             : 360      FORMAT('         <force calculate="', l1, '" relaxXYZ="', 3l1, '"/>')
     561           0 :          WRITE (fileNum, 360) atoms%l_geo(iAtomType), atoms%relax(1, iAtomType), atoms%relax(2, iAtomType), atoms%relax(3, iAtomType)
     562             : 
     563           0 :          IF (l_nocoOpt .OR. l_explicit) THEN
     564             : 362         FORMAT('         <nocoParams  alpha="', f0.8, '" beta="', &
     565             :                    f0.8,  '"/>')
     566           0 :             WRITE (fileNum, 362)  noco%alph_inp(iAtomType), &
     567           0 :                noco%beta_inp(iAtomType)
     568             :          END IF
     569             : 
     570           0 :          WRITE (fileNum, '(a)') '      </atomGroup>'
     571             :       END DO
     572           0 :       WRITE (fileNum, '(a)') '   </atomGroups>'
     573           0 :       if (.not. l_include(4)) then
     574           0 :          close (99)
     575           0 :          fileNum = 98
     576             :       endif
     577             : 
     578             : 368   FORMAT('   <output dos="', l1, '" band="', l1,  '" slice="', l1, '">')
     579           0 :       WRITE (fileNum, 368) banddos%dos, band, sliceplot%slice
     580             : 
     581             : !      <checks vchk="F" cdinf="F" disp="F"/>
     582             : 370   FORMAT('      <checks vchk="', l1, '" cdinf="', l1, '"/>')
     583           0 :       WRITE (fileNum, 370) input%vchk, input%cdinf
     584             : 
     585             : !      <densityOfStates ndir="0" minEnergy="-0.50000" maxEnergy="0.50000" sigma="0.01500"/>
     586           0 :       WRITE(tempStringA,'(f0.8,a)') banddos%e2_dos, '*Htr'
     587           0 :       WRITE(tempStringB,'(f0.8,a)') banddos%e1_dos, '*Htr'
     588             : 380   FORMAT('      <bandDOS minEnergy="', a, '" maxEnergy="', a, '" sigma="', f0.8, '" storeEVData="', l1, '"/>')
     589           0 :       WRITE (fileNum, 380)  TRIM(ADJUSTL(tempStringA)), TRIM(ADJUSTL(tempStringB)), banddos%sig_dos, banddos%l_storeEVData
     590             : 
     591             : !      <vacuumDOS layers="0" integ="F" star="F" nstars="0" locx1="0.00" locy1="0.00" locx2="0.00" locy2="0.00" nstm="0" tworkf="0.000000"/>
     592             : 390   FORMAT('      <vacuumDOS vacdos="', l1, '" integ="', l1, '" star="', l1, '" nstars="', i0, '" locx1="', f0.5, '" locy1="', f0.5, '" locx2="', f0.5, '" locy2="', f0.5, '" nstm="', i0, '" tworkf="', f0.5, '"/>')
     593           0 :       WRITE (fileNum, 390) banddos%vacdos, input%integ, banddos%starcoeff, banddos%nstars, banddos%locx(1), banddos%locy(1), banddos%locx(2), banddos%locy(2), 0, 0.0
     594             : 
     595             : !      <unfoldingBand unfoldBand="F" supercellX="1" supercellY="1" supercellZ="1"/>
     596             : 395   FORMAT('      <unfoldingBand unfoldBand="', l1, '" supercellX="', i0, '" supercellY="', i0, '" supercellZ="', i0, '"/>')
     597           0 :       WRITE (fileNum, 395) banddos%unfoldband, banddos%s_cell_x, banddos%s_cell_y, banddos%s_cell_z
     598             : 
     599             : !!      <juPhon l_potout="F" l_eigout="F"/>
     600             : !396   FORMAT('      <juPhon l_potout="', l1, '" l_eigout="', l1, '"/>')
     601             : !      WRITE (fileNum, 396) juPhon%l_potout, juPhon%l_eigout
     602             : 
     603             : !      <plotting iplot="0" />
     604           0 :       IF(SIZE(sliceplot%plot)>0) THEN
     605             : 400      FORMAT('      <plotting iplot="', i0, '" polar="', l1, '">')
     606           0 :          WRITE (fileNum, 400) sliceplot%iplot, sliceplot%polar
     607             : 401      FORMAT('         <plot TwoD="', l1, '" vec1="', 3f5.1,  '" vec2="', 3f5.1, '" vec3="', 3f5.1, '" zero="', 3f5.1, '" file="', a, '"/>')
     608           0 :          WRITE (fileNum, 401) sliceplot%plot(1)%twodim, sliceplot%plot(1)%vec1(:), sliceplot%plot(1)%vec2(:), sliceplot%plot(1)%vec3(:),&
     609           0 :                               sliceplot%plot(1)%zero(:), TRIM(ADJUSTL(sliceplot%plot(1)%filename))
     610           0 :          WRITE (fileNum, '(a)') '      </plotting>'
     611             :       ELSE
     612             : 402      FORMAT('      <plotting iplot="', i0, '" polar="', l1, '"/>')
     613           0 :          WRITE (fileNum, 402) sliceplot%iplot, sliceplot%polar
     614             :       ENDIF
     615             : 
     616             : !      <chargeDensitySlicing numkpt="0" minEigenval="0.000000" maxEigenval="0.000000" nnne="0" pallst="F"/>
     617             : 410   FORMAT('      <chargeDensitySlicing numkpt="', i0, '" minEigenval="', f0.8, '" maxEigenval="', f0.8, '" nnne="', i0, '" pallst="', l1, '"/>')
     618           0 :       WRITE (fileNum, 410) sliceplot%kk, sliceplot%e1s, sliceplot%e2s, sliceplot%nnne, input%pallst
     619             : 
     620             : !      <specialOutput form66="F" eonly="F" bmt="F"/>
     621             : 420   FORMAT('      <specialOutput eonly="', l1, '"/>')
     622           0 :       WRITE (fileNum, 420) input%eonly
     623             : 
     624             : !      <magneticCircularDichroism energyLo="-10.0" energyUp="0.0"/>
     625             : 430   FORMAT('      <magneticCircularDichroism mcd="',l1,'" energyLo="', f0.8, '" energyUp="', f0.8, '"/>')
     626           0 :       WRITE (fileNum, 430) banddos%l_mcd,banddos%e_mcd_lo, banddos%e_mcd_up
     627             : 
     628           0 :       WRITE (fileNum, '(a)') '   </output>'
     629           0 :       IF (present(filename)) THEN
     630           0 :          WRITE (fileNum, '(a)') '  <!-- We include the file relax.xml here to enable relaxations (see documentation) -->'
     631           0 :          WRITE (fileNum, '(a)') '  <xi:include xmlns:xi="http://www.w3.org/2001/XInclude" href="'//TRIM(add_filename)//'relax.xml"> <xi:fallback/> </xi:include>'
     632           0 :          WRITE (fileNum, '(a)') '</fleurInput>'
     633           0 :          CLOSE (fileNum)
     634             :       ELSE
     635           0 :          CALL closeXMLElement('inputData')
     636             :       END IF
     637             : 
     638           0 :    END SUBROUTINE w_inpXML
     639           0 : END MODULE m_winpXML

Generated by: LCOV version 1.14