TABLE OF CONTENTS


ABINIT/m_scfcv [ Modules ]

[ Top ] [ Modules ]

NAME

  m_scfcv

FUNCTION

  FIXME: add description.

COPYRIGHT

  Copyright (C) 2014-2024 ABINIT group (JB)
  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_scfcv
25 
26  use defs_basis
27  use defs_wvltypes
28  use defs_rectypes
29  use m_abicore
30  use m_errors
31  use m_wffile
32  use m_rec
33  use m_efield
34  use m_entropyDMFT
35  use m_hdr
36  use m_extfpmd
37  use m_dtfil
38 
39  use defs_datatypes,     only : pseudopotential_type
40  use defs_abitypes,      only : MPI_type
41  use m_scf_history,      only : scf_history_type
42  use m_results_gs ,      only : results_gs_type
43  use m_electronpositron, only : electronpositron_type
44  use m_pawang,           only : pawang_type
45  use m_pawrad,           only : pawrad_type
46  use m_pawtab,           only : pawtab_type
47  use m_pawcprj,          only : pawcprj_type
48  use m_pawrhoij,         only : pawrhoij_type
49  use m_pawfgr,           only : pawfgr_type
50  use m_paw_dmft,         only : paw_dmft_type
51  use m_paw_uj,           only : macro_uj_type
52  use m_data4entropyDMFT, only : data4entropyDMFT_t, data4entropyDMFT_init, data4entropyDMFT_destroy
53  use m_scfcv_core,       only : scfcv_core
54 
55  implicit none
56 
57  private
58 
59  public :: scfcv_init
60  public :: scfcv_destroy
61  public :: scfcv_run

ABINIT/m_scfcv/scfcv_destroy [ Functions ]

[ Top ] [ Functions ]

NAME

  scfcv_destroy

FUNCTION

  FIXME: add description.

INPUTS

  scfcv=structure of scfcv

OUTPUT

SIDE EFFECTS

NOTES

SOURCE

364 subroutine scfcv_destroy(this)
365 
366 !Arguments ------------------------------------
367 type(scfcv_t), intent(inout) :: this
368 
369 !Local variables-------------------------------
370 
371 ! *************************************************************************
372 
373  DBG_ENTER("COLL")
374 
375  !scalars
376  this%mcg => null()
377  this%mcprj => null()
378  this%my_natom => null()
379  this%ndtpawuj => null()
380  this%pwind_alloc => null()
381  this%initialized => null()
382  this%nfftf => null()
383  this%cpus => null()
384  this%ecore  => null()
385  this%fatvshift => null()
386  this%pawang => null()
387  this%psps => null()
388  this%mpi_enreg => null()
389  this%dtfil => null()
390  this%dtset => null()
391  this%dtefield => null()
392  this%electronpositron => null()
393  this%hdr => null()
394  this%extfpmd => null()
395  this%pawfgr => null()
396  this%rec_set => null()
397  this%results_gs => null()
398  this%scf_history => null()
399  this%wffnew => null()
400  this%wffnow => null()
401  this%wvl => null()
402  this%paw_dmft => null()
403 
404  !arrays
405  this%atindx => null()
406  this%atindx1 => null()
407  this%irrzon => null()
408  this%symrec => null()
409  this%indsym => null()
410  !no_abirules
411  this%kg => null()
412  this%nattyp => null()
413  this%npwarr => null()
414  this%pwind => null()
415  this%phnons => null()
416  this%pwnsfac => null()
417  this%ylm => null()
418  this%ylmgr => null()
419  this%cg => null()
420  this%cprj => null()
421  this%dmatpawu => null()
422  this%eigen => null()
423  this%occ => null()
424  !this%rprimd
425  !this%rhog => null()
426  !this%rhor => null()
427  this%taug => null()
428  this%taur => null()
429  this%resid => null()
430  this%pawrad => null()
431  this%pawtab => null()
432  this%dtpawuj => null()
433  this%pawrhoij => null()
434 
435  ! This call should be done inside destroy_sc_dmft
436  !if ( this%dtset%usedmft /= 0 ) then
437  !  call data4entropyDMFT_destroy(this%paw_dmft%forentropyDMFT)
438  !end if
439  !call entropyDMFT_destroy(this%entropyDMFT)
440 
441  DBG_EXIT("COLL")
442 
443 end subroutine scfcv_destroy

ABINIT/m_scfcv/scfcv_init [ Functions ]

[ Top ] [ Functions ]

NAME

  scfcv_init

