mirror of
https://github.com/QuantumPackage/qp2.git
synced 2024-11-07 05:53:37 +01:00
Added JSON to fci_tc_bi
This commit is contained in:
parent
918839fbf6
commit
54a88fe4ca
@ -1,6 +1,7 @@
|
|||||||
|
json
|
||||||
mpi
|
mpi
|
||||||
perturbation
|
perturbation
|
||||||
zmq
|
zmq
|
||||||
iterations_tc
|
iterations
|
||||||
csf
|
csf
|
||||||
tc_bi_ortho
|
tc_bi_ortho
|
||||||
|
@ -101,7 +101,7 @@ subroutine run_stochastic_cipsi
|
|||||||
|
|
||||||
call increment_n_iter(psi_energy_with_nucl_rep, pt2_data)
|
call increment_n_iter(psi_energy_with_nucl_rep, pt2_data)
|
||||||
call print_extrapolated_energy()
|
call print_extrapolated_energy()
|
||||||
call print_mol_properties()
|
! call print_mol_properties()
|
||||||
call write_cipsi_json(pt2_data,pt2_data_err)
|
call write_cipsi_json(pt2_data,pt2_data_err)
|
||||||
|
|
||||||
if (qp_stop()) exit
|
if (qp_stop()) exit
|
||||||
|
53
src/cipsi_tc_bi_ortho/write_cipsi_json.irp.f
Normal file
53
src/cipsi_tc_bi_ortho/write_cipsi_json.irp.f
Normal file
@ -0,0 +1,53 @@
|
|||||||
|
subroutine write_cipsi_json(pt2_data, pt2_data_err)
|
||||||
|
use selection_types
|
||||||
|
implicit none
|
||||||
|
BEGIN_DOC
|
||||||
|
! Writes JSON data for CIPSI runs
|
||||||
|
END_DOC
|
||||||
|
type(pt2_type), intent(in) :: pt2_data, pt2_data_err
|
||||||
|
integer :: i,j,k
|
||||||
|
|
||||||
|
call lock_io
|
||||||
|
character*(64), allocatable :: fmtk(:)
|
||||||
|
integer :: N_states_p, N_iter_p
|
||||||
|
N_states_p = min(N_states,N_det)
|
||||||
|
N_iter_p = min(N_iter,8)
|
||||||
|
allocate(fmtk(0:N_iter_p))
|
||||||
|
fmtk(:) = '('' '',E22.15,'','')'
|
||||||
|
fmtk(N_iter_p) = '('' '',E22.15)'
|
||||||
|
|
||||||
|
write(json_unit, json_dict_uopen_fmt)
|
||||||
|
write(json_unit, json_int_fmt) 'n_det', N_det
|
||||||
|
if (s2_eig) then
|
||||||
|
write(json_unit, json_int_fmt) 'n_cfg', N_configuration
|
||||||
|
if (only_expected_s2) then
|
||||||
|
write(json_unit, json_int_fmt) 'n_csf', N_csf
|
||||||
|
endif
|
||||||
|
endif
|
||||||
|
write(json_unit, json_array_open_fmt) 'states'
|
||||||
|
do k=1,N_states_p
|
||||||
|
write(json_unit, json_dict_uopen_fmt)
|
||||||
|
write(json_unit, json_real_fmt) 'energy', psi_energy_with_nucl_rep(k)
|
||||||
|
write(json_unit, json_real_fmt) 's2', psi_s2(k)
|
||||||
|
write(json_unit, json_real_fmt) 'pt2', pt2_data % pt2(k)
|
||||||
|
write(json_unit, json_real_fmt) 'pt2_err', pt2_data_err % pt2(k)
|
||||||
|
write(json_unit, json_real_fmt) 'rpt2', pt2_data % rpt2(k)
|
||||||
|
write(json_unit, json_real_fmt) 'rpt2_err', pt2_data_err % rpt2(k)
|
||||||
|
write(json_unit, json_real_fmt) 'variance', pt2_data % variance(k)
|
||||||
|
write(json_unit, json_real_fmt) 'variance_err', pt2_data_err % variance(k)
|
||||||
|
write(json_unit, json_array_open_fmt) 'ex_energy'
|
||||||
|
do i=2,N_iter_p
|
||||||
|
write(json_unit, fmtk(i)) extrapolated_energy(i,k)
|
||||||
|
enddo
|
||||||
|
write(json_unit, json_array_close_fmtx)
|
||||||
|
if (k < N_states_p) then
|
||||||
|
write(json_unit, json_dict_close_fmt)
|
||||||
|
else
|
||||||
|
write(json_unit, json_dict_close_fmtx)
|
||||||
|
endif
|
||||||
|
enddo
|
||||||
|
write(json_unit, json_array_close_fmtx)
|
||||||
|
write(json_unit, json_dict_close_fmt)
|
||||||
|
deallocate(fmtk)
|
||||||
|
call unlock_io
|
||||||
|
end
|
@ -1,3 +1,4 @@
|
|||||||
|
json
|
||||||
tc_bi_ortho
|
tc_bi_ortho
|
||||||
davidson_undressed
|
davidson_undressed
|
||||||
cipsi_tc_bi_ortho
|
cipsi_tc_bi_ortho
|
||||||
|
@ -4,6 +4,6 @@ subroutine save_energy(E,pt2)
|
|||||||
! Saves the energy in |EZFIO|.
|
! Saves the energy in |EZFIO|.
|
||||||
END_DOC
|
END_DOC
|
||||||
double precision, intent(in) :: E(N_states), pt2(N_states)
|
double precision, intent(in) :: E(N_states), pt2(N_states)
|
||||||
call ezfio_set_fci_tc_energy(E(1:N_states))
|
call ezfio_set_fci_tc_bi_energy(E(1:N_states))
|
||||||
call ezfio_set_fci_tc_energy_pt2(E(1:N_states)+pt2(1:N_states))
|
call ezfio_set_fci_tc_bi_energy_pt2(E(1:N_states)+pt2(1:N_states))
|
||||||
end
|
end
|
||||||
|
@ -1,24 +0,0 @@
|
|||||||
[n_iter]
|
|
||||||
interface: ezfio
|
|
||||||
doc: Number of saved iterations
|
|
||||||
type:integer
|
|
||||||
default: 1
|
|
||||||
|
|
||||||
[n_det_iterations]
|
|
||||||
interface: ezfio, provider
|
|
||||||
doc: Number of determinants at each iteration
|
|
||||||
type: integer
|
|
||||||
size: (100)
|
|
||||||
|
|
||||||
[energy_iterations]
|
|
||||||
interface: ezfio, provider
|
|
||||||
doc: The variational energy at each iteration
|
|
||||||
type: double precision
|
|
||||||
size: (determinants.n_states,100)
|
|
||||||
|
|
||||||
[pt2_iterations]
|
|
||||||
interface: ezfio, provider
|
|
||||||
doc: The |PT2| correction at each iteration
|
|
||||||
type: double precision
|
|
||||||
size: (determinants.n_states,100)
|
|
||||||
|
|
@ -1,37 +0,0 @@
|
|||||||
BEGIN_PROVIDER [ integer, n_iter ]
|
|
||||||
implicit none
|
|
||||||
BEGIN_DOC
|
|
||||||
! number of iterations
|
|
||||||
END_DOC
|
|
||||||
|
|
||||||
logical :: has
|
|
||||||
PROVIDE ezfio_filename
|
|
||||||
if (mpi_master) then
|
|
||||||
|
|
||||||
double precision :: zeros(N_states,100)
|
|
||||||
integer :: izeros(100)
|
|
||||||
zeros = 0.d0
|
|
||||||
izeros = 0
|
|
||||||
call ezfio_set_iterations_n_iter(0)
|
|
||||||
call ezfio_set_iterations_energy_iterations(zeros)
|
|
||||||
call ezfio_set_iterations_pt2_iterations(zeros)
|
|
||||||
call ezfio_set_iterations_n_det_iterations(izeros)
|
|
||||||
n_iter = 1
|
|
||||||
endif
|
|
||||||
IRP_IF MPI_DEBUG
|
|
||||||
print *, irp_here, mpi_rank
|
|
||||||
call MPI_BARRIER(MPI_COMM_WORLD, ierr)
|
|
||||||
IRP_ENDIF
|
|
||||||
IRP_IF MPI
|
|
||||||
include 'mpif.h'
|
|
||||||
integer :: ierr
|
|
||||||
call MPI_BCAST( n_iter, 1, MPI_INTEGER, 0, MPI_COMM_WORLD, ierr)
|
|
||||||
if (ierr /= MPI_SUCCESS) then
|
|
||||||
stop 'Unable to read n_iter with MPI'
|
|
||||||
endif
|
|
||||||
IRP_ENDIF
|
|
||||||
|
|
||||||
call write_time(6)
|
|
||||||
|
|
||||||
END_PROVIDER
|
|
||||||
|
|
@ -1,43 +0,0 @@
|
|||||||
BEGIN_PROVIDER [ double precision, extrapolated_energy, (N_iter,N_states) ]
|
|
||||||
implicit none
|
|
||||||
BEGIN_DOC
|
|
||||||
! Extrapolated energy, using E_var = f(PT2) where PT2=0
|
|
||||||
END_DOC
|
|
||||||
! integer :: i
|
|
||||||
extrapolated_energy = 0.D0
|
|
||||||
END_PROVIDER
|
|
||||||
|
|
||||||
subroutine get_extrapolated_energy(Niter,ept2,pt1,extrap_energy)
|
|
||||||
implicit none
|
|
||||||
integer, intent(in) :: Niter
|
|
||||||
double precision, intent(in) :: ept2(Niter),pt1(Niter),extrap_energy(Niter)
|
|
||||||
call extrapolate_data(Niter,ept2,pt1,extrap_energy)
|
|
||||||
end
|
|
||||||
|
|
||||||
subroutine save_iterations(e_, pt2_,n_)
|
|
||||||
implicit none
|
|
||||||
BEGIN_DOC
|
|
||||||
! Update the energy in the EZFIO file.
|
|
||||||
END_DOC
|
|
||||||
integer, intent(in) :: n_
|
|
||||||
double precision, intent(in) :: e_(N_states), pt2_(N_states)
|
|
||||||
integer :: i
|
|
||||||
|
|
||||||
if (N_iter == 101) then
|
|
||||||
do i=2,N_iter-1
|
|
||||||
energy_iterations(1:N_states,N_iter-1) = energy_iterations(1:N_states,N_iter)
|
|
||||||
pt2_iterations(1:N_states,N_iter-1) = pt2_iterations(1:N_states,N_iter)
|
|
||||||
enddo
|
|
||||||
N_iter = N_iter-1
|
|
||||||
TOUCH N_iter
|
|
||||||
endif
|
|
||||||
|
|
||||||
energy_iterations(1:N_states,N_iter) = e_(1:N_states)
|
|
||||||
pt2_iterations(1:N_states,N_iter) = pt2_(1:N_states)
|
|
||||||
n_det_iterations(N_iter) = n_
|
|
||||||
call ezfio_set_iterations_N_iter(N_iter)
|
|
||||||
call ezfio_set_iterations_energy_iterations(energy_iterations)
|
|
||||||
call ezfio_set_iterations_pt2_iterations(pt2_iterations)
|
|
||||||
call ezfio_set_iterations_n_det_iterations(n_det_iterations)
|
|
||||||
end
|
|
||||||
|
|
@ -1,46 +0,0 @@
|
|||||||
subroutine print_extrapolated_energy
|
|
||||||
implicit none
|
|
||||||
BEGIN_DOC
|
|
||||||
! Print the extrapolated energy in the output
|
|
||||||
END_DOC
|
|
||||||
|
|
||||||
integer :: i,k
|
|
||||||
|
|
||||||
if (N_iter< 2) then
|
|
||||||
return
|
|
||||||
endif
|
|
||||||
write(*,'(A)') ''
|
|
||||||
write(*,'(A)') 'Extrapolated energies'
|
|
||||||
write(*,'(A)') '------------------------'
|
|
||||||
write(*,'(A)') ''
|
|
||||||
|
|
||||||
print *, ''
|
|
||||||
print *, 'State ', 1
|
|
||||||
print *, ''
|
|
||||||
write(*,*) '=========== ', '==================='
|
|
||||||
write(*,*) 'minimum PT2 ', 'Extrapolated energy'
|
|
||||||
write(*,*) '=========== ', '==================='
|
|
||||||
do k=2,min(N_iter,8)
|
|
||||||
write(*,'(F11.4,2X,F18.8)') pt2_iterations(1,N_iter+1-k), extrapolated_energy(k,1)
|
|
||||||
enddo
|
|
||||||
write(*,*) '=========== ', '==================='
|
|
||||||
|
|
||||||
do i=2, min(N_states,N_det)
|
|
||||||
print *, ''
|
|
||||||
print *, 'State ', i
|
|
||||||
print *, ''
|
|
||||||
write(*,*) '=========== ', '=================== ', '=================== ', '==================='
|
|
||||||
write(*,*) 'minimum PT2 ', 'Extrapolated energy ', ' Excitation (a.u) ', ' Excitation (eV) '
|
|
||||||
write(*,*) '=========== ', '=================== ', '=================== ', '==================='
|
|
||||||
do k=2,min(N_iter,8)
|
|
||||||
write(*,'(F11.4,X,3(X,F18.8))') pt2_iterations(i,N_iter+1-k), extrapolated_energy(k,i), &
|
|
||||||
extrapolated_energy(k,i) - extrapolated_energy(k,1), &
|
|
||||||
(extrapolated_energy(k,i) - extrapolated_energy(k,1) ) * 27.211396641308d0
|
|
||||||
enddo
|
|
||||||
write(*,*) '=========== ', '=================== ', '=================== ', '==================='
|
|
||||||
enddo
|
|
||||||
|
|
||||||
print *, ''
|
|
||||||
|
|
||||||
end subroutine
|
|
||||||
|
|
@ -1,104 +0,0 @@
|
|||||||
subroutine print_summary(e_,pt2_data,pt2_data_err,n_det_,n_configuration_,n_st,s2_)
|
|
||||||
use selection_types
|
|
||||||
implicit none
|
|
||||||
BEGIN_DOC
|
|
||||||
! Print the extrapolated energy in the output
|
|
||||||
END_DOC
|
|
||||||
|
|
||||||
integer, intent(in) :: n_det_, n_configuration_, n_st
|
|
||||||
double precision, intent(in) :: e_(n_st), s2_(n_st)
|
|
||||||
type(pt2_type) , intent(in) :: pt2_data, pt2_data_err
|
|
||||||
integer :: i, k
|
|
||||||
integer :: N_states_p
|
|
||||||
character*(9) :: pt2_string
|
|
||||||
character*(512) :: fmt
|
|
||||||
|
|
||||||
if (do_pt2) then
|
|
||||||
pt2_string = ' '
|
|
||||||
else
|
|
||||||
pt2_string = '(approx)'
|
|
||||||
endif
|
|
||||||
|
|
||||||
N_states_p = min(N_det_,n_st)
|
|
||||||
|
|
||||||
print *, ''
|
|
||||||
print '(A,I12)', 'Summary at N_det = ', N_det_
|
|
||||||
print '(A)', '-----------------------------------'
|
|
||||||
print *, ''
|
|
||||||
|
|
||||||
write(fmt,*) '(''# ============'',', N_states_p, '(1X,''=============================''))'
|
|
||||||
write(*,fmt)
|
|
||||||
write(fmt,*) '(13X,', N_states_p, '(6X,A7,1X,I6,10X))'
|
|
||||||
write(*,fmt) ('State',k, k=1,N_states_p)
|
|
||||||
write(fmt,*) '(''# ============'',', N_states_p, '(1X,''=============================''))'
|
|
||||||
write(*,fmt)
|
|
||||||
write(fmt,*) '(A13,', N_states_p, '(1X,F14.8,15X))'
|
|
||||||
write(*,fmt) '# E ', e_(1:N_states_p)
|
|
||||||
if (N_states_p > 1) then
|
|
||||||
write(*,fmt) '# Excit. (au)', e_(1:N_states_p)-e_(1)
|
|
||||||
write(*,fmt) '# Excit. (eV)', (e_(1:N_states_p)-e_(1))*27.211396641308d0
|
|
||||||
endif
|
|
||||||
write(fmt,*) '(A13,', 2*N_states_p, '(1X,F14.8))'
|
|
||||||
write(*,fmt) '# PT2 '//pt2_string, (pt2_data % pt2(k), pt2_data_err % pt2(k), k=1,N_states_p)
|
|
||||||
write(*,fmt) '# rPT2'//pt2_string, (pt2_data % rpt2(k), pt2_data_err % rpt2(k), k=1,N_states_p)
|
|
||||||
write(*,'(A)') '#'
|
|
||||||
write(*,fmt) '# E+PT2 ', (e_(k)+pt2_data % pt2(k),pt2_data_err % pt2(k), k=1,N_states_p)
|
|
||||||
write(*,fmt) '# E+rPT2 ', (e_(k)+pt2_data % rpt2(k),pt2_data_err % rpt2(k), k=1,N_states_p)
|
|
||||||
if (N_states_p > 1) then
|
|
||||||
write(*,fmt) '# Excit. (au)', ( (e_(k)+pt2_data % pt2(k)-e_(1)-pt2_data % pt2(1)), &
|
|
||||||
dsqrt(pt2_data_err % pt2(k)*pt2_data_err % pt2(k)+pt2_data_err % pt2(1)*pt2_data_err % pt2(1)), k=1,N_states_p)
|
|
||||||
write(*,fmt) '# Excit. (eV)', ( (e_(k)+pt2_data % pt2(k)-e_(1)-pt2_data % pt2(1))*27.211396641308d0, &
|
|
||||||
dsqrt(pt2_data_err % pt2(k)*pt2_data_err % pt2(k)+pt2_data_err % pt2(1)*pt2_data_err % pt2(1))*27.211396641308d0, k=1,N_states_p)
|
|
||||||
endif
|
|
||||||
write(fmt,*) '(''# ============'',', N_states_p, '(1X,''=============================''))'
|
|
||||||
write(*,fmt)
|
|
||||||
print *, ''
|
|
||||||
|
|
||||||
print *, 'N_det = ', N_det_
|
|
||||||
print *, 'N_states = ', n_st
|
|
||||||
if (s2_eig) then
|
|
||||||
print *, 'N_cfg = ', N_configuration_
|
|
||||||
if (only_expected_s2) then
|
|
||||||
print *, 'N_csf = ', N_csf
|
|
||||||
endif
|
|
||||||
endif
|
|
||||||
print *, ''
|
|
||||||
|
|
||||||
do k=1, N_states_p
|
|
||||||
print*,'* State ',k
|
|
||||||
print *, '< S^2 > = ', s2_(k)
|
|
||||||
print *, 'E = ', e_(k)
|
|
||||||
print *, 'Variance = ', pt2_data % variance(k), ' +/- ', pt2_data_err % variance(k)
|
|
||||||
print *, 'PT norm = ', dsqrt(pt2_data % overlap(k,k)), ' +/- ', 0.5d0*dsqrt(pt2_data % overlap(k,k)) * pt2_data_err % overlap(k,k) / (pt2_data % overlap(k,k))
|
|
||||||
print *, 'PT2 = ', pt2_data % pt2(k), ' +/- ', pt2_data_err % pt2(k)
|
|
||||||
print *, 'rPT2 = ', pt2_data % rpt2(k), ' +/- ', pt2_data_err % rpt2(k)
|
|
||||||
print *, 'E+PT2 '//pt2_string//' = ', e_(k)+pt2_data % pt2(k), ' +/- ', pt2_data_err % pt2(k)
|
|
||||||
print *, 'E+rPT2'//pt2_string//' = ', e_(k)+pt2_data % rpt2(k), ' +/- ', pt2_data_err % rpt2(k)
|
|
||||||
print *, ''
|
|
||||||
enddo
|
|
||||||
|
|
||||||
print *, '-----'
|
|
||||||
if(n_st.gt.1)then
|
|
||||||
print *, 'Variational Energy difference (au | eV)'
|
|
||||||
do i=2, N_states_p
|
|
||||||
print*,'Delta E = ', (e_(i) - e_(1)), &
|
|
||||||
(e_(i) - e_(1)) * 27.211396641308d0
|
|
||||||
enddo
|
|
||||||
print *, '-----'
|
|
||||||
print*, 'Variational + perturbative Energy difference (au | eV)'
|
|
||||||
do i=2, N_states_p
|
|
||||||
print*,'Delta E = ', (e_(i)+ pt2_data % pt2(i) - (e_(1) + pt2_data % pt2(1))), &
|
|
||||||
(e_(i)+ pt2_data % pt2(i) - (e_(1) + pt2_data % pt2(1))) * 27.211396641308d0
|
|
||||||
enddo
|
|
||||||
print *, '-----'
|
|
||||||
print*, 'Variational + renormalized perturbative Energy difference (au | eV)'
|
|
||||||
do i=2, N_states_p
|
|
||||||
print*,'Delta E = ', (e_(i)+ pt2_data % rpt2(i) - (e_(1) + pt2_data % rpt2(1))), &
|
|
||||||
(e_(i)+ pt2_data % rpt2(i) - (e_(1) + pt2_data % rpt2(1))) * 27.211396641308d0
|
|
||||||
enddo
|
|
||||||
endif
|
|
||||||
|
|
||||||
! call print_energy_components()
|
|
||||||
|
|
||||||
end subroutine
|
|
||||||
|
|
Loading…
Reference in New Issue
Block a user