mod_types Module

Module defining necessary types for the MPI communication, as well as memory management and initialization of the needed arrays.


Uses


Variables

Type Visibility Attributes Name Initial
type(type_inc), public, save :: t_inc
type(type_tgmatices), public, save :: t_tgmat
type(type_mpi_cartesian_grid_info), public, save :: t_mpi_c_grid
type(type_lloyd), public, save :: t_lloyd
type(type_dtmatjijdij), public, allocatable, save :: t_dtmatjij(:)
type(type_cpa), public, save :: t_cpa
type(type_imp), public, save :: t_imp
type(type_madel), public, save :: t_madel

Derived Types

type, public ::  type_tgmatices

T y p e

h o l d i n g

s i n g l e

s i t e

t

m a t r i x ,

r e f e r e n c e

G F

a n d

s t r u c t u r a l

G F

( g m a t )

f o r

d i s t r i b u t i o n

b e t w e e n

1 a ,

1 b

a n d

1 c

p a r t s

o f

t h e

c o d e

Read more…

Components

Type Visibility Attributes Name Initial
logical, public :: tmat_to_file = .false.
logical, public :: gmat_to_file = .false.
logical, public :: gref_to_file = .false.
integer, public :: nelements = 4
complex(kind=dp), public, dimension(:,:,:), allocatable :: tmat

Single-site t-matrix ! dimensions=LMMAXD, LMMAXD, IREC; IREC= IE+IELAST(ISPIN-1)+IELASTNSPIN*(I1-1) ;IE=1,...,IELAST, ISPIN=1,...,NSPIN, I1=1,...,NATYP)

complex(kind=dp), public, dimension(:,:,:), allocatable :: gmat

Structural Greens function ! dimensions=LMMAXD, LMMAXD, IREC; IREC= IQDOS+NQDOS(IE-1)+NQDOSIELAST(ISPIN-1)+IELASTNSPIN*(I1-1) ;IE=1,...,IELAST, ISPIN=1,...,NSPIN, I1=1,...,NATYP)

complex(kind=dp), public, dimension(:,:,:,:), allocatable :: gref

Reference Greens function ! GINP(NACLSD*LMGF0D,LMGF0D,NCLSD) IREC=IE=1,...,IELAST

type, public ::  type_cpa

T y p e

h o l d i n g

C P A

i n f o r m a t i o n

Read more…

Components

Type Visibility Attributes Name Initial
logical, public :: dmatproj_to_file = .false.
integer, public :: nelements = 3
complex(kind=dp), public, dimension(:,:,:,:), allocatable :: dmatts
complex(kind=dp), public, dimension(:,:,:,:), allocatable :: dtilts

type, public ::  type_dtmatjijdij

D a t a

t y p e

f o r

t h e

d e r i v a t i v e s

o f

t h e

t

m a t r i x

w i t h

r e s p e c t

t o

c h a n g i n g

t h e

n o n - c o l l i n e a r

a n g l e s

i n

d i r e c t i o n s

{ x , y , z }

Read more…

Components

Type Visibility Attributes Name Initial
integer, public :: nelements = 3
logical, public :: calculate = .false.
complex(kind=dp), public, dimension(:,:,:,:), allocatable :: dtmat_xyz

Derivatives of the t-matrix with respect to non-collinear angles ! dimensions= LMMAXD, LMMAXD, 3, IELAST; 3={x,y,z}

type, public ::  type_inc

T y p e

h o l d i n g

s o m e

a r r a y

d i m e n s i o n s

n e e d e d

i n d e p e n d e n t l y

o f

t _ p a r a m s

Read more…

Components

Type Visibility Attributes Name Initial
integer, public :: nparams = 17
integer, public :: ielast = -1
integer, public :: nqdos = -1
integer, public :: naclsmax = -1
integer, public :: i_iteration = -1
integer, public :: n_iteration = -1
integer, public :: mit_bry = 1
integer, public :: nshell0 = -1
integer, public :: nkmesh = -1
logical, public :: newsosol = .false.

use new solver for SOC

logical, public :: nosoc = .false.

use new solver without SOC (test option 'NOSOC ')

logical, public :: deci_out = .false.

use deci_out case

integer, public :: i_write = 0

switch to control if things are written out or not (verbosity levels 0,1,2)

integer, public :: i_time = 1

switch to control if timing files are written (verbosity levels 0,1,2)

integer, public :: nsra = -1
integer, public :: irmdnew = -1
integer, public :: kvrel = -1
integer, public, dimension(:), allocatable :: kmesh
integer, public, dimension(:), allocatable :: kmesh_ie

type, public ::  type_mpi_cartesian_grid_info

T y p e

h o l d i n g

i n f o r m a t i o n

o n

t h e

M P I

p a r a l l e l i z a t i o n

s c h e m e

Read more…

Components