FUNCTION

  FIXME: add description.

INPUTS

  scfcv=structure of scfcv
  argin(sizein)=description

OUTPUT

  argout(sizeout)=description

SIDE EFFECTS

NOTES

SOURCE

172 subroutine scfcv_init(this,atindx,atindx1,cg,cprj,cpus,&
173 &  dmatpawu,dtefield,dtfil,dtpawuj,dtset,ecore,eigen,hdr,extfpmd,&
174 &  indsym,initialized,irrzon,kg,mcg,mcprj,mpi_enreg,my_natom,nattyp,ndtpawuj,&
175 &  nfftf,npwarr,occ,pawang,pawfgr,pawrad,pawrhoij,&
176 &  pawtab,phnons,psps,pwind,pwind_alloc,pwnsfac,rec_set,&
177 &  resid,results_gs,scf_history,fatvshift,&
178 &  symrec,taug,taur,wvl,ylm,ylmgr,paw_dmft,wffnew,wffnow)
179 
180 
181 !Arguments ------------------------------------
182 !scalars
183  type(scfcv_t), intent(inout) :: this
184  integer,intent(in),target :: mcg,mcprj,my_natom,ndtpawuj,pwind_alloc
185  integer,intent(in),target :: initialized,nfftf
186  real(dp),intent(in),target :: cpus,ecore
187  real(dp),intent(in),target :: fatvshift
188  type(MPI_type),intent(in),target :: mpi_enreg
189  type(datafiles_type),intent(in),target :: dtfil
190  type(dataset_type),intent(in),target :: dtset
191  type(efield_type),intent(in),target :: dtefield
192 ! type(electronpositron_type),pointer :: electronpositron
193  type(hdr_type),intent(in),target :: hdr
194  type(extfpmd_type),intent(in),pointer :: extfpmd
195  type(pawang_type),intent(in),target :: pawang
196  type(pawfgr_type),intent(in),target :: pawfgr
197  type(pseudopotential_type),intent(in),target :: psps
198  type(recursion_type),intent(in),target :: rec_set
199  type(results_gs_type),intent(in),target :: results_gs
200  type(scf_history_type),intent(in),target :: scf_history
201 ! type(wffile_type),intent(in),target :: wffnew,wffnow
202  type(wvl_data),intent(in),target :: wvl
203 !arrays
204  integer,intent(in),target :: atindx(dtset%natom),atindx1(dtset%natom)
205  integer,intent(in),target :: indsym(4,dtset%nsym,dtset%natom)
206 !no_abirules
207  integer, intent(in),target :: irrzon(dtset%nfft**(1-1/dtset%nsym),2,(dtset%nspden/dtset%nsppol)-3*(dtset%nspden/4))
208  integer, intent(in),target :: kg(3,dtset%mpw*dtset%mkmem)
209  integer, intent(in),target :: nattyp(psps%ntypat),npwarr(dtset%nkpt),pwind(pwind_alloc,2,3)
210  integer, intent(in),target :: symrec(3,3,dtset%nsym)
211  real(dp), intent(in),target :: cg(2,mcg),dmatpawu(:,:,:,:)
212  real(dp), intent(in),target :: eigen(dtset%mband*dtset%nkpt*dtset%nsppol)
213  real(dp), intent(in),target :: occ(dtset%mband*dtset%nkpt*dtset%nsppol)
214  real(dp), intent(in),target :: phnons(2,dtset%nfft**(1-1/dtset%nsym),(dtset%nspden/dtset%nsppol)-3*(dtset%nspden/4))
215  real(dp), intent(in),target :: pwnsfac(2,pwind_alloc)
216 ! real(dp), intent(in),target :: rprimd(3,3)
217 ! real(dp), pointer :: rhog(:,:),rhor(:,:)
218  real(dp), pointer :: taug(:,:),taur(:,:)
219  real(dp), intent(in),target :: resid(dtset%mband*dtset%nkpt*dtset%nsppol)
220 ! real(dp), intent(in),target :: xred(3,dtset%natom),xred_old(3,dtset%natom)
221  real(dp), intent(in),target :: ylm(dtset%mpw*dtset%mkmem,psps%mpsang*psps%mpsang*psps%useylm)
222  real(dp), intent(in),target :: ylmgr(dtset%mpw*dtset%mkmem,3,psps%mpsang*psps%mpsang*psps%useylm)
223  type(macro_uj_type),intent(in),target :: dtpawuj(0:ndtpawuj)
224  type(pawrhoij_type), intent(in),target :: pawrhoij(my_natom*psps%usepaw)
225  type(pawrad_type), intent(in),target :: pawrad(psps%ntypat*psps%usepaw)
226  type(pawtab_type), intent(in),target :: pawtab(psps%ntypat*psps%usepaw)
227  !type(dataset_type),intent(in),target :: dtset
228 ! type(electronpositron_type),intent(in),target :: electronpositron
229  type(paw_dmft_type), intent(in),target :: paw_dmft
230  type(wffile_type),intent(in),target :: wffnew,wffnow
231  type(pawcprj_type), allocatable,intent(in),target :: cprj(:,:)
232 !Local variables -------------------------
233 !scalars
234  logical :: DEBUG=.FALSE.
235 ! *************************************************************************
236 
237  DBG_ENTER("COLL")
238 
239  if (DEBUG) then
240    write(std_out,*) 'INTENT(IN) ARGUMENTS ON SCFCV'
241  !  write(std_out,*) 'atindx=',ab_scfcv_in%atindx
242  !  write(std_out,*) 'atindx1=',ab_scfcv_in%atindx1
243  !  write(std_out,*) 'cpus=',ab_scfcv_in%cpus
244  !  write(std_out,*) 'ecore=',ab_scfcv_in%ecore
245  !  write(std_out,*) 'fatvshift=',ab_scfcv_in%fatvshift
246  !  write(std_out,*) 'indsym=',ab_scfcv_in%indsym
247  !  write(std_out,*) 'kg=',ab_scfcv_in%kg
248  !  write(std_out,*) 'my_natom=',ab_scfcv_in%my_natom
249  !  write(std_out,*) 'nattyp=',ab_scfcv_in%nattyp
250  !  write(std_out,*) 'ndtpawuj=',ab_scfcv_in%ndtpawuj
251  !  write(std_out,*) 'npwarr=',ab_scfcv_in%npwarr
252  !  write(std_out,*) 'phnons=',ab_scfcv_in%phnons
253  !  write(std_out,*) 'pwind=',ab_scfcv_in%pwind
254  !  write(std_out,*) 'pwind_alloc=',ab_scfcv_in%pwind_alloc
255  !  write(std_out,*) 'pwnsfac=',ab_scfcv_in%pwnsfac
256  !  write(std_out,*) 'ylm=',ab_scfcv_in%ylm
257  !  write(std_out,*) 'ylmgr=',ab_scfcv_in%ylmgr
258 !!  write(std_out,*) 'pawang=',ab_scfcv_in%pawang
259 !!  write(std_out,*) 'pawrad=',ab_scfcv_in%pawrad
260 !!  write(std_out,*) 'pawtab=',ab_scfcv_in%pawtab
261 !!  write(std_out,*) 'psps=',ab_scfcv_in%psps
262  end if
263 
264  this%atindx=>atindx
265  this%atindx1=>atindx1
266  this%cpus=>cpus
267  this%ecore=>ecore
268  this%fatvshift=>fatvshift
269  this%indsym=>indsym
270  this%kg=>kg
271  this%mcg=>mcg
272  this%mcprj=>mcprj
273  this%my_natom=>my_natom
274  this%nattyp=>nattyp
275  this%ndtpawuj=>ndtpawuj
276  this%npwarr=>npwarr
277  this%pawang=>pawang
278  this%pawrad=>pawrad
279  this%pawtab=>pawtab
280  this%phnons=>phnons
281  this%psps=>psps
282  this%pwind=>pwind
283  this%pwind_alloc=>pwind_alloc
284  this%pwnsfac=>pwnsfac
285  this%ylm=>ylm
286  this%ylmgr=>ylmgr
287 
288  this%cg=>cg
289  this%cprj=>cprj
290  this%dmatpawu=>dmatpawu
291  this%dtefield=>dtefield
292  this%dtfil=>dtfil
293  this%dtpawuj=>dtpawuj
294  this%eigen=>eigen
295  this%hdr=>hdr
296  this%extfpmd=>extfpmd
297  this%initialized=>initialized
298  this%irrzon=>irrzon
299  this%mpi_enreg=>mpi_enreg
300  this%nfftf=>nfftf
301  this%occ=>occ
302  this%pawfgr=>pawfgr
303  this%pawrhoij=>pawrhoij
304  this%pawtab=>pawtab
305  this%rec_set=>rec_set
306  this%resid=>resid
307  this%results_gs=>results_gs
308  this%scf_history=>scf_history
309  this%symrec=>symrec
310  this%taug=>taug
311  this%taur=>taur
312  this%wvl=>wvl
313 
314  this%dtset=>dtset
315  !this%electronpositron=>electronpositron
316  this%paw_dmft=>paw_dmft
317  !this%rhog=>rhog
318  !this%rhor=>rhor
319  !this%rprimd=>rprimd
320  this%wffnew=>wffnew
321  this%wffnow=>wffnow
322  !this%xred=>xred
323  !this%xred_old=>xred_old
324 
325 
326  !!!!!!!!! INITIALIZE or REINITIALIZE parallelization here !!
327  ! TODO at next step
328  !if ( this%dtset%usedmft /= 0 ) then
329  !  call data4entropyDMFT_init(this%paw_dmft%forentropyDMFT,&
330  !                            this%dtset%natom,&
331  !                            this%dtset%typat,&
332  !                            this%dtset%lpawu,&
333  !                            this%dtset%dmft_t2g==1, &
334  !                            this%dtset%upawu,&   !!! Should use this%pawtab%upawu
335  !                            this%dtset%jpawu)    !!! Should use this%pawtab%jpawu
336  !end if
337 
338  !call entropyDMFT_init(this%entropyDMFT,this%dtset,this%pawtab,this%mpi_enreg%comm_cell,this%dtfil%filnam_ds(3),this%dtfil%filnam_ds(4)) ! Do something only if DMFT and dmft_entropy = 1
339 
340  DBG_EXIT("COLL")
341 
342 end subroutine scfcv_init

