TABLE OF CONTENTS


ABINIT/derf_ab [ Functions ]

[ Top ] [ Functions ]

NAME

 derf_ab

FUNCTION

 Some wrappers for BigDFT which uses different names for the same routines.

COPYRIGHT

 Copyright (C) 1998-2018 ABINIT group (DC)
 This file is distributed under the terms of the
 GNU General Public License, see ~abinit/COPYING
 or http://www.gnu.org/copyleft/gpl.txt .
 For the initials of contributors, see ~abinit/doc/developers/contributors.txt .

INPUTS

OUTPUT

SIDE EFFECTS

PARENTS

      mklocl_realspace,mklocl_wavelets

CHILDREN

SOURCE

303 subroutine derf_ab(derf_yy,yy)
304 
305  use m_profiling_abi
306  use defs_basis
307 
308  use m_special_funcs,  only : abi_derf
309 
310 !This section has been created automatically by the script Abilint (TD).
311 !Do not modify the following lines by hand.
312 #undef ABI_FUNC
313 #define ABI_FUNC 'derf_ab'
314 !End of the abilint section
315 
316  implicit none
317 
318 !Arguments ------------------------------------
319 !scalars
320  real(dp),intent(in) :: yy
321  real(dp),intent(out) :: derf_yy
322 
323 !Local variables-------------------------------
324 
325 ! *********************************************************************
326 
327  derf_yy = abi_derf(yy)
328 
329 end subroutine derf_ab

ABINIT/derfcf [ Functions ]

[ Top ] [ Functions ]

NAME

 derfcf

FUNCTION

 Some wrappers for BigDFT which uses different names for the same routines.

COPYRIGHT

 Copyright (C) 1998-2018 ABINIT group (DC)
 This file is distributed under the terms of the
 GNU General Public License, see ~abinit/COPYING
 or http://www.gnu.org/copyleft/gpl.txt .
 For the initials of contributors, see ~abinit/doc/developers/contributors.txt .

INPUTS

OUTPUT

SIDE EFFECTS

PARENTS

CHILDREN

SOURCE

250 subroutine derfcf(derfc_yy,yy)
251 
252  use m_profiling_abi
253  use defs_basis
254 
255  use m_special_funcs,  only : abi_derfc
256 
257 !This section has been created automatically by the script Abilint (TD).
258 !Do not modify the following lines by hand.
259 #undef ABI_FUNC
260 #define ABI_FUNC 'derfcf'
261 !End of the abilint section
262 
263  implicit none
264 !Arguments ------------------------------------
265 !scalars
266  real(dp),intent(in) :: yy
267  real(dp),intent(out) :: derfc_yy
268 !Local variables-------------------------------
269 
270 ! *********************************************************************
271 
272  derfc_yy = abi_derfc(yy)
273 
274 end subroutine derfcf

ABINIT/wvl_wfs_set [ Functions ]

[ Top ] [ Functions ]

NAME

 wvl_wfs_set

FUNCTION

 Compute the access keys for the wavefunctions when the positions
 of the atoms are given.

 For memory occupation optimisation reasons, the wavefunctions are not allocated
 here. See the initialisation routines wvl_wfsinp_disk(), wvl_wfsinp_scratch()
 and wvl_wfsinp_reformat() to do it. After allocation, use wvl_wfs_free()
 to deallocate all stuff (descriptors and arrays).

COPYRIGHT

 Copyright (C) 1998-2018 ABINIT group (DC)
 This file is distributed under the terms of the
 GNU General Public License, see ~abinit/COPYING
 or http://www.gnu.org/copyleft/gpl.txt .
 For the initials of contributors, see ~abinit/doc/developers/contributors.txt .

INPUTS

  dtset <type(dataset_type)>=internal variables used by wavelets, describing
   | wvl_internal=desciption of the wavelet box.
   | natom=number of atoms.
  mpi_enreg=informations about MPI parallelization
  psps <type(pseudopotential_type)>=variables related to pseudopotentials
  rprimd(3,3)=dimensional primitive translations in real space (bohr)
  xred(3,natom)=reduced dimensionless atomic coordinates

OUTPUT

  wfs <type(wvl_projector_type)>=wavefunctions informations for wavelets.
   | keys=its access keys for compact storage.

PARENTS

      gstate,wvl_wfsinp_reformat

CHILDREN

