mod_bfield Module


Uses


Variables

Type Visibility Attributes Name Initial
type(type_bfield), public, save :: bfield

Derived Types

type, public ::  type_bfield

T y p e

u s e d

i n

t _ p a r a m s

t o

s t o r e

a l l

r e l e v a n t

i n f o r m a t i o n

f o r

b f i e l d s

a n d

c o n s t r a i n i n g

f i e l d s

Read more…

Components

Type Visibility Attributes Name Initial
logical, public :: lbfield = .False.
logical, public :: lbfield_constr = .False.
logical, public :: lbfield_all = .False.
logical, public :: lbfield_trans = .False.
logical, public :: lbfield_mt = .False.
logical, public :: ltorque = .False.
integer, public :: ibfield = 0
integer, public :: ibfield_constr = 0
integer, public :: itscf0 = 0
integer, public :: itscf1 = 10000
real(kind=dp), public, dimension (:,:), allocatable :: bfield
real(kind=dp), public, dimension (:), allocatable :: bfield_strength
real(kind=dp), public, dimension (:,:), allocatable :: bfield_constr
real(kind=dp), public, dimension (:), allocatable :: theta
real(kind=dp), public, dimension (:), allocatable :: phi
real(kind=dp), public, dimension (:,:,:,:), allocatable :: thetallmat
real(kind=dp), public, dimension(:,:), allocatable :: mag_torque

Functions

public function this_readline(ifile, ios)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: ifile
integer, intent(out) :: ios

Return Value character(len=200)


Subroutines

public subroutine init_bfield(bfield, natyp, lbfield, lbfield_constr, lbfield_all, lbfield_trans, lbfield_mt, ltorque, ibfield, ibfield_constr, itscf0, itscf1, npan_log, npan_eq, ncheb, ntotd, nfund, ncelld, lmax, iend, ntcell, ipan_intervall, ifunm, icleb, cleb, thetasnew)

Author
Sascha Brinker
License
Creative Commons License
Category
memory-management, profiling, KKRhost, bfield

A l l o c a t e

i n i t i a l

m a g n e t i c

f i e l d

p a r a m e t e r s

t o

b e

b r o a d c a s t e d

v i a

m p i

Read more…

Arguments

Type IntentOptional Attributes Name
type(type_bfield), intent(inout) :: bfield
integer, intent(in) :: natyp
logical, intent(in) :: lbfield
logical, intent(in) :: lbfield_constr
logical, intent(in) :: lbfield_all
logical, intent(in) :: lbfield_trans
logical, intent(in) :: lbfield_mt
logical, intent(in) :: ltorque
integer, intent(in) :: ibfield
integer, intent(in) :: ibfield_constr
integer, intent(in) :: itscf0
integer, intent(in) :: itscf1
integer, intent(in) :: npan_log
integer, intent(in) :: npan_eq
integer, intent(in) :: ncheb
integer, intent(in) :: ntotd
integer, intent(in) :: nfund
integer, intent(in) :: ncelld
integer, intent(in) :: lmax
integer, intent(in) :: iend
integer, intent(in), dimension (natyp) :: ntcell
integer, intent(in), dimension (0:ntotd, natyp) :: ipan_intervall
integer, intent(in), dimension (1:(2*lmax+1)**2,natyp) :: ifunm
integer, intent(in), dimension (ncleb, 4) :: icleb

Pointer array

real(kind=dp), intent(in), dimension (ncleb) :: cleb

GAUNT coefficients (GAUNT)

real(kind=dp), intent(in), dimension (ntotd*(ncheb+1), nfund, ncelld) :: thetasnew

interpolated shape function in Chebychev radial mesh

public subroutine save_bconstr(natyp, bconstr_in, bconstr_out)

Author
MdSD
License
Creative Commons License
Category
KKRhost, bfield

W r i t e s

t h e

a t o m - w i s e

c o n s t r a i n i n g

f i e l d

t o

b c o n s t r _ o u t . d a t