Type Visibility Attributes Name Initial
integer, public :: nparams = 12
integer, public :: mympi_comm_ie = -1
integer, public :: mympi_comm_at = -1
integer, public :: myrank_ie = -1
integer, public :: myrank_at = -1
integer, public :: myrank_atcomm = -1
integer, public :: nranks_ie = -1
integer, public :: nranks_at = -1
integer, public :: nranks_atcomm = -1
integer, public :: ntot1 = -1
integer, public :: ntot2 = -1
integer, public, dimension(2) :: dims = [-1, -1]
integer, public, dimension(:), allocatable :: ntot_pt1
integer, public, dimension(:), allocatable :: ioff_pt1
integer, public, dimension(:), allocatable :: ntot_pt2
integer, public, dimension(:), allocatable :: ioff_pt2

type, public ::  type_lloyd

T y p e

h o l d i n g

i n f o r m a t i o n

n e e d e d

f o r

l l o y d

s u c h

a s

d e r i v a t i v e s

o f

s i n g l e

s i t e

t

m a t r i x ,

r e f e r e n c e

G F

o r

t h e

t r a c e

o f

a l p h a

m a t r i x

a n d

Read more…

Components

Type Visibility Attributes Name Initial
logical, public :: dtmat_to_file = .false.
logical, public :: tralpha_to_file = .false.
logical, public :: cdos_diff_lly_to_file = .false.
logical, public :: dgref_to_file = .false.
logical, public :: g0tr_to_file = .false.
integer, public :: n1 = 6
complex(kind=dp), public, dimension(:), allocatable :: g0tr
complex(kind=dp), public, dimension(:), allocatable :: tralpha
complex(kind=dp), public, dimension(:,:), allocatable :: cdos
complex(kind=dp), public, dimension(:,:,:), allocatable :: dtmat
complex(kind=dp), public, dimension(:,:,:,:), allocatable :: dgref

type, public ::  type_imp

T y p e

h o l d i n g

i n f o r m a t i o n

f o r

i m p u r i t y

p o t e n t i a l ,

n e e d e d

i n

G R E E N I M P

m o d e

Read more…

Components

Type Visibility Attributes Name Initial
integer, public :: n1 = 12
integer, public :: n2 = 17
integer, public :: natomimp = -1
integer, public :: ihost = -1
integer, public :: irmd

Maximum number of radial points

integer, public :: irid

Shape functions parameters in non-spherical part

integer, public :: ipand

Number of panels in non-spherical part

integer, public :: nfund

Shape functions parameters in non-spherical part

integer, public :: nspin

Counter for spin directions

integer, public :: natypd

Number of kinds of atoms in unit cell

integer, public :: irmind

irmd - irnsd

integer, public :: lmpotd

(lpot+1)**2

integer, public, dimension(:), allocatable :: ipanimp

Radial mesh, Panel mesh for impurities ! IPANIMP(NATOMIMP)

integer, public, dimension(:), allocatable :: irwsimp

Radial mesh, IRWS for imps ! IRWSIMP(NATOMIMP)

integer, public, dimension(:), allocatable :: hostimp

Layer index of host atoms ! HOSTIMP(NATYPD)

integer, public, dimension(:), allocatable :: atomimp

Layer index of imp atoms ! ATOMIMP(NATOMIMP)

integer, public, dimension(:), allocatable :: irminimp

Radial mesh, IRMIN for imps ! IRMINIMP(NATOMIMP))

integer, public, dimension(:,:), allocatable :: ircutimp

Radial mesh, RCUT for imps ! IRCUTIMP(0:IPAND,NATOMIMP)

real(kind=dp), public, dimension(:), allocatable :: zimp

atom charge of imps, ! ZIMP(NATOMIMP)

real(kind=dp), public, dimension(:), allocatable :: phiimp

phi of nonco_angle of impurity ! PHIIMP(NATOMIMP)

real(kind=dp), public, dimension(:), allocatable :: thetaimp

theta of nonco_angle of impurity ! THETAIMP(NATOMIMP)

real(kind=dp), public, dimension(:,:), allocatable :: rimp

Rmesh of imps, ! RIMP(IRMD,NATOMIMP)

real(kind=dp), public, dimension(:,:), allocatable :: rclsimp

impurity positions(scoef file) ! RCLSIMP(3,NATOMIMPD)

real(kind=dp), public, dimension(:,:), allocatable :: vispimp

impurity potential ! VISPIMP(IRMD,NATOMIMP*NSPIN)

real(kind=dp), public, dimension(:,:,:), allocatable :: vinsimp

impurity potential ! VINSIMP(IRMIND:IRMD,LMPOTD,NATOMIMP*NSPIN)

real(kind=dp), public, dimension(:,:,:), allocatable :: thetasimp

shape functions of imps ! THETASIMP(IRID,NFUND,NATOMIMP)

real(kind=dp), public, dimension(:), allocatable :: socscale

scale values of SOC

complex(kind=dp), public, dimension(:,:,:,:), allocatable :: rllimp

