The Elk Code
 
Loading...
Searching...
No Matches
modmain.f90
Go to the documentation of this file.
1
2! Copyright (C) 2002-2009 J. K. Dewhurst, S. Sharma and C. Ambrosch-Draxl.
3! This file is distributed under the terms of the GNU General Public License.
4! See the file COPYING for license details.
5
6module modmain
7
8!----------------------------!
9! lattice parameters !
10!----------------------------!
11! lattice vectors stored column-wise
12real(8) avec(3,3),avec0(3,3),davec(3,3)
13! inverse of lattice vector matrix
14real(8) ainv(3,3)
15! reciprocal lattice vectors
16real(8) bvec(3,3),bvec0(3,3)
17! inverse of reciprocal lattice vector matrix
18real(8) binv(3,3),binv0(3,3)
19! unit cell volume
21! Brillouin zone volume
22real(8) omegabz
23! any vector with length less than epslat is considered zero
24real(8) epslat
25
26!--------------------------!
27! atomic variables !
28!--------------------------!
29! maximum allowed species
30integer, parameter :: maxspecies=8
31! maximum allowed atoms per species
32integer, parameter :: maxatoms=200
33! number of species
34integer nspecies
35! number of atoms for each species
37! maximum number of atoms over all the species
38integer natmmax
39! total number of atoms
41! index to atoms and species
43! inverse atoms and species indices
46! molecule is .true. is the system is an isolated molecule
47logical molecule
48! primcell is .true. if primitive unit cell is to be found automatically
50! atomic positions in lattice coordinates
53! atomic positions in Cartesian coordinates
55! magnitude of random displacements added to the atomic positions
56real(8) rndatposc
57! tatdisp is .true. if small amplitude atomic displacements are to be included
58! when calculating the Coulomb potential
59logical :: tatdisp=.false.
60! trdatdv is .true. if the atomic displacements and velocities are to be read
61! from file
62logical trdatdv
63! atomic displacements and velocities in Cartesian coordinates
65! atomic damping force coefficient
66real(8) atdfc
67
68!----------------------------------!
69! atomic species variables !
70!----------------------------------!
71! species files path
72character(256) sppath
73! species filenames
74character(256) spfname(maxspecies)
75! species name
76character(64) spname(maxspecies)
77! species symbol
78character(64) spsymb(maxspecies)
79! species nuclear charge
81! ptnucl is .true. if the nuclei are to be treated as point charges, if .false.
82! the nuclei have a finite spherical distribution
83logical ptnucl
84! nuclear radius
86! nuclear volume
88! number of radial mesh points to nuclear radius
90! Thomson radius
92! Thomson volume
94! number of radial mesh points to Thomson radius
96! nuclear Coulomb potential
97real(8), allocatable :: vcln(:,:)
98! species electronic charge
100! species mass
102! smallest radial point for each species
104! effective infinity for species
106! number of radial points to effective infinity for each species
108! maximum nrsp over all the species
109integer nrspmax
110! maximum allowed states for each species
111integer, parameter :: maxstsp=40
112! number of states for each species
114! maximum nstsp over all the species
115integer nstspmax
116! core-valence cut-off energy for species file generation
117real(8) ecvcut
118! semi-core-valence cut-off energy for species file generation
119real(8) esccut
120! state principle quantum number for each species
122! state l value for each species
124! state k value for each species
126! spcore is .true. if species state is core
128! total number of core states
129integer nstcr
130! state eigenvalue for each species
132! state occupancy for each species
134! species radial mesh to effective infinity
135real(8), allocatable :: rsp(:,:)
136! species charge density
137real(8), allocatable :: rhosp(:,:)
138! species self-consistent potential
139real(8), allocatable :: vrsp(:,:)
140! exchange-correlation type for atomic species (the converged ground-state of
141! the crystal does not depend on this choice)
142integer xctsp(3)
143
144!---------------------------------------------------------------!
145! muffin-tin radial mesh and angular momentum variables !
146!---------------------------------------------------------------!
147! scale factor for number of muffin-tin points
149! number of muffin-tin radial points for each species
151! maximum nrmt over all the species
152integer nrmtmax
153! muffin-tin radius scale factor
154real(8) rmtscf
155! order of averaging applied to the muffin-tin radii
156integer mrmtav
157! optional default muffin-tin radius for all atoms
158real(8) rmtall
159! minimum allowed distance between muffin-tin surfaces
160real(8) rmtdelta
161! muffin-tin radii
163! trmt0 is .true. if the original muffin-tin radii rmt0 are to be retained
164! between tasks
165logical trmt0
166! (R_mt)ˡ for l up to lmaxo+3
167real(8), allocatable :: rmtl(:,:)
168! total muffin-tin volume
169real(8) omegamt
170! radial step length for coarse mesh
171integer lradstp
172! number of coarse radial mesh points
174! maximum nrcmt over all the species
175integer nrcmtmax
176! coarse muffin-tin radial mesh
177real(8), allocatable :: rcmt(:,:)
178! r^l on fine radial mesh
179real(8), allocatable :: rlmt(:,:,:)
180! r^l on coarse radial mesh
181real(8), allocatable :: rlcmt(:,:,:)
182! weights for spline integration on fine radial mesh multiplied by r²
183real(8), allocatable :: wr2mt(:,:)
184! weights for spline partial integration on fine radial mesh
185real(8), allocatable :: wprmt(:,:,:)
186! weights for spline coefficients on fine radial mesh
187real(8), allocatable :: wcrmt(:,:,:)
188! weights for spline integration on coarse radial mesh multiplied by r²
189real(8), allocatable :: wr2cmt(:,:)
190! weights for spline partial integration on coarse radial mesh
191real(8), allocatable :: wprcmt(:,:,:)
192! weights for spline coefficients on coarse radial mesh
193real(8), allocatable :: wcrcmt(:,:,:)
194! maximum allowable angular momentum for augmented plane waves
195integer, parameter :: maxlapw=30
196! maximum angular momentum for augmented plane waves
198! (lmaxapw+1)²
199integer lmmaxapw
200! maximum angular momentum on the outer part of the muffin-tin
202! (lmaxo+1)²
203integer lmmaxo
204! maximum angular momentum on the inner part of the muffin-tin
206! (lmaxi+1)²
207integer lmmaxi
208! fraction of muffin-tin radius which constitutes the inner part
209real(8) fracinr
210! number of fine/coarse radial points on the inner part of the muffin-tin
212! number of fine/coarse points in packed muffin-tins
215! maximum number of points over all packed muffin-tins
217! total number of muffin-tin points for all atoms
218integer npcmttot
219! index to first muffin-tin point in packed array for all atoms
220integer, allocatable :: ipcmt(:)
221! smoothing order used when calculating gradients in the muffin-tin
222integer msmgmt
223
224!--------------------------------!
225! spin related variables !
226!--------------------------------!
227! spinpol is .true. for spin-polarised calculations
229! spinorb is .true. for spin-orbit coupling
231! scale factor of spin-orbit coupling term in Hamiltonian
232real(8) socscf
233! bforb is .true. for external B-field-orbit coupling
234logical bforb
235! bfdmag is .true. for external B-field diamagnetic coupling
236logical bfdmag
237! dimension of magnetisation and magnetic vector fields (1 or 3)
238integer ndmag
239! ncmag is .true. if the magnetisation is non-collinear, i.e. when ndmag = 3
240logical ncmag
241! if cmagz is .true. then collinear magnetism along the z-axis is enforced
243! fixed spin moment type
244! 0 : none
245! 1 (-1) : total moment (direction)
246! 2 (-2) : individual muffin-tin moments (direction)
247! 3 (-3) : total and muffin-tin moments (direction)
248! 4 : total moment magnitude
249! 5 : individual muffin-tin moment magnitudes
250! 6 : total and muffin-tin moment magnitudes
252! fixed total spin magnetic moment
253real(8) momfix(3),momfix0(3),dmomfix(3)
254! fixed total spin magnetic moment magnitude
255real(8) momfixm
256! fixed spin moment global effective field in Cartesian coordinates
257real(8) bfsmc(3)
258! muffin-tin fixed spin moments
260! muffin-tin fixed spin moment magnitudes
262! muffin-tin fixed spin moment effective fields in Cartesian coordinates
263real(8), allocatable :: bfsmcmt(:,:)
264! fixed spin moment field step size
265real(8) taufsm
266! second-variational spinor dimension (1 or 2)
267integer nspinor
268! global external magnetic field in Cartesian coordinates
269real(8) bfieldc(3)
270! initial field
272! external magnetic field in each muffin-tin in Cartesian coordinates
274! initial field as read in from input file
276! magnitude of random vectors added to muffin-tin fields
277real(8) rndbfcmt
278! external magnetic fields are multiplied by reducebf after each s.c. loop
280! small change in magnetic field used for calculating the magnetoelectric tensor
281real(8) deltabf
282! spinsprl is .true. if a spin-spiral is to be calculated
284! ssdph is .true. if the muffin-tin spin-spiral magnetisation is de-phased
285logical ssdph
286! spin-spiral phase factor for each atom
287complex(8), allocatable :: zqss(:)
288! number of spin-dependent first-variational functions per state
289integer nspnfv
290! map from second- to first-variational spin index
291integer jspnfv(2)
292! spin-spiral q-vector in lattice coordinates
293real(8) vqlss(3),dvqlss(3)
294! spin-spiral q-vector in Cartesian coordinates
295real(8) vqcss(3)
296! current q-point in spin-spiral supercell calculation
297integer iqss
298! number of primitive unit cells in spin-spiral supercell
299integer nscss
300! number of fixed spin direction points on the sphere for finding the magnetic
301! anisotropy energy (MAE)
303! (theta,phi) coordinates for each MAE direction
304real(8), allocatable :: tpmae(:,:)
305
306!----------------------------------------------------!
307! static electric field and vector potential !
308!----------------------------------------------------!
309! tefield is .true. if a polarising constant electric field is applied
310logical tefield
311! electric field vector in Cartesian coordinates
312real(8) efieldc(3)
313! electric field vector in lattice coordinates
314real(8) efieldl(3)
315! average electric field in Cartesian coordinates in each muffin-tin
316real(8), allocatable :: efcmt(:,:)
317! maximum distance over which the electric field is applied
318real(8) dmaxefc
319! maximum allowed absolute value of the potential generated by efieldc
320real(8) vmaxefc
321! tafield is .true. if a constant vector potential is applied
322logical tafield
323! vector potential A-field in Cartesian coordinates which couples to the
324! paramagnetic current
325real(8) afieldc(3),afieldc0(3),dafieldc(3)
326! A-field in lattice coordinates
327real(8) afieldl(3)
328! tafsp is .true. if a constant spin-dependent vector potential is applied
329logical tafsp
330! spin-dependent vector potential (3 x 3 tensor) in Cartesian coordinates
331real(8) afspc(3,3),dafspc(3,3)
332
333!----------------------------!
334! symmetry variables !
335!----------------------------!
336! type of symmetry allowed for the crystal
337! 0 : only the identity element is used
338! 1 : full symmetry group is used
339! 2 : only symmorphic symmetries are allowed
340integer symtype
341! number of Bravais lattice point group symmetries
342integer nsymlat
343! Bravais lattice point group symmetries
344integer symlat(3,3,48)
345! determinants of lattice symmetry matrices (1 or -1)
346integer symlatd(48)
347! index to inverses of the lattice symmetries
348integer isymlat(48)
349! lattice point group symmetries in Cartesian coordinates
350real(8) symlatc(3,3,48)
351! tshift is .true. if atomic basis is allowed to be shifted
353! tsyminv is .true. if the crystal has inversion symmetry
354logical tsyminv
355! maximum of symmetries allowed
356integer, parameter :: maxsymcrys=192
357! number of crystal symmetries
358integer nsymcrys
359! crystal symmetry translation vector in lattice and Cartesian coordinates
361! tv0symc is .true. if the translation vector is zero
363! spatial rotation element in lattice point group for each crystal symmetry
365! global spin rotation element in lattice point group for each crystal symmetry
367! equivalent atom index for each crystal symmetry
368integer, allocatable :: ieqatom(:,:,:)
369! eqatoms(ia,ja,is) is .true. if atoms ia and ja are equivalent
370logical, allocatable :: eqatoms(:,:,:)
371! tfeqat is .true. if this is the first atom in a subset of equivalent atoms
372logical, allocatable :: tfeqat(:,:)
373! number of site symmetries
374integer, allocatable :: nsymsite(:)
375! site symmetry spatial rotation element in lattice point group
376integer, allocatable :: lsplsyms(:,:)
377! site symmetry global spin rotation element in lattice point group
378integer, allocatable :: lspnsyms(:,:)
379
380!----------------------------!
381! G-vector variables !
382!----------------------------!
383! G-vector cut-off for interstitial potential and density
385! G-vector grid sizes
386integer ngridg(3),ngridg0(3)
387! G-vector grid sizes for coarse grid with |G| < 2 gkmax
388integer ngdgc(3)
389! total number of G-vectors
391! total number of G-vectors for coarse grid
392integer ngtc
393! integer grid intervals for each direction
394integer intgv(2,3)
395! number of G-vectors with |G| < gmaxvr
396integer ngvec
397! number of G-vectors for coarse grid with |G| < 2 gkmax
398integer ngvc
399! G-vector integer coordinates (i1,i2,i3)
400integer, allocatable :: ivg(:,:),ivg0(:,:)
401! map from (i1,i2,i3) to G-vector index
402integer, allocatable :: ivgig(:,:,:)
403! number of prime factors for the G-vector FFT
404integer npfftg
405! map from G-vector index to FFT array
406integer, allocatable :: igfft(:),igfft0(:)
407! number of prime factors for the coarse G-vector FFT
408integer npfftgc
409! map from G-vector index to FFT array for coarse grid
410integer, allocatable :: igfc(:)
411! number of complex FFT elements for real-complex transforms
412integer nfgrz
413! number of elements on the coarse grid
414integer nfgrzc
415! map from real-complex FFT index to G-point index
416integer, allocatable :: igrzf(:)
417! map on the coarse grid
418integer, allocatable :: igrzfc(:)
419! G-vectors in Cartesian coordinates
420real(8), allocatable :: vgc(:,:)
421! length of G-vectors
422real(8), allocatable :: gc(:)
423! Coulomb Green's function in G-space = 4π / G²
424real(8), allocatable :: gclg(:)
425! spherical Bessel functions jₗ(|G|Rₘₜ)
426real(8), allocatable :: jlgrmt(:,:,:)
427! spherical harmonics of the G-vectors
428complex(8), allocatable :: ylmg(:,:)
429! structure factors for the G-vectors
430complex(8), allocatable :: sfacg(:,:)
431! smooth step function form factors for all species and G-vectors
432real(8), allocatable :: ffacg(:,:)
433! characteristic function in G-space: 0 inside the muffin-tins and 1 outside
434complex(8), allocatable :: cfunig(:)
435! characteristic function in real-space: 0 inside the muffin-tins and 1 outside
436real(8), allocatable :: cfunir(:)
437! characteristic function in real-space for coarse grid
438real(8), allocatable :: cfrc(:)
439
440!---------------------------!
441! k-point variables !
442!---------------------------!
443! autokpt is .true. if the k-point set is determined automatically
445! radius of sphere used to determine k-point density when autokpt is .true.
446real(8) radkpt
447! k-point grid sizes
448integer ngridk(3),ngridk0(3),dngridk(3)
449! k-point offset
450real(8) vkloff(3),vkloff0(3)
451! type of reduction to perform on k-point set
452! 0 : no reduction
453! 1 : reduce with full crystal symmetry group
454! 2 : reduce with symmorphic symmetries only
456! number of point group symmetries used for k-point reduction
457integer nsymkpt
458! point group symmetry matrices used for k-point reduction
459integer symkpt(3,3,48)
460! total number of reduced k-points
461integer nkpt
462! total number of non-reduced k-points
463integer nkptnr
464! locations of k-points on integer grid
465integer, allocatable :: ivk(:,:)
466! map from integer grid to reduced k-point index
467integer, allocatable :: ivkik(:,:,:)
468! map from integer grid to non-reduced k-point index
469integer, allocatable :: ivkiknr(:,:,:)
470! k-points in lattice coordinates
471real(8), allocatable :: vkl(:,:)
472! k-points in Cartesian coordinates
473real(8), allocatable :: vkc(:,:)
474! reduced k-point weights
475real(8), allocatable :: wkpt(:)
476! weight of each non-reduced k-point
477real(8) wkptnr
478! k-point at which to determine effective mass tensor
479real(8) vklem(3)
480! displacement size for computing the effective mass tensor
481real(8) deltaem
482! number of displacements in each direction
483integer ndspem
484! number of k-points subdivision used for calculating the polarisation phase
485integer nkspolar
486
487!------------------------------!
488! G+k-vector variables !
489!------------------------------!
490! species for which the muffin-tin radius will be used for calculating gkmax
491integer isgkmax
492! smallest muffin-tin radius times gkmax
494! maximum |G+k| cut-off for APW functions
495real(8) gkmax
496! number of G+k-vectors for augmented plane waves
497integer, allocatable :: ngk(:,:)
498! maximum number of G+k-vectors over all k-points
499integer ngkmax
500! index from G+k-vectors to G-vectors
501integer, allocatable :: igkig(:,:,:)
502! G+k-vectors in lattice coordinates
503real(8), allocatable :: vgkl(:,:,:,:)
504! G+k-vectors in Cartesian coordinates
505real(8), allocatable :: vgkc(:,:,:,:)
506! length of G+k-vectors
507real(8), allocatable :: gkc(:,:,:)
508! structure factors for the G+k-vectors
509complex(8), allocatable :: sfacgk(:,:,:,:)
510
511!---------------------------!
512! q-point variables !
513!---------------------------!
514! q-point grid sizes
515integer ngridq(3)
516! integer grid intervals for the q-points
517integer intq(2,3)
518! type of reduction to perform on q-point set (see reducek)
519integer reduceq
520! number of point group symmetries used for q-point reduction
521integer nsymqpt
522! point group symmetry matrices used for q-point reduction
523integer symqpt(3,3,48)
524! total number of reduced q-points
525integer nqpt
526! total number of non-reduced q-points
527integer nqptnr
528! locations of q-points on integer grid
529integer, allocatable :: ivq(:,:)
530! map from integer grid to reduced index
531integer, allocatable :: ivqiq(:,:,:)
532! map from integer grid to non-reduced index
533integer, allocatable :: ivqiqnr(:,:,:)
534! number of prime factors for the q-vector FFT
535integer npfftq
536! map from q-vector index to complex-complex FFT array
537integer, allocatable :: iqfft(:)
538! number of complex FFT elements for real-complex transforms
539integer nfqrz
540! map from q-point index to real-complex FFT index
541integer, allocatable :: ifqrz(:)
542! map from real-complex FFT index to q-point index
543integer, allocatable :: iqrzf(:)
544! q-points in lattice coordinates
545real(8), allocatable :: vql(:,:)
546! q-points in Cartesian coordinates
547real(8), allocatable :: vqc(:,:)
548! q-point weights
549real(8), allocatable :: wqpt(:)
550! weight for each non-reduced q-point
551real(8) wqptnr
552! regularised Coulomb Green's function in q-space
553real(8), allocatable :: gclq(:)
554! if t0gclq0 is .true. then the Coulomb Green's function at q = 0 is set to zero
555logical t0gclq0
556
557!-----------------------------------------------------!
558! spherical harmonic transform (SHT) matrices !
559!-----------------------------------------------------!
560! trotsht is .true. if the spherical cover used for the SHT is to be rotated
561logical :: trotsht=.false.
562! spherical cover rotation matrix
563real(8) rotsht(3,3)
564! real backward SHT matrix for lmaxi
565real(8), allocatable :: rbshti(:,:)
566! real forward SHT matrix for lmaxi
567real(8), allocatable :: rfshti(:,:)
568! real backward SHT matrix for lmaxo
569real(8), allocatable :: rbshto(:,:)
570! real forward SHT matrix for lmaxo
571real(8), allocatable :: rfshto(:,:)
572! complex backward SHT matrix for lmaxi
573complex(8), allocatable :: zbshti(:,:)
574! complex forward SHT matrix for lmaxi
575complex(8), allocatable :: zfshti(:,:)
576! complex backward SHT matrix for lmaxo
577complex(8), allocatable :: zbshto(:,:)
578! complex forward SHT matrix for lmaxo
579complex(8), allocatable :: zfshto(:,:)
580! single-precision copies of the complex SHT matrices
581complex(4), allocatable :: cbshti(:,:),cfshti(:,:)
582complex(4), allocatable :: cbshto(:,:),cfshto(:,:)
583
584!---------------------------------------------------------------!
585! density, potential and exchange-correlation variables !
586!---------------------------------------------------------------!
587! exchange-correlation functional type
588integer xctype(3)
589! exchange-correlation functional description
590character(264) xcdescr
591! exchange-correlation functional spin requirement
592integer xcspin
593! exchange-correlation functional density gradient requirement
594! 0 : no gradients
595! 1 : gradients required for GGA with no post-processing: |∇ρ|, ∇²ρ,
596! (∇ρ).(∇|∇ρ|)
597! 2 : gradients required for GGA with post-processing: |∇ρ|²
598! 3 : as 2 but with the laplacian, ∇²ρ
599! 4 : as 2 but with the kinetic energy density, τ
600! 5 : as 4 but with the laplacian, ∇²ρ
601! 6 : as 4 but for potential-only meta-GGA functionals
602integer xcgrad
603! small constant used to stabilise non-collinear GGA
604real(8) dncgga
605! kinetic energy density functional type
606integer ktype(3)
607! kinetic energy density functional description
608character(264) kdescr
609! kinetic energy density gradient requirement (see xcgrad)
610integer kgrad
611! combined target array for rhomt, rhoir, magmt and magir
612real(8), allocatable, target :: rhmg(:)
613! muffin-tin and interstitial charge density
614real(8), pointer, contiguous :: rhomt(:,:),rhoir(:)
615! muffin-tin and interstitial magnetisation vector field
616real(8), pointer, contiguous :: magmt(:,:,:),magir(:,:)
617! trhonorm is .true. if the density is to be normalised after every iteration
618logical trhonorm
619! tjr is .true. if the current density j(r) is to be calculated
620logical tjr,tjr0
621! muffin-tin and interstitial gauge-invariant current density vector field
622real(8), allocatable :: jrmt(:,:,:),jrir(:,:)
623! muffin-tin and interstitial Coulomb potential
624real(8), allocatable :: vclmt(:,:),vclir(:)
625! Poisson solver pseudocharge density constant
626integer npsd
627! lmaxo+npsd+1
628integer lnpsd
629! muffin-tin and interstitial exchange energy density
630real(8), allocatable :: exmt(:,:),exir(:)
631! muffin-tin and interstitial correlation energy density
632real(8), allocatable :: ecmt(:,:),ecir(:)
633! muffin-tin and interstitial exchange-correlation potential
634real(8), allocatable :: vxcmt(:,:),vxcir(:)
635! muffin-tin and interstitial exchange-correlation magnetic field
636real(8), allocatable :: bxcmt(:,:,:),bxcir(:,:)
637! muffin-tin and interstitial magnetic dipole field
638real(8), allocatable :: bdmt(:,:,:),bdir(:,:)
639! average dipole field in each muffin-tin
640real(8), allocatable :: bdmta(:,:)
641! tbdip is .true. if the spin and current dipole fields are to be added to the
642! Kohn-Sham magnetic field
643logical tbdip
644! dipole magnetic field scaling factor (default 1)
645real(8) bdipscf
646! combined target array for vsmt, vsir, bsmt and bsir
647real(8), allocatable, target :: vsbs(:)
648! muffin-tin Kohn-Sham effective potential
649real(8), pointer, contiguous :: vsmt(:,:)
650! interstitial Kohn-Sham effective potential
651real(8), allocatable :: vsir(:)
652! vsir multiplied by the characteristic function and stored on a coarse grid
653real(8), pointer, contiguous :: vsirc(:)
654! muffin-tin Kohn-Sham effective magnetic field in spherical coordinates and on
655! a coarse radial mesh
656real(8), pointer, contiguous :: bsmt(:,:,:)
657! interstitial Kohn-Sham effective magnetic field
658real(8), allocatable :: bsir(:,:)
659! bsir multiplied by the characteristic function and stored on a coarse grid
660real(8), pointer, contiguous :: bsirc(:,:)
661! G-space interstitial Kohn-Sham effective potential
662complex(8), allocatable :: vsig(:)
663! nosource is .true. if the field is to be made source-free
664logical nosource
665! tssxc is .true. if scaled spin exchange-correlation is to be used
666logical tssxc
667! spin exchange-correlation scaling factor
669! spin-orbit coupling radial function
670real(8), allocatable :: socfr(:,:)
671! kinetic energy density
672real(8), allocatable :: taumt(:,:,:),tauir(:,:)
673! core kinetic energy density
674real(8), allocatable :: taucr(:,:,:)
675! meta-GGA exchange-correlation potential
676real(8), allocatable :: wxcmt(:,:),wxcir(:)
677! Tran-Blaha '09 constant c [Phys. Rev. Lett. 102, 226401 (2009)]
678real(8) c_tb09
679! tc_tb09 is .true. if the Tran-Blaha constant has been read in
680logical tc_tb09
681! if trdstate is .true. the density and potential can be read from STATE.OUT
682logical :: trdstate=.false.
683! temperature in degrees Kelvin
684real(8) tempk
685! if mixrho is .true. then the (density, magnetisation) is mixed, otherwise the
686! (potential, magnetic field)
687logical mixrho
688! mixing vector: either (density, magnetisation) or (potential, magnetic field)
689real(8), pointer, contiguous :: vmixer(:)
690
691!--------------------------!
692! mixing variables !
693!--------------------------!
694! type of mixing to use for the potential
695integer mixtype
696! mixing type description
697character(64) mixdescr
698! if mixsave is .true. then the mixer work array is saved after each self-
699! consistent loop and will be read in at the beginning of a restart
700logical mixsave
701! adaptive mixing parameters (formerly beta0 and betamax)
702real(8) amixpm(2)
703! subspace dimension for Broyden mixing
704integer mixsdb
705! Broyden mixing parameters alpha and w0
706real(8) broydpm(2)
707
708!----------------------------------------------!
709! charge, moment and current variables !
710!----------------------------------------------!
711! tolerance for error in total charge
712real(8) epschg
713! total nuclear charge
714real(8) chgzn
715! core charges
717! total core charge
718real(8) chgcrtot
719! core leakage charge
720real(8), allocatable :: chgcrlk(:)
721! total valence charge
722real(8) chgval
723! excess charge
725! total charge
726real(8) chgtot
727! calculated total charge
728real(8) chgcalc
729! interstitial region charge
730real(8) chgir
731! muffin-tin charges
732real(8), allocatable :: chgmt(:)
733! total muffin-tin charge
734real(8) chgmttot
735! effective Wigner radius
736real(8) rwigner
737! total moment
738real(8) momtot(3)
739! total moment magnitude
740real(8) momtotm
741! interstitial region moment
742real(8) momir(3)
743! muffin-tin moments
744real(8), allocatable :: mommt(:,:)
745! total muffin-tin moment
746real(8) mommttot(3)
747! total gauge-invariant current and its magnitude
748real(8) jtot(3),jtotm
749
750!-----------------------------------------!
751! APW and local-orbital variables !
752!-----------------------------------------!
753! maximum allowable APW order
754integer, parameter :: maxapword=3
755! polynomial order used for APW radial derivatives
756integer, parameter :: npapw=8
757! APW order
759! maximum of apword over all angular momenta and species
761! total number of APW coefficients (l, m and order) for each species
763! energy step size used for APW numerical derivatives
764real(8) deapw
765! APW initial linearisation energies
767! APW linearisation energies
768real(8), allocatable :: apwe(:,:,:)
769! APW derivative order
771! apwve is .true. if the linearisation energies are allowed to vary
773! APW radial functions
774real(8), allocatable :: apwfr(:,:,:,:,:)
775! single-precision APW radial functions
776real(4), allocatable :: apwfr_sp(:,:,:,:)
777! derivative of radial functions at the muffin-tin surface multiplied by R_MT²/2
778real(8), allocatable :: apwdfr(:,:,:)
779! maximum number of local-orbitals
780integer, parameter :: maxlorb=200
781! maximum allowable local-orbital order
782integer, parameter :: maxlorbord=4
783! polynomial order used for local-orbital radial derivatives
784integer, parameter :: nplorb=8
785! number of local-orbitals
787! maximum nlorb over all species
788integer nlomax
789! total number of local-orbitals
790integer nlotot
791! local-orbital order
793! maximum lorbord over all species
795! local-orbital angular momentum
797! maximum lorbl over all species
798integer lolmax
799! (lolmax+1)²
800integer lolmmax
801! energy step size used for local-orbital numerical derivatives
802real(8) delorb
803! local-orbital initial energies
805! index which arranges the local-orbitals in ascending order of energy
807! local-orbital energies
808real(8), allocatable :: lorbe(:,:,:)
809! local-orbital derivative order
811! lorbve is .true. if the linearisation energies are allowed to vary
813! local-orbital radial functions
814real(8), allocatable :: lofr(:,:,:,:)
815! single-precision local-orbital radial functions
816real(4), allocatable :: lofr_sp(:,:,:)
817! tfr_sp is .true. if the single-precision radial functions are to be stored
818logical tfr_sp
819! band energy search tolerance
820real(8) epsband
821! maximum allowed change in energy during band energy search; enforced only if
822! default energy is less than zero
823real(8) demaxbnd
824! minimum default linearisation energy over all APWs and local-orbitals
825real(8) e0min
826! if autolinengy is .true. then the fixed linearisation energies are set to the
827! Fermi energy minus dlefe
829! difference between linearisation and Fermi energies when autolinengy is .true.
830real(8) dlefe
831! lorbcnd is .true. if conduction state local-orbitals should be added
832logical lorbcnd
833! conduction state local-orbital order
834integer lorbordc
835! excess order of the APW and local-orbital functions
836integer nxoapwlo
837! excess local orbitals
838integer nxlo
839! number of (l,m) components used for generating the muffin-tin wavefunctions
841
842!-------------------------------------------!
843! overlap and Hamiltonian variables !
844!-------------------------------------------!
845! overlap and Hamiltonian matrices sizes at each k-point
846integer, allocatable :: nmat(:,:)
847! maximum nmat over all k-points
848integer nmatmax
849! index to the position of the local-orbitals in the H and O matrices
850integer, allocatable :: idxlo(:,:,:)
851! APW-local-orbital overlap integrals
852real(8), allocatable :: oalo(:,:,:)
853! local-orbital-local-orbital overlap integrals
854real(8), allocatable :: ololo(:,:,:)
855! APW-APW Hamiltonian integrals
856real(8), allocatable :: haa(:,:,:,:,:,:)
857! local-orbital-APW Hamiltonian integrals
858real(8), allocatable :: hloa(:,:,:,:,:)
859! local-orbital-local-orbital Hamiltonian integrals
860real(8), allocatable :: hlolo(:,:,:,:)
861! complex Gaunt coefficient array
862complex(8), allocatable :: gntyry(:,:,:)
863! tefvr is .true. if the first-variational eigenvalue equation is to be solved
864! as a real symmetric problem
865logical tefvr
866! tefvit is .true. if the first-variational eigenvalue equation is to be solved
867! iteratively
868logical tefvit
869! minimum and maximum allowed number of eigenvalue equation iterations
871! eigenvalue mixing parameter for iterative solver
872real(8) befvit
873! iterative solver convergence tolerance
874real(8) epsefvit
875
876!--------------------------------------------!
877! eigenvalue and occupancy variables !
878!--------------------------------------------!
879! number of empty states per atom and spin
881! number of empty states
882integer nempty
883! number of first-variational states
884integer nstfv
885! number of second-variational states
886integer nstsv
887! smearing type
888integer stype
889! smearing function description
890character(64) sdescr
891! smearing width
893! autoswidth is .true. if the smearing width is to be determined automatically
895! effective mass used in smearing width formula
896real(8) mstar
897! maximum allowed occupancy (1 or 2)
898real(8) occmax
899! convergence tolerance for occupation numbers
900real(8) epsocc
901! second-variational occupation numbers
902real(8), allocatable :: occsv(:,:)
903! Fermi energy for second-variational states
904real(8) efermi
905! tscissor is .true. if the scissor correction is non-zero
906logical tscissor
907! scissor correction applied to eigenvalues and momentum matrix elements
908real(8) scissor
909! density of states at the Fermi energy
910real(8) fermidos
911! estimated indirect and direct band gaps
912real(8) bandgap(2)
913! k-points of indirect and direct gaps
914integer ikgap(3)
915! error tolerance for the first-variational eigenvalues
916real(8) evaltol
917! second-variational eigenvalues
918real(8), allocatable :: evalsv(:,:)
919! tevecsv is .true. if second-variational eigenvectors are calculated
920logical tevecsv
921! maximum number of k-point and states indices in user-defined list
922integer, parameter :: maxkst=20
923! number of k-point and states indices in user-defined list
924integer nkstlist
925! user-defined list of k-point and state indices
926integer kstlist(2,maxkst)
927
928!------------------------------!
929! core state variables !
930!------------------------------!
931! occupation numbers for core states
932real(8), allocatable :: occcr(:,:)
933! eigenvalues for core states
934real(8), allocatable :: evalcr(:,:)
935! radial wavefunctions for core states
936real(8), allocatable :: rwfcr(:,:,:,:)
937! radial charge density for core states
938real(8), allocatable :: rhocr(:,:,:)
939! spincore is .true. if the core is to be treated as spin-polarised
940logical spincore
941! number of core spin-channels
942integer nspncr
943
944!--------------------------!
945! energy variables !
946!--------------------------!
947! core, valence and total occupied eigenvalue sum
948real(8) evalsum
949! electron kinetic energy
950real(8) engykn
951! core electron kinetic energy
952real(8) engykncr
953! nuclear-nuclear energy
954real(8) engynn
955! electron-nuclear energy
956real(8) engyen
957! Hartree energy
958real(8) engyhar
959! Coulomb energy (E_nn + E_en + E_H)
960real(8) engycl
961! electronic Coulomb potential energy
962real(8) engyvcl
963! Madelung term
964real(8) engymad
965! exchange-correlation potential energy
966real(8) engyvxc
967! exchange-correlation effective field energy
968real(8) engybxc
969! energy of external global magnetic field
970real(8) engybext
971! exchange energy
972real(8) engyx
973! correlation energy
974real(8) engyc
975! electronic entropy
976real(8) entrpy
977! entropic contribution to free energy
978real(8) engyts
979! total energy
980real(8) engytot
981
982!--------------------------------------------!
983! force, stress and strain variables !
984!--------------------------------------------!
985! tforce is .true. if force should be calculated
987! Hellmann-Feynman force on each atom
988real(8), allocatable :: forcehf(:,:)
989! total force on each atom
990real(8), allocatable :: forcetot(:,:)
991! previous total force on each atom
992real(8), allocatable :: forcetotp(:,:)
993! maximum force magnitude over all atoms
994real(8) forcemax
995! maximum allowed force magnitude; if this force is reached for any atom then
996! all forces are rescaled so that the maximum force magnitude is this value
997real(8) maxforce
998! tfav0 is .true. if the average force should be zero in order to prevent
999! translation of the atomic basis
1001! atomic position optimisation type
1002! 0 : no optimisation
1003! 1 : unconstrained optimisation
1004integer atpopt
1005! maximum number of atomic position optimisation steps
1007! default step size parameter for atomic position optimisation
1008real(8) tau0atp
1009! step size parameters for each atom
1010real(8), allocatable :: tauatp(:)
1011! number of strain tensors
1012integer nstrain
1013! current strain tensor
1014integer :: istrain=0
1015! strain tensors
1016real(8) strain(3,3,9)
1017! small displacement parameter multiplied by the strain tensor for computing the
1018! stress tensor; also used for calculating the piezoelectric tensor
1019real(8) deltast
1020! symmetry reduced stress tensor components
1021real(8) stress(9)
1022! previous stress tensor
1023real(8) stressp(9)
1024! stress tensor component magnitude maximum
1026! reference lattice vectors for generating the G-vectors and derived quantities
1027real(8) avecref(3,3)
1028! tavref is .true. if avecref is non-zero
1029logical tavref
1030! lattice vector optimisation type
1031! 0 : no optimisation
1032! 1 : unconstrained optimisation
1033! 2 : iso-volumetric optimisation
1034integer latvopt
1035! maximum number of lattice vector optimisation steps
1037! default step size parameter for lattice vector optimisation
1039! step size for each stress tensor component acting on the lattice vectors
1040real(8) taulatv(9)
1041
1042!--------------------------------------------------------!
1043! self-consistent loop and convergence variables !
1044!--------------------------------------------------------!
1045! maximum number of self-consistent loops
1047! current self-consistent loop number
1048integer iscl
1049! tlast is .true. if the calculation is on the last self-consistent loop
1050logical tlast
1051! tstop is .true. if the STOP file exists
1052logical tstop
1053! trestart is .true. if the code should be completely restarted
1055! number of self-consistent loops after which STATE.OUT is written
1056integer nwrite
1057! Kohn-Sham potential convergence tolerance
1058real(8) epspot
1059! energy convergence tolerance
1060real(8) epsengy
1061! force convergence tolerance
1063! stress tensor convergence tolerance
1065
1066!----------------------------------------------------------!
1067! density of states, optics and response variables !
1068!----------------------------------------------------------!
1069! number of energy intervals in the DOS/optics function plot
1070integer nwplot
1071! fine k-point grid size for integration of functions in the Brillouin zone
1072integer ngrkf
1073! smoothing level for DOS/optics function plot
1074integer nswplot
1075! energy interval for DOS/optics function plot
1076real(8) wplot(2)
1077! maximum angular momentum for the partial DOS plot
1078integer lmaxdos
1079! dosocc is .true. if the DOS is to be weighted by the occupancy
1080logical dosocc
1081! tpdos is .true. if the partial DOS should be calculated
1082logical tpdos
1083! dosmsum is .true. if the partial DOS is to be summed over m
1084logical dosmsum
1085! dosssum is .true. if the partial DOS is to be summed over spin
1086logical dosssum
1087! number of optical matrix components required
1089! required optical matrix components
1090integer optcomp(3,27)
1091! intraband is .true. if the intraband term is to be added to the optical matrix
1093! lmirep is .true. if the (l,m) band characters should correspond to the
1094! irreducible representations of the site symmetries
1095logical lmirep
1096! spin-quantisation axis in Cartesian coordinates used when plotting the
1097! spin-resolved DOS (z-axis by default)
1098real(8) sqados(3)
1099! q-vector in lattice and Cartesian coordinates for calculating the matrix
1100! elements ⟨i,k+q| exp(iq⋅r) |j,k⟩
1101real(8) vecql(3),vecqc(3)
1102! maximum initial-state energy allowed in ELNES transitions
1104! structure factor energy window
1105real(8) wsfac(2)
1106
1107!-------------------------------------!
1108! 1D/2D/3D plotting variables !
1109!-------------------------------------!
1110! number of vertices in 1D plot
1111integer nvp1d
1112! total number of points in 1D plot
1113integer npp1d
1114! starting point for 1D plot
1115integer ip01d
1116! vertices in lattice coordinates for 1D plot
1117real(8), allocatable :: vvlp1d(:,:)
1118! distance to vertices in 1D plot
1119real(8), allocatable :: dvp1d(:)
1120! plot vectors in lattice coordinates for 1D plot
1121real(8), allocatable :: vplp1d(:,:)
1122! distance to points in 1D plot
1123real(8), allocatable :: dpp1d(:)
1124! corner vectors of 2D plot in lattice coordinates
1125real(8) vclp2d(3,0:2)
1126! grid sizes of 2D plot
1127integer np2d(2)
1128! corner vectors of 3D plot in lattice coordinates
1129real(8) vclp3d(3,0:3)
1130! grid sizes of 3D plot
1131integer np3d(3)
1132
1133!-------------------------------------------------------------!
1134! OEP, Hartree-Fock and Kohn-Sham inversion variables !
1135!-------------------------------------------------------------!
1136! maximum number of core states over all species
1137integer ncrmax
1138! maximum number of OEP iterations
1140! OEP initial and subsequent step sizes
1142! exchange potential and magnetic field
1143real(8), allocatable :: vxmt(:,:),vxir(:),bxmt(:,:,:),bxir(:,:)
1144! OEP residual functions
1145real(8), allocatable :: dvxmt(:,:),dvxir(:),dbxmt(:,:,:),dbxir(:,:)
1146! magnitude of the OEP residual
1147real(8) resoep
1148! hybrid is .true. if a hybrid functional is to be used
1150! hybrid functional mixing coefficient
1151real(8) hybridc
1152
1153!-------------------------------------------------------------!
1154! response function and perturbation theory variables !
1155!-------------------------------------------------------------!
1156! |G| cut-off for response functions
1157real(8) gmaxrf
1158! energy cut-off for response functions
1159real(8) emaxrf
1160! number of G-vectors for response functions
1161integer ngrf
1162! matrix bandwidth of response functions in the G-vector basis
1163integer mbwgrf
1164! number of response function frequencies
1165integer nwrf
1166! complex response function frequencies
1167complex(8), allocatable :: wrf(:)
1168! maximum number of spherical Bessel functions on the coarse radial mesh over
1169! all species
1170integer njcmax
1171
1172!-------------------------------------------------!
1173! Bethe-Salpeter equation (BSE) variables !
1174!-------------------------------------------------!
1175! number of valence and conduction states for transitions
1177! default number of valence and conduction states
1179! maximum number of extra valence and conduction states
1180integer, parameter :: maxxbse=20
1181! number of extra valence and conduction states
1183! extra valence and conduction states
1185! total number of transitions
1186integer nvcbse
1187! size of blocks in BSE Hamiltonian matrix
1188integer nbbse
1189! size of BSE matrix (= 2*nbbse)
1190integer nmbse
1191! index from BSE valence states to second-variational states
1192integer, allocatable :: istbse(:,:)
1193! index from BSE conduction states to second-variational states
1194integer, allocatable :: jstbse(:,:)
1195! index from BSE valence-conduction pair and k-point to location in BSE matrix
1196integer, allocatable :: ijkbse(:,:,:)
1197! BSE Hamiltonian
1198complex(8), allocatable :: hmlbse(:,:)
1199! BSE Hamiltonian eigenvalues
1200real(8), allocatable :: evalbse(:)
1201! if bsefull is .true. then the full BSE Hamiltonian is calculated, otherwise
1202! only the Hermitian block
1203logical bsefull
1204! if hxbse/hdbse is .true. then the exchange/direct term is included in the BSE
1205! Hamiltonian
1207
1208!--------------------------!
1209! timing variables !
1210!--------------------------!
1211! initialisation
1213! Hamiltonian and overlap matrix set up
1214real(8) timemat
1215! first-variational calculation
1216real(8) timefv
1217! second-variational calculation
1218real(8) timesv
1219! charge density calculation
1220real(8) timerho
1221! potential calculation
1222real(8) timepot
1223! force calculation
1224real(8) timefor
1225
1226!-----------------------------!
1227! numerical constants !
1228!-----------------------------!
1229real(8), parameter :: pi=3.1415926535897932385d0
1230real(8), parameter :: twopi=6.2831853071795864769d0
1231real(8), parameter :: fourpi=12.566370614359172954d0
1232! spherical harmonic Y₀₀ = 1/√4π and its inverse
1233real(8), parameter :: y00=0.28209479177387814347d0
1234real(8), parameter :: y00i=3.54490770181103205460d0
1235! complex constants
1236complex(4), parameter :: czero=(0.e0,0.e0),cone=(1.e0,0.e0)
1237complex(4), parameter :: ci=(0.e0,1.e0),cmi=(0.e0,-1.e0)
1238complex(8), parameter :: zzero=(0.d0,0.d0),zone=(1.d0,0.d0)
1239complex(8), parameter :: zi=(0.d0,1.d0),zmi=(0.d0,-1.d0)
1240! Pauli spin matrices:
1241! σ_x = ⎛0 1⎞ σ_y = ⎛0 -i⎞ σ_z = ⎛1 0⎞
1242! ⎝1 0⎠ ⎝i 0⎠ ⎝0 -1⎠
1243! Planck constant in SI units (exact, CODATA 2018)
1244real(8), parameter :: h_si=6.62607015d-34
1245! reduced Planck constant ℏ in SI units
1246real(8), parameter :: hbar_si=h_si/twopi
1247! speed of light in SI units (exact, CODATA 2018)
1248real(8), parameter :: sol_si=299792458d0
1249! speed of light in atomic units (1/α) (CODATA 2018)
1250real(8), parameter :: sol=137.035999084d0
1251! scaled speed of light
1252real(8) solsc
1253! Hartree in SI units (CODATA 2018)
1254real(8), parameter :: ha_si=4.3597447222071d-18
1255! Hartree in eV (CODATA 2018)
1256real(8), parameter :: ha_ev=27.211386245988d0
1257! Hartree in inverse meters
1258real(8), parameter :: ha_im=ha_si/(h_si*sol_si)
1259! Boltzmann constant in SI units (exact, CODATA 2018)
1260real(8), parameter :: kb_si=1.380649d-23
1261! Boltzmann constant in Hartree/kelvin
1262real(8), parameter :: kboltz=kb_si/ha_si
1263! electron charge in SI units (exact, CODATA 2018)
1264real(8), parameter :: e_si=1.602176634d-19
1265! Bohr radius in SI units (CODATA 2018)
1266real(8), parameter :: br_si=0.529177210903d-10
1267! Bohr radius in Angstroms
1268real(8), parameter :: br_ang=br_si*1.d10
1269! atomic unit of magnetic flux density in SI
1270real(8), parameter :: b_si=hbar_si/(e_si*br_si**2)
1271! atomic unit of electric field in SI
1272real(8), parameter :: ef_si=ha_si/(e_si*br_si)
1273! atomic unit of time in SI
1274real(8), parameter :: t_si=hbar_si/ha_si
1275! electron g-factor (CODATA 2018)
1276real(8), parameter :: gfacte=2.00231930436256d0
1277! electron mass in SI (CODATA 2018)
1278real(8), parameter :: em_si=9.1093837015d-31
1279! atomic mass unit in SI (CODATA 2018)
1280real(8), parameter :: amu_si=1.66053906660d-27
1281! atomic mass unit in electron masses
1282real(8), parameter :: amu=amu_si/em_si
1283
1284!---------------------------------!
1285! miscellaneous variables !
1286!---------------------------------!
1287! code version
1288integer, parameter :: version(3)=[10,6,11]
1289! maximum number of tasks
1290integer, parameter :: maxtasks=40
1291! number of tasks
1292integer ntasks
1293! task index
1294integer itask
1295! task array
1297! current task
1298integer task
1299! filename extension for files generated by gndstate
1300character(256) :: filext='.OUT'
1301! scratch space path
1302character(256) scrpath
1303! number of note lines
1304integer notelns
1305! notes to include in INFO.OUT
1306character(256), allocatable :: notes(:)
1307
1308end module
1309
real(8) resoep
Definition modmain.f90:1147
real(8), dimension(:,:,:,:), allocatable vgkc
Definition modmain.f90:505
integer, dimension(maxstsp, maxspecies) lsp
Definition modmain.f90:123
real(8) deltast
Definition modmain.f90:1019
real(8), dimension(:,:), allocatable rhosp
Definition modmain.f90:137
real(8) rndatposc
Definition modmain.f90:56
real(8) gmaxvr
Definition modmain.f90:384
real(8), dimension(:,:), allocatable evalcr
Definition modmain.f90:934
logical bsefull
Definition modmain.f90:1203
integer, dimension(maxspecies) nrmti
Definition modmain.f90:211
real(8), parameter y00
Definition modmain.f90:1233
logical spinorb0
Definition modmain.f90:230
logical, dimension(:,:), allocatable tfeqat
Definition modmain.f90:372
real(8), dimension(:,:,:), allocatable wcrmt
Definition modmain.f90:187
logical tscissor
Definition modmain.f90:906
real(8), dimension(:), allocatable wkpt
Definition modmain.f90:475
integer nspncr
Definition modmain.f90:942
real(8) epsengy
Definition modmain.f90:1060
real(8), parameter gfacte
Definition modmain.f90:1276
real(8), dimension(3) sqados
Definition modmain.f90:1098
real(8) delorb
Definition modmain.f90:802
integer lmaxi0
Definition modmain.f90:205
integer, dimension(2, 3) intq
Definition modmain.f90:517
real(8), dimension(:,:), allocatable rmtl
Definition modmain.f90:167
real(8) chgmttot
Definition modmain.f90:734
logical tjr0
Definition modmain.f90:620
integer nfgrzc
Definition modmain.f90:414
integer, dimension(48) isymlat
Definition modmain.f90:348
integer reduceq
Definition modmain.f90:519
integer nstrain
Definition modmain.f90:1012
real(8) hybridc
Definition modmain.f90:1151
integer, dimension(:,:), allocatable ivg0
Definition modmain.f90:400
integer natmtot0
Definition modmain.f90:40
real(8), dimension(3) bfieldc
Definition modmain.f90:269
real(8), dimension(3) jtot
Definition modmain.f90:748
logical tbdip
Definition modmain.f90:643
real(8) epspot
Definition modmain.f90:1058
integer natmmax
Definition modmain.f90:38
integer lorbordmax
Definition modmain.f90:794
real(8), parameter y00i
Definition modmain.f90:1234
real(8), dimension(:,:,:), allocatable bxcmt
Definition modmain.f90:636
integer njcmax
Definition modmain.f90:1170
real(8), dimension(3, 3) avec0
Definition modmain.f90:12
logical dosssum
Definition modmain.f90:1086
real(8) epsforce
Definition modmain.f90:1062
real(8), dimension(3) bfieldc00
Definition modmain.f90:271
real(8), dimension(:), allocatable gclq
Definition modmain.f90:553
logical hxbse
Definition modmain.f90:1206
real(8), dimension(3, maxatoms, maxspecies) datposl
Definition modmain.f90:52
real(8) drgkmax
Definition modmain.f90:493
real(8), dimension(3) mommttot
Definition modmain.f90:746
integer itask
Definition modmain.f90:1294
integer nwrite
Definition modmain.f90:1056
integer, dimension(2, 3) intgv
Definition modmain.f90:394
integer, dimension(2) np2d
Definition modmain.f90:1127
complex(8), parameter zzero
Definition modmain.f90:1238
integer npp1d
Definition modmain.f90:1113
real(8), dimension(3, 0:2) vclp2d
Definition modmain.f90:1125
real(8), dimension(maxapword, 0:maxlapw, maxspecies) apwe0
Definition modmain.f90:766
integer ngtot
Definition modmain.f90:390
integer, dimension(3) ngridg
Definition modmain.f90:386
logical autoswidth
Definition modmain.f90:894
real(8), dimension(3) efieldc
Definition modmain.f90:312
logical autokpt0
Definition modmain.f90:444
logical spinsprl0
Definition modmain.f90:283
logical ncmag
Definition modmain.f90:240
real(8) radkpt
Definition modmain.f90:446
real(8), dimension(:,:), allocatable rfshto
Definition modmain.f90:571
real(8) atdfc
Definition modmain.f90:66
real(8) swidth0
Definition modmain.f90:892
logical tshift
Definition modmain.f90:352
integer nxlo
Definition modmain.f90:838
integer, parameter maxlapw
Definition modmain.f90:195
complex(4), parameter czero
Definition modmain.f90:1236
complex(8), dimension(:), allocatable zqss
Definition modmain.f90:287
integer kgrad
Definition modmain.f90:610
integer nvcbse
Definition modmain.f90:1186
complex(4), parameter ci
Definition modmain.f90:1237
real(8) evaltol
Definition modmain.f90:916
integer, parameter maxxbse
Definition modmain.f90:1180
integer npfftq
Definition modmain.f90:535
integer, dimension(maxstsp, maxspecies) nsp
Definition modmain.f90:121
real(8) forcemax
Definition modmain.f90:994
real(8), dimension(:,:,:), allocatable gkc
Definition modmain.f90:507
real(8) efermi
Definition modmain.f90:904
integer nsymlat
Definition modmain.f90:342
integer nkptnr
Definition modmain.f90:463
real(8), dimension(:,:,:), allocatable apwe
Definition modmain.f90:768
real(8), parameter pi
Definition modmain.f90:1229
complex(8), parameter zmi
Definition modmain.f90:1239
real(8), dimension(:), allocatable chgcrlk
Definition modmain.f90:720
real(8) chgcalc
Definition modmain.f90:728
logical mixrho
Definition modmain.f90:687
character(264) kdescr
Definition modmain.f90:608
integer nspinor
Definition modmain.f90:267
logical trhonorm
Definition modmain.f90:618
logical tfav00
Definition modmain.f90:1000
integer, dimension(:,:), allocatable istbse
Definition modmain.f90:1192
real(8), dimension(3) afieldc0
Definition modmain.f90:325
integer, parameter maxstsp
Definition modmain.f90:111
real(8), dimension(3) vkloff0
Definition modmain.f90:450
real(8), dimension(:), allocatable cfrc
Definition modmain.f90:438
integer dlmaxo
Definition modmain.f90:201
real(8), dimension(:,:,:), pointer, contiguous magmt
Definition modmain.f90:616
integer symtype
Definition modmain.f90:340
real(8) nrmtscf
Definition modmain.f90:148
real(8), dimension(3, 3, 48) symlatc
Definition modmain.f90:350
character(256), dimension(maxspecies) spfname
Definition modmain.f90:74
integer nfgrz
Definition modmain.f90:412
integer, dimension(3) ngdgc
Definition modmain.f90:388
real(8) dsxcscf
Definition modmain.f90:668
logical tefvit
Definition modmain.f90:868
integer, dimension(3) ngridk0
Definition modmain.f90:448
real(8), dimension(3, maxatoms, maxspecies) atposc
Definition modmain.f90:54
integer ngrkf
Definition modmain.f90:1072
real(8), dimension(:,:), allocatable bdir
Definition modmain.f90:638
integer dlmaxapw
Definition modmain.f90:197
integer xcspin
Definition modmain.f90:592
integer nfqrz
Definition modmain.f90:539
integer nvp1d
Definition modmain.f90:1111
real(8) epsstress
Definition modmain.f90:1064
integer, dimension(maxspecies) nrmt
Definition modmain.f90:150
real(8) deltabf
Definition modmain.f90:281
integer, dimension(3, 27) optcomp
Definition modmain.f90:1090
real(8), dimension(3, 3) dafspc
Definition modmain.f90:331
integer npmae
Definition modmain.f90:302
integer, dimension(maxspecies) natoms
Definition modmain.f90:36
real(8), dimension(:), pointer, contiguous rhoir
Definition modmain.f90:614
character(256) filext
Definition modmain.f90:1300
real(8) momfixm
Definition modmain.f90:255
logical, dimension(maxstsp, maxspecies) spcore
Definition modmain.f90:127
integer nvbse0
Definition modmain.f90:1178
real(8), dimension(:,:), allocatable exmt
Definition modmain.f90:630
complex(4), parameter cmi
Definition modmain.f90:1237
real(8) timepot
Definition modmain.f90:1222
real(8) reducebf0
Definition modmain.f90:279
real(8) nempty0
Definition modmain.f90:880
real(8), dimension(3) afieldc
Definition modmain.f90:325
logical ptnucl
Definition modmain.f90:83
logical nosource
Definition modmain.f90:664
real(8), parameter hbar_si
Definition modmain.f90:1246
integer, dimension(:,:,:), allocatable ieqatom
Definition modmain.f90:368
real(8), dimension(:,:), allocatable rcmt
Definition modmain.f90:177
real(8), dimension(3) momfix
Definition modmain.f90:253
real(8) engykn
Definition modmain.f90:950
real(8), dimension(:,:), allocatable dbxir
Definition modmain.f90:1145
complex(4), dimension(:,:), allocatable cfshti
Definition modmain.f90:581
real(8), dimension(:,:), allocatable mommt
Definition modmain.f90:744
character(64) mixdescr
Definition modmain.f90:697
real(8), dimension(3, 3) bvec
Definition modmain.f90:16
real(8), parameter br_ang
Definition modmain.f90:1268
real(8), dimension(maxspecies) rmt
Definition modmain.f90:162
integer, dimension(:,:), allocatable ivq
Definition modmain.f90:529
integer npmae0
Definition modmain.f90:302
real(8) engykncr
Definition modmain.f90:952
real(8), dimension(:,:), allocatable bxir
Definition modmain.f90:1143
integer msmgmt
Definition modmain.f90:222
integer, dimension(:,:,:), allocatable idxlo
Definition modmain.f90:850
integer, dimension(maxatoms, maxspecies) idxas
Definition modmain.f90:42
integer nvxbse
Definition modmain.f90:1182
integer, dimension(maxspecies) npcmti
Definition modmain.f90:214
complex(8), dimension(:,:), allocatable zfshto
Definition modmain.f90:579
real(8), dimension(:,:,:), allocatable taumt
Definition modmain.f90:672
real(8), dimension(:,:,:), allocatable jlgrmt
Definition modmain.f90:426
real(8), dimension(3) vecql
Definition modmain.f90:1101
real(8), dimension(3, maxatoms, maxspecies) bfcmt
Definition modmain.f90:273
integer lmmaxi
Definition modmain.f90:207
character(64) sdescr
Definition modmain.f90:890
logical spinpol
Definition modmain.f90:228
real(8), parameter em_si
Definition modmain.f90:1278
real(8), dimension(:,:), allocatable tpmae
Definition modmain.f90:304
character(256) scrpath
Definition modmain.f90:1302
real(8) chgcrtot
Definition modmain.f90:718
integer nbbse
Definition modmain.f90:1188
logical spincore
Definition modmain.f90:940
integer, dimension(:), allocatable igrzf
Definition modmain.f90:416
real(4), dimension(:,:,:,:), allocatable apwfr_sp
Definition modmain.f90:776
real(8) omega
Definition modmain.f90:20
integer, dimension(maxspecies) npmti
Definition modmain.f90:213
integer fsmtype
Definition modmain.f90:251
real(8), parameter amu
Definition modmain.f90:1282
real(8) timefor
Definition modmain.f90:1224
integer, dimension(:,:), allocatable lspnsyms
Definition modmain.f90:378
integer maxlatvstp
Definition modmain.f90:1036
real(8), dimension(:,:), allocatable rbshto
Definition modmain.f90:569
real(8), dimension(:,:), allocatable ecmt
Definition modmain.f90:632
complex(8), parameter zi
Definition modmain.f90:1239
real(8), dimension(3, maxatoms, maxspecies) mommtfix0
Definition modmain.f90:259
integer ngvec
Definition modmain.f90:396
integer nwplot
Definition modmain.f90:1070
real(8) engyhar
Definition modmain.f90:958
real(8) esccut
Definition modmain.f90:119
real(8), parameter sol
Definition modmain.f90:1250
integer, dimension(:,:), allocatable ngk
Definition modmain.f90:497
integer, dimension(:), allocatable nsymsite
Definition modmain.f90:374
real(8) engynn
Definition modmain.f90:954
real(8), dimension(:,:), allocatable bfsmcmt
Definition modmain.f90:263
integer nstspmax
Definition modmain.f90:115
real(8) deltaem
Definition modmain.f90:481
real(8), dimension(2) broydpm
Definition modmain.f90:706
real(8) chgval
Definition modmain.f90:722
integer, dimension(:,:,:), allocatable igkig
Definition modmain.f90:501
integer, parameter maxapword
Definition modmain.f90:754
real(8), dimension(2) wsfac
Definition modmain.f90:1105
real(8), dimension(3) vecqc
Definition modmain.f90:1101
real(8), dimension(3, 3) avecref
Definition modmain.f90:1027
real(8), parameter twopi
Definition modmain.f90:1230
real(8), dimension(:,:,:), allocatable taucr
Definition modmain.f90:674
real(8), dimension(:,:), allocatable ffacg
Definition modmain.f90:432
integer, dimension(maxspecies) nrcmt
Definition modmain.f90:173
integer nxoapwlo
Definition modmain.f90:836
real(8), dimension(:,:), allocatable rbshti
Definition modmain.f90:565
integer, dimension(3) ktype
Definition modmain.f90:606
integer lolmax
Definition modmain.f90:798
logical trmt0
Definition modmain.f90:165
integer nwrf
Definition modmain.f90:1165
real(8), dimension(3, 3) binv
Definition modmain.f90:18
integer, dimension(:,:), allocatable ivk
Definition modmain.f90:465
real(8), dimension(:,:), allocatable vvlp1d
Definition modmain.f90:1117
real(8), dimension(:,:), allocatable bxcir
Definition modmain.f90:636
real(8), parameter ha_ev
Definition modmain.f90:1256
real(8) mstar
Definition modmain.f90:896
logical lmirep
Definition modmain.f90:1095
integer, dimension(3) ikgap
Definition modmain.f90:914
real(8) engycl
Definition modmain.f90:960
integer nqptnr
Definition modmain.f90:527
complex(8), dimension(:), allocatable cfunig
Definition modmain.f90:434
logical trotsht
Definition modmain.f90:561
integer npfftg
Definition modmain.f90:404
complex(8), parameter zone
Definition modmain.f90:1238
real(8) ecvcut
Definition modmain.f90:117
complex(8), dimension(:,:), allocatable zbshto
Definition modmain.f90:577
real(8) gkmax
Definition modmain.f90:495
integer nswplot
Definition modmain.f90:1074
real(8), dimension(3, 3) bvec0
Definition modmain.f90:16
integer ip01d
Definition modmain.f90:1115
integer, dimension(3) xctype
Definition modmain.f90:588
integer atpopt
Definition modmain.f90:1004
complex(8), dimension(:,:), allocatable hmlbse
Definition modmain.f90:1198
real(8) engyvcl
Definition modmain.f90:962
integer, dimension(:,:,:), allocatable ivqiq
Definition modmain.f90:531
integer, dimension(0:maxlapw, maxspecies) apword
Definition modmain.f90:758
logical spinorb
Definition modmain.f90:230
real(8), dimension(:,:), allocatable rsp
Definition modmain.f90:135
real(8) entrpy
Definition modmain.f90:976
integer notelns
Definition modmain.f90:1304
real(8) demaxbnd
Definition modmain.f90:823
integer, dimension(maxatoms *maxspecies) idxia
Definition modmain.f90:45
integer, dimension(:), allocatable igfc
Definition modmain.f90:410
integer, dimension(:,:), allocatable lsplsyms
Definition modmain.f90:376
real(8), dimension(:), allocatable vxcir
Definition modmain.f90:634
real(8) taufsm
Definition modmain.f90:265
real(8), dimension(2) bandgap
Definition modmain.f90:912
integer mixsdb
Definition modmain.f90:704
logical molecule
Definition modmain.f90:47
integer, dimension(maxatoms *maxspecies) idxis
Definition modmain.f90:44
real(8), dimension(maxlorbord, maxlorb, maxspecies) lorbe0
Definition modmain.f90:804
real(8) jtotm
Definition modmain.f90:748
logical hybrid
Definition modmain.f90:1149
real(8), dimension(maxspecies) chgcr
Definition modmain.f90:716
character(256), dimension(:), allocatable notes
Definition modmain.f90:1306
integer lradstp
Definition modmain.f90:171
integer, dimension(maxlorbord, maxlorb, maxspecies) lorbdm
Definition modmain.f90:810
real(8), dimension(maxstsp, maxspecies) occsp
Definition modmain.f90:133
integer nsymqpt
Definition modmain.f90:521
integer npcmttot
Definition modmain.f90:218
integer nstcr
Definition modmain.f90:129
logical autolinengy
Definition modmain.f90:828
character(264) xcdescr
Definition modmain.f90:590
real(8) engybext
Definition modmain.f90:970
logical trestart
Definition modmain.f90:1054
real(8), dimension(maxatoms, maxspecies) mommtfixm
Definition modmain.f90:261
real(8), dimension(9) stressp
Definition modmain.f90:1023
integer nlotot
Definition modmain.f90:790
logical tsyminv
Definition modmain.f90:354
real(8), dimension(3) momir
Definition modmain.f90:742
real(8) maxforce
Definition modmain.f90:997
logical tafield
Definition modmain.f90:322
complex(8), dimension(:,:), allocatable sfacg
Definition modmain.f90:430
logical tjr
Definition modmain.f90:620
integer, dimension(3, 3, 48) symqpt
Definition modmain.f90:523
integer, dimension(maxspecies) nstsp
Definition modmain.f90:113
real(8), parameter fourpi
Definition modmain.f90:1231
integer lmmaxapw
Definition modmain.f90:199
logical dosocc
Definition modmain.f90:1080
real(8), dimension(3, 3) avec
Definition modmain.f90:12
real(8) timerho
Definition modmain.f90:1220
real(8), dimension(:), allocatable, target rhmg
Definition modmain.f90:612
real(8), dimension(3) efieldl
Definition modmain.f90:314
real(8) dnempty0
Definition modmain.f90:880
logical dosmsum
Definition modmain.f90:1084
real(8), parameter amu_si
Definition modmain.f90:1280
real(8), dimension(:,:,:,:,:,:), allocatable haa
Definition modmain.f90:856
integer npsd
Definition modmain.f90:626
integer maxatpstp
Definition modmain.f90:1006
integer lmaxdos
Definition modmain.f90:1078
integer ntasks
Definition modmain.f90:1292
integer, dimension(3) xctsp
Definition modmain.f90:142
real(8), dimension(3) vqcss
Definition modmain.f90:295
real(8), dimension(:,:), allocatable vqc
Definition modmain.f90:547
integer mixtype
Definition modmain.f90:695
logical trdatdv
Definition modmain.f90:62
real(8) timemat
Definition modmain.f90:1214
integer apwordmax
Definition modmain.f90:760
real(4), dimension(:,:,:), allocatable lofr_sp
Definition modmain.f90:816
real(8), dimension(3, 3) afspc
Definition modmain.f90:331
real(8), parameter kb_si
Definition modmain.f90:1260
real(8) chgtot
Definition modmain.f90:726
logical lorbcnd
Definition modmain.f90:832
real(8), dimension(:,:,:,:), allocatable rwfcr
Definition modmain.f90:936
integer nlomax
Definition modmain.f90:788
real(8) engyen
Definition modmain.f90:956
real(8) timefv
Definition modmain.f90:1216
real(8) e0min
Definition modmain.f90:825
integer ngtc
Definition modmain.f90:392
real(8) rndbfcmt
Definition modmain.f90:277
complex(8), dimension(:,:), allocatable zbshti
Definition modmain.f90:573
real(8), dimension(3, maxsymcrys) vtlsymc
Definition modmain.f90:360
integer fsmtype0
Definition modmain.f90:251
real(8), dimension(:,:,:), allocatable rlcmt
Definition modmain.f90:181
logical tavref
Definition modmain.f90:1029
integer, dimension(maxspecies) nrtmsn
Definition modmain.f90:95
real(8), dimension(maxspecies) voltmsn
Definition modmain.f90:93
real(8) swidth
Definition modmain.f90:892
logical tafsp
Definition modmain.f90:329
integer, dimension(maxsymcrys) lspnsymc
Definition modmain.f90:366
real(8), dimension(3) bfsmc
Definition modmain.f90:257
real(8), parameter br_si
Definition modmain.f90:1266
real(8), dimension(:), allocatable tauatp
Definition modmain.f90:1010
logical tshift0
Definition modmain.f90:352
logical autokpt
Definition modmain.f90:444
integer nqpt
Definition modmain.f90:525
integer latvopt
Definition modmain.f90:1034
integer nkspolar
Definition modmain.f90:485
logical tefield
Definition modmain.f90:310
logical tstop
Definition modmain.f90:1052
real(8) epslat
Definition modmain.f90:24
integer nkpt
Definition modmain.f90:461
real(8) evalsum
Definition modmain.f90:948
logical spinpol0
Definition modmain.f90:228
real(8), dimension(:,:), allocatable wr2cmt
Definition modmain.f90:189
integer, dimension(:), allocatable ifqrz
Definition modmain.f90:541
real(8), dimension(:), allocatable vxir
Definition modmain.f90:1143
real(8) engyvxc
Definition modmain.f90:966
real(8) tau0latv
Definition modmain.f90:1038
integer natmtot
Definition modmain.f90:40
real(8), dimension(2) wplot
Definition modmain.f90:1076
real(8), dimension(:), allocatable cfunir
Definition modmain.f90:436
real(8), dimension(3) dafieldc
Definition modmain.f90:325
integer nspnfv
Definition modmain.f90:289
integer nkstlist
Definition modmain.f90:924
real(8), dimension(3, 3) davec
Definition modmain.f90:12
real(8), dimension(3) momtot
Definition modmain.f90:738
real(8), parameter t_si
Definition modmain.f90:1274
integer, dimension(maxapword, 0:maxlapw, maxspecies) apwdm
Definition modmain.f90:770
logical cmagz
Definition modmain.f90:242
logical tfav0
Definition modmain.f90:1000
real(8) omegabz
Definition modmain.f90:22
real(8), dimension(9) stress
Definition modmain.f90:1021
integer lmaxapw
Definition modmain.f90:197
real(8), dimension(3, 3) rotsht
Definition modmain.f90:563
real(8), dimension(3, maxatoms, maxspecies) bfcmt00
Definition modmain.f90:275
real(8) tau0oep
Definition modmain.f90:1141
real(8), dimension(:,:,:), allocatable wcrcmt
Definition modmain.f90:193
real(8), dimension(:,:), allocatable vql
Definition modmain.f90:545
real(8), dimension(:,:,:,:), allocatable vgkl
Definition modmain.f90:503
real(8), dimension(:,:,:,:), allocatable hlolo
Definition modmain.f90:860
integer, dimension(:,:,:), allocatable ijkbse
Definition modmain.f90:1196
integer npcmtmax
Definition modmain.f90:216
real(8), dimension(maxspecies) spze
Definition modmain.f90:99
logical tc_tb09
Definition modmain.f90:680
integer ngtot0
Definition modmain.f90:390
complex(4), dimension(:,:), allocatable cbshto
Definition modmain.f90:582
real(8), dimension(3, 3, 9) strain
Definition modmain.f90:1016
integer, dimension(:,:), allocatable jstbse
Definition modmain.f90:1194
integer isgkmax
Definition modmain.f90:491
real(8), dimension(:), allocatable wqpt
Definition modmain.f90:549
integer, dimension(3) ngridk
Definition modmain.f90:448
real(8), dimension(:,:,:), allocatable wprcmt
Definition modmain.f90:191
character(64), dimension(maxspecies) spsymb
Definition modmain.f90:78
real(8), dimension(:,:), allocatable rfshti
Definition modmain.f90:567
integer maxscl0
Definition modmain.f90:1046
integer, parameter maxspecies
Definition modmain.f90:30
real(8) rmtdelta
Definition modmain.f90:160
real(8), dimension(:), allocatable, target vsbs
Definition modmain.f90:647
integer noptcomp
Definition modmain.f90:1088
integer, dimension(maxlorb, maxspecies) lorbord
Definition modmain.f90:792
integer iqss
Definition modmain.f90:297
real(8), dimension(:,:), allocatable vplp1d
Definition modmain.f90:1121
real(8) fermidos
Definition modmain.f90:910
integer maxitoep
Definition modmain.f90:1139
real(8), dimension(3, maxatoms, maxspecies) atposl0
Definition modmain.f90:51
real(8), dimension(3, 0:3) vclp3d
Definition modmain.f90:1129
logical bforb
Definition modmain.f90:234
integer, dimension(maxspecies) npcmt
Definition modmain.f90:214
real(8) engyts
Definition modmain.f90:978
integer, dimension(:), allocatable igfft
Definition modmain.f90:406
real(8) tauoep
Definition modmain.f90:1141
logical trdstate
Definition modmain.f90:682
integer, dimension(maxxbse) istxbse
Definition modmain.f90:1184
real(8), dimension(:), allocatable dvp1d
Definition modmain.f90:1119
real(8), dimension(:), allocatable vclir
Definition modmain.f90:624
real(8), dimension(3) dvqlss
Definition modmain.f90:293
real(8), parameter kboltz
Definition modmain.f90:1262
real(8) omega0
Definition modmain.f90:20
complex(8), dimension(:,:,:), allocatable gntyry
Definition modmain.f90:862
integer nmatmax
Definition modmain.f90:848
logical tlast
Definition modmain.f90:1050
real(8), dimension(3, maxatoms, maxspecies) mommtfix
Definition modmain.f90:259
real(8), dimension(:,:,:), allocatable apwdfr
Definition modmain.f90:778
integer, dimension(3), parameter version
Definition modmain.f90:1288
real(8), dimension(3, 3) binv0
Definition modmain.f90:18
real(8), dimension(:,:,:,:,:), allocatable apwfr
Definition modmain.f90:774
real(8) engyx
Definition modmain.f90:972
integer, parameter maxkst
Definition modmain.f90:922
integer task
Definition modmain.f90:1298
complex(4), parameter cone
Definition modmain.f90:1236
integer nstsv
Definition modmain.f90:886
real(8), dimension(2) amixpm
Definition modmain.f90:702
integer istrain
Definition modmain.f90:1014
real(8) dlefe
Definition modmain.f90:830
integer, dimension(:), allocatable iqrzf
Definition modmain.f90:543
logical cmagz0
Definition modmain.f90:242
real(8), dimension(:), allocatable dpp1d
Definition modmain.f90:1123
real(8), dimension(3, maxatoms, maxspecies) atposc0
Definition modmain.f90:54
real(8), dimension(:,:), pointer, contiguous magir
Definition modmain.f90:616
logical tatdisp
Definition modmain.f90:59
integer, parameter maxlorbord
Definition modmain.f90:782
real(8) engymad
Definition modmain.f90:964
real(8), dimension(:), allocatable chgmt
Definition modmain.f90:732
real(8) epschg
Definition modmain.f90:712
logical mixsave
Definition modmain.f90:700
logical tpdos
Definition modmain.f90:1082
real(8), dimension(:,:), allocatable socfr
Definition modmain.f90:670
integer nsymkpt
Definition modmain.f90:457
real(8) omegamt
Definition modmain.f90:169
integer, dimension(3) np3d
Definition modmain.f90:1131
real(8) rmtall
Definition modmain.f90:158
real(8), dimension(:,:), allocatable bdmta
Definition modmain.f90:640
integer ncrmax
Definition modmain.f90:1137
integer, dimension(maxspecies) lmoapw
Definition modmain.f90:762
integer, dimension(48) symlatd
Definition modmain.f90:346
real(8), dimension(:,:,:), allocatable wprmt
Definition modmain.f90:185
logical tfr_sp
Definition modmain.f90:818
integer, dimension(maxstsp, maxspecies) ksp
Definition modmain.f90:125
real(8) dnrmtscf
Definition modmain.f90:148
integer ngrf
Definition modmain.f90:1161
integer mrmtav
Definition modmain.f90:156
real(8), dimension(3) momfix0
Definition modmain.f90:253
integer npmtmax
Definition modmain.f90:216
integer, dimension(maxlorb, maxspecies) idxelo
Definition modmain.f90:806
real(8), dimension(:,:), allocatable forcetot
Definition modmain.f90:990
real(8) chgzn
Definition modmain.f90:714
real(8), dimension(:,:,:), allocatable jrmt
Definition modmain.f90:622
real(8) socscf
Definition modmain.f90:232
logical spinsprl
Definition modmain.f90:283
real(8) c_tb09
Definition modmain.f90:678
integer lorbordc
Definition modmain.f90:834
integer, dimension(:,:,:), allocatable ivqiqnr
Definition modmain.f90:533
real(8), dimension(:), allocatable evalbse
Definition modmain.f90:1200
real(8) momtotm
Definition modmain.f90:740
logical, dimension(maxapword, 0:maxlapw, maxspecies) apwve
Definition modmain.f90:772
integer, dimension(maxatoms *maxspecies) idxis0
Definition modmain.f90:44
character(256) sppath
Definition modmain.f90:72
real(8), dimension(:,:,:), allocatable bxmt
Definition modmain.f90:1143
real(8), dimension(maxspecies) rtmsn
Definition modmain.f90:91
real(8), parameter ha_si
Definition modmain.f90:1254
logical hdbse
Definition modmain.f90:1206
real(8) scissor
Definition modmain.f90:908
integer lmaxo
Definition modmain.f90:201
complex(8), dimension(:), allocatable vsig
Definition modmain.f90:662
real(8), dimension(:,:), pointer, contiguous vsmt
Definition modmain.f90:649
real(8), dimension(3) bfieldc0
Definition modmain.f90:271
logical, dimension(maxsymcrys) tv0symc
Definition modmain.f90:362
real(8) wqptnr
Definition modmain.f90:551
integer, dimension(3, 3, 48) symkpt
Definition modmain.f90:459
integer, dimension(3) ngridg0
Definition modmain.f90:386
integer, dimension(maxspecies) npmt
Definition modmain.f90:213
real(8), dimension(:,:), allocatable bsir
Definition modmain.f90:658
integer, dimension(:,:), allocatable ivg
Definition modmain.f90:400
real(8), dimension(3, maxsymcrys) vtcsymc
Definition modmain.f90:360
real(8) solsc
Definition modmain.f90:1252
real(8), dimension(3, 3) ainv
Definition modmain.f90:14
real(8) dchgexs
Definition modmain.f90:724
real(8), dimension(3) afieldl
Definition modmain.f90:327
complex(8), dimension(:), allocatable wrf
Definition modmain.f90:1167
real(8), dimension(:,:), allocatable vclmt
Definition modmain.f90:624
real(8), dimension(:,:), allocatable vrsp
Definition modmain.f90:139
integer, dimension(2) jspnfv
Definition modmain.f90:291
integer maxscl
Definition modmain.f90:1046
real(8) tau0atp
Definition modmain.f90:1008
real(8), parameter sol_si
Definition modmain.f90:1248
real(8) stressmax
Definition modmain.f90:1025
real(8) gmaxrf
Definition modmain.f90:1157
real(8) rwigner
Definition modmain.f90:736
real(8) epsocc
Definition modmain.f90:900
integer, dimension(3) dngridk
Definition modmain.f90:448
real(8), dimension(maxspecies) rmaxsp
Definition modmain.f90:105
real(8), dimension(:,:), allocatable vkl
Definition modmain.f90:471
real(8) chgexs
Definition modmain.f90:724
real(8), dimension(3) dbfieldc0
Definition modmain.f90:271
integer, dimension(:), allocatable iqfft
Definition modmain.f90:537
integer, parameter npapw
Definition modmain.f90:756
integer ngkmax
Definition modmain.f90:499
real(8) timeinit
Definition modmain.f90:1212
real(8), dimension(:,:), pointer, contiguous bsirc
Definition modmain.f90:660
real(8), parameter e_si
Definition modmain.f90:1264
integer, parameter maxtasks
Definition modmain.f90:1290
real(8), dimension(:,:,:), allocatable bdmt
Definition modmain.f90:638
integer mbwgrf
Definition modmain.f90:1163
real(8), dimension(:,:), allocatable dvxmt
Definition modmain.f90:1145
logical tssxc
Definition modmain.f90:666
integer, dimension(:,:,:), allocatable ivkiknr
Definition modmain.f90:469
real(8) dgmaxvr
Definition modmain.f90:384
real(8) occmax
Definition modmain.f90:898
logical ssdph
Definition modmain.f90:285
logical hybrid0
Definition modmain.f90:1149
real(8), dimension(maxspecies) rminsp
Definition modmain.f90:103
real(8) befvit
Definition modmain.f90:872
real(8), dimension(maxstsp, maxspecies) evalsp
Definition modmain.f90:131
real(8) rmtscf
Definition modmain.f90:154
real(8) reducebf
Definition modmain.f90:279
logical, dimension(:,:,:), allocatable eqatoms
Definition modmain.f90:370
real(8), dimension(9) taulatv
Definition modmain.f90:1040
integer, dimension(:,:), allocatable nmat
Definition modmain.f90:846
real(8), dimension(:,:), allocatable wr2mt
Definition modmain.f90:183
real(8) engytot
Definition modmain.f90:980
integer, dimension(maxspecies) natoms0
Definition modmain.f90:36
integer ncxbse
Definition modmain.f90:1182
logical bfdmag
Definition modmain.f90:236
real(8), dimension(:,:), allocatable vgc
Definition modmain.f90:420
real(8), dimension(:,:), allocatable vcln
Definition modmain.f90:97
integer, dimension(:), allocatable igrzfc
Definition modmain.f90:418
integer nscss
Definition modmain.f90:299
integer lolmmax
Definition modmain.f90:800
integer reducek
Definition modmain.f90:455
real(8), dimension(:,:), allocatable vxcmt
Definition modmain.f90:634
real(8) emaxrf
Definition modmain.f90:1159
real(8), dimension(:), allocatable gclg
Definition modmain.f90:424
real(8) fracinr
Definition modmain.f90:209
integer, dimension(maxspecies) nrsp
Definition modmain.f90:107
real(8) dncgga
Definition modmain.f90:604
real(8) bdipscf
Definition modmain.f90:645
real(8), dimension(:), pointer, contiguous vsirc
Definition modmain.f90:653
integer lmaxi
Definition modmain.f90:205
real(8), dimension(:,:), allocatable forcehf
Definition modmain.f90:988
real(8), dimension(maxspecies) rmt0
Definition modmain.f90:162
real(8), dimension(3) vqlss
Definition modmain.f90:293
integer, dimension(maxspecies) nlorb
Definition modmain.f90:786
logical tforce
Definition modmain.f90:986
real(8), parameter ha_im
Definition modmain.f90:1258
complex(4), dimension(:,:), allocatable cfshto
Definition modmain.f90:582
integer, dimension(:,:,:), allocatable ivkik
Definition modmain.f90:467
integer nrcmtmax
Definition modmain.f90:175
integer nrmtmax
Definition modmain.f90:152
integer, parameter nplorb
Definition modmain.f90:784
integer xcgrad
Definition modmain.f90:602
real(8) engyc
Definition modmain.f90:974
real(8), dimension(:), allocatable vsir
Definition modmain.f90:651
real(8), dimension(3) vkloff
Definition modmain.f90:450
integer nsymcrys
Definition modmain.f90:358
real(8), dimension(:,:), allocatable forcetotp
Definition modmain.f90:992
real(8) tempk
Definition modmain.f90:684
real(8), dimension(:,:), allocatable vxmt
Definition modmain.f90:1143
real(8), parameter b_si
Definition modmain.f90:1270
real(8), dimension(maxspecies) rnucl
Definition modmain.f90:85
real(8), dimension(:), allocatable exir
Definition modmain.f90:630
real(8), dimension(:,:), allocatable vkc
Definition modmain.f90:473
real(8) dmaxefc
Definition modmain.f90:318
real(8), dimension(:,:,:), allocatable ololo
Definition modmain.f90:854
integer minitefv
Definition modmain.f90:870
logical intraband
Definition modmain.f90:1092
integer lmmaxo
Definition modmain.f90:203
integer, dimension(3, 3, 48) symlat
Definition modmain.f90:344
real(8), dimension(:,:,:), allocatable oalo
Definition modmain.f90:852
integer ngvc
Definition modmain.f90:398
real(8), dimension(:,:,:), pointer, contiguous bsmt
Definition modmain.f90:656
integer nrspmax
Definition modmain.f90:109
real(8), dimension(:,:,:), allocatable rhocr
Definition modmain.f90:938
real(8) chgir
Definition modmain.f90:730
integer nstfv
Definition modmain.f90:884
real(8) epsband
Definition modmain.f90:820
integer stype
Definition modmain.f90:888
real(8), dimension(:,:,:,:,:), allocatable hloa
Definition modmain.f90:858
real(8), dimension(:,:), pointer, contiguous rhomt
Definition modmain.f90:614
integer nmbse
Definition modmain.f90:1190
real(8) epsefvit
Definition modmain.f90:874
real(8) sxcscf
Definition modmain.f90:668
complex(8), dimension(:,:), allocatable ylmg
Definition modmain.f90:428
complex(8), dimension(:,:,:,:), allocatable sfacgk
Definition modmain.f90:509
integer, dimension(maxspecies) nrcmti
Definition modmain.f90:211
integer nspecies
Definition modmain.f90:34
integer, dimension(3) ngridq
Definition modmain.f90:515
real(8) rgkmax
Definition modmain.f90:493
real(8), dimension(:,:), allocatable occsv
Definition modmain.f90:902
real(8), dimension(:,:), allocatable efcmt
Definition modmain.f90:316
integer nempty
Definition modmain.f90:882
real(8), dimension(:), allocatable gc
Definition modmain.f90:422
real(8) timesv
Definition modmain.f90:1218
integer, dimension(maxxbse) jstxbse
Definition modmain.f90:1184
real(8), dimension(3, 0:1, maxatoms, maxspecies) atdvc
Definition modmain.f90:64
integer, dimension(:,:,:), allocatable ivgig
Definition modmain.f90:402
integer, dimension(maxspecies) nlmwf
Definition modmain.f90:840
logical tefvr
Definition modmain.f90:865
integer npfftgc
Definition modmain.f90:408
real(8), parameter h_si
Definition modmain.f90:1244
integer iscl
Definition modmain.f90:1048
real(8), dimension(:), allocatable dvxir
Definition modmain.f90:1145
logical primcell0
Definition modmain.f90:49
real(8) deapw
Definition modmain.f90:764
real(8), dimension(3) vklem
Definition modmain.f90:479
logical, dimension(maxlorbord, maxlorb, maxspecies) lorbve
Definition modmain.f90:812
real(8) emaxelnes
Definition modmain.f90:1103
real(8), dimension(:,:,:), allocatable rlmt
Definition modmain.f90:179
integer lnpsd
Definition modmain.f90:628
real(8), dimension(:,:), allocatable tauir
Definition modmain.f90:672
complex(8), dimension(:,:), allocatable zfshti
Definition modmain.f90:575
integer, parameter maxatoms
Definition modmain.f90:32
logical tforce0
Definition modmain.f90:986
real(8), dimension(:), allocatable wxcir
Definition modmain.f90:676
integer, dimension(:), allocatable ipcmt
Definition modmain.f90:220
integer, parameter maxsymcrys
Definition modmain.f90:356
real(8), dimension(3, maxatoms, maxspecies) atposl
Definition modmain.f90:51
integer ndmag
Definition modmain.f90:238
real(8), dimension(:,:,:), allocatable dbxmt
Definition modmain.f90:1145
real(8) vmaxefc
Definition modmain.f90:320
real(8), dimension(maxspecies) volnucl
Definition modmain.f90:87
integer, dimension(maxspecies) nrnucl
Definition modmain.f90:89
real(8), dimension(:,:), allocatable wxcmt
Definition modmain.f90:676
character(64), dimension(maxspecies) spname
Definition modmain.f90:76
real(8) wkptnr
Definition modmain.f90:477
real(8), dimension(:,:,:,:), allocatable lofr
Definition modmain.f90:814
real(8), dimension(:), allocatable ecir
Definition modmain.f90:632
complex(4), dimension(:,:), allocatable cbshti
Definition modmain.f90:581
integer ncbse0
Definition modmain.f90:1178
real(8), dimension(:), pointer, contiguous vmixer
Definition modmain.f90:689
real(8), dimension(3, maxatoms, maxspecies) bfcmt0
Definition modmain.f90:275
integer, dimension(maxsymcrys) lsplsymc
Definition modmain.f90:364
real(8), dimension(:,:), allocatable evalsv
Definition modmain.f90:918
integer, parameter maxlorb
Definition modmain.f90:780
real(8), dimension(maxspecies) spmass
Definition modmain.f90:101
real(8) engybxc
Definition modmain.f90:968
real(8), dimension(maxspecies) spzn
Definition modmain.f90:80
integer, dimension(2, maxkst) kstlist
Definition modmain.f90:926
integer ncbse
Definition modmain.f90:1176
integer, dimension(:), allocatable igfft0
Definition modmain.f90:406
real(8), dimension(:,:), allocatable jrir
Definition modmain.f90:622
integer, dimension(maxlorb, maxspecies) lorbl
Definition modmain.f90:796
real(8), dimension(3) dmomfix
Definition modmain.f90:253
integer maxitefv
Definition modmain.f90:870
logical t0gclq0
Definition modmain.f90:555
integer nvbse
Definition modmain.f90:1176
integer ndspem
Definition modmain.f90:483
real(8), parameter ef_si
Definition modmain.f90:1272
logical tevecsv
Definition modmain.f90:920
logical primcell
Definition modmain.f90:49
real(8), dimension(:,:), allocatable occcr
Definition modmain.f90:932
integer, dimension(maxtasks) tasks
Definition modmain.f90:1296
real(8), dimension(:,:,:), allocatable lorbe
Definition modmain.f90:808
integer reducek0
Definition modmain.f90:455