ABINIT/m_scfcv/scfcv_run [ Functions ]

[ Top ] [ Functions ]

NAME

  scfcv_run

FUNCTION

  FIXME: add description.

INPUTS

  itimes(2)=itime array, contain itime=itimes(1) and itimimage_gstate=itimes(2) from outer loops
  scfcv=structure of scfcv

OUTPUT

SOURCE

461 subroutine scfcv_run(this, electronpositron, itimes, rhog, rhor, rprimd, xred, xred_old, conv_retcode)
462 
463 !Arguments ------------------------------------
464  type(scfcv_t), intent(inout) :: this
465  integer,intent(in) :: itimes(2)
466  type(electronpositron_type),pointer:: electronpositron
467  real(dp), intent(inout) :: rprimd(3,3)
468  real(dp), intent(inout) :: xred(3,this%dtset%natom)
469  real(dp), intent(inout) :: xred_old(3,this%dtset%natom)
470  real(dp), pointer, intent(inout) :: rhog(:,:)
471  real(dp), pointer, intent(inout) :: rhor(:,:)
472  integer ,intent(out) :: conv_retcode
473 
474 !Local variables-------------------------------
475 
476 ! *************************************************************************
477 
478  DBG_ENTER("COLL")
479 
480 !!!  Should be changed if special parallelization.
481 
482  ! Moved inside mover.F90 before this call
483  !call scfcv_reformatWFK(this,rhog, rhor, rprimd, xred, xred_old)
484 
485  ! First initialize the datatype to gather information
486 
487  !debug purpose
488  !this%electronpositron => electronpositron
489  if ( this%dtset%dmft_entropy == 0 ) then
490    call scfcv_scfcv(this, electronpositron, itimes, rhog, rhor, rprimd, xred, xred_old, conv_retcode)
491  elseif ( this%dtset%dmft_entropy >=1 ) then
492    call scfcv_runWEntropyDMFT(this, electronpositron,itimes, rhog,rhor,rprimd,xred,xred_old,conv_retcode)
493  end if
494 
495  DBG_EXIT("COLL")
496 
497 end subroutine scfcv_run

