mirror of
https://github.com/QuantumPackage/qp2.git
synced 2024-11-19 04:22:32 +01:00
Added JSON in FCI
This commit is contained in:
parent
528bf20e1e
commit
5fb6ed0180
@ -1,3 +1,4 @@
|
|||||||
|
json
|
||||||
perturbation
|
perturbation
|
||||||
zmq
|
zmq
|
||||||
mpi
|
mpi
|
||||||
|
@ -16,7 +16,6 @@ subroutine run_cipsi
|
|||||||
double precision, external :: memory_of_double
|
double precision, external :: memory_of_double
|
||||||
PROVIDE H_apply_buffer_allocated
|
PROVIDE H_apply_buffer_allocated
|
||||||
|
|
||||||
N_iter = 1
|
|
||||||
threshold_generators = 1.d0
|
threshold_generators = 1.d0
|
||||||
SOFT_TOUCH threshold_generators
|
SOFT_TOUCH threshold_generators
|
||||||
|
|
||||||
@ -76,7 +75,6 @@ subroutine run_cipsi
|
|||||||
)
|
)
|
||||||
write(*,'(A)') '--------------------------------------------------------------------------------'
|
write(*,'(A)') '--------------------------------------------------------------------------------'
|
||||||
|
|
||||||
|
|
||||||
to_select = int(sqrt(dble(N_states))*dble(N_det)*selection_factor)
|
to_select = int(sqrt(dble(N_states))*dble(N_det)*selection_factor)
|
||||||
to_select = max(N_states_diag, to_select)
|
to_select = max(N_states_diag, to_select)
|
||||||
if (do_pt2) then
|
if (do_pt2) then
|
||||||
@ -106,10 +104,10 @@ subroutine run_cipsi
|
|||||||
|
|
||||||
call save_energy(psi_energy_with_nucl_rep, pt2_data % pt2)
|
call save_energy(psi_energy_with_nucl_rep, pt2_data % pt2)
|
||||||
|
|
||||||
call save_iterations(psi_energy_with_nucl_rep(1:N_states),pt2_data % rpt2,N_det)
|
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()
|
||||||
N_iter += 1
|
call write_cipsi_json(pt2_data,pt2_data_err)
|
||||||
|
|
||||||
if (qp_stop()) exit
|
if (qp_stop()) exit
|
||||||
|
|
||||||
@ -155,11 +153,13 @@ subroutine run_cipsi
|
|||||||
call save_energy(psi_energy_with_nucl_rep, pt2_data % pt2)
|
call save_energy(psi_energy_with_nucl_rep, pt2_data % pt2)
|
||||||
call print_summary(psi_energy_with_nucl_rep(1:N_states), &
|
call print_summary(psi_energy_with_nucl_rep(1:N_states), &
|
||||||
pt2_data, pt2_data_err, N_det,N_configuration,N_states,psi_s2)
|
pt2_data, pt2_data_err, N_det,N_configuration,N_states,psi_s2)
|
||||||
call save_iterations(psi_energy_with_nucl_rep(1:N_states),pt2_data % rpt2,N_det)
|
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)
|
||||||
endif
|
endif
|
||||||
call pt2_dealloc(pt2_data)
|
call pt2_dealloc(pt2_data)
|
||||||
call pt2_dealloc(pt2_data_err)
|
call pt2_dealloc(pt2_data_err)
|
||||||
|
|
||||||
end
|
end
|
||||||
|
|
||||||
|
@ -15,7 +15,6 @@ subroutine run_stochastic_cipsi
|
|||||||
double precision, external :: memory_of_double
|
double precision, external :: memory_of_double
|
||||||
PROVIDE H_apply_buffer_allocated distributed_davidson mo_two_e_integrals_in_map
|
PROVIDE H_apply_buffer_allocated distributed_davidson mo_two_e_integrals_in_map
|
||||||
|
|
||||||
N_iter = 1
|
|
||||||
threshold_generators = 1.d0
|
threshold_generators = 1.d0
|
||||||
SOFT_TOUCH threshold_generators
|
SOFT_TOUCH threshold_generators
|
||||||
|
|
||||||
@ -96,10 +95,10 @@ subroutine run_stochastic_cipsi
|
|||||||
|
|
||||||
call save_energy(psi_energy_with_nucl_rep, pt2_data % pt2)
|
call save_energy(psi_energy_with_nucl_rep, pt2_data % pt2)
|
||||||
|
|
||||||
call save_iterations(psi_energy_with_nucl_rep(1:N_states),pt2_data % rpt2,N_det)
|
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()
|
||||||
N_iter += 1
|
call write_cipsi_json(pt2_data,pt2_data_err)
|
||||||
|
|
||||||
if (qp_stop()) exit
|
if (qp_stop()) exit
|
||||||
|
|
||||||
@ -135,9 +134,10 @@ subroutine run_stochastic_cipsi
|
|||||||
call save_energy(psi_energy_with_nucl_rep, pt2_data % pt2)
|
call save_energy(psi_energy_with_nucl_rep, pt2_data % pt2)
|
||||||
call print_summary(psi_energy_with_nucl_rep, &
|
call print_summary(psi_energy_with_nucl_rep, &
|
||||||
pt2_data , pt2_data_err, N_det, N_configuration, N_states, psi_s2)
|
pt2_data , pt2_data_err, N_det, N_configuration, N_states, psi_s2)
|
||||||
call save_iterations(psi_energy_with_nucl_rep(1:N_states),pt2_data % rpt2,N_det)
|
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)
|
||||||
endif
|
endif
|
||||||
call pt2_dealloc(pt2_data)
|
call pt2_dealloc(pt2_data)
|
||||||
call pt2_dealloc(pt2_data_err)
|
call pt2_dealloc(pt2_data_err)
|
||||||
|
53
src/cipsi/write_cipsi_json.irp.f
Normal file
53
src/cipsi/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
|
@ -39,12 +39,19 @@ program fci
|
|||||||
if (.not.is_zmq_slave) then
|
if (.not.is_zmq_slave) then
|
||||||
PROVIDE psi_det psi_coef mo_two_e_integrals_in_map
|
PROVIDE psi_det psi_coef mo_two_e_integrals_in_map
|
||||||
|
|
||||||
|
write(json_unit,json_array_open_fmt) 'fci'
|
||||||
|
|
||||||
if (do_pt2) then
|
if (do_pt2) then
|
||||||
call run_stochastic_cipsi
|
call run_stochastic_cipsi
|
||||||
else
|
else
|
||||||
call run_cipsi
|
call run_cipsi
|
||||||
endif
|
endif
|
||||||
|
|
||||||
|
write(json_unit,json_dict_uopen_fmt)
|
||||||
|
write(json_unit,json_dict_close_fmtx)
|
||||||
|
write(json_unit,json_array_close_fmtx)
|
||||||
|
call json_close
|
||||||
|
|
||||||
else
|
else
|
||||||
PROVIDE mo_two_e_integrals_in_map pt2_min_parallel_tasks
|
PROVIDE mo_two_e_integrals_in_map pt2_min_parallel_tasks
|
||||||
|
|
||||||
|
@ -80,15 +80,14 @@ subroutine run
|
|||||||
|
|
||||||
mo_label = 'Orthonormalized'
|
mo_label = 'Orthonormalized'
|
||||||
|
|
||||||
write(json_unit,*) '"scf" : ['
|
write(json_unit,json_array_open_fmt) 'scf'
|
||||||
|
|
||||||
call Roothaan_Hall_SCF
|
call Roothaan_Hall_SCF
|
||||||
call ezfio_set_hartree_fock_energy(SCF_energy)
|
|
||||||
|
|
||||||
write(json_unit,*) ']'
|
|
||||||
|
|
||||||
|
write(json_unit,json_array_close_fmtx)
|
||||||
call json_close
|
call json_close
|
||||||
|
|
||||||
|
call ezfio_set_hartree_fock_energy(SCF_energy)
|
||||||
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,42 +1,65 @@
|
|||||||
BEGIN_PROVIDER [ double precision, extrapolated_energy, (N_iter,N_states) ]
|
BEGIN_PROVIDER [ integer, N_iter ]
|
||||||
implicit none
|
|
||||||
BEGIN_DOC
|
|
||||||
! Extrapolated energy, using E_var = f(PT2) where PT2=0
|
|
||||||
END_DOC
|
|
||||||
integer :: i
|
|
||||||
do i=1,min(N_states,N_det)
|
|
||||||
call extrapolate_data(N_iter, &
|
|
||||||
energy_iterations(i,1:N_iter), &
|
|
||||||
pt2_iterations(i,1:N_iter), &
|
|
||||||
extrapolated_energy(1:N_iter,i))
|
|
||||||
enddo
|
|
||||||
END_PROVIDER
|
|
||||||
|
|
||||||
|
|
||||||
subroutine save_iterations(e_, pt2_,n_)
|
|
||||||
implicit none
|
implicit none
|
||||||
BEGIN_DOC
|
BEGIN_DOC
|
||||||
! Update the energy in the EZFIO file.
|
! Number of CIPSI iterations
|
||||||
END_DOC
|
END_DOC
|
||||||
integer, intent(in) :: n_
|
|
||||||
double precision, intent(in) :: e_(N_states), pt2_(N_states)
|
|
||||||
integer :: i
|
|
||||||
|
|
||||||
if (N_iter == 101) then
|
N_iter = 0
|
||||||
do i=2,N_iter-1
|
END_PROVIDER
|
||||||
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)
|
BEGIN_PROVIDER [ integer, N_iter_max ]
|
||||||
|
implicit none
|
||||||
|
BEGIN_DOC
|
||||||
|
! Max number of iterations for extrapolations
|
||||||
|
END_DOC
|
||||||
|
N_iter_max = 8
|
||||||
|
END_PROVIDER
|
||||||
|
|
||||||
|
BEGIN_PROVIDER [ double precision, energy_iterations , (n_states,N_iter_max) ]
|
||||||
|
&BEGIN_PROVIDER [ double precision, pt2_iterations , (n_states,N_iter_max) ]
|
||||||
|
&BEGIN_PROVIDER [ double precision, extrapolated_energy, (N_iter_max,N_states) ]
|
||||||
|
implicit none
|
||||||
|
BEGIN_DOC
|
||||||
|
! The energy at each iteration for the extrapolations
|
||||||
|
END_DOC
|
||||||
|
|
||||||
|
energy_iterations = 0.d0
|
||||||
|
pt2_iterations = 0.d0
|
||||||
|
extrapolated_energy = 0.d0
|
||||||
|
END_PROVIDER
|
||||||
|
|
||||||
|
subroutine increment_n_iter(e, pt2_data)
|
||||||
|
use selection_types
|
||||||
|
implicit none
|
||||||
|
BEGIN_DOC
|
||||||
|
! Does what is necessary to increment n_iter
|
||||||
|
END_DOC
|
||||||
|
double precision, intent(in) :: e(*)
|
||||||
|
type(pt2_type), intent(in) :: pt2_data
|
||||||
|
integer :: k, i
|
||||||
|
|
||||||
|
if (N_det < N_states) return
|
||||||
|
|
||||||
|
if (N_iter < N_iter_max) then
|
||||||
|
N_iter += 1
|
||||||
|
else
|
||||||
|
do k=2,N_iter
|
||||||
|
energy_iterations(1:N_states,k-1) = energy_iterations(1:N_states,k)
|
||||||
|
pt2_iterations(1:N_states,k-1) = pt2_iterations(1:N_states,k)
|
||||||
enddo
|
enddo
|
||||||
N_iter = N_iter-1
|
|
||||||
TOUCH N_iter
|
|
||||||
endif
|
endif
|
||||||
|
energy_iterations(1:N_states,N_iter) = e(1:N_states)
|
||||||
|
pt2_iterations(1:N_states,N_iter) = pt2_data % rpt2(1:N_states)
|
||||||
|
|
||||||
energy_iterations(1:N_states,N_iter) = e_(1:N_states)
|
if (N_iter < 2) then
|
||||||
pt2_iterations(1:N_states,N_iter) = pt2_(1:N_states)
|
extrapolated_energy(1,:) = energy_iterations(:,1) + pt2_iterations(:,1)
|
||||||
n_det_iterations(N_iter) = n_
|
extrapolated_energy(2,:) = energy_iterations(:,2) + pt2_iterations(:,2)
|
||||||
call ezfio_set_iterations_N_iter(N_iter)
|
else
|
||||||
call ezfio_set_iterations_energy_iterations(energy_iterations)
|
do i=1,N_states
|
||||||
call ezfio_set_iterations_pt2_iterations(pt2_iterations)
|
call extrapolate_data(N_iter, &
|
||||||
call ezfio_set_iterations_n_det_iterations(n_det_iterations)
|
energy_iterations(i,1:N_iter), &
|
||||||
|
pt2_iterations(i,1:N_iter), &
|
||||||
|
extrapolated_energy(1:N_iter,i))
|
||||||
|
enddo
|
||||||
|
endif
|
||||||
end
|
end
|
||||||
|
|
||||||
|
@ -5,10 +5,14 @@ subroutine print_extrapolated_energy
|
|||||||
END_DOC
|
END_DOC
|
||||||
|
|
||||||
integer :: i,k
|
integer :: i,k
|
||||||
|
integer :: N_states_p, N_iter_p
|
||||||
|
|
||||||
if (N_iter< 2) then
|
if (N_iter< 2) then
|
||||||
return
|
return
|
||||||
endif
|
endif
|
||||||
|
N_states_p = min(N_states,N_det)
|
||||||
|
N_iter_p = min(N_iter, 8)
|
||||||
|
|
||||||
write(*,'(A)') ''
|
write(*,'(A)') ''
|
||||||
write(*,'(A)') 'Extrapolated energies'
|
write(*,'(A)') 'Extrapolated energies'
|
||||||
write(*,'(A)') '------------------------'
|
write(*,'(A)') '------------------------'
|
||||||
@ -20,20 +24,20 @@ subroutine print_extrapolated_energy
|
|||||||
write(*,*) '=========== ', '==================='
|
write(*,*) '=========== ', '==================='
|
||||||
write(*,*) 'minimum PT2 ', 'Extrapolated energy'
|
write(*,*) 'minimum PT2 ', 'Extrapolated energy'
|
||||||
write(*,*) '=========== ', '==================='
|
write(*,*) '=========== ', '==================='
|
||||||
do k=2,min(N_iter,8)
|
do k=2,N_iter_p
|
||||||
write(*,'(F11.4,2X,F18.8)') pt2_iterations(1,N_iter+1-k), extrapolated_energy(k,1)
|
write(*,'(F11.4,2X,F18.8)') pt2_iterations(1,k), extrapolated_energy(k,1)
|
||||||
enddo
|
enddo
|
||||||
write(*,*) '=========== ', '==================='
|
write(*,*) '=========== ', '==================='
|
||||||
|
|
||||||
do i=2, min(N_states,N_det)
|
do i=2, N_states_p
|
||||||
print *, ''
|
print *, ''
|
||||||
print *, 'State ', i
|
print *, 'State ', i
|
||||||
print *, ''
|
print *, ''
|
||||||
write(*,*) '=========== ', '=================== ', '=================== ', '==================='
|
write(*,*) '=========== ', '=================== ', '=================== ', '==================='
|
||||||
write(*,*) 'minimum PT2 ', 'Extrapolated energy ', ' Excitation (a.u) ', ' Excitation (eV) '
|
write(*,*) 'minimum PT2 ', 'Extrapolated energy ', ' Excitation (a.u) ', ' Excitation (eV) '
|
||||||
write(*,*) '=========== ', '=================== ', '=================== ', '==================='
|
write(*,*) '=========== ', '=================== ', '=================== ', '==================='
|
||||||
do k=2,min(N_iter,8)
|
do k=2,N_iter_p
|
||||||
write(*,'(F11.4,X,3(X,F18.8))') pt2_iterations(i,N_iter+1-k), extrapolated_energy(k,i), &
|
write(*,'(F11.4,X,3(X,F18.8))') pt2_iterations(i,k), extrapolated_energy(k,i), &
|
||||||
extrapolated_energy(k,i) - extrapolated_energy(k,1), &
|
extrapolated_energy(k,i) - extrapolated_energy(k,1), &
|
||||||
(extrapolated_energy(k,i) - extrapolated_energy(k,1) ) * 27.211396641308d0
|
(extrapolated_energy(k,i) - extrapolated_energy(k,1) ) * 27.211396641308d0
|
||||||
enddo
|
enddo
|
||||||
|
@ -8,6 +8,16 @@
|
|||||||
&BEGIN_PROVIDER [ character*(64), json_true_fmtx ]
|
&BEGIN_PROVIDER [ character*(64), json_true_fmtx ]
|
||||||
&BEGIN_PROVIDER [ character*(64), json_false_fmt ]
|
&BEGIN_PROVIDER [ character*(64), json_false_fmt ]
|
||||||
&BEGIN_PROVIDER [ character*(64), json_false_fmtx ]
|
&BEGIN_PROVIDER [ character*(64), json_false_fmtx ]
|
||||||
|
&BEGIN_PROVIDER [ character*(64), json_array_open_fmt ]
|
||||||
|
&BEGIN_PROVIDER [ character*(64), json_array_uopen_fmt ]
|
||||||
|
&BEGIN_PROVIDER [ character*(64), json_array_close_fmt ]
|
||||||
|
&BEGIN_PROVIDER [ character*(64), json_array_close_uopen_fmt ]
|
||||||
|
&BEGIN_PROVIDER [ character*(64), json_array_close_fmtx ]
|
||||||
|
&BEGIN_PROVIDER [ character*(64), json_dict_open_fmt ]
|
||||||
|
&BEGIN_PROVIDER [ character*(64), json_dict_uopen_fmt ]
|
||||||
|
&BEGIN_PROVIDER [ character*(64), json_dict_close_uopen_fmt ]
|
||||||
|
&BEGIN_PROVIDER [ character*(64), json_dict_close_fmt ]
|
||||||
|
&BEGIN_PROVIDER [ character*(64), json_dict_close_fmtx ]
|
||||||
implicit none
|
implicit none
|
||||||
BEGIN_DOC
|
BEGIN_DOC
|
||||||
! Formats for JSON output.
|
! Formats for JSON output.
|
||||||
@ -23,4 +33,14 @@
|
|||||||
json_true_fmtx = '('' "'',A,''": true'')'
|
json_true_fmtx = '('' "'',A,''": true'')'
|
||||||
json_false_fmt = '('' "'',A,''": false,'')'
|
json_false_fmt = '('' "'',A,''": false,'')'
|
||||||
json_false_fmtx = '('' "'',A,''": false'')'
|
json_false_fmtx = '('' "'',A,''": false'')'
|
||||||
|
json_array_open_fmt = '('' "'',A,''": ['')'
|
||||||
|
json_array_uopen_fmt = '('' ['')'
|
||||||
|
json_array_close_fmt = '('' ],'')'
|
||||||
|
json_array_close_uopen_fmt = '('' ], ['')'
|
||||||
|
json_array_close_fmtx = '('' ]'')'
|
||||||
|
json_dict_open_fmt = '('' "'',A,''": {'')'
|
||||||
|
json_dict_uopen_fmt = '('' {'')'
|
||||||
|
json_dict_close_fmt = '('' },'')'
|
||||||
|
json_dict_close_uopen_fmt = '('' }, {'')'
|
||||||
|
json_dict_close_fmtx = '('' }'')'
|
||||||
END_PROVIDER
|
END_PROVIDER
|
||||||
|
@ -155,9 +155,9 @@ END_DOC
|
|||||||
|
|
||||||
call lock_io
|
call lock_io
|
||||||
if (iteration_SCF == 1) then
|
if (iteration_SCF == 1) then
|
||||||
write(json_unit, *) '{'
|
write(json_unit, json_dict_uopen_fmt)
|
||||||
else
|
else
|
||||||
write(json_unit, *) '}, {'
|
write(json_unit, json_dict_close_uopen_fmt)
|
||||||
endif
|
endif
|
||||||
write(json_unit, json_int_fmt) 'iteration', iteration_SCF
|
write(json_unit, json_int_fmt) 'iteration', iteration_SCF
|
||||||
write(json_unit, json_real_fmt) 'energy', energy_SCF
|
write(json_unit, json_real_fmt) 'energy', energy_SCF
|
||||||
@ -185,7 +185,7 @@ END_DOC
|
|||||||
if (qp_stop()) exit
|
if (qp_stop()) exit
|
||||||
|
|
||||||
enddo
|
enddo
|
||||||
write(json_unit, *) '}'
|
write(json_unit, json_dict_close_fmtx)
|
||||||
|
|
||||||
if (iteration_SCF < n_it_SCF_max) then
|
if (iteration_SCF < n_it_SCF_max) then
|
||||||
mo_label = 'Canonical'
|
mo_label = 'Canonical'
|
||||||
|
Loading…
Reference in New Issue
Block a user