LCOV - code coverage report
Current view: top level - eigen_soc - anglso.f90 (source / functions) Hit Total Coverage
Test: FLEUR test coverage Lines: 30 48 62.5 %
Date: 2024-04-16 04:21:52 Functions: 1 1 100.0 %

          Line data    Source code
       1             : MODULE m_anglso
       2             : contains
       3      576000 :   COMPLEX FUNCTION anglso(theta,phi,l1,m1,is1,l2,m2,is2,compo)
       4             :     USE m_juDFT
       5             :     USE m_constants
       6             :     !
       7             :     ! calculates spin-orbit matrix for theta,phi =/= 0
       8             :     !
       9             :     IMPLICIT NONE
      10             :     !     ..
      11             :     !     .. Scalar Arguments ..
      12             :     INTEGER, INTENT(IN) :: is1,is2,l1,l2,m1,m2
      13             :     INTEGER, INTENT(IN),OPTIONAL :: compo
      14             :     REAL,    INTENT(IN) :: theta,phi             
      15             :     !     ..
      16             :     !     .. Local Scalars ..
      17             :     REAL sgm1,sgm2,xlz,xlpl,xlmn,angl_r,angl_i
      18             :     LOGICAL :: l_standard_euler_angles
      19             : 
      20      576000 :     anglso = CMPLX(0.0,0.0)
      21      576000 :     IF (l1.NE.l2) THEN
      22             :        RETURN
      23             :     ENDIF
      24             :     !
      25             : 
      26       70800 :     l_standard_euler_angles=.FALSE.     
      27             : 
      28       70800 :     sgm1 = is1
      29       70800 :     sgm2 = is2
      30       70800 :     IF (l1.LT.0) THEN
      31           0 :        WRITE (oUnit,FMT=*) ' PROGRAM STOPS IN ANGLSO ( L < 0 ) .'
      32           0 :        WRITE (oUnit,FMT=*) ' L1 =',l1,'    L2 =',l2
      33           0 :        CALL juDFT_error("ANGLSO (L <0 )",calledby="anglso")
      34       70800 :     ELSE IF ((ABS(m1).GT.l1) .OR. (ABS(m2).GT.l2)) THEN
      35           0 :        WRITE (oUnit,FMT=*) ' PROGRAM STOPS IN ANGLSO ( M < L OR L < M )'
      36           0 :        WRITE (oUnit,FMT=*) ' L1 =',l1,'    L2 =',l2
      37           0 :        WRITE (oUnit,FMT=*) ' M1 =',m1,'    M2 =',m2
      38           0 :        CALL juDFT_error("ANGLSO ( M < L OR L < M )",calledby="anglso")
      39       70800 :     ELSE IF ((is1.NE.-1.AND.is1.NE.1) .OR. (is2.NE.-1.AND.is2.NE.1)) THEN
      40           0 :        WRITE (oUnit,FMT=*) ' PROGRAM STOPS IN ANGLSO ( S >< +-1/2 ) .'
      41           0 :        WRITE (oUnit,FMT=*) ' S1 =',0.5*sgm1,'    S2 =',0.5*sgm2
      42           0 :        CALL juDFT_error("ANGLSO ( S >< +-1/2 )",calledby ="anglso")
      43             :     END IF
      44             :     !
      45             :     ! lz,l+,l-
      46             :     !
      47       70800 :     xlz = 0.0
      48       70800 :     xlpl= 0.0
      49       70800 :     xlmn= 0.0
      50             :     ! is1.eq.is2-2 -> <-| |+> => l+   
      51       70800 :     IF (m1.EQ.m2+1) THEN
      52        4400 :        xlpl = SQRT(REAL((l2-m2)* (l2+m2+1)))
      53             :        ! is1.eq.is2+2 -> <+| |-> => l-   
      54       66400 :     ELSE IF (m1.EQ.m2-1) THEN
      55        4400 :        xlmn = SQRT(REAL((l2+m2)* (l2-m2+1)))
      56             :        ! is1.eq.is2 -> <+| |+> => lz   
      57       62000 :     ELSE IF (m1.EQ.m2  ) THEN
      58        4800 :        xlz  = m2
      59             :     END IF
      60             :     
      61       70800 :     IF(PRESENT(compo))THEN
      62             : !      Used for the wannier-interpolation of SOC:
      63             : !      wann_socmat_vec allow us to
      64             : !      add SOC during the wannier-interpolation.
      65             : !      Therefore, theta and phi are specified during the
      66             : !      Wannier-interpolation step and not here.
      67             : !      Therefore, write out only xlz, xlpl, and xlmn and RETURN
      68             : !      afterwards, without using theta and phi.
      69             : !      xlz, xlpl and xlmn are needed in subroutine wann_socmat_vec.F
      70           0 :        if(compo.eq.1)then
      71           0 :           anglso = CMPLX(xlz,0.0) 
      72           0 :        elseif(compo.eq.2)then
      73           0 :           anglso = CMPLX(xlmn,0.0)
      74           0 :        elseif(compo.eq.3)then
      75           0 :           anglso = CMPLX(xlpl,0.0)
      76             :        else
      77           0 :          CALL juDFT_error("maucompo",calledby ="anglso")
      78             :        endif   
      79           0 :        RETURN
      80             :     END IF   
      81             :     
      82             :     
      83             :     !
      84             :     ! rotated spin-orbit angular matrix
      85             :     ! <1| |1> or <2| |2>          
      86             :     !
      87             : 
      88             :     !     If l_standard_euler_angles is set to .false., the old version
      89             :     !     of this subroutine is used, which works fine if only MAE is
      90             :     !     needed. In the old version, theta and phi specify the direction
      91             :     !     of spin quantization. However, there remains the degree of freedom
      92             :     !     of rotation around the spin quantization direction. The new version
      93             :     !     of this subroutine, which is switched on by setting l_standard_euler_angles
      94             :     !     to true, rotates x, y and z axes first by phi around z counterclockwisely
      95             :     !     and then the resulting axes x', y' and z' by theta around y' 
      96             :     !     counterclockwisely to obtain the final coordinate frame x'', y'' and z''.
      97             :     !     This new version is useful when one is interested also in the spin
      98             :     !     perpendicular to the spin quantization axis. The old version seems to be
      99             :     !     different from the new one as follows when theta and phi differ from zero:
     100             :     !     x''_old = -x''_new
     101             :     !     y''_old = -y''_new
     102             :     !     z''_old = z''
     103             :     !     If theta and phi are zero, there is no difference, leading thus to a
     104             :     !     discontinuous Euler transformation in the old version and a continuous
     105             :     !     transformation in the new version.
     106             :     !     Both versions do not differ for MAE, but if the standard Pauli matrix
     107             :     !     is used to obtain x or y components of spin, the spin is discontinuous
     108             :     !     in the old version as a function of theta and phi.
     109             : 
     110             :     IF(l_standard_euler_angles)THEN     
     111             : 
     112             :        IF (is1.EQ.is2) THEN
     113             :           angl_r = isign(1,is1) * ( COS(theta)*xlz +&
     114             :                &                          0.5*SIN(theta)*COS(phi)*(xlmn + xlpl) )
     115             :           angl_i = isign(1,is1)*0.5*SIN(theta)*SIN(phi)*(xlmn - xlpl)
     116             :           ! <1| |2>
     117             :        ELSEIF (is1.EQ.is2+2) THEN
     118             :           angl_r =  - SIN(theta)*xlz +  COS(phi)*(&
     119             :                &             COS(theta/2.)**2 * xlmn - SIN(theta/2.)**2 * xlpl )
     120             :           angl_i = SIN(phi)*( &
     121             :                &              COS(theta/2.)**2 * xlmn + SIN(theta/2.)**2 * xlpl )
     122             :           ! <2| |1>
     123             :        ELSEIF (is1.EQ.is2-2) THEN
     124             :           angl_r = - SIN(theta)*xlz +  COS(phi)*(&
     125             :                &            + COS(theta/2.)**2 * xlpl - SIN(theta/2.)**2 * xlmn )
     126             :           angl_i =  SIN(phi)*( &
     127             :                &             - COS(theta/2.)**2 * xlpl - SIN(theta/2.)**2 * xlmn )
     128             :        ELSE
     129             :           angl_r = 0.0
     130             :           angl_i = 0.0
     131             :        ENDIF
     132             : 
     133             :     ELSE        
     134       70800 :        IF (is1.EQ.is2) THEN
     135             :           angl_r = isign(1,is1) * ( COS(theta)*xlz +&
     136       35400 :                &                          0.5*SIN(theta)*COS(phi)*(xlmn + xlpl) )
     137       35400 :           angl_i = isign(1,is1)*0.5*SIN(theta)*SIN(phi)*(xlmn - xlpl)
     138             :           ! <1| |2>
     139       35400 :        ELSEIF (is1.EQ.is2+2) THEN
     140             :           angl_r =  SIN(theta)*xlz +  COS(phi)*(&
     141       17700 :                &            - COS(theta/2.)**2 * xlmn + SIN(theta/2.)**2 * xlpl )
     142             :           angl_i = -SIN(phi)*( &
     143       17700 :                &              COS(theta/2.)**2 * xlmn + SIN(theta/2.)**2 * xlpl )
     144             :           ! <2| |1>
     145       17700 :        ELSEIF (is1.EQ.is2-2) THEN
     146             :           angl_r =  SIN(theta)*xlz +  COS(phi)*(&
     147       17700 :                &            - COS(theta/2.)**2 * xlpl + SIN(theta/2.)**2 * xlmn )
     148             :           angl_i =  SIN(phi)*( &
     149       17700 :                &              COS(theta/2.)**2 * xlpl + SIN(theta/2.)**2 * xlmn )
     150             :        ELSE
     151             :           angl_r = 0.0
     152             :           angl_i = 0.0
     153             :        ENDIF
     154             :     ENDIF
     155             :     !
     156       70800 :     anglso = CMPLX(angl_r,angl_i)
     157             : 
     158       70800 :     RETURN
     159             :   END FUNCTION anglso
     160             : END MODULE m_anglso

Generated by: LCOV version 1.14