mod_calconfs Module



Variables

Type Visibility Attributes Name Initial
integer, private, parameter :: SPCZMAX = 1
integer, private, parameter :: SPCXY0 = 2
integer, private, parameter :: ROT_NO = 0
integer, private, parameter :: ROT_FULLBZ = 1
integer, private, parameter :: ROT_SPEC = 2
logical, private, save :: cfg_read = .false.
type(cfg_TYPE), private, save :: cfg

Derived Types

type, private ::  cfg_TYPE

Components

Type Visibility Attributes Name Initial
integer, public :: N1 = 16
integer, public :: lspin = -1
integer, public :: lfvel = -1
integer, public :: lrashba = -1
integer, public :: lspinperatom = -1
integer, public :: ltorqperatom = -1
integer, public :: ltorq = -1
integer, public :: lspinflux = -1
integer, public :: lalpha = -1
integer, public :: nsqa = -1
integer, public :: mode = -1
integer, public :: rotatemode = -1
integer, public :: ilayer = -1
double precision, public :: dk_fv = -1d0
logical, public :: saveeigv = .false.
logical, public :: simpson = .false.
integer, public :: N2 = 3
integer, public, allocatable :: ispincomb(:)
double precision, public, allocatable :: nvect(:,:)

Functions

public function get_nsqa()

Arguments

None

Return Value integer


Subroutines

public subroutine calc_on_fsurf_inputcard(inc, lattice, cluster, tgmatrx, nkpts, kpoints)

Arguments

Type IntentOptional Attributes Name
type(inc_TYPE), intent(in) :: inc
type(lattice_TYPE), intent(in) :: lattice
type(cluster_TYPE), intent(in) :: cluster
type(tgmatrx_TYPE), intent(in) :: tgmatrx
integer, intent(inout) :: nkpts
double precision, intent(inout), allocatable :: kpoints(:,:)

public subroutine calc_on_fsurf(inc, lattice, cluster, tgmatrx, nkpts, kpoints, fermivelocity, spinvalue, save_eigv, spinvec, spinvec_atom, torqvalue, torqvalue_atom, spinflux_atom, alphavalue)

Arguments

Type IntentOptional Attributes Name
type(inc_TYPE), intent(in) :: inc
type(lattice_TYPE), intent(in) :: lattice
type(cluster_TYPE), intent(in) :: cluster
type(tgmatrx_TYPE), intent(in) :: tgmatrx
integer, intent(in) :: nkpts
double precision, intent(in) :: kpoints(3,nkpts)
double precision, intent(inout), allocatable :: fermivelocity(:,:)
double precision, intent(inout), allocatable :: spinvalue(:,:,:)
logical, intent(in), optional :: save_eigv
double precision, intent(inout), allocatable :: spinvec(:,:,:,:)
double precision, intent(inout), allocatable :: spinvec_atom(:,:,:,:)
double precision, intent(inout), allocatable :: torqvalue(:,:,:)
double precision, intent(inout), allocatable :: torqvalue_atom(:,:,:,:)
double precision, intent(inout), allocatable :: spinflux_atom(:,:,:,:)
double precision, intent(inout), allocatable :: alphavalue(:,:,:)

public subroutine calc_spinvalue_state(inc, tgmatrx, rveig_in, spin_value, eigvect_rot)

Arguments

Type IntentOptional Attributes Name
type(inc_TYPE), intent(in) :: inc
type(tgmatrx_TYPE), intent(in) :: tgmatrx
double complex, intent(in) :: rveig_in(inc%almso,inc%ndegen)
double precision, intent(out) :: spin_value(inc%ndegen,cfg%nsqa)
double complex, intent(out), optional :: eigvect_rot(inc%lmmaxso,inc%natypd,inc%ndegen,cfg%nsqa)

private subroutine calc_spinvalue_state_generalized(inc, tgmatrx, rveig_in, spin_value, spinvec, spinvec_atom, torq_value, torq_value_atom, spinflux_atom, alpha_value, eigvect_rot)

Arguments