Read more…

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: natyp
real(kind=dp), intent(in), dimension(4,natyp) :: bconstr_in

bx, by, bz, mspin

real(kind=dp), intent(inout), dimension(natyp,3) :: bconstr_out

bx, by, bz

public subroutine read_bconstr(natyp, bconstr_out)

Author
MdSD
License
Creative Commons License
Category
KKRhost, bfield

R e a d s

t h e

a t o m - w i s e

c o n s t r a i n i n g

f i e l d

f r o m

b c o n s t r . d a t

Read more…

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: natyp
real(kind=dp), intent(out), dimension(natyp,3) :: bconstr_out

bx, by, bz

public subroutine read_bfield(bfield, natyp)

Author
Sascha Brinker
License
Creative Commons License
Category
KKRhost, bfield

R e a d s

t h e

a t o m - w i s e

m a g n e t i c

f i e l d

f r o m

b f i e l d . d a t

Read more…

Arguments

Type IntentOptional Attributes Name
type(type_bfield), intent(inout) :: bfield
integer, intent(in) :: natyp

public subroutine read_numbofbfields(natom)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: natom

public subroutine add_bfield(bfield, iatom, lmax, nspin, irmdnew, imt1, iend, ncheb, theta, phi, ifunm, icleb, cleb, thetasnew, mode, vnspll0, vnspll1, thetansll)

Author
Sascha Brinker
License
Creative Commons License
Category
KKRhost, bfield

A d d s

m a g n e t i c

f i e l d

t o

t h e

L L '

e x p a n s i o n

o f

t h e

p o t e n t i a l

Read more…

Arguments

Type IntentOptional Attributes Name
type(type_bfield), intent(in) :: bfield
integer, intent(in) :: iatom
integer, intent(in) :: lmax
integer, intent(in) :: nspin
integer, intent(in) :: irmdnew
integer, intent(in) :: imt1
integer, intent(in) :: iend
integer, intent(in) :: ncheb
real(kind=dp), intent(in) :: theta
real(kind=dp), intent(in) :: phi
integer, intent(in), dimension (1:(2*lmax+1)**2) :: ifunm
integer, intent(in), dimension (ncleb, 4) :: icleb

Pointer array

real(kind=dp), intent(in), dimension (ncleb) :: cleb

GAUNT coefficients (GAUNT) ! CHECK THE DIMENSION AND HOW IT IS USED!!!

real(kind=dp), intent(in), dimension (irmdnew, nfund) :: thetasnew
character(len=*), intent(in) :: mode

either '1' or 'transpose', depending whether SOC potential is constructed for right or left solution

complex(kind=dp), intent(in), dimension(lmmaxd, lmmaxd, irmdnew) :: vnspll0

input potential in (l,m,s) basis

complex(kind=dp), intent(out), dimension(lmmaxd, lmmaxd, irmdnew) :: vnspll1

input potential in (l,m,s) basis

real(kind=dp), intent(in), dimension(1:(lmax+1)**2,1:(lmax+1)**2,1:irmdnew) :: thetansll

public subroutine calc_thetallmat(thetansll, lmax, imt1, iend, irmdnew, thetasnew, ifunm, icleb, cleb)

Author
Sascha Brinker
License
Creative Commons License
Category
KKRhost, geometry, new-mesh, shapefun

S h a p e

f u n c t i o n

L L '

e x p a n s i o n

Read more…

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(out), dimension((lmax+1)**2,(lmax+1)**2,irmdnew) :: thetansll
integer, intent(in) :: lmax
integer, intent(in) :: imt1
integer, intent(in) :: iend
integer, intent(in) :: irmdnew
real(kind=dp), intent(in), dimension (irmdnew, nfund) :: thetasnew
integer, intent(in), dimension (1:(2*lmax+1)**2) :: ifunm
integer, intent(in), dimension (ncleb, 4) :: icleb

Pointer array

real(kind=dp), intent(in), dimension (ncleb) :: cleb

GAUNT coefficients (GAUNT)