SOURCE

 42 #if defined HAVE_CONFIG_H
 43 #include "config.h"
 44 #endif
 45 
 46 #include "abi_common.h"
 47 
 48 subroutine wvl_wfs_set(alphadiis, spinmagntarget, kpt, me, natom, nband, nkpt, nproc, nspinor, &
 49 &  nsppol, nwfshist, occ, psps, rprimd, wfs, wtk, wvl, wvl_crmult, wvl_frmult, xred)
 50 
 51  use defs_basis
 52  use defs_datatypes
 53  use defs_wvltypes
 54  use m_profiling_abi
 55  use m_errors
 56 
 57  use m_geometry, only : xred2xcart
 58 #if defined HAVE_BIGDFT
 59  use BigDFT_API, only: createWavefunctionsDescriptors, orbitals_descriptors, &
 60        & orbitals_communicators, allocate_diis_objects, &
 61        & input_variables, check_linear_and_create_Lzd, check_communications, &
 62        & INPUT_IG_OFF, nullify_locreg_descriptors
 63 #endif
 64 
 65 !This section has been created automatically by the script Abilint (TD).
 66 !Do not modify the following lines by hand.
 67 #undef ABI_FUNC
 68 #define ABI_FUNC 'wvl_wfs_set'
 69  use interfaces_14_hidewrite
 70 !End of the abilint section
 71 
 72  implicit none
 73 
 74 !Arguments ------------------------------------
 75 !scalars
 76  integer, intent(in) :: natom, nkpt, nsppol, nspinor, nband, nwfshist,me,nproc
 77  real(dp), intent(in) :: spinmagntarget, wvl_crmult, wvl_frmult, alphadiis
 78  type(pseudopotential_type),intent(in) :: psps
 79  type(wvl_wf_type),intent(out) :: wfs
 80  type(wvl_internal_type), intent(in) :: wvl
 81 !arrays
 82  real(dp), intent(in) :: kpt(3,nkpt)
 83  real(dp), intent(in) :: wtk(nkpt), occ(:)
 84  real(dp),intent(in) :: rprimd(3,3),xred(3,natom)
 85 
 86 !Local variables-------------------------------
 87 #if defined HAVE_BIGDFT
 88 !scalars
 89  integer :: ii,idata, norb, norbu, norbd
 90  logical :: parallel
 91  character(len=500) :: message
 92  type(input_variables) :: in  ! To be removed, waiting for BigDFT upgrade
 93 !arrays
 94  real(dp), allocatable :: kpt_(:,:)
 95  real(dp),allocatable :: xcart(:,:)
 96 #endif
 97 
 98 ! *********************************************************************
 99 