Type IntentOptional Attributes Name
type(inc_TYPE), intent(in) :: inc
type(tgmatrx_TYPE), intent(in) :: tgmatrx
double complex, intent(in) :: rveig_in(inc%almso,inc%ndegen)
double precision, intent(out) :: spin_value(inc%ndegen,cfg%nsqa)
double precision, intent(inout), allocatable :: spinvec(:,:,:)
double precision, intent(inout), allocatable :: spinvec_atom(:,:,:)
double precision, intent(inout), allocatable :: torq_value(:,:)
double precision, intent(inout), allocatable :: torq_value_atom(:,:,:)
double precision, intent(inout), allocatable :: spinflux_atom(:,:,:)
double precision, intent(inout), allocatable :: alpha_value(:,:)
double complex, intent(inout), optional :: eigvect_rot(:,:,:,:)

private subroutine calc_fermivel_new(inc, lattice, cluster, tgmatrx, kpoint, eigw_in, LVin, RVin, fermi_velocity)

Arguments

Type IntentOptional Attributes Name
type(inc_TYPE), intent(in) :: inc
type(lattice_TYPE), intent(in) :: lattice
type(cluster_TYPE), intent(in) :: cluster
type(tgmatrx_TYPE), intent(in) :: tgmatrx
double precision, intent(in) :: kpoint(3)
double complex, intent(in) :: eigw_in
double complex, intent(in) :: LVin(inc%almso)
double complex, intent(in) :: RVin(inc%almso)
double precision, intent(out) :: fermi_velocity(3)

private subroutine calc_fermivel(inc, lattice, cluster, tgmatrx, kpoint, eigw_in, LVin, RVin, fermi_velocity)

Arguments

Type IntentOptional Attributes Name
type(inc_TYPE), intent(in) :: inc
type(lattice_TYPE), intent(in) :: lattice
type(cluster_TYPE), intent(in) :: cluster
type(tgmatrx_TYPE), intent(in) :: tgmatrx
double precision, intent(in) :: kpoint(3)
double complex, intent(in) :: eigw_in
double complex, intent(in) :: LVin(inc%almso)
double complex, intent(in) :: RVin(inc%almso)
double precision, intent(out) :: fermi_velocity(3)

private subroutine read_cfg(force_spinread)

Arguments

Type IntentOptional Attributes Name
logical, intent(in), optional :: force_spinread

private subroutine convert_nvect(angrep, dtmpin, nvect)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: angrep
double precision, intent(in) :: dtmpin(3)
double precision, intent(out) :: nvect(3)

private subroutine save_fermivelocity(filemode, nkpts, fermivel, nsym, isym)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: filemode
integer, intent(in) :: nkpts
double precision, intent(in) :: fermivel(3,nkpts)
integer, intent(in) :: nsym
integer, intent(in) :: isym(nsym)

private subroutine save_spinvalue(filemode, nkpts, nsqa, ndegen, ispincomb, nvect, spinval, nsym, isym)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: filemode
integer, intent(in) :: nkpts
integer, intent(in) :: nsqa
integer, intent(in) :: ndegen
integer, intent(in) :: ispincomb(nsqa)
double precision, intent(in) :: nvect(3,nsqa)
double precision, intent(in) :: spinval(ndegen,nsqa,nkpts)
integer, intent(in) :: nsym
integer, intent(in) :: isym(nsym)

private subroutine save_spinvec(filemode, nkpts, nsqa, ndegen, ispincomb, nvect, spinvec, nsym, isym)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: filemode
integer, intent(in) :: nkpts
integer, intent(in) :: nsqa
integer, intent(in) :: ndegen
integer, intent(in) :: ispincomb(nsqa)
double precision, intent(in) :: nvect(3,nsqa)
double precision, intent(in) :: spinvec(3,ndegen,nsqa,nkpts)
integer, intent(in) :: nsym
integer, intent(in) :: isym(nsym)

private subroutine save_spinvec_atom(filemode, nkpts, ndegen, natyp, spinvec_atom, nsym, isym)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: filemode
integer, intent(in) :: nkpts
integer, intent(in) :: ndegen
integer, intent(in) :: natyp
double precision, intent(in) :: spinvec_atom(3,natyp,ndegen,nkpts)
integer, intent(in) :: nsym
integer, intent(in) :: isym(nsym)