ABINIT/m_scfcv/scfcv_runWEntropyDMFT [ Functions ]

[ Top ] [ Functions ]

NAME

  scfcv_runWEntropyDMFT

FUNCTION

  FIXME: add description.

INPUTS

  itimes(2)=itime array, contain itime=itimes(1) and itimimage_gstate=itimes(2) from outer loops
  scfcv=structure of scfcv
  argin(sizein)=description

OUTPUT

  argout(sizeout)=description

SIDE EFFECTS

NOTES

SOURCE

574 subroutine scfcv_runWEntropyDMFT(this,electronpositron,itimes,rhog,rhor,rprimd,xred,xred_old,conv_retcode)
575 
576 
577 !Arguments ------------------------------------
578  type(scfcv_t), intent(inout) :: this
579  integer,intent(in) :: itimes(2)
580  type(electronpositron_type),pointer :: electronpositron
581  real(dp), intent(inout) :: rprimd(3,3)
582  real(dp), intent(inout) :: xred(3,this%dtset%natom)
583  real(dp), intent(inout) :: xred_old(3,this%dtset%natom)
584  real(dp), pointer, intent(inout) :: rhog(:,:)
585  real(dp), pointer, intent(inout) :: rhor(:,:)
586  integer , intent(out)   :: conv_retcode
587 
588 !Local variables-------------------------------
589 
590 ! *************************************************************************
591 
592  DBG_ENTER("COLL")
593 
594  !if ( this%dtset%usedmft /= 0 ) then
595  !  call data4entropyDMFT_init(this%paw_dmft%forentropyDMFT,&
596  !                            this%dtset%natom,&
597  !                            this%dtset%typat,&
598  !                            this%dtset%lpawu,&
599  !                            this%dtset%dmft_t2g==1, &
600  !                            this%dtset%upawu,&     !!! Should use this%pawtab%upawu
601  !                            this%dtset%jpawu)      !!! Should use this%pawtab%jpawu
602  !end if
603 
604  call entropyDMFT_init(this%entropyDMFT,this%dtset,this%pawtab,this%mpi_enreg%comm_cell,&
605 &       this%dtfil%filnam_ds(3),this%dtfil%filnam_ds(4)) ! Do something only if DMFT and dmft_entropy = 1
606 
607  ! Start loop over all integration points (lambda)
608  ! TODO WORK ON PARALLELISATION HERE
609  do while (entropyDMFT_nextLambda(this%entropyDMFT,this%dtset,this%pawtab,this%pawang,this%pawrad))
610 
611  !-----------------------------------------------------
612    call scfcv_scfcv(this, electronpositron,itimes,rhog,rhor,rprimd,xred,xred_old,conv_retcode)
613  !-----------------------------------------------------
614    call entropyDMFT_addIntegrand(this%entropyDMFT,this%dtset, this%results_gs%energies,this%paw_dmft%forentropyDMFT)
615 
616  end do !!! End loop for entropy DMFT
617 
618  ! GATHER DATA HERE OR INSIDE THE NEXT CALL ?
619  call entropyDMFT_computeEntropy(this%entropyDMFT,this%results_gs%energies%entropy)
620  !-----------------------------------------------------
621  ! This call should be done inside destroy_sc_dmft
622  !if ( this%dtset%usedmft /= 0 ) then
623  !  call data4entropyDMFT_destroy(this%paw_dmft%forentropyDMFT)
624  !end if
625  call entropyDMFT_destroy(this%entropyDMFT)
626 
627  DBG_EXIT("COLL")
628 
629 end subroutine scfcv_runWEntropyDMFT