100 #if defined HAVE_BIGDFT
101 
102  parallel = (nproc > 1)
103 
104 !Consistency checks, are all pseudo true GTH pseudo with geometric informations?
105 !Skip for PAW case: we do not have GTH parameters
106  do idata = 1, psps%npsp, 1
107    if (.not. psps%gth_params%set(idata) .and. psps%usepaw==0) then
108      write(message, '(a,a,a,a,I0,a,a,a)' ) ch10,&
109 &     ' wvl_wfs_set:  consistency checks failed,', ch10, &
110 &     '  no GTH parameters found for type number ', idata, '.', ch10, &
111 &     '  Check your input pseudo files.'
112      MSG_ERROR(message)
113    end if
114    if (.not. psps%gth_params%hasGeometry(idata)) then
115      write(message, '(a,a,a,a,a,a)' ) ch10,&
116 &     ' wvl_wfs_set:  consistency checks failed,', ch10, &
117 &     '  the given GTH parameters has no geometry informations.', ch10, &
118 &     '  Upgrade your input pseudo files to GTH with geometric informations.'
119      MSG_ERROR(message)
120    end if
121  end do
122 
123 !Store xcart for each atom
124  ABI_ALLOCATE(xcart,(3, natom))
125  call xred2xcart(natom, rprimd, xcart, xred)
126 
127 !Nullify possibly unset pointers
128  nullify(wfs%ks%psi)
129  nullify(wfs%ks%hpsi)
130  nullify(wfs%ks%psit)
131 
132 !Static allocations.
133  norb = nband / nkpt
134  norbu = 0
135  norbd = 0
136  if (nsppol == 2) then
137    if (spinmagntarget < -real(90, dp)) then
138      norbu = min(norb / 2, norb)
139    else
140      norbu = min(norb / 2 + int(spinmagntarget), norb)
141    end if
142    norbd = norb - norbu
143  else
144    norbu = norb
145    norbd = 0
146  end if
147  ABI_ALLOCATE(kpt_, (3, nkpt))
148  do ii = 1, nkpt
149    kpt_(:,ii) = kpt(:,ii) / (/ rprimd(1,1), rprimd(2,2), rprimd(3,3) /) * two_pi
150  end do
151 
152  call orbitals_descriptors(me, nproc,norb,norbu,norbd,nsppol,nspinor, &
153 & nkpt,kpt_,wtk,wfs%ks%orbs,.false.)
154  ABI_DEALLOCATE(kpt_)
155 !We copy occ_orig to wfs%ks%orbs%occup
156  wfs%ks%orbs%occup(1:norb * nkpt) = occ(1:norb * nkpt)
157 !We allocate the eigen values storage.
158  ABI_ALLOCATE(wfs%ks%orbs%eval,(wfs%ks%orbs%norb * wfs%ks%orbs%nkpts))
159 
160  write(message, '(a,a)' ) ch10,&
161 & ' wvl_wfs_set: Create access keys for wavefunctions.'
162  call wrtout(std_out,message,'COLL')
163 
164  call nullify_locreg_descriptors(wfs%ks%lzd%Glr)
165  wfs%ks%lzd%Glr = wvl%Glr
166  call createWavefunctionsDescriptors(me, wvl%h(1), wvl%h(2), wvl%h(3), &
167 & wvl%atoms, xcart, psps%gth_params%radii_cf, &
168 & wvl_crmult, wvl_frmult, wfs%ks%lzd%Glr)
169 !The memory is not allocated there for memory occupation optimisation reasons.
170 
171  call orbitals_communicators(me,nproc,wfs%ks%lzd%Glr,wfs%ks%orbs,wfs%ks%comms)
172 
173  write(message, '(a,2I8)' ) &
174 & '  | all orbitals have coarse segments, elements:', &
175 & wfs%ks%lzd%Glr%wfd%nseg_c, wfs%ks%lzd%Glr%wfd%nvctr_c
176  call wrtout(std_out,message,'COLL')
177  write(message, '(a,2I8)' ) &
178 & '  | all orbitals have fine   segments, elements:', &
179 & wfs%ks%lzd%Glr%wfd%nseg_f, 7 * wfs%ks%lzd%Glr%wfd%nvctr_f
180  call wrtout(std_out,message,'COLL')
181 
182 !allocate arrays necessary for DIIS convergence acceleration
183  call allocate_diis_objects(nwfshist,alphadiis,&
184 & sum(wfs%ks%comms%ncntt(0:nproc-1)), wfs%ks%orbs%nkptsp, wfs%ks%orbs%nspinor, &
185 & wfs%ks%diis)
186 
187  ABI_DATATYPE_ALLOCATE(wfs%ks%confdatarr, (wfs%ks%orbs%norbp))
188  call default_confinement_data(wfs%ks%confdatarr,wfs%ks%orbs%norbp)
189 
190  call check_linear_and_create_Lzd(me,nproc,INPUT_IG_OFF,wfs%ks%lzd,&
191 & wvl%atoms,wfs%ks%orbs,nsppol,xcart)
192  wfs%ks%lzd%hgrids = wvl%h
193 
194 !check the communication distribution
195  call check_communications(me,nproc,wfs%ks%orbs,wfs%ks%Lzd,wfs%ks%comms)
196 
197 !Deallocations
198  ABI_DEALLOCATE(xcart)
199 
200 !DEBUG
201  write(std_out,*) 'wvl_wfs_set: TODO, update BigDFT sic_input_variables_default()'
202 !ENDDEBUG
203  call sic_input_variables_default(in)
204 
205  wfs%ks%SIC                  = in%SIC
206  wfs%ks%exctxpar             = "OP2P"
207  wfs%ks%c_obj                = 0
208  wfs%ks%orthpar%directDiag   = .true.
209  wfs%ks%orthpar%norbpInguess = 5
210  wfs%ks%orthpar%bsLow        = 300
211  wfs%ks%orthpar%bsUp         = 800
212  wfs%ks%orthpar%methOrtho    = 0
213  wfs%ks%orthpar%iguessTol    = 1.d-4
214 
215 #else
216  BIGDFT_NOTENABLED_ERROR()
217  if (.false.) write(std_out,*) natom,nkpt,nsppol,nspinor,nband,nwfshist,me,nproc,&
218 & spinmagntarget,wvl_crmult,wvl_frmult,alphadiis,psps%npsp,wfs%ks,wvl%h(1),&
219 & kpt(1,1),wtk(1),occ(1),rprimd(1,1),xred(1,1)
220 #endif
221 
222 end subroutine wvl_wfs_set