private subroutine save_torqvalue(filemode, nkpts, ndegen, torqval, nsym, isym)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: filemode
integer, intent(in) :: nkpts
integer, intent(in) :: ndegen
double precision, intent(in) :: torqval(3,ndegen,nkpts)
integer, intent(in) :: nsym
integer, intent(in) :: isym(nsym)

private subroutine save_torqvalue_atom(filemode, nkpts, ndegen, natyp, torqval_atom, nsym, isym)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: filemode
integer, intent(in) :: nkpts
integer, intent(in) :: ndegen
integer, intent(in) :: natyp
double precision, intent(in) :: torqval_atom(3,natyp,ndegen,nkpts)
integer, intent(in) :: nsym
integer, intent(in) :: isym(nsym)

private subroutine save_spinflux_atom(filemode, nkpts, ndegen, natyp, spinflux_atom, nsym, isym)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: filemode
integer, intent(in) :: nkpts
integer, intent(in) :: ndegen
integer, intent(in) :: natyp
double precision, intent(in) :: spinflux_atom(3,natyp,ndegen,nkpts)
integer, intent(in) :: nsym
integer, intent(in) :: isym(nsym)

private subroutine save_alpha(filemode, nkpts, ndegen, alpha, nsym, isym)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: filemode
integer, intent(in) :: nkpts
integer, intent(in) :: ndegen
double precision, intent(in) :: alpha(3,ndegen,nkpts)
integer, intent(in) :: nsym
integer, intent(in) :: isym(nsym)

public subroutine calculate_response_functions_CRTA_int(nsym, isym, rotmat, alat, BZVol, ndeg, natyp, nkpts, areas, fermivel, torqval, torqval_atom, spinvec_atom, spinflux)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: nsym
integer, intent(in) :: isym(nsym)
double precision, intent(in) :: rotmat(64,3,3)
double precision, intent(in) :: alat
double precision, intent(in) :: BZVol
integer, intent(in) :: ndeg
integer, intent(in) :: natyp
integer, intent(in) :: nkpts
double precision, intent(in) :: areas(nkpts)
double precision, intent(in) :: fermivel(3,nkpts)
double precision, intent(in), allocatable :: torqval(:,:,:)
double precision, intent(in), allocatable :: torqval_atom(:,:,:,:)
double precision, intent(in), allocatable :: spinvec_atom(:,:,:,:)
double precision, intent(in), allocatable :: spinflux(:,:,:,:)

public subroutine calculate_response_functions_CRTA_vis(nBZdim, nsym, isym, rotmat, alat, BZVol, ndeg, natyp, nkpts, nkpts_all, kpt2irr, irr2kpt, kpoints, fermivel, torqval, torqval_atom, spinvec_atom, spinflux)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: nBZdim
integer, intent(in) :: nsym
integer, intent(in) :: isym(nsym)
double precision, intent(in) :: rotmat(64,3,3)
double precision, intent(in) :: alat
double precision, intent(in) :: BZVol
integer, intent(in) :: ndeg
integer, intent(in) :: natyp
integer, intent(in) :: nkpts
integer, intent(in) :: nkpts_all
integer, intent(in) :: kpt2irr(nkpts_all)
integer, intent(in) :: irr2kpt(nkpts)
double precision, intent(in) :: kpoints(3,nkpts)
double precision, intent(in) :: fermivel(3,nkpts)
double precision, intent(in), allocatable :: torqval(:,:,:)
double precision, intent(in), allocatable :: torqval_atom(:,:,:,:)
double precision, intent(in), allocatable :: spinvec_atom(:,:,:,:)
double precision, intent(in), allocatable :: spinflux(:,:,:,:)

private subroutine calculate_torkance_CRTA_vis_simpson2D(nsym, isym, rotmat, alat, BZVol, ndeg, nkpts, nkpts_all, kpt2irr, irr2kpt, kpoints, fermivel, torqval)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: nsym
integer, intent(in) :: isym(nsym)
double precision, intent(in) :: rotmat(64,3,3)
double precision, intent(in) :: alat
double precision, intent(in) :: BZVol
integer, intent(in) :: ndeg
integer, intent(in) :: nkpts
integer, intent(in) :: nkpts_all
integer, intent(in) :: kpt2irr(nkpts_all)
integer, intent(in) :: irr2kpt(nkpts)
double precision, intent(in) :: kpoints(3,nkpts)
double precision, intent(in) :: fermivel(3,nkpts)
double precision, intent(in) :: torqval(3,ndeg,nkpts)