impurity wavefunctions ! RLL(NVEC*lmmaxd,lmmaxd,IRMDNEW(I1))

type, public ::  type_madel

T y p e

h o l d i n g

i n f o r m a t i o n

f o r

t h e

m a d e l u n g

p o t e n t i a l s

Read more…

Components

Type Visibility Attributes Name Initial
integer, public :: n1 = 12
integer, public :: irmd

Maximum number of radial points

real(kind=dp), public, dimension(:,:,:), allocatable :: avmad

Structure-dependent matrix, dimension: irec, lmpot x lmpot

real(kind=dp), public, dimension(:,:), allocatable :: bvmad

Structure-dependent vector, dimension: irec, lmpot


Subroutines

public subroutine init_tgmat(t_inc, t_tgmat, t_mpi_c_grid)

License
Creative Commons License
Category
initialization, memory-management, structural-greensfunction, reference-system, KKRhost

S u b r o u t i n e

t o

a l l o c a t e

a n d

i n i t i a l i z e

a r r a y s

o f

t _ t g m a t

Read more…

Arguments

Type IntentOptional Attributes Name
type(type_inc), intent(in) :: t_inc
type(type_tgmatices), intent(inout) :: t_tgmat
type(type_mpi_cartesian_grid_info), intent(in) :: t_mpi_c_grid

public subroutine init_t_cpa(t_inc, t_cpa, nenergy)

License
Creative Commons License
Category
initialization, memory-management, coherent-potential-approx, KKRhost

S u b r o u t i n e

t o

a l l o c a t e

a n d

i n i t i a l i z e

a r r a y s

o f

t _ c p a

Read more…

Arguments

Type IntentOptional Attributes Name
type(type_inc), intent(in) :: t_inc
type(type_cpa), intent(inout) :: t_cpa
integer, intent(in) :: nenergy

public subroutine init_t_dtmatjij(t_inc, t_dtmatjij)

License
Creative Commons License
Category
initialization, memory-management, KKRhost

S u b r o u t i n e

t o

a l l o c a t e

a n d

i n i t i a l i z e

a r r a y s

o f

t _ d t m a t J i j

Read more…

Arguments

Type IntentOptional Attributes Name
type(type_inc), intent(in) :: t_inc
type(type_dtmatjijdij), intent(inout), allocatable :: t_dtmatjij(:)

public subroutine init_t_dtmatjij_at(t_inc, t_mpi_c_grid, t_dtmatjij_at)

License
Creative Commons License
Category
initialization, memory-management, KKRhost

S u b r o u t i n e

t o

a l l o c a t e

a n d

i n i t i a l i z e

a r r a y s

o f

t _ d t m a t J i j _ a t

Read more…

Arguments

Type IntentOptional Attributes Name
type(type_inc), intent(in) :: t_inc
type(type_mpi_cartesian_grid_info), intent(in) :: t_mpi_c_grid
type(type_dtmatjijdij), intent(inout) :: t_dtmatjij_at

public subroutine init_params_t_imp(t_imp, ipand, natypd, irmd, irid, nfund, nspin, irmind, lmpotd)

License
Creative Commons License
Category
initialization, KKRhost

S t o r e

p a r a m e t e r s

n e e d e d

i n

t _ i m p

Read more…

Arguments

Type IntentOptional Attributes Name
type(type_imp), intent(inout) :: t_imp
integer, intent(in) :: ipand

Number of panels in non-spherical part

integer, intent(in) :: natypd

Number of kinds of atoms in unit cell

integer, intent(in) :: irmd

Maximum number of radial points

integer, intent(in) :: irid

Shape functions parameters in non-spherical part

integer, intent(in) :: nfund

Shape functions parameters in non-spherical part

integer, intent(in) :: nspin

Counter for spin directions

integer, intent(in) :: irmind

irmd - irnsd

integer, intent(in) :: lmpotd

(lpot+1)**2

public subroutine init_t_imp(t_inc, t_imp)

License
Creative Commons License
Category
initialization, memory-management, KKRhost

S u b r o u t i n e

t o

a l l o c a t e

a n d

i n i t i a l i z e

a r r a y s

o f

t _ i m p

Read more…

Arguments

Type IntentOptional Attributes Name
type(type_inc), intent(in) :: t_inc
type(type_imp), intent(inout) :: t_imp

public subroutine init_tlloyd(t_inc, t_lloyd, t_mpi_c_grid)

License
Creative Commons License
Category
initialization, memory-management, KKRhost

S u b r o u t i n e

t o

a l l o c a t e

a n d

i n i t i a l i z e

t _ l l o y d

Read more…

Arguments

Type IntentOptional Attributes Name
type(type_inc), intent(in) :: t_inc
type(type_lloyd), intent(inout) :: t_lloyd
type(type_mpi_cartesian_grid_info), intent(in) :: t_mpi_c_grid