LCOV - code coverage report
Current view: top level - mix - v_mix.f90 (source / functions) Hit Total Coverage
Test: FLEUR test coverage Lines: 0 22 0.0 %
Date: 2024-05-01 04:44:11 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_vmix
       8             :    !
       9             :    ! mix the old and new density matrix for the lda+U method
      10             :    !                                                 gb.2001
      11             :    ! --------------------------------------------------------
      12             :    ! Extension to multiple U per atom type by G.M. 2017
      13             :    USE m_juDFT
      14             :    USE m_types
      15             :    USE m_constants
      16             :    USE m_xmlOutput
      17             : 
      18             :    IMPLICIT NONE
      19             : 
      20             :    CONTAINS
      21             : 
      22           0 :    SUBROUTINE v_mix(input,atoms,noco,nIJ_llp_mmp_in,nIJ_llp_mmp_out)
      23             : 
      24             :       TYPE(t_input),INTENT(IN)    :: input
      25             :       TYPE(t_atoms),INTENT(IN)    :: atoms
      26             :       TYPE(t_noco), INTENT(IN)    :: noco
      27             :       COMPLEX,      INTENT(IN)    :: nIJ_llp_mmp_out(-lmaxU_const:,-lmaxU_const:,:,:)
      28             :       COMPLEX,      INTENT(INOUT) :: nIJ_llp_mmp_in (-lmaxU_const:,-lmaxU_const:,:,:)
      29             : 
      30             : 
      31             :       INTEGER :: jsp, i_pair, i_v, latom1, latom2, matom1, matom2, natom2
      32             : !      REAL    :: alpha,spinf,gam,del,uParam,jParam
      33           0 :       REAL    :: dist(SIZE(nIJ_llp_mmp_in,4))
      34             : 
      35             :       CHARACTER(LEN=20)   :: attributes(6)
      36             : !      COMPLEX,ALLOCATABLE :: nIJ_llp_mmp(:,:,:,:)
      37             : 
      38             :       !
      39             :       ! check for possible rotation of n_mmp
      40             :       !
      41             :       !zero=0.0
      42             :       !CALL nmat_rot(zero,-atoms%lda_u%theta,-atoms%lda_u%phi,3,atoms%n_u,input%jspins,atoms%lda_u%l,n_mmp_out)
      43             : 
      44             :       ! Write out n_mmp_out to out.xml file
      45           0 :       CALL openXMLElementNoAttributes('ldaVDensityMatrix')
      46             : !      DO jsp = 1, SIZE(n_mmp_out,4)
      47             : !         DO i_u = 1, atoms%n_u
      48             : !            l = atoms%lda_u(i_u)%l
      49             : !            itype = atoms%lda_u(i_u)%atomType
      50             : !            uParam = atoms%lda_u(i_u)%u
      51             : !            jParam = atoms%lda_u(i_u)%j
      52             : !            attributes = ''
      53             : !            WRITE(attributes(1),'(i0)') jsp
      54             : !            WRITE(attributes(2),'(i0)') itype
      55             : !            WRITE(attributes(3),'(i0)') i_u
      56             : !            WRITE(attributes(4),'(i0)') l
      57             : !            WRITE(attributes(5),'(f15.8)') uParam
      58             : !            WRITE(attributes(6),'(f15.8)') jParam
      59             : !            CALL writeXMLElementMatrixPoly('densityMatrixFor',&
      60             : !                                          (/'spin    ','atomType','uIndex  ','l       ','U       ','J       '/),&
      61             : !                                          attributes,n_mmp_out(-l:l,-l:l,i_u,jsp))
      62             : !         END DO
      63             : !      END DO
      64           0 :       CALL closeXMLElement('ldaVDensityMatrix')
      65             : 
      66             :       ! exit subroutine if density matrix does not exist
      67           0 :       IF(.NOT.ANY(ABS(nIJ_llp_mmp_in(:,:,:,:)).GT.1e-12)) RETURN
      68             : 
      69             :       !Calculate distance
      70           0 :       dist = 0.0
      71           0 :       DO jsp = 1, SIZE(nIJ_llp_mmp_in,4)
      72           0 :          i_pair=0 !counts number of pairs
      73           0 :          DO i_v = 1, atoms%n_v  !loop over pairs which are corrected by U+V 
      74           0 :             latom1 = atoms%lda_v(i_v)%thisAtomL
      75           0 :             Do natom2 = 1, atoms%lda_v(i_v)%numOtherAtoms
      76           0 :                i_pair = i_pair + 1
      77           0 :                latom2 = atoms%lda_v(i_v)%otherAtomL
      78           0 :                Do matom1 = -latom1, latom1
      79           0 :                   Do matom2 = -latom2, latom2
      80           0 :                      dist(jsp) = dist(jsp) + ABS(nIJ_llp_mmp_out(matom1,matom2,i_pair,jsp) - nIJ_llp_mmp_in(matom1,matom2,i_pair,jsp))
      81             :                   END DO
      82             :                END DO
      83             :             END DO
      84             :          END DO
      85             :       END DO
      86             : 
      87             :       !Write to outfile
      88           0 :       IF(input%jspins.EQ.1) THEN
      89           0 :          WRITE (oUnit,'(a,f12.6)') 'nIJ_llp_mmp distance =',dist(1)
      90             :       ELSE
      91           0 :          DO jsp = 1, SIZE(nIJ_llp_mmp_in,4)
      92             : !            if (jsp > 2 .and. .not.any(noco%l_spinoffd_ldau)) cycle
      93           0 :             WRITE (oUnit,'(a,i1,a,f12.6)') 'nIJ_llp_mmp distance spin ',jsp,' =',dist(jsp)
      94             :          ENDDO
      95             :       ENDIF
      96             : 
      97             :       IF (.FALSE.) THEN !(input%ldauLinMix) THEN
      98             : 
      99             :          ! mix here straight with given mixing factors
     100             : !         ALLOCATE (n_mmp(-lmaxU_const:lmaxU_const,-lmaxU_const:lmaxU_const,SIZE(n_mmp_in,dim=3),SIZE(n_mmp_in,dim=4)))
     101             : !         n_mmp = cmplx_0
     102             : 
     103             : !         alpha = input%ldauMixParam
     104             : !         spinf = input%ldauSpinf
     105             : 
     106             : !         IF (input%jspins.EQ.1) THEN
     107             : !            DO i_u = 1, atoms%n_u
     108             : !               DO m = -lmaxU_const,lmaxU_const
     109             : !                  DO mp = -lmaxU_const,lmaxU_const
     110             : 
     111             : !                     n_mmp(m,mp,i_u,1) =      alpha * n_mmp_out(m,mp,i_u,1) + &
     112             : !                                        (1.0-alpha) * n_mmp_in (m,mp,i_u,1)
     113             : 
     114             : !                  END DO
     115             : !               END DO
     116             : !            END DO
     117             : !         ELSE
     118             : !            gam = 0.5 * alpha * (1.0 + spinf)
     119             : !            del = 0.5 * alpha * (1.0 - spinf)
     120             : !            DO i_u = 1,atoms%n_u
     121             : !               DO m = -lmaxU_const,lmaxU_const
     122             : !                  DO mp = -lmaxU_const,lmaxU_const
     123             : 
     124             : !                     n_mmp(m,mp,i_u,1) =       gam * n_mmp_out(m,mp,i_u,1) + &
     125             : !                                         (1.0-gam) * n_mmp_in (m,mp,i_u,1) - &
     126             : !                                               del * n_mmp_out(m,mp,i_u,2) + &
     127             : !                                               del * n_mmp_in (m,mp,i_u,2)
     128             : 
     129             : !                     n_mmp(m,mp,i_u,2) =       gam * n_mmp_out(m,mp,i_u,2) + &
     130             : !                                         (1.0-gam) * n_mmp_in (m,mp,i_u,2) - &
     131             : !                                               del * n_mmp_out(m,mp,i_u,1) + &
     132             : !                                               del * n_mmp_in (m,mp,i_u,1)
     133             : !                     IF(noco%l_mperp) THEN
     134             : !                        n_mmp(m,mp,i_u,3) =       alpha * n_mmp_out(m,mp,i_u,3) + &
     135             : !                                            (1.0-alpha) * n_mmp_in (m,mp,i_u,3)
     136             : !                     ENDIF
     137             : 
     138             : !                  END DO
     139             : !               END DO
     140             : !            END DO
     141             : 
     142             : !         ENDIF
     143             : !         n_mmp_in = n_mmp
     144             : !         DEALLOCATE(n_mmp)
     145             :       ENDIF
     146             : 
     147           0 :       CALL openXMLElementNoAttributes('ldaVDensityMatrixConvergence')
     148             : !      DO jsp = 1, SIZE(dist)
     149             : !         if (jsp > 2 .and. .not.any(noco%l_spinoffd_ldau)) cycle
     150             : !         attributes = ''
     151             : !         WRITE(attributes(1),'(i0)') jsp
     152             : !         WRITE(attributes(2),'(f13.6)') dist(jsp)
     153             : !         CALL writeXMLElementForm('distance',['spin    ','distance'],attributes(:2),reshape([4,8,1,13],[2,2]))
     154             : !      ENDDO
     155           0 :       CALL closeXMLElement('ldaVDensityMatrixConvergence')
     156             : 
     157             :    END SUBROUTINE v_mix
     158             : END MODULE m_vmix

Generated by: LCOV version 1.14