public subroutine order_lines(kpt2irr, nkpts_all, kpt2irr_ord, band_indices, nkpts_band, nbands)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: kpt2irr(nkpts_all)
integer, intent(in) :: nkpts_all
integer, intent(out) :: kpt2irr_ord(nkpts_all)
integer, intent(out) :: band_indices(nkpts_all)
integer, allocatable :: nkpts_band(:)
integer, intent(out) :: nbands

private recursive subroutine traceback_band(i_ord, i_band, i, kpt2irr, nkpts_all, kpt2irr_ord, band_indices, i_ord_new)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: i_ord
integer, intent(in) :: i_band
integer, intent(in) :: i
integer, intent(in) :: kpt2irr(nkpts_all)
integer, intent(in) :: nkpts_all
integer, intent(out) :: kpt2irr_ord(nkpts_all)
integer, intent(out) :: band_indices(nkpts_all)
integer :: i_ord_new

public subroutine calculate_spinmixing_int(nsym, ndeg, nsqa, nkpts, areas, fermivel, spinval, spinmix, dos, printout, BZVol)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: nsym
integer, intent(in) :: ndeg
integer, intent(in) :: nsqa
integer, intent(in) :: nkpts
double precision, intent(in) :: areas(nkpts)
double precision, intent(in) :: fermivel(3,nkpts)
double precision, intent(in) :: spinval(ndeg,nsqa,nkpts)
double precision, intent(out) :: spinmix(nsqa)
double precision, intent(out) :: dos
logical, intent(in) :: printout
double precision, intent(in), optional :: BZVol

public subroutine calculate_dos_int(nsym, isym, rotmat, alat, BZVol, nkpts, areas, fermivel, BZdim)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: nsym
integer, intent(in) :: isym(nsym)
double precision, intent(in) :: rotmat(64,3,3)
double precision, intent(in) :: alat
double precision, intent(in) :: BZVol
integer, intent(in) :: nkpts
double precision, intent(in) :: areas(nkpts)
double precision, intent(in) :: fermivel(3,nkpts)
integer, intent(in) :: BZdim

public subroutine calculate_spinmixing_vis(nsym, ndeg, nsqa, nkpts, nkpts_all, kpt2irr, kpoints, fermivel, spinval, spinmix, dos, printout, BZVol, nBZdim)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: nsym
integer, intent(in) :: ndeg
integer, intent(in) :: nsqa
integer, intent(in) :: nkpts
integer, intent(in) :: nkpts_all
integer, intent(in) :: kpt2irr(nkpts_all)
double precision, intent(in) :: kpoints(3,nkpts)
double precision, intent(in) :: fermivel(3,nkpts)
double precision, intent(in) :: spinval(ndeg,nsqa,nkpts)
double precision, intent(out) :: spinmix(nsqa)
double precision, intent(out) :: dos
logical, intent(in) :: printout
double precision, intent(in) :: BZVol
integer, intent(in) :: nBZdim

private subroutine calculate_dos_vis(nsym, nkpts, nkpts_all, kpt2irr, kpoints, fermivel, dos, printout, BZVol)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: nsym
integer, intent(in) :: nkpts
integer, intent(in) :: nkpts_all
integer, intent(in) :: kpt2irr(nkpts_all)
double precision, intent(in) :: kpoints(3,nkpts)
double precision, intent(in) :: fermivel(3,nkpts)
double precision, intent(out) :: dos
logical, intent(in) :: printout
double precision, intent(in), optional :: BZVol

private subroutine calculate_and_save_weights(nkpts, nsym, isym, areas, fermivel)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: nkpts
integer, intent(in) :: nsym
integer, intent(in) :: isym(nsym)
double precision, intent(in) :: areas(nkpts)
double precision, intent(in) :: fermivel(3,nkpts)