~nickpapior/siesta/trunk-kpoint-dos

1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
! ---
! Copyright (C) 1996-2016	The SIESTA group
!  This file is distributed under the terms of the
!  GNU General Public License: see COPYING in the top directory
!  or http://www.gnu.org/copyleft/gpl.txt .
! See Docs/Contributors.txt for a list of contributors.
! ---
module main_vars
  use precision, only: dp, sp
  use subs, only: ival
  use m_getopts
  use units, only: Ang, pi

  implicit none

  public 

  integer :: ierr, klb, it, is, k, nw
  integer :: nao, ia, iz, ko, nkp, nsp, nen, mxwf, io, ie
  integer :: nnao, ik, is0, iw, iw0, i1, i2, i3, i4
  integer :: no_s, nspin, nh, im, ii, io2
  integer :: ncb, nln, il, nwd, n, l, i, noc0, ic, io1, isr, iov
  integer :: j, m, idos, lorb, naoatx

  integer :: nspecies, na_u, no_u
  integer, allocatable :: no(:), nquant(:,:), lquant(:,:), zeta(:,:)
  integer, allocatable :: iaorb(:), iphorb(:)
  character(len=20), allocatable :: label(:)

  real(dp) :: qtot, temp_in_file, dm, alfa, vvv
  real(dp) :: qcos, qsin, w0, want
  real(dp) :: min_energy, max_energy, e_step, energy, weight, efermi
  real(dp) :: low_e, high_e, eigval
  integer  :: intdos_u, number_of_wfns

  real(dp) :: minimum_spec_energy = -huge(1.0_dp)
  real(dp) :: maximum_spec_energy = huge(1.0_dp)

  real(dp)            ::  smear = 0.5        ! Units of energy are eV 
  integer             ::  npts_energy = 200

  integer :: nshmx
  integer, parameter :: ncbmx=20
  integer, parameter :: nlwmx=30

  character :: sflnm*50, taux*100, wrd(nlwmx)*20, cx*20
  integer :: mpr_u=50, wk_u=51
  integer :: out_u=70, wfs_u=72, hs_u=73
  integer :: stt_u=60, tab_u=61, fat_u=66
  logical   :: wk_x, wfs_x, hs_x, tab_x

  ! OUT file
  integer, allocatable :: isa(:)
  integer, allocatable :: za(:), zc(:), zn(:), zl(:), zx(:), zz(:)
  real(dp), allocatable :: zval(:)

  ! WFS file
  integer, allocatable :: nwf(:,:)
  real(dp),    allocatable :: pk(:,:)
  real(dp), allocatable ::   ados(:,:), ww(:)
  real(dp), allocatable ::   intdos(:), intebs(:)

  ! HS file
  integer, allocatable :: numh(:), listhptr(:), listh(:)  
  integer, allocatable :: indxuo(:)
  real(dp),    allocatable :: hamilt(:,:), Sover(:), xij(:,:), dij(:)

  real(dp),    allocatable :: wk(:)
  real(SP),  allocatable :: wf(:,:)       ! Note single precision

  ! MPR file
  character :: what*4, tit(ncbmx)*30
  logical   :: dos, coop
  real(dp)  :: dtc(ncbmx,2)

  integer              :: noc(ncbmx,2)
  integer, allocatable :: koc(:,:,:)
  logical, allocatable :: orb_mask(:,:,:)

  ! RESULTS
  real(dp),  allocatable :: coop_vals(:,:,:)
  real(dp),  allocatable :: cohp_vals(:,:,:)
  real(dp),  allocatable :: pdos_vals(:,:,:)
  logical,   allocatable :: ref_mask(:)

  !
  logical :: gamma
  real(dp) :: r_dummy(3), dummy_weight, ztot
  integer  :: idummy
  !
  character(len=200) :: opt_arg, mflnm, ref_line
  character(len=10)  :: opt_name 
  integer :: nargs, iostat, n_opts, nlabels, iorb, ikb
  integer :: nkb, nkp_wfs

  logical :: debug    = .false.
  logical :: simple_dos = .true.
  logical :: ref_line_given = .false.
  logical :: energies_only = .false.

end module main_vars
!------------------------------------------------------------------