ABINIT/m_scfcv/scfcv_scfcv [ Functions ]

[ Top ] [ Functions ]

NAME

  scfcv_scfcv

FUNCTION

  FIXME: add description.

INPUTS

  scfcv=structure of scfcv
  itimes(2)=itime array, contain itime=itimes(1) and itimimage_gstate=itimes(2) from outer loops

OUTPUT

NOTES

  Wrapper to scfcv to avoid circular dependencies ...

SOURCE

650 subroutine scfcv_scfcv(this, electronpositron, itimes, rhog, rhor, rprimd, xred, xred_old, conv_retcode)
651 
652  type(scfcv_t), intent(inout) :: this
653  integer,intent(in) :: itimes(2)
654  type(electronpositron_type),pointer :: electronpositron
655  real(dp), intent(inout) :: rprimd(3,3)
656  real(dp), intent(inout) :: xred(3,this%dtset%natom)
657  real(dp), intent(inout) :: xred_old(3,this%dtset%natom)
658  real(dp), pointer, intent(inout) :: rhog(:,:)
659  real(dp), pointer, intent(inout) :: rhor(:,:)
660  integer , intent(out)   :: conv_retcode
661 
662    call scfcv_core(this%atindx,this%atindx1,this%cg,this%cprj,this%cpus,this%dmatpawu,this%dtefield,this%dtfil,&
663     this%dtpawuj,&
664     this%dtset,this%ecore,this%eigen,electronpositron,this%fatvshift,this%hdr,this%extfpmd,this%indsym,&
665     this%initialized,this%irrzon,itimes,this%kg,this%mcg,this%mcprj,this%mpi_enreg,this%my_natom,this%nattyp,this%ndtpawuj,&
666     this%nfftf,this%npwarr,&
667     this%occ,this%paw_dmft,this%pawang,this%pawfgr,this%pawrad,this%pawrhoij,this%pawtab,this%phnons,this%psps,this%pwind,&
668     this%pwind_alloc,this%pwnsfac,this%rec_set,this%resid,this%results_gs,rhog,rhor,rprimd,&
669     this%scf_history,this%symrec,this%taug,this%taur,this%wffnew,this%wvl,xred,xred_old,this%ylm,this%ylmgr,&
670     conv_retcode)
671 
672 end subroutine scfcv_scfcv
673 
674 end module m_scfcv

