1!
2! Copyright (C) 1996-2016	The SIESTA group
3!  This file is distributed under the terms of the
4!  GNU General Public License: see COPYING in the top directory
5!  or http://www.gnu.org/copyleft/gpl.txt.
6! See Docs/Contributors.txt for a list of contributors.
7!
8!{\src2tex{textfont=tt}}
9!!****f* ABINIT/defs_common
10!! NAME
11!! defs_common
12!!
13!! FUNCTION
14!! This module contains definitions of structured datatypes.
15!! In the future, it might contain all these definitions.
16!! At present, it contains those for the routines in the common directory
17!! for the iowfdenpot directory, and all higher directories :
18!! - dataset_type : the "dataset" for the main abinit code
19!! - dtfil_type : the data related to files
20!! - hdr_type   : the header of wf, den and pot files
21!! - bandstructure_type : different information about the band structure
22!! - anaddb_dtset_type : the "dataset" for anaddb
23!! - aim_dtset_type : the "dataset" for aim
24!!
25!! COPYRIGHT
26!! Copyright (C) 2001-2003 ABINIT group (XG)
27!! This file is distributed under the terms of the
28!! GNU General Public License, see ~ABINIT/Infos/copyright
29!! or http://www.gnu.org/copyleft/gpl.txt .
30!!
31!! NOTES
32!!
33!! (1) The dataset_type datatype
34!! The dataset_type structured datatype gather all the input variables,
35!! except those that are labelled NOT INTERNAL.
36!! For one dataset, it is initialized in driver.f, and will not change
37!! at all during the treatment of the dataset.
38!! The "evolving" input variables are also stored, with their
39!! name appended with _orig, to make clear that this is the original
40!! value, decided by the user, and not a possibly modified, intermediate value.
41!! The following input variables are NOT INTERNAL, that is, they
42!! are input variables used to determine other input variables,
43!! after suitable processing, and do not appear anymore afterwards
44!! (so, they do not appear as components of a dataset_type variable) :
45!! cpuh,cpum(but cpus is present),fband,kptbounds,ndivk,nobj,
46!! objaat,objbat,objaax,objbax,objan,objbn,objarf,objbrf,objaro,objbro
47!! objatr,objbtr,vaclst,vacuum
48!!
49!! (2) The datafil_type datatype
50!! The datafiles_type structures datatype gather all the variables related
51!! to files, such as filename, and file units.
52!! For one dataset, it is initialized in driver.f, and will not change
53!! at all during the treatment of the dataset.
54!!
55!! (3) The hdr_type datatype
56!! It contains all the information needed to write a header for a
57!! wf, den or pot file.
58!! The structure of the header is explained in the abinis_help.htm file.
59!! The datatype is considered as an object, to which are attached a whole
60!! set of "methods", actually, different subroutines.
61!! A few of these subroutines are : hdr_init, hdr_update, hdr_clean,
62!! hdr_check, hdr_io, hdr_skip.
63!!
64!! (4) The bz_type datatype
65!! It contains different information about the Brillouin zone to be
66!! considered, according to the context : k points, occupation numbers,
67!! storage mode of wavefunctions, weights ...
68!! For example, the initial Brillouin zone, set up in the dataset, will be treated
69!! in the response function part of the code, to give a reduced
70!! Brillouin zone different from the original one, due to the
71!! breaking of the symmetries related to the existence of a wavevector,
72!! or the lack of time-reversal invariance
73!!
74!! (5) The anaddb_dataset_type datatype
75!! The anaddb_dataset_type structured datatype (will in the future)
76!! gather all the input variables for the anaddb code.
77!!
78!! (6) The aim_dataset_type datatype
79!! The aim_dataset_type structured datatype
80!! gathers all the input variables for the anaddb code.
81!!
82!! TODO
83!!
84!! SOURCE
85
86 module defs_common
87
88 use defs_basis
89
90 implicit none
91
92!Structures
93
94!----------------------------------------------------------------------
95
96 type dataset_type
97! Since all these input variables are described in the abinis_help.htm
98! file, they are not described in length here ...
99! Integer
100  integer :: berryopt,brvltt,ceksph,chkexit,chkprim,delayperm,enunit,&
101&  getcell,getddk,geteps,getden,getkss,getocc,getvel,getwfk,&
102&  getwfkden,getwfq,&
103&  getxcart,getxred,get1den,get1wf,get1wfden,&
104&  ikhxc,intxc,ionmov,iprcch,iprcel,iprcfc,irdwfk,irdwfq,ird1wf,irdddk,&
105&  iscf,isecur,istatr,istatshft,ixc,&
106!  jdtset contains the actual number of the dataset
107&  jdtset,kpara,&
108&  kptopt,kssform,localrdwf,&
109&  mband,mffmem,mgfft,mkmem,mkqmem,mk1mem,mpw,mqgrid,&
110&  natom,natrd,nbdblock,nbdbuf,&
111&  nberry,nbndsto,ncomsto,nconeq,ndtset,nfft,nfreqsus,ngwpt,nkpt,nline,&
112&  nnsclo,npack,npara,npsp,npspalch,npweps,npwmat,npwwfn,nqpt,&
113&  nsheps,nshiftk,nshmat,nshwfn,nspden,&
114&  nspinor,nsppol,nstep,nsym,ntime,&
115&  ntypalch,ntype,ntyppure,occopt,optcell,optdriver,ortalg,parareel,paw,pawgratio,&
116&  prtbbb,prtcml,prtden,prtdos,prtgeo,prtkpt,&
117&  prtpot,prtvha,prtvhxc,prtvol,prtvxc,&
118&  prtwf,prt1dm,ptgroupma,&
119&  restartxf,rfasr,rfelfd,rfmeth,rfphon,rfstrs,rfthrd,&
120&  rfuser,rf1elfd,rf1phon,rf2elfd,rf2phon,rf3elfd,rf3phon,&
121&  signperm,spgaxor,spgorig,spgroup,td_mexcit,&
122&  timopt,useylm,useria,&
123&  userib,useric,userid,userie,vacnum,wfoptalg
124! Integer arrays
125  integer :: bdberry(4),dsifkpt(3),kptrlatt(3,3),ngfft(8),nloalg(5),&
126&  rfatpol(2),rfdir(3),rf1atpol(2),rf1dir(3),&
127&  rf2atpol(2),rf2dir(3),rf3atpol(2),rf3dir(3)
128! Integer pointers
129  integer, pointer ::  algalch(:)    ! algalch(ntypalch)
130  integer, pointer ::  bdgw(:,:)     ! bdgw(2,ngwpt)
131  integer, pointer ::  iatfix(:,:)   ! iatfix(3,natom)
132  integer, pointer ::  istwfk(:)     ! istwfk(nkpt)
133  integer, pointer ::  kberry(:,:)   ! kberry(3,nberry)
134  integer, pointer ::  nband(:)      ! nband(nkpt*nsppol)
135  integer, pointer ::  so_typat(:)   ! so_typat(ntype)
136  integer, pointer ::  symafm(:)     ! symafm(nsym)
137  integer, pointer ::  symrel(:,:,:) ! symrel(3,3,nsym)
138  integer, pointer ::  type(:)       ! type(natom)
139! Real
140  real(dp) :: charge,cpus,dedlnn,diecut,diegap,dielam,&
141&  dielng,diemac,diemix,dilatmx,dtion,&
142&  ecut,ecuteps,ecutgros,ecutmat,ecutsm,ecutwfn,&
143&  eshift,fband,fixmom,freqsusin,freqsuslo,friction,kptnrm,kptrlen,mdftemp,&
144&  mditemp,mdwall,nelect,noseinert,plasfrq,qptnrm,sciss,strfact,strprecon,&
145&  td_maxene,toldfe,toldff,&
146&  tolmxf,tolvrs,tolwfr,tphysel,tsmear,userra,userrb,userrc,userrd,&
147&  userre,vacwidth,vis,zcut
148! Real arrays
149  real(dp) :: acell_orig(3),angdeg_orig(3),boxcenter(3),&
150&  genafm(3),qprtrb(3),qpt(3),qptn(3),rprim_orig(3,3),&
151&  rprimd_orig(3,3),strtarget(6),vprtrb(2)
152! Real pointers
153  real(dp), pointer :: amu(:)         ! amu(ntype)
154  real(dp), pointer :: densty(:,:)    ! densty(ntype,4)
155  real(dp), pointer :: kpt(:,:)       ! kpt(3,nkpt)
156  real(dp), pointer :: kptgw(:,:)     ! kptgw(3,ngwpt)
157  real(dp), pointer :: kptns(:,:)     ! kptns(3,nkpt)
158  real(dp), pointer :: mixalch(:,:)   ! mixalch(npspalch,ntypalch)
159  real(dp), pointer :: occ_orig(:)    ! occ_orig(mband*nkpt*nsppol)
160  real(dp), pointer :: shiftk(:,:)    ! shifk(3,nshiftk)
161  real(dp), pointer :: spinat(:,:)    ! spinat(3,natom)
162  real(dp), pointer :: tnons(:,:)     ! tnons(3,nsym)
163  real(dp), pointer :: vel_orig(:,:)  ! vel_orig(3,natom)
164  real(dp), pointer :: wtatcon(:,:,:) ! wtatcon(3,natom,nconeq)
165  real(dp), pointer :: wtk(:)         ! wtk(nkpt)
166  real(dp), pointer :: xred_orig(:,:) ! xred_orig(3,natom)
167  real(dp), pointer :: ziontypat(:)   ! ziontypat(ntype)
168  real(dp), pointer :: znucl(:)       ! znucl(npsp)
169 end type dataset_type
170
171!----------------------------------------------------------------------
172
173 type datafiles_type
174
175  integer :: ireadwf
176   ! if(optdriver/=1), that is, no response-function computation,
177   !   ireadwf non-zero  if the wffknm file must be read
178   !   (if irdwfk non-zero or getwfk non-zero)
179   ! if(optdriver==1), that is, response-function computation,
180   !   ireadwf non-zero  if the wff1nm file must be read
181   !   (if ird1wf non-zero or get1wf non-zero)
182  integer :: unddb   ! unit number for Derivative DataBase
183  integer :: undot   ! unit number for ddk 1WF file
184  integer :: unkg    ! unit number for k+G data
185  integer :: unkgq   ! unit number for k+G+q data
186  integer :: unkg1   ! unit number for first-order k+G+q data
187  integer :: unwff1  ! unit number for wavefunctions, number one
188  integer :: unwff2  ! unit number for wavefunctions, number two
189  integer :: unwffgs ! unit number for ground-state wavefunctions
190  integer :: unwffkq ! unit number for k+q ground-state wavefunctions
191  integer :: unwft1  ! unit number for wavefunctions, temporary one
192  integer :: unwft2  ! unit number for wavefunctions, temporary two
193  integer :: unwftgs ! unit number for ground-state wavefunctions, temporary
194  integer :: unwftkq ! unit number for k+q ground-state wavefunctions, temporary
195  integer :: unylm   ! unit number for Ylm(k) data
196  integer :: unylm1  ! unit number for first-order Ylm(k+q) data
197  integer :: ungsc   ! unit number for <g|S|c> data (Paw only)
198
199  character*(fnlen) :: filnam_ds(5)
200   ! if no dataset mode, the five names from the standard input :
201   !   ab_in, ab_out, abi, abo, tmp
202   ! if dataset mode, the same 5 filenames, appended with //'_DS'//trim(jdtset)
203
204  character*(fnlen) :: fildensin
205   ! if no dataset mode             : abi//'DEN'
206   ! if dataset mode, and getden==0 : abi//'_DS'//trim(jdtset)//'DEN'
207   ! if dataset mode, and getden/=0 : abo//'_DS'//trim(jgetden)//'DEN'
208
209  character*(fnlen) :: filkss
210   ! if no dataset mode             : abi//'KSS'
211   ! if dataset mode, and getkss==0 : abi//'_DS'//trim(jdtset)//'KSS'
212   ! if dataset mode, and getkss/=0 : abo//'_DS'//trim(jgetkss)//'KSS'
213
214  character*(fnlen) :: filem1
215   ! if no dataset mode             : abi//'EM1'
216   ! if dataset mode, and geteps==0 : abi//'_DS'//trim(jdtset)//'EM1'
217   ! if dataset mode, and geteps/=0 : abo//'_DS'//trim(jgeteps)//'EM1'
218
219! character*(fnlen) :: filpsp(ntype)
220   ! the filenames of the pseudopotential files, from the standard input.
221
222  character*(fnlen) :: filstat
223   ! tmp//'_STATUS'
224
225  character*(fnlen) :: wffknm
226   ! the name of the ground-state wavefunction file to be read (see driver.f)
227
228  character*(fnlen) :: wffqnm
229   ! the name of the k+q ground-state wavefunction file to be read (see driver.f)
230   ! only useful in the response-function case
231
232  character*(fnlen) :: wffddk
233   ! the generic name of the ddk response wavefunction file(s) to be read (see driver.f)
234   ! (the final name is formed by appending the number of the perturbation)
235   ! only useful in the response-function case
236
237  character*(fnlen) :: wff1nm
238   ! the generic name of the first-order wavefunction file(s) to be read (see driver.f)
239   ! (the final name is formed by appending the number of the perturbation)
240   ! only useful in the response-function case
241
242  character*(fnlen) :: fildens1in   ! to be described by MVeithen
243  character*(fnlen) :: wffknmden   ! to be described by MVeithen
244  character*(fnlen) :: wff1nmden   ! to be described by MVeithen
245
246 end type datafiles_type
247
248!----------------------------------------------------------------------
249
250 type hdr_type
251  integer :: bantot        ! total number of bands (sum of nband on all kpts and spins)
252  integer :: date          ! starting date
253  integer :: headform      ! format of the header
254  integer :: intxc,ixc,natom,nkpt,npsp,nspden        ! input variables
255  integer :: nspinor,nsppol,nsym,ntype,occopt        ! input variables
256  integer :: ngfft(3)      ! input variable
257
258! This record is not a part of the hdr_type, although it is present in the
259! header of the files. This is because it depends on the kind of file
260! that is written, while all other information does not depend on it.
261! It was preferred to let it be initialized or defined outside of hdr_type.
262! integer :: fform         ! file descriptor (or file format)
263
264  integer, pointer :: istwfk(:)    ! input variable istwfk(nkpt)
265  integer, pointer :: nband(:)     ! input variable nband(nkpt*nsppol)
266  integer, pointer :: npwarr(:)    ! npwarr(nkpt) array holding npw for each k point
267  integer, pointer :: pspcod(:)    ! pscod(npsp) from psps
268  integer, pointer :: pspdat(:)    ! psdat(npsp) from psps
269  integer, pointer :: pspso(:)     ! pspso(npsp) from psps
270  integer, pointer :: pspxc(:)     ! pspxc(npsp) from psps
271  integer, pointer :: so_typat(:)  ! input variable so_typat(ntype)
272  integer, pointer :: symafm(:)    ! input variable symafm(nsym)
273  integer, pointer :: symrel(:,:,:)! input variable symrel(3,3,nsym)
274  integer, pointer :: type(:)      ! input variable type(natom)
275
276  real(dp) :: ecut                  ! input variable
277  real(dp) :: ecutsm                ! input variable
278  real(dp) :: ecut_eff              ! ecut*dilatmx**2 (dilatmx is an input variable)
279  real(dp) :: etot,fermie,residm    ! EVOLVING variables
280  real(dp) :: rprimd(3,3)           ! EVOLVING variables
281  real(dp) :: tphysel               ! input variable
282  real(dp) :: tsmear                ! input variable
283  real(dp), pointer :: kptns(:,:)   ! input variable kptns(3,nkpt)
284  real(dp), pointer :: occ(:)       ! EVOLVING variable occ(bantot)
285  real(dp), pointer :: tnons(:,:)   ! input variable tnons(3,nsym)
286  real(dp), pointer :: xred(:,:)    ! EVOLVING variable xred(3,natom)
287  real(dp), pointer :: zionpsp(:)   ! zionpsp(npsp) from psps
288  real(dp), pointer :: znuclpsp(:)  ! znuclpsp(npsp) from psps
289                                    ! Note the difference between znucl and znuclpsp !!
290  real(dp), pointer :: znucltypat(:)! znucltypat(ntype) from alchemy
291
292  character*6 :: codvsn              ! version of the code
293  character*132, pointer :: title(:) ! title(npsp) from psps
294!Should make a list of supplementary infos
295
296 end type hdr_type
297
298!----------------------------------------------------------------------
299
300 type bandstructure_type
301
302  integer :: bantot                  ! total number of bands (sum(nband(:))
303  integer :: nkpt                    ! number of k points
304  integer :: nsppol                  ! number of spin-polarizations
305  integer, pointer :: istwfk(:)      ! istwfk(nkpt) storage mode at each k point
306  integer, pointer :: nband(:)       ! nband(nkpt*nsppol) number of bands
307                                     !    at each k point and spin-polarisation
308  integer, pointer :: npwarr(:)      ! npwarr(nkpt) number of plane waves at each k point
309  real(dp), pointer :: kptns(:,:)    ! kptns(3,nkpt)  k-point vectors
310  real(dp), pointer :: eig(:)        ! eig(bantot)  eigenvalues of each band
311  real(dp), pointer :: occ(:)        ! occ(bantot)  occupation of each band
312  real(dp), pointer :: doccde(:)     ! doccde(bantot)  derivative of the
313                                     !    occupation of each band wrt energy (needed for RF)
314  real(dp), pointer :: wtk(:)        ! wtk(nkpt)  weight of each k point
315
316 end type bandstructure_type
317
318!----------------------------------------------------------------------
319
320 type anaddb_dataset_type
321
322! Since all these input variables are described in the anaddb_help.htm
323! file, they are not described in length here ...
324
325! Real pointers
326  real(dp), pointer :: qnrml1(:)  ! qnrml1(nph1l)
327  real(dp), pointer :: qnrml2(:)  ! qnrml2(nph2l)
328  real(dp), pointer :: qph1l(:,:) ! qph1l(3,nph1l)
329  real(dp), pointer :: qph2l(:,:) ! qph2l(3,nph2l)
330
331 end type anaddb_dataset_type
332
333!----------------------------------------------------------------------
334
335 type aim_dataset_type
336
337! Since all these input variables are described in the aim_help.htm
338! file, they are not described in length here ...
339
340! Integer
341  integer :: crit,denout,dltyp,gpsurf,irho,ivol,lapout,nsa,nsb,nsc
342  integer :: ngrid(3)
343  integer :: batom  !! Warning : corresponds to the input variable atom
344  integer :: foll   !! Warning : corresponds to the input variable follow
345  integer :: isurf  !! Warning : corresponds to the input variable surf
346  integer :: irsur  !! Warning : corresponds to the input variable rsurf
347  integer :: nph    !! Warning : corresponds to the input variable nphi
348  integer :: npt    !! Warning : corresponds to the input variable inpt
349  integer :: nth    !! Warning : corresponds to the input variable ntheta
350  integer :: plden  !! Warning : not documented in help file ?!
351
352! Real
353  real(dp) :: atrad,coff1,coff2,dpclim,folstp,lgrad,lgrad2,lstep,lstep2,&
354&  maxatd,maxcpd,phimax,phimin
355  real(dp) :: foldep(3),scal(3),vpts(3,4)
356  real(dp) :: dr0    !! Warning : correspond to the input variable radstp
357  real(dp) :: phi0   !! Warning : correspond to the input variable rsurdir(2)
358  real(dp) :: rmin   !! Warning : correspond to the input variable ratmin
359  real(dp) :: th0    !! Warning : correspond to the input variable rsurdir(1)
360  real(dp) :: themax !! Warning : correspond to the input variable thetamax
361  real(dp) :: themin !! Warning : correspond to the input variable thetamin
362
363 end type aim_dataset_type
364
365!----------------------------------------------------------------------
366
367 end module defs_common
368!!***
369