TABLE OF CONTENTS


ABINIT/m_data4entropyDMFT [ Modules ]

[ Top ] [ Modules ]

NAME

  m_data4entropyDMFT

FUNCTION

  FIXME: add description.

COPYRIGHT

  Copyright (C) 2014-2024 ABINIT group (J. Bieder)
  This file is distributed under the terms of the
  GNU General Public License, see ~abinit/COPYING
  or http://www.gnu.org/copyleft/gpl.txt .

NOTES

SOURCE

18 #if defined HAVE_CONFIG_H
19 #include "config.h"
20 #endif
21 
22 #include "abi_common.h"
23 
24 module m_data4entropyDMFT
25 
26   use defs_basis
27   use m_errors
28   use m_abicore
29 
30   implicit none
31 
32   private
33 
34   public :: data4entropyDMFT_init
35   public :: data4entropyDMFT_destroy
36   public :: data4entropyDMFT_setDocc            ! Must be call for each lambda
37   public :: data4entropyDMFT_setHu              ! Hu density
38   public :: data4entropyDMFT_setDc

ABINIT/m_data4entropyDMFT/data4entropyDMFT_init [ Functions ]

[ Top ] [ Functions ]

NAME

  data4entropyDMFT_init

FUNCTION

  FIXME: add description.

COPYRIGHT

  Copyright (C) 2014-2024 ABINIT group (J. Bieder)
  This file is distributed under the terms of the
  GNU General Public License, see ~abinit/COPYING
  or http://www.gnu.org/copyleft/gpl.txt .

INPUTS

  argin(sizein)=description

OUTPUT

  argout(sizeout)=description

SIDE EFFECTS

NOTES

SOURCE

 98 subroutine data4entropyDMFT_init(this,natom,typat,lpawu,uset2g,upawu,jpawu)
 99 
100 !Arguments ------------------------------------
101   type(data4entropyDMFT_t) , intent(inout) :: this
102   integer               , intent(in   ) :: natom
103   integer , dimension(:), intent(in   ) :: typat
104   integer , dimension(:), intent(in   ) :: lpawu
105   logical               , intent(in   ) :: uset2g
106   real(dp), dimension(:), intent(in   ) :: upawu
107   real(dp), dimension(:), intent(in   ) :: jpawu
108 !Local variables ------------------------------
109   integer :: maxlpawu
110   integer :: iatom
111   integer :: ilpawu
112   integer :: nlpawu
113   integer :: ityp
114   character(len=500) :: message
115 
116   this%natom = natom
117 
118   if ( size(typat) .ne. natom ) then
119     write(message,'(a,i5,a,a,i5,a)') "Disagreement between number of atoms (",natom,")", &
120      " and the number of atom types (",size(typat),")."
121     ABI_ERROR(message)
122   end if
123 
124   this%ntypat = maxval(typat) !!! Carefull This should always work but can we have
125   ! one type that is not use (ntypat = 5; typat = 1 2 3 4)?
126   if ( this%ntypat .ne. size(upawu) .or. this%ntypat .ne. size(jpawu) ) then
127     write(message,'(a)') "Disagreement between size of ntypat,upawu and jpawu"
128     ABI_ERROR(message)
129   end if
130 
131   maxlpawu = -1
132   nlpawu = size(lpawu)
133   do iatom=1,natom
134     ityp=typat(iatom)
135     if (ityp.le.0 .or. ityp.gt.nlpawu) then
136       write(message,'(a)') "Try to access the lpawu value of an atom type that has not a lpawu value."
137       ABI_ERROR(message)
138     end if
139     ilpawu=lpawu(ityp)
140     if(uset2g.and.ilpawu==2) ilpawu=1
141     if ( ilpawu > maxlpawu ) maxlpawu = ilpawu
142   enddo
143   this%maxlpawu = maxlpawu
144 
145   ABI_MALLOC(this%docc,(1:2*(2*maxlpawu+1),1:2*(2*maxlpawu+1),1:natom))
146   this%docc(:,:,:) = zero
147 
148   ABI_MALLOC(this%hu_dens,(1:2*(2*maxlpawu+1),1:2*(2*maxlpawu+1),1:this%ntypat))
149   this%hu_dens(:,:,:) = zero
150 
151   ABI_MALLOC(this%e_dc,(1:natom))
152   this%e_dc(:) = zero
153 
154   ABI_MALLOC(this%J_over_U,(1:natom))
155   this%J_over_U(:) = zero
156   do iatom=1,natom
157     ityp=typat(iatom) ! no need to check since already done once before
158     if ( lpawu(ityp) /= -1 .and. upawu(ityp) /= zero) then
159       this%J_over_U(iatom) = jpawu(ityp) / upawu(ityp)
160     end if
161   enddo
162 
163   this%isset = .true.
164 end subroutine data4entropyDMFT_init

