LCOV - code coverage report
Current view: top level - ldaX - types_selfen.F90 (source / functions) Hit Total Coverage
Test: FLEUR test coverage Lines: 0 50 0.0 %
Date: 2024-05-15 04:28:08 Functions: 0 5 0.0 %

          Line data    Source code
       1             : MODULE m_types_selfen
       2             : 
       3             :    !------------------------------------------------------------------------
       4             :    !This type contains the array for the selfenergy from the impurity solver
       5             :    !We separate the individual elements because the number of energy points
       6             :    !can differ massively and would lead to wasted storage
       7             :    !------------------------------------------------------------------------
       8             : 
       9             :    USE m_constants
      10             : 
      11             :    IMPLICIT NONE
      12             : 
      13             :    PRIVATE
      14             : 
      15             :    TYPE t_selfen
      16             : 
      17             :       INTEGER :: l = -1
      18             :       REAL,ALLOCATABLE    :: muMatch(:)
      19             : 
      20             :       COMPLEX, ALLOCATABLE :: data(:,:,:,:)
      21             : 
      22             :       CONTAINS
      23             :          PROCEDURE, PASS :: init    => init_selfen
      24             :          PROCEDURE       :: collect => collect_selfen
      25             :          PROCEDURE       :: postProcess => postProcess_selfen
      26             : 
      27             :    END TYPE t_selfen
      28             : 
      29             :    PUBLIC t_selfen
      30             : 
      31             :    CONTAINS
      32             : 
      33           0 :       SUBROUTINE init_selfen(this,l,nz,jspins,l_fullMatch)
      34             : 
      35             :          CLASS(t_selfen), INTENT(INOUT) :: this
      36             :          INTEGER,         INTENT(IN)    :: l
      37             :          INTEGER,         INTENT(IN)    :: nz
      38             :          INTEGER,         INTENT(IN)    :: jspins
      39             :          LOGICAL,         INTENT(IN)    :: l_fullMatch
      40             : 
      41           0 :          this%l = l
      42           0 :          ALLOCATE(this%muMatch(MERGE(1,jspins,l_fullMatch)),source=0.0)
      43           0 :          ALLOCATE(this%data(2*(2*l+1),2*(2*l+1),nz,2),source = cmplx_0)
      44             : 
      45           0 :       END SUBROUTINE init_selfen
      46             : 
      47           0 :       SUBROUTINE collect_selfen(this,mpi_communicator)
      48             : 
      49             : #ifdef CPP_MPI
      50             :          USE mpi
      51             : #endif
      52             : 
      53             :          CLASS(t_selfen),     INTENT(INOUT) :: this
      54             :          INTEGER,             INTENT(IN)    :: mpi_communicator
      55             : #ifdef CPP_MPI
      56             : 
      57             :          INTEGER:: ierr,irank,n
      58           0 :          COMPLEX,ALLOCATABLE::ctmp(:)
      59             :          REAL, ALLOCATABLE :: rtmp(:)
      60             : 
      61           0 :          CALL MPI_COMM_RANK(mpi_communicator,irank,ierr)
      62             : 
      63           0 :          n = SIZE(this%muMatch)
      64           0 :          ALLOCATE(rtmp(n))
      65           0 :          CALL MPI_REDUCE(this%muMatch,rtmp,n,MPI_DOUBLE_PRECISION,MPI_SUM,0,mpi_communicator,ierr)
      66           0 :          IF(irank.EQ.0) this%muMatch = reshape(rtmp,[n])
      67           0 :          DEALLOCATE(rtmp)
      68             : 
      69           0 :          n = SIZE(this%data)
      70           0 :          ALLOCATE(ctmp(n))
      71           0 :          CALL MPI_REDUCE(this%data,ctmp,n,MPI_DOUBLE_COMPLEX,MPI_SUM,0,mpi_communicator,ierr)
      72           0 :          IF(irank.EQ.0) CALL zcopy(n,ctmp,1,this%data,1)
      73           0 :          DEALLOCATE(ctmp)
      74             : #endif
      75             : 
      76           0 :       END SUBROUTINE collect_selfen
      77             : 
      78           0 :       SUBROUTINE postProcess_selfen(this,noco,nococonv,atomType,l,jspins,vmmp)
      79             : 
      80             :          USE m_types_noco
      81             :          USE m_types_nococonv
      82             :          USE m_rotMMPmat
      83             : 
      84             :          CLASS(t_selfen), INTENT(INOUT) :: this
      85             :          TYPE(t_noco),    INTENT(IN)    :: noco
      86             :          TYPE(t_nococonv),INTENT(IN)    :: nococonv
      87             :          INTEGER,         INTENT(IN)    :: atomType,l
      88             :          INTEGER,         INTENT(IN)    :: jspins
      89             :          COMPLEX,         INTENT(IN)    :: vmmp(-lmaxU_const:,-lmaxU_const:,:)
      90             : 
      91             :          INTEGER :: i,j,iz,ipm,m,mp,ispin,ns
      92             :          COMPLEX,ALLOCATABLE :: swapMat(:,:)
      93           0 :          COMPLEX,ALLOCATABLE :: vmmp_local(:,:,:)
      94             : 
      95           0 :          ns = 2*this%l+1
      96             : 
      97           0 :          ALLOCATE(swapMat(2*ns,2*ns),source=cmplx_0)
      98           0 :          ALLOCATE(vmmp_local(-lmaxU_const:lmaxU_const,-lmaxU_const:lmaxU_const,SIZE(vmmp,3)),source=cmplx_0)
      99             : 
     100             :          !Transformation matrix is a Block matrix of form
     101             :          ! | 0  I |
     102             :          ! | I  0 |
     103             :          !to swap the order of the spins
     104           0 :          swapMat = 0.0
     105           0 :          DO i = 1, ns
     106           0 :             swapMat(i,ns+i) = 1.0
     107           0 :             swapMat(ns+i,i) = 1.0
     108             :          ENDDO
     109             : 
     110             :          !The DFT+U correction is in the global frame of real space
     111             :          !For the calculation of the impurity greens function we shift into the local frame
     112           0 :          IF(noco%l_noco) THEN
     113           0 :             vmmp_local = rotMMPmat(vmmp,0.0,-nococonv%beta(atomType),-nococonv%alph(atomType),l)
     114           0 :          ELSE IF(noco%l_soc) THEN
     115           0 :             vmmp_local = rotMMPmat(vmmp,0.0,-nococonv%theta,-nococonv%phi,l)
     116             :          ELSE
     117           0 :             vmmp_local = vmmp
     118             :          ENDIF
     119             : 
     120           0 :          DO ipm = 1, 2
     121           0 :             DO iz = 1, SIZE(this%data,3)
     122             :                !---------------------------------------------
     123             :                ! Convert the selfenergy to hartree
     124             :                !---------------------------------------------
     125           0 :                this%data(:,:,iz,ipm) = this%data(:,:,iz,ipm)/hartree_to_ev_const
     126             :                !---------------------------------------------
     127             :                ! The order of spins is reversed in the Solver (transformation matrix is symmetric)
     128             :                !---------------------------------------------
     129           0 :                this%data(:,:,iz,ipm) = matmul(this%data(:,:,iz,ipm),swapMat)
     130           0 :                this%data(:,:,iz,ipm) = matmul(swapMat,this%data(:,:,iz,ipm))
     131             :                !---------------------------------------------------------------------
     132             :                ! The DFT green's function also includes the previous DFT+U correction
     133             :                ! This is removed by substracting it from the selfenergy
     134             :                !---------------------------------------------------------------------
     135           0 :                DO i = 1, ns
     136           0 :                   m  = i-1-this%l
     137           0 :                   DO j = 1, ns
     138           0 :                      mp = j-1-this%l
     139           0 :                      DO ispin = 1, SIZE(vmmp_local,3)
     140           0 :                         IF(ispin < 3) THEN
     141             :                            this%data(i+(ispin-1)*ns,j+(ispin-1)*ns,iz,ipm) = this%data(i+(ispin-1)*ns,j+(ispin-1)*ns,iz,ipm) &
     142           0 :                                                                              - vmmp_local(m,mp,ispin)/(3.0-jspins)
     143           0 :                            IF(jspins.EQ.1) this%data(i+ns,j+ns,iz,ipm) = this%data(i+ns,j+ns,iz,ipm) - vmmp_local(-m,-mp,ispin)/(3.0-jspins)
     144             :                         ELSE
     145             :                            !----------------------------------------------------------------------------
     146             :                            ! The offdiagonal elements only have to be removed if they are actually added
     147             :                            ! to the hamiltonian (so noco%l_mperp and any(noco%l_unrestrictMT))
     148             :                            !----------------------------------------------------------------------------
     149           0 :                            this%data(i+ns,j,iz,ipm) = this%data(i+ns,j,iz,ipm) - vmmp_local(m,mp,ispin)
     150           0 :                            this%data(i,j+ns,iz,ipm) = this%data(i,j+ns,iz,ipm) - conjg(vmmp_local(mp,m,ispin))
     151             :                         ENDIF
     152             :                      ENDDO
     153             :                   ENDDO
     154             :                ENDDO
     155             :             ENDDO
     156             :          ENDDO
     157           0 :       END SUBROUTINE postProcess_selfen
     158             : 
     159           0 : END MODULE m_types_selfen

Generated by: LCOV version 1.14