m_scfcv/scfcv_t [ Types ]

[ Top ] [ m_scfcv ] [ Types ]

NAME

  scfcv_t

FUNCTION

  This structured datatype contains the necessary data

COPYRIGHT

  Copyright (C) 2014-2024 ABINIT group (JB)
  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

 81  type, public :: scfcv_t
 82   !scalars
 83    integer,pointer :: mcg => null()
 84    integer,pointer :: mcprj => null()
 85    integer,pointer :: my_natom => null()
 86    integer,pointer :: ndtpawuj => null()
 87    integer,pointer :: pwind_alloc => null()
 88    integer,pointer :: initialized => null()
 89    integer,pointer :: nfftf => null()
 90    real(dp),pointer :: cpus => null()
 91    real(dp),pointer :: ecore  => null()
 92    real(dp),pointer :: fatvshift => null()
 93    type(pawang_type),pointer :: pawang => null()
 94    type(pseudopotential_type),pointer :: psps => null()
 95    type(MPI_type),pointer :: mpi_enreg => null()
 96    type(datafiles_type),pointer :: dtfil => null()
 97    type(dataset_type),pointer :: dtset => null()
 98    type(efield_type),pointer :: dtefield => null()
 99    type(electronpositron_type),pointer :: electronpositron => null()
100    type(hdr_type),pointer :: hdr => null()
101    type(extfpmd_type),pointer :: extfpmd => null()
102    type(pawfgr_type),pointer :: pawfgr => null()
103    type(recursion_type),pointer :: rec_set => null()
104    type(results_gs_type),pointer :: results_gs => null()
105    type(scf_history_type),pointer :: scf_history => null()
106    type(wffile_type),pointer :: wffnew => null()
107    type(wffile_type),pointer :: wffnow => null()
108    type(wvl_data),pointer :: wvl => null()
109    type(paw_dmft_type), pointer :: paw_dmft => null()
110 
111    !arrays
112    integer,pointer :: atindx(:) => null()
113    integer,pointer :: atindx1(:) => null()
114    integer, pointer :: irrzon(:,:,:) => null()
115    integer, pointer :: symrec(:,:,:) => null()
116    integer,pointer :: indsym(:,:,:) => null()
117    !no_abirules
118    integer, pointer :: kg(:,:) => null()
119    integer, pointer :: nattyp(:) => null()
120    integer, pointer :: npwarr(:) => null()
121    integer, pointer :: pwind(:,:,:) => null()
122    real(dp), pointer :: dmatpawu(:,:,:,:) => null()
123    real(dp), pointer :: phnons(:,:,:) => null()
124    real(dp), pointer :: pwnsfac(:,:) => null()
125    real(dp), pointer :: ylm(:,:) => null()
126    real(dp), pointer :: ylmgr(:,:,:) => null()
127    real(dp), pointer :: cg(:,:) => null()
128    real(dp), pointer :: eigen(:) => null()
129    real(dp), pointer :: occ(:) => null()
130    !real(dp), pointer :: rprimd(:,:) => null()
131    !real(dp), pointer :: rhog(:,:) => null()
132    !real(dp), pointer :: rhor(:,:) => null()
133    real(dp), pointer :: taug(:,:) => null()
134    real(dp), pointer :: taur(:,:) => null()
135    real(dp), pointer :: resid(:) => null()
136    type(pawrad_type), pointer :: pawrad(:) => null()
137    type(pawtab_type), pointer :: pawtab(:) => null()
138    type(macro_uj_type),pointer :: dtpawuj(:) => null()
139    type(pawrhoij_type), pointer :: pawrhoij(:) => null()
140    type(pawcprj_type),pointer :: cprj(:,:) => null()
141    ! PRIVATE ATTRIBUTS
142    type(entropyDMFT_t) ABI_PRIVATE :: entropyDMFT
143  end type scfcv_t