ABINIT/m_data4entropyDMFT/data4entropyDMFT_setDc [ Functions ]

[ Top ] [ Functions ]

NAME

  data4entropyDMFT_setHu

FUNCTION

  FIXME: add description.

COPYRIGHT

  Copyright (C) 2014-2024 ABINIT group (J. Bieder)
  This file is distributed under the terms of the
  GNU General Public License, see ~abinit/COPYING
  or http://www.gnu.org/copyleft/gpl.txt .

INPUTS

  argin(sizein)=description

OUTPUT

  argout(sizeout)=description

SIDE EFFECTS

NOTES

SOURCE

334 subroutine data4entropyDMFT_setDc(this,dc)
335 
336 !Arguments ------------------------------------
337     type(data4entropyDMFT_t) , intent(inout) :: this
338     real(dp), dimension(:), intent(in   ) :: dc
339 !Local variables ------------------------------
340     character(len=500) :: message
341 
342     if ( .not. this%isset ) then
343       ABI_ERROR("data4entropyDMFT type not initialized")
344     end if
345 
346     if ( size(dc,1) .gt. this%natom ) then
347       write(message,'(a,i4,a,i4,a)') "Size of dc (",size(dc,1), &
348         ") is greater than the number of atom natom(",this%natom,")."
349       ABI_ERROR(message)
350     end if
351 
352     this%e_dc(:) = dc(:)
353 
354 end subroutine data4entropyDMFT_setDc

ABINIT/m_data4entropyDMFT/data4entropyDMFT_setDocc [ Functions ]

[ Top ] [ Functions ]

NAME

  data4entropyDMFT_setDocc

FUNCTION

  FIXME: add description.

COPYRIGHT

  Copyright (C) 2014-2024 ABINIT group (J. Bieder)
  This file is distributed under the terms of the
  GNU General Public License, see ~abinit/COPYING
  or http://www.gnu.org/copyleft/gpl.txt .

INPUTS

  argin(sizein)=description

OUTPUT

  argout(sizeout)=description

SIDE EFFECTS

NOTES

SOURCE

192 subroutine data4entropyDMFT_setDocc(this,iatom,Docc,Nocc)
193 
194 !Arguments ------------------------------------
195     type(data4entropyDMFT_t), intent(inout) :: this
196     integer           , intent(in   ) :: iatom
197     real(dp), optional, intent(in   ) :: Docc(:,:) !iflavor,iflavor
198     real(dp), optional, intent(in   ) :: Nocc(:)   !iflavor
199 !Local variables ------------------------------
200     integer            :: maxnflavor
201     integer            :: iflavor1
202     integer            :: iflavor2
203     character(len=500) :: message
204 
205     if ( .not. this%isset ) then
206       ABI_ERROR("data4entropyDMFT type not initialized")
207     end if
208 
209     if ( iatom .gt. this%natom ) then
210       write(message,'(a,i4,a,i4,a)') "Value of iatom (",iatom, &
211         ") is greater than the number of atom natom(",this%natom,")."
212       ABI_ERROR(message)
213     end if
214 
215     if ( .not. present(Docc) .and. .not. present(Nocc) ) then
216       write(message,'(2a)') "Neither Docc nor Nocc is present to set double", &
217       "occupancy. Should have one and only one of those."
218       ABI_ERROR(message)
219     end if
220 
221     if ( present(Docc) .and. present(Nocc) ) then
222       write(message,'(2a)') "Both Docc and Nocc are present to set double", &
223       "occupancy. Should have one and only one of those."
224       ABI_ERROR(message)
225     end if
226 
227     maxnflavor=2*(2*this%maxlpawu+1)
228     if ( present(Docc) ) then
229       if ( size(Docc,1) .gt. maxnflavor .or. size(Docc,2) .gt. maxnflavor &
230           .or. size(Docc,1) .ne. size(Docc,2) ) then
231         write(message,'(a,i2,a,i2,a,i2)') "Problem with Docc shape/size : dim1=",size(Docc,1), &
232                               " dim2=",size(Docc,2), " max=", maxnflavor
233         ABI_ERROR(message)
234       end if
235       this%docc(1:size(Docc,1),1:size(Docc,1),iatom) = Docc(:,:)
236     else if ( present(Nocc) ) then ! Need to compute n_i*n_j (only used for DFT+U)
237       if ( size(Nocc,1) .gt. maxnflavor) then
238         write(message,'(a,i2,a,i2)') "Problem with Nocc size : dim1=",size(Nocc,1), &
239                               " maxnflavor=", maxnflavor
240         ABI_ERROR(message)
241       end if
242 
243       do iflavor1 = 1, (2*size(Nocc,1)+1)
244         do iflavor2 = 1, (2*size(Nocc,1)+1)
245           this%docc(iflavor2,iflavor1,iatom) = Nocc(iflavor1)*Nocc(iflavor2)
246         end do
247       end do
248     end if
249 
250 end subroutine data4entropyDMFT_setDocc

