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 : MODULE m_bfield
7 : USE m_juDFT
8 : CONTAINS
9 674 : SUBROUTINE bfield(input,stars,noco,atoms,field,vTot,nococonv)
10 : !This subroutine adds a Zeeman-field to the potential
11 : !field%b_field is the field applied everywhere
12 : !field%b_field_mt is the field specific to the MT-sphere of a single atom type
13 : USE m_types
14 : USE m_constants
15 : USE m_rotMMPmat
16 :
17 : IMPLICIT NONE
18 : TYPE(t_input),INTENT(IN)::input
19 : TYPE(t_noco),INTENT(IN) ::noco
20 : TYPE(t_stars),INTENT(IN) :: stars
21 : TYPE(t_atoms),INTENT(IN)::atoms
22 : TYPE(t_field),INTENT(IN)::field
23 : TYPE(t_potden),INTENT(INOUT)::vtot
24 : TYPE(t_nococonv):: nococonv
25 : INTEGER :: iType
26 : COMPLEX :: bOffdiag
27 : REAL :: bExternal(4)
28 :
29 :
30 674 : IF (.NOT.field%l_b_field) RETURN !no B-field specified
31 :
32 0 : IF (input%jspins.NE.2) CALL judft_error("B-fields can only be used in spin-polarized calculations")
33 : !IF (noco%l_noco) CALL judft_error("B-fields not implemented in noco case")
34 :
35 : !Interstitial
36 0 : vTot%pw_w(:,1)=vTot%pw_w(:,1)-(field%b_field/2.0)*stars%ustep(:)
37 0 : vTot%pw_w(:,2)=vTot%pw_w(:,2)+(field%b_field/2.0)*stars%ustep(:)
38 :
39 : !MT-spheres
40 0 : DO iType = 1, atoms%ntype
41 0 : bExternal = 0.0
42 0 : bOffdiag = 0.0
43 0 : bExternal(1) = -field%b_field / 2
44 0 : bExternal(2) = field%b_field / 2
45 :
46 0 : IF (noco%l_noco) THEN
47 0 : CALL nococonv%rotdenmat(nococonv%alph(iType), nococonv%beta(iType), bExternal(1), bExternal(2), bOffdiag, .FALSE.)
48 0 : bExternal(3) = REAL(bOffdiag)
49 0 : bExternal(4) = AIMAG(bOffdiag)
50 : END IF
51 :
52 0 : vTot%mt(:atoms%jri(iType),0,iType,1) = vTot%mt(:atoms%jri(iType),0,iType,1) + sfp_const * (bExternal(1) * 2.0 - field%b_field_mt(iType)) / 2.0
53 0 : vTot%mt(:atoms%jri(iType),0,iType,2) = vTot%mt(:atoms%jri(iType),0,iType,2) + sfp_const * (bExternal(2) * 2.0 + field%b_field_mt(iType)) / 2.0
54 :
55 0 : IF (noco%l_noco) THEN
56 0 : vTot%mt(:atoms%jri(iType),0,iType,3) = vTot%mt(:atoms%jri(iType),0,iType,3) + sfp_const * bExternal(3)
57 0 : vTot%mt(:atoms%jri(iType),0,iType,4) = vTot%mt(:atoms%jri(iType),0,iType,4) + sfp_const * bExternal(4)
58 : END IF
59 : ENDDO
60 :
61 : !Vacuum
62 0 : IF (input%film) THEN
63 0 : vTot%vac(:,1,:,1)=vTot%vac(:,1,:,1)-field%b_field/2.0
64 0 : vTot%vac(:,1,:,2)=vTot%vac(:,1,:,2)+field%b_field/2.0
65 : END IF
66 : END SUBROUTINE bfield
67 : END MODULE m_bfield
|