diff --git a/src/RelaxSE.F90 b/src/RelaxSE.F90 index e87b99bd0780dcd30ef9401def89377e981d3d09..c5b7521335740c1cb92bbd2a5e25834602d5508b 100644 --- a/src/RelaxSE.F90 +++ b/src/RelaxSE.F90 @@ -218,22 +218,6 @@ Program RelaxSE flush(f_output) endif - if (lprop) then - write(f_output,*) - call wrt_info(prog_info,g_info,o_info,v_info,det_info,d,sym_info,f_info) - write(f_output,*)">>> x_info written on file" - flush(f_info) - flush(f_output) - write(f_output,*) - call deter_init(det,det_info%ndet) - call fill_detd(det, d) - call wrt_bdet(det,det_info%ndet,f_bdet) - write(f_output,*)">>> Determinants written on file" - flush(f_output) - flush(f_bdet) - call deter_free(det) - endif - !Initialisation of the bare h matrix ! contains ntot * ntot elements ! their indices run from ngel+1 to ngel+ntot @@ -259,7 +243,25 @@ Program RelaxSE #ifdef VAR_MPI call MPI_BARRIER(MPI_COMM_WORLD,ierr) #endif - + + ! write info for prop + if (lprop) then + write(f_output,*) + call wrt_info(prog_info,g_info,o_info,v_info,det_info,int_info,d,sym_info,f_info) + write(f_output,*)">>> x_info written on file" + flush(f_info) + flush(f_output) + write(f_output,*) + call deter_init(det,det_info%ndet) + call fill_detd(det, d) + call wrt_bdet(det,det_info%ndet,f_bdet) + write(f_output,*)">>> Determinants written on file" + flush(f_output) + flush(f_bdet) + call deter_free(det) + endif + + !Build the fock matrix !Add the 2e- part to the bare h_pq !f_pq = h_pq + sum[ 2(ij|oo) - (io|jo)] @@ -283,7 +285,8 @@ Program RelaxSE flush(f_output) endif call get_e0(ener_info, hcoeur, o_info, int_info, prog_info) - + + !----- !----- Diag 0 !----- diff --git a/src/init_prop.F90 b/src/init_prop.F90 index bafe3068e275fbc529890b706bb52225215ae96e..72c8a115c4384b2eb50b4e107584728b1fe914b2 100644 --- a/src/init_prop.F90 +++ b/src/init_prop.F90 @@ -28,7 +28,7 @@ !!---- -subroutine init_prop(g_info, prog_info, o_info, v_info, det_info, sym_info, prop_info) +subroutine init_prop(g_info, prog_info, o_info, v_info, det_info, int_info, sym_info, prop_info) !!$ Initialisation des variables !!$ -------- Donness globales --------------------------------- use dimensions @@ -44,6 +44,7 @@ subroutine init_prop(g_info, prog_info, o_info, v_info, det_info, sym_info, prop type(o_infotype), intent(inout) :: o_info type(v_infotype), intent(inout) :: v_info type(det_infotype), intent(inout) :: det_info + type(int_infotype), intent(inout) :: int_info type(sym_infotype), intent(inout) :: sym_info type(prop_infotype), intent(inout) :: prop_info @@ -96,6 +97,41 @@ subroutine init_prop(g_info, prog_info, o_info, v_info, det_info, sym_info, prop det_info%nmonoref0 = 0 det_info%ndiref0 = 0 + ! int_info + int_info%n_1int = 0 + int_info%n_oooo = 0 + int_info%n_aaaa = 0 + int_info%n_aaao = 0 + !int_info%n_aoaa = 0 + int_info%n_aaoo = 0 + int_info%n_aoao = 0 + int_info%n_aooo = 0 + int_info%n_vooo = 0 + int_info%n_vaoo = 0 + int_info%n_voao = 0 + int_info%n_vaao = 0 + int_info%n_voaa = 0 + int_info%n_vaaa = 0 + int_info%n_vvoo = 0 + int_info%n_vovo = 0 + int_info%n_vvao = 0 + int_info%n_vavo = 0 + !int_info%n_vova = 0 + int_info%n_vvaa = 0 + int_info%n_vava = 0 + int_info%n_vvvo = 0 + int_info%n_vvva = 0 + int_info%n_vvvv = 0 + int_info%n_gint = 0 + int_info%n_2int = 0 + int_info%nintkind = 0 + int_info%CASS_nintkind = 21 + allocate(int_info%CASS_intkind(int_info%CASS_nintkind)) + int_info%CASS_intkind(:) & + = (/ 'fock', 'aaaa', 'aaao', 'vaaa', 'aaoo', 'vaao', 'vvaa','vaoo', & + 'vvao','vvoo', 'vava','vvvo','vvva','vvvv','oooo','vovo','aooo','vavo',& + 'vooo','aoao','voao'/) + !sym_info sym_info%iChTb(:,:) = 0 sym_info%iIrTb(:,:) = 0 diff --git a/src/prop.F90 b/src/prop.F90 index a5298c40bf76d62d09d8ae2da704128edeace17b..652c4f96bf664228ba1712bdba28575cfe428483 100644 --- a/src/prop.F90 +++ b/src/prop.F90 @@ -43,6 +43,7 @@ Program proprietes use gener_monos use utils_char use utils_wrt + use densite !!$ -------- Donnes locales ----------------------------------- implicit none @@ -53,6 +54,7 @@ Program proprietes type(o_infotype) :: o_info type(v_infotype) :: v_info type(det_infotype) :: det_info + type(int_infotype) :: int_info type(sym_infotype) :: sym_info @@ -74,6 +76,9 @@ Program proprietes Integer(KIND=kd_int) :: nprop character*5, dimension(:), allocatable :: whichprop + ! proprietes + real(kd_dble), dimension(:,:,:), allocatable :: rho_tot,rho_spin + ! impressions integer, parameter :: pas = 10 character*1, parameter :: A1=" " @@ -95,7 +100,7 @@ Program proprietes !!$----- !!$----- Initialisations !!$----- - call init_prop(g_info, prog_info, o_info, v_info, det_info,sym_info, prop_info) + call init_prop(g_info, prog_info, o_info, v_info, det_info, int_info, sym_info, prop_info) #ifdef VAR_OMP !$OMP PARALLEL SHARED(nb_thread) @@ -119,6 +124,7 @@ Program proprietes read(f_info) o_info read(f_info) v_info read(f_info) det_info + read(f_info) int_info read(f_info) nblock allocate(shtblkdet(nblock), nblkdet(nblock), deter_index(nblock)) shtblkdet(:) = 0 @@ -256,6 +262,7 @@ Program proprietes write(f_output,*) write(f_output,*) " >>> One particule density matrix" write(f_output,*) " Not yet implemented" + call dens(ndet,nvec,nblock,psi,det,d,rspin,o_info,int_info,prog_info,rho_tot,rho_spin) end select end do diff --git a/src/utils_wrt.F90 b/src/utils_wrt.F90 index 9154821e07d8f30bcc1605b782fafb0369ded657..c38e6403417748f483aa1b972e06127228cd0944 100644 --- a/src/utils_wrt.F90 +++ b/src/utils_wrt.F90 @@ -153,7 +153,7 @@ contains !> @param !> @param !$============================================================ - subroutine wrt_info(prog_info,g_info,o_info,v_info,det_info,d,sym_info,iunit) + subroutine wrt_info(prog_info,g_info,o_info,v_info,det_info,int_info,d,sym_info,iunit) ! -------- Donnes locales ----------------------------------- Implicit none type(prog_infotype), intent(in) :: prog_info @@ -161,6 +161,7 @@ contains type(o_infotype), intent(in) :: o_info type(v_infotype), intent(in) :: v_info type(det_infotype), intent(in) :: det_info + type(int_infotype), intent(in) :: int_info type(deter_dblocklist),intent(in):: d type(sym_infotype), intent(in) :: sym_info integer, intent(in) :: iunit @@ -181,6 +182,7 @@ contains write(iunit) o_info write(iunit) v_info write(iunit) det_info + write(iunit) int_info write(iunit) nblock write(iunit) shtblkdet(1:nblock), nblkdet(1:nblock), deter_index(1:nblock) write(iunit) sym_info