ABINIT/m_data4entropyDMFT/data4entropyDMFT_setHu [ Functions ]

[ Top ] [ Functions ]

NAME

  data4entropyDMFT_setHu

FUNCTION

  FIXME: add description.

COPYRIGHT

  Copyright (C) 2014-2024 ABINIT group (J. Bieder)
  This file is distributed under the terms of the
  GNU General Public License, see ~abinit/COPYING
  or http://www.gnu.org/copyleft/gpl.txt .

INPUTS

  argin(sizein)=description

OUTPUT

  argout(sizeout)=description

SIDE EFFECTS

NOTES

SOURCE

278 subroutine data4entropyDMFT_setHu(this,itypat,hu)
279 
280 !Arguments ------------------------------------
281     type(data4entropyDMFT_t), intent(inout) :: this
282     integer           , intent(in   ) :: itypat
283     real(dp)          , intent(in   ) :: hu(:,:)   !iflavor
284 !Local variables ------------------------------
285     integer            :: maxnflavor
286     character(len=500) :: message
287 
288     if ( .not. this%isset ) then
289       ABI_ERROR("data4entropyDMFT type not initialized")
290     end if
291 
292     if ( itypat .gt. this%ntypat ) then
293       write(message,'(a,i4,a,i4,a)') "Value of itypat (",itypat, &
294         ") is greater than the number of types of atoms (",this%ntypat,")."
295       ABI_ERROR(message)
296     end if
297 
298     maxnflavor=2*(2*this%maxlpawu+1)
299     if ( size(hu,1) .gt. maxnflavor .or. size(hu,1) .ne. size(hu,2) ) then
300       write(message,'(a,i2,a,i2,a,i2,a,i2)') "Problem with hu size : dim1=",size(hu,1), &
301                             " dim2=", size(hu,2), " max=", maxnflavor
302       ABI_ERROR(message)
303     end if
304     this%hu_dens(1:size(hu,1),1:size(hu,1),itypat) = hu(:,:)
305 
306 end subroutine data4entropyDMFT_setHu

ABINIT/m_data4entropyDMFT/data4etotdmf_destroy [ Functions ]

[ Top ] [ Functions ]

NAME

  data4entropyDMFT_destroy

FUNCTION

  FIXME: add description.

COPYRIGHT

  Copyright (C) 2014-2024 ABINIT group (J. Bieder)
  This file is distributed under the terms of the
  GNU General Public License, see ~abinit/COPYING
  or http://www.gnu.org/copyleft/gpl.txt .

INPUTS

  argin(sizein)=description

OUTPUT

  argout(sizeout)=description

SIDE EFFECTS

NOTES

SOURCE

382 subroutine data4entropyDMFT_destroy(this)
383 
384   !Arguments ------------------------------------
385   type(data4entropyDMFT_t), intent(inout) :: this
386 
387   if ( .not. this%isset ) return
388   if (allocated(this%docc))  then
389     ABI_FREE(this%docc)
390   endif
391   if (allocated(this%J_over_U))  then
392     ABI_FREE(this%J_over_U)
393   endif
394   if (allocated(this%e_dc))  then
395     ABI_FREE(this%e_dc)
396   endif
397   if (allocated(this%hu_dens))  then
398     ABI_FREE(this%hu_dens)
399   endif
400   this%maxlpawu = 0
401   this%natom = 0
402   this%ntypat = 0
403   this%isset = .FALSE.
404 end subroutine data4entropyDMFT_destroy

m_data4entropyDMFT/data4entropyDMFT [ Types ]

[ Top ] [ m_data4entropyDMFT ] [ Types ]

NAME

  data4entropyDMFT

FUNCTION

  This structured datatype contains the necessary data

COPYRIGHT

  Copyright (C) 2014-2024 ABINIT group (J. Bieder)
  This file is distributed under the terms of the
  GNU General Public License, see ~abinit/COPYING
  or http://www.gnu.org/copyleft/gpl.txt .

SOURCE

57   type, public :: data4entropyDMFT_t
58     logical               :: isset = .false.! Are we initialized ?
59     integer               :: maxlpawu       ! maximal value for lpawu
60     integer               :: natom          ! number of atoms
61     integer               :: ntypat         ! number of types of atoms
62     real(dp), allocatable :: docc(:,:,:)    ! double occupation for each atom
63     real(dp), allocatable :: J_over_U(:)    ! calculate J/U for each atom
64     real(dp), allocatable :: e_dc(:)        ! double counting energy calculated for u=1 and j=u/j
65     real(dp), allocatable :: hu_dens(:,:,:) ! interaction matrice in density representation
66   end type data4entropyDMFT_t