2021-02-09 22:33:39 +01:00
|
|
|
!
|
|
|
|
! Shows FDF capabilities..
|
|
|
|
!
|
|
|
|
PROGRAM iochamp
|
|
|
|
USE fdf
|
|
|
|
USE prec
|
2021-02-23 10:43:38 +01:00
|
|
|
USE parse
|
2021-02-23 22:44:22 +01:00
|
|
|
use io_fdf
|
2021-02-25 12:41:14 +01:00
|
|
|
|
|
|
|
! Note the following two modules are being used to store and process the parsed data
|
|
|
|
use keywords
|
|
|
|
use periodic_table
|
|
|
|
!
|
2021-02-09 22:33:39 +01:00
|
|
|
implicit none
|
|
|
|
!--------------------------------------------------------------- Local Variables
|
|
|
|
integer, parameter :: maxa = 100
|
2021-02-11 21:59:19 +01:00
|
|
|
logical :: doit, debug, check, val, logic(10)
|
|
|
|
logical :: beginning, ending
|
2021-02-25 12:41:14 +01:00
|
|
|
character(len=72) :: fname, axis, status, filename, fmt
|
2021-02-11 21:59:19 +01:00
|
|
|
character(len=72) :: molecule_name, key, comment
|
2021-02-09 22:33:39 +01:00
|
|
|
character(2) :: symbol(maxa)
|
2021-02-11 21:59:19 +01:00
|
|
|
character(len=20) :: chunks(10), subblock(10)
|
2021-02-23 10:43:38 +01:00
|
|
|
character(len=30) :: keyword(5)
|
|
|
|
integer(sp) :: i, j, ia, na, external_entry, number_of_atoms, ind
|
2021-02-09 22:33:39 +01:00
|
|
|
integer(sp) :: isa(maxa)
|
2021-02-19 02:05:50 +01:00
|
|
|
real(dp) :: coeff(maxa)
|
2021-02-09 22:33:39 +01:00
|
|
|
real(sp) :: wmix
|
|
|
|
real(dp) :: cutoff, phonon_energy, factor
|
|
|
|
real(dp) :: xa(3, maxa)
|
|
|
|
real(dp) :: listr(maxa)
|
2021-02-11 21:59:19 +01:00
|
|
|
type(block_fdf) :: bfdf, bfdf2
|
|
|
|
type(parsed_line), pointer :: pline, pline2
|
2021-02-10 00:29:00 +01:00
|
|
|
!type(fdf_file) :: fdffile
|
2021-02-25 14:57:29 +01:00
|
|
|
integer :: max_iteration, max_iter, linecount, argument(5)
|
|
|
|
real(dp) :: float_value
|
|
|
|
character(len=20) :: real_format = '(A, T20, F14.8)'
|
2021-02-11 21:59:19 +01:00
|
|
|
character(len=20) :: int_format = '(A, T20, I8)'
|
2021-03-03 15:53:47 +01:00
|
|
|
character(len=80) :: string_format = '(A, T40, A)'
|
2021-02-09 22:33:39 +01:00
|
|
|
|
2021-02-23 22:44:22 +01:00
|
|
|
! for determinants sections
|
2021-02-25 12:41:14 +01:00
|
|
|
integer :: nelectrons, nexcitation, iostat
|
2021-02-23 22:44:22 +01:00
|
|
|
integer, allocatable :: det_alpha(:), det_beta(:)
|
2021-02-24 09:47:16 +01:00
|
|
|
real(selected_real_kind(6,15)), allocatable :: det_coeff(:)
|
2021-02-23 22:44:22 +01:00
|
|
|
character(len=20) :: temp1, temp2, temp3, temp4, temp5
|
2021-02-09 22:33:39 +01:00
|
|
|
!------------------------------------------------------------------------- BEGIN
|
|
|
|
|
|
|
|
! Initialize
|
|
|
|
call fdf_init('test-champ.inp', 'test-champ.out')
|
|
|
|
|
|
|
|
! strings/characters
|
2021-02-25 12:41:14 +01:00
|
|
|
title = fdf_string('title', 'Default title')
|
|
|
|
write(6,'(A)') 'Title of the calculation :: ', title
|
|
|
|
|
2021-03-03 12:00:32 +01:00
|
|
|
! Get the directory where the pooled data is kept
|
2021-02-25 12:41:14 +01:00
|
|
|
path_pool = fdf_string('pool', './')
|
2021-03-03 15:53:47 +01:00
|
|
|
write(6,fmt=string_format) 'pool directory location :: ', path_pool
|
2021-02-25 12:41:14 +01:00
|
|
|
|
2021-03-03 12:00:32 +01:00
|
|
|
! Get all the filenames from which the data is to be read
|
2021-03-03 15:53:47 +01:00
|
|
|
file_molecule = fdf_load_filename('molecule', 'default.xyz')
|
|
|
|
write(6,fmt=string_format) 'filename molecule :: ', trim(file_molecule)
|
|
|
|
|
2021-03-03 12:00:32 +01:00
|
|
|
file_pseudo = fdf_load_filename('pseudopot', 'default.psp')
|
2021-03-03 15:53:47 +01:00
|
|
|
write(6,fmt=string_format) 'filename pseuodpotential :: ', trim(file_pseudo)
|
2021-02-25 12:41:14 +01:00
|
|
|
|
2021-03-03 12:00:32 +01:00
|
|
|
file_basis = fdf_load_filename('basis', 'default.bas')
|
2021-03-03 15:53:47 +01:00
|
|
|
write(6,fmt=string_format) 'filename basis :: ', trim(file_basis)
|
2021-02-25 12:41:14 +01:00
|
|
|
|
2021-03-03 12:00:32 +01:00
|
|
|
file_determinants = fdf_load_filename('determinants', 'default.det')
|
2021-03-03 15:53:47 +01:00
|
|
|
write(6,fmt=string_format) 'filename determinants :: ', trim(file_determinants)
|
2021-02-25 12:41:14 +01:00
|
|
|
|
2021-03-03 12:00:32 +01:00
|
|
|
file_orbitals = fdf_load_filename('orbitals', 'default.orb')
|
2021-03-03 15:53:47 +01:00
|
|
|
write(6,fmt=string_format) 'filename orbitals :: ', trim(file_orbitals)
|
2021-02-25 12:41:14 +01:00
|
|
|
|
2021-03-03 12:00:32 +01:00
|
|
|
file_jastrow = fdf_load_filename('jastrow', 'default.jas')
|
2021-03-03 15:53:47 +01:00
|
|
|
write(6,fmt=string_format) 'filename jastrow :: ',trim(file_jastrow)
|
2021-02-25 12:41:14 +01:00
|
|
|
|
2021-03-03 12:00:32 +01:00
|
|
|
file_jastrow_deriv = fdf_load_filename('jastrow_deriv', 'default.jasder')
|
2021-03-03 15:53:47 +01:00
|
|
|
write(6,fmt=string_format) 'filename jastrow derivatives :: ', trim(file_jastrow_deriv)
|
2021-02-25 12:41:14 +01:00
|
|
|
|
|
|
|
|
2021-02-25 14:57:29 +01:00
|
|
|
! &optwf ioptwf 1 ioptci 1 ioptjas 1 ioptorb 1
|
|
|
|
optimize_wavefunction = fdf_boolean("optimize_wavefunction", .false.)
|
|
|
|
write(6,*) ' optimize_wavefunction = ', optimize_wavefunction
|
2021-02-25 12:41:14 +01:00
|
|
|
|
2021-02-25 14:57:29 +01:00
|
|
|
optimize_ci = fdf_boolean('optimize_ci', .false.)
|
|
|
|
write(6,*) ' optimize_ci = ', optimize_ci
|
|
|
|
|
|
|
|
optimize_jastrow = fdf_boolean('optimize_jastrow', .false.)
|
|
|
|
write(6,*) ' optimize_jastrow = ', optimize_jastrow
|
|
|
|
|
|
|
|
optimize_orbitals = fdf_boolean('optimize_orbitals', .false.)
|
|
|
|
write(6,*) ' optimize_orbitals = ', optimize_orbitals
|
|
|
|
|
|
|
|
write(6,'(A)')
|
|
|
|
write(6,*) '------------------------------------------------------'
|
2021-02-25 12:41:14 +01:00
|
|
|
|
2021-02-09 22:33:39 +01:00
|
|
|
|
2021-02-23 10:43:38 +01:00
|
|
|
!Integer numbers (keyword, default_value). The variable is assigned default_value when keyword is not present
|
2021-02-25 14:57:29 +01:00
|
|
|
! &optwf ncore 0 nextorb 280 no_active 0
|
|
|
|
! &optwf nblk_max 200 nopt_iter 2
|
|
|
|
ncore = fdf_integer('ncore', 0)
|
|
|
|
write(6,fmt=int_format) 'NCore =', ncore
|
|
|
|
|
2021-02-09 22:33:39 +01:00
|
|
|
nextorb = fdf_integer('nextorb', 0)
|
|
|
|
write(6,fmt=int_format) 'Next Orb =', nextorb
|
|
|
|
|
2021-02-25 14:57:29 +01:00
|
|
|
no_active = fdf_integer('no_active', 0)
|
|
|
|
write(6,fmt=int_format) 'no_active =', no_active
|
|
|
|
|
2021-02-09 22:33:39 +01:00
|
|
|
nblk_max = fdf_integer('nblk_max', 0)
|
|
|
|
write(6,fmt=int_format) 'nblk max =', nblk_max
|
|
|
|
|
|
|
|
nopt_iter = fdf_integer('nopt_iter', 0)
|
|
|
|
write(6,fmt=int_format) 'nopt_iter =', nopt_iter
|
|
|
|
|
|
|
|
|
|
|
|
! floats (keyword, default_value) variable is assigned default_value when keyword is not present
|
2021-02-25 14:57:29 +01:00
|
|
|
|
|
|
|
! &optwf sr_tau 0.025 sr_eps 0.001 sr_adiag 0.01
|
|
|
|
! &optwf isample_cmat 0 energy_tol 0.0
|
|
|
|
|
2021-02-11 21:59:19 +01:00
|
|
|
sr_tau = fdf_get('sr_tau', 0.025d0)
|
2021-02-09 22:33:39 +01:00
|
|
|
write(6,fmt=real_format) 'sr_tau:', sr_tau
|
|
|
|
|
2021-02-11 21:59:19 +01:00
|
|
|
sr_eps = fdf_get('sr_eps', 0.001d0)
|
2021-02-09 22:33:39 +01:00
|
|
|
write(6,fmt=real_format) 'sr_eps:', sr_eps
|
|
|
|
|
2021-02-11 21:59:19 +01:00
|
|
|
sr_adiag = fdf_get('sr_adiag', 0.01d0)
|
2021-02-09 22:33:39 +01:00
|
|
|
write(6,fmt=real_format) 'sr_adiag:', sr_adiag
|
|
|
|
|
2021-02-11 21:59:19 +01:00
|
|
|
energy_tol = fdf_get('energy_tol', 0.00001d0)
|
2021-02-09 22:33:39 +01:00
|
|
|
write(6,fmt=real_format) 'energy_tol:', energy_tol
|
|
|
|
|
2021-02-25 14:57:29 +01:00
|
|
|
! &optwf method sr_n multiple_adiag 0
|
2021-02-23 10:43:38 +01:00
|
|
|
|
2021-02-25 14:57:29 +01:00
|
|
|
opt_method = fdf_get('opt_method', "sr_n")
|
|
|
|
write(6,*) 'Optimization method ', opt_method
|
2021-02-23 10:43:38 +01:00
|
|
|
|
2021-02-25 14:57:29 +01:00
|
|
|
multiple_adiag = fdf_get('multiple_adiag', .false.)
|
|
|
|
write(6,*) 'multiple_adiag:', multiple_adiag
|
2021-02-23 10:43:38 +01:00
|
|
|
|
2021-02-09 22:33:39 +01:00
|
|
|
|
|
|
|
|
2021-02-18 21:38:16 +01:00
|
|
|
|
|
|
|
|
2021-02-25 14:57:29 +01:00
|
|
|
! logical :: true, .true., yes, T, and TRUE are equivalent
|
|
|
|
debug = fdf_boolean('Debug', .TRUE.)
|
|
|
|
write(6,'(A, L2)') 'Debug:', debug
|
2021-02-18 21:38:16 +01:00
|
|
|
|
|
|
|
|
|
|
|
|
2021-02-09 22:33:39 +01:00
|
|
|
|
2021-02-25 14:57:29 +01:00
|
|
|
! ianalyt_lap 1 isc 2 nspin1 1 nspin2 1 ifock 0
|
|
|
|
analytic_laplacian = fdf_get('ianalyt_lap', 1)
|
|
|
|
write(6,*) 'analytic laplacian from global.fdf pointer explained ', ianalyt_lap
|
2021-02-09 22:33:39 +01:00
|
|
|
|
2021-02-25 14:57:29 +01:00
|
|
|
nspin1 = fdf_get('nspin1', 1)
|
|
|
|
write(6,*) 'nspin1 from global.fdf ', nspin1
|
2021-02-18 11:01:41 +01:00
|
|
|
|
2021-02-25 14:57:29 +01:00
|
|
|
nspin2 = fdf_get('nspin2', 1)
|
|
|
|
write(6,*) 'nspin2 from global.fdf ', nspin2
|
2021-02-09 22:33:39 +01:00
|
|
|
|
2021-02-25 14:57:29 +01:00
|
|
|
ifock = fdf_get('ifock', 1)
|
|
|
|
write(6,*) 'ifock from global.fdf ', ifock
|
2021-02-09 22:33:39 +01:00
|
|
|
|
2021-02-23 10:43:38 +01:00
|
|
|
|
2021-02-25 14:57:29 +01:00
|
|
|
! mixed types in one line (for example, reading a number with units)
|
|
|
|
tau = fdf_get('tau', 0.05)
|
|
|
|
write(6,fmt=real_format) 'DMC tau = ', tau
|
2021-02-23 10:43:38 +01:00
|
|
|
|
2021-02-25 14:57:29 +01:00
|
|
|
etrial = fdf_physical('etrial', -20.d0, 'eV')
|
|
|
|
write(6,fmt=real_format) 'Energy CutOff in eV :: ', energy_trial
|
2021-02-23 10:43:38 +01:00
|
|
|
|
2021-02-25 14:57:29 +01:00
|
|
|
write(6,'(A)')
|
2021-02-09 22:33:39 +01:00
|
|
|
|
2021-02-25 14:57:29 +01:00
|
|
|
write(6,*) '------------------------------------------------------'
|
2021-02-09 22:33:39 +01:00
|
|
|
|
|
|
|
|
2021-02-11 21:59:19 +01:00
|
|
|
|
2021-02-18 21:38:16 +01:00
|
|
|
|
2021-02-11 21:59:19 +01:00
|
|
|
! write(6,'(A,4X)') 'optimize_wavefunction using bline', (subblock(i), i = 1, 4)
|
|
|
|
|
|
|
|
if (fdf_block('general', bfdf)) then
|
|
|
|
write(*,*) "inside general block"
|
|
|
|
i = 1
|
|
|
|
do while(fdf_bline(bfdf, pline))
|
|
|
|
doit = fdf_bsearch(pline, "pool")
|
|
|
|
write(*,*) "pool found", doit
|
|
|
|
i = i + 1
|
|
|
|
enddo
|
|
|
|
endif
|
2021-02-09 22:33:39 +01:00
|
|
|
|
2021-02-18 11:01:41 +01:00
|
|
|
write(6,'(A)')
|
|
|
|
|
|
|
|
write(6,*) '------------------------------------------------------'
|
2021-02-11 21:59:19 +01:00
|
|
|
|
2021-02-09 22:33:39 +01:00
|
|
|
|
2021-02-18 11:01:41 +01:00
|
|
|
|
|
|
|
|
2021-02-18 11:27:37 +01:00
|
|
|
if (fdf_block('molecule', bfdf)) then
|
|
|
|
! External file reading
|
|
|
|
write(6,*) 'beginning of external file coordinates block '
|
|
|
|
ia = 1
|
2021-02-18 21:38:16 +01:00
|
|
|
! write(*,*) "linecount", fdf_block_linecount("molecule")
|
2021-02-18 11:27:37 +01:00
|
|
|
|
|
|
|
do while((fdf_bline(bfdf, pline)))
|
|
|
|
|
|
|
|
if (pline%ntokens == 1) then
|
2021-02-25 15:12:35 +01:00
|
|
|
natoms = fdf_bintegers(pline, 1)
|
|
|
|
write(*,*) "Number of atoms = ", natoms
|
2021-02-18 11:27:37 +01:00
|
|
|
endif
|
2021-02-25 15:12:35 +01:00
|
|
|
|
|
|
|
if (.not. allocated(cent)) allocate(cent(3,natoms))
|
2021-02-18 23:21:04 +01:00
|
|
|
|
2021-02-18 11:27:37 +01:00
|
|
|
if (pline%ntokens == 4) then
|
|
|
|
symbol(ia) = fdf_bnames(pline, 1)
|
|
|
|
do i= 1, 3
|
2021-02-25 15:12:35 +01:00
|
|
|
cent(i,ia) = fdf_bvalues(pline, i)
|
2021-02-18 11:27:37 +01:00
|
|
|
enddo
|
|
|
|
ia = ia + 1
|
|
|
|
endif
|
|
|
|
enddo
|
|
|
|
endif
|
|
|
|
write(6,*) 'Coordinates from Molecule block: External file'
|
2021-02-25 15:12:35 +01:00
|
|
|
do ia= 1, natoms
|
|
|
|
write(6,'(A4,3F10.6)') symbol(ia), (cent(i,ia),i=1,3)
|
2021-02-18 11:27:37 +01:00
|
|
|
enddo
|
|
|
|
|
|
|
|
|
2021-02-10 00:29:00 +01:00
|
|
|
|
2021-02-18 11:01:41 +01:00
|
|
|
write(6,'(A)')
|
|
|
|
|
|
|
|
write(6,*) '------------------------------------------------------'
|
2021-02-10 00:29:00 +01:00
|
|
|
|
|
|
|
|
|
|
|
! Molecule coordinate block begins here
|
|
|
|
|
|
|
|
if (fdf_block('Coordinates', bfdf)) then
|
|
|
|
ia = 1
|
|
|
|
do while(fdf_bline(bfdf, pline))
|
|
|
|
symbol(ia) = fdf_bnames(pline, 1)
|
|
|
|
do i= 1, 3
|
2021-02-18 22:38:59 +01:00
|
|
|
xa(i,ia) = fdf_bvalues(pline, i)
|
2021-02-10 00:29:00 +01:00
|
|
|
enddo
|
|
|
|
ia = ia + 1
|
|
|
|
enddo
|
|
|
|
na = ia - 1
|
2021-02-09 22:33:39 +01:00
|
|
|
|
2021-02-25 14:57:29 +01:00
|
|
|
endif
|
2021-02-09 22:33:39 +01:00
|
|
|
|
2021-02-25 14:57:29 +01:00
|
|
|
if (fdf_block('Coordinates', bfdf)) then
|
|
|
|
write(6,*) 'Coordinates:'
|
|
|
|
do ia = 1, na
|
|
|
|
write(6,'(A, 4x, 3F10.6)') symbol(ia), (xa(i,ia),i=1,3)
|
|
|
|
enddo
|
|
|
|
endif
|
2021-02-18 11:01:41 +01:00
|
|
|
|
2021-02-10 00:29:00 +01:00
|
|
|
|
2021-02-18 11:01:41 +01:00
|
|
|
write(6,*) '------------------------------------------------------'
|
2021-02-09 22:33:39 +01:00
|
|
|
|
|
|
|
|
2021-02-18 11:01:41 +01:00
|
|
|
if (fdf_block('inline_xyz', bfdf)) then
|
2021-02-11 21:59:19 +01:00
|
|
|
! Forward reading
|
2021-02-18 21:38:16 +01:00
|
|
|
write(6,*) 'Reading an inline_xyz block '
|
2021-02-09 22:33:39 +01:00
|
|
|
ia = 1
|
2021-02-11 21:59:19 +01:00
|
|
|
|
2021-02-18 23:21:04 +01:00
|
|
|
do while((fdf_bline(bfdf, pline)))
|
2021-02-11 21:59:19 +01:00
|
|
|
|
2021-02-18 23:21:04 +01:00
|
|
|
if (pline%ntokens == 1) then
|
2021-02-11 21:59:19 +01:00
|
|
|
number_of_atoms = fdf_bintegers(pline, 1)
|
2021-02-18 21:38:16 +01:00
|
|
|
write(*,*) "Number of atoms", number_of_atoms
|
2021-02-11 21:59:19 +01:00
|
|
|
endif
|
2021-02-18 11:01:41 +01:00
|
|
|
na = number_of_atoms
|
|
|
|
|
2021-02-11 21:59:19 +01:00
|
|
|
if (pline%ntokens == 4) then
|
|
|
|
symbol(ia) = fdf_bnames(pline, 1)
|
2021-02-18 11:27:37 +01:00
|
|
|
do i= 1, 3
|
2021-02-18 22:38:59 +01:00
|
|
|
xa(i,ia) = fdf_bvalues(pline, i)
|
2021-02-11 21:59:19 +01:00
|
|
|
enddo
|
|
|
|
ia = ia + 1
|
|
|
|
endif
|
2021-02-09 22:33:39 +01:00
|
|
|
enddo
|
|
|
|
|
2021-02-18 11:01:41 +01:00
|
|
|
write(6,*) 'Inline XYZ Coordinates block:'
|
2021-02-09 22:33:39 +01:00
|
|
|
do ia= 1, na
|
|
|
|
write(6,'(A4,3F10.6)') symbol(ia), (xa(i,ia),i=1,3)
|
|
|
|
enddo
|
2021-02-18 11:01:41 +01:00
|
|
|
endif
|
2021-02-09 22:33:39 +01:00
|
|
|
|
2021-02-19 00:33:15 +01:00
|
|
|
write(6,'(A)')
|
|
|
|
|
|
|
|
write(6,*) '------------------------------------------------------'
|
|
|
|
|
|
|
|
|
2021-02-09 22:33:39 +01:00
|
|
|
|
2021-02-25 14:57:29 +01:00
|
|
|
! if (fdf_block('inline_xyz2', bfdf)) then
|
|
|
|
! ! Forward reading
|
|
|
|
! write(6,*) 'Reading an inline_xyz2 block '
|
|
|
|
! ia = 1
|
2021-02-18 22:38:59 +01:00
|
|
|
|
2021-02-25 14:57:29 +01:00
|
|
|
! do while(fdf_bline(bfdf, pline))
|
2021-02-18 22:38:59 +01:00
|
|
|
|
2021-02-25 14:57:29 +01:00
|
|
|
! if (pline%ntokens == 1) then
|
|
|
|
! number_of_atoms = fdf_bintegers(pline, 1)
|
|
|
|
! write(*,*) "Number of atoms", number_of_atoms
|
|
|
|
! endif
|
|
|
|
! na = number_of_atoms
|
2021-02-18 23:21:04 +01:00
|
|
|
|
2021-02-25 14:57:29 +01:00
|
|
|
! if (pline%ntokens == 4) then
|
|
|
|
! symbol(ia) = fdf_bnames(pline, 1)
|
|
|
|
! do i= 1, 3
|
|
|
|
! xa(i,ia) = fdf_bvalues(pline, i)
|
|
|
|
! enddo
|
|
|
|
! ia = ia + 1
|
|
|
|
! endif
|
|
|
|
! enddo
|
2021-02-18 22:38:59 +01:00
|
|
|
|
2021-02-25 14:57:29 +01:00
|
|
|
! write(6,*) 'Inline XYZ2 Coordinates block:'
|
|
|
|
! do ia= 1, na
|
|
|
|
! write(6,'(A4,3F10.6)') symbol(ia), (xa(i,ia),i=1,3)
|
|
|
|
! enddo
|
|
|
|
! endif
|
2021-02-18 22:38:59 +01:00
|
|
|
|
2021-02-25 14:57:29 +01:00
|
|
|
! write(6,'(A)')
|
2021-02-19 02:05:50 +01:00
|
|
|
|
2021-02-25 14:57:29 +01:00
|
|
|
! write(6,*) '------------------------------------------------------'
|
2021-02-18 22:38:59 +01:00
|
|
|
|
2021-02-19 02:05:50 +01:00
|
|
|
|
2021-02-25 14:57:29 +01:00
|
|
|
! if (fdf_block('molecule2', bfdf)) then
|
|
|
|
! ! External file reading
|
|
|
|
! write(6,*) 'beginning of external file coordinates block '
|
|
|
|
! ia = 1
|
|
|
|
! ! write(*,*) "linecount", fdf_block_linecount("molecule")
|
2021-02-23 22:44:22 +01:00
|
|
|
|
2021-02-25 14:57:29 +01:00
|
|
|
! do while((fdf_bline(bfdf, pline)))
|
2021-02-23 22:44:22 +01:00
|
|
|
|
2021-02-25 14:57:29 +01:00
|
|
|
! if (pline%ntokens == 1) then
|
|
|
|
! number_of_atoms = fdf_bintegers(pline, 1)
|
|
|
|
! write(*,*) "number of atoms", number_of_atoms
|
|
|
|
! endif
|
|
|
|
! na = number_of_atoms
|
2021-02-23 22:44:22 +01:00
|
|
|
|
2021-02-25 14:57:29 +01:00
|
|
|
! if (pline%ntokens == 4) then
|
|
|
|
! symbol(ia) = fdf_bnames(pline, 1)
|
|
|
|
! do i= 1, 3
|
|
|
|
! xa(i,ia) = fdf_bvalues(pline, i)
|
|
|
|
! enddo
|
|
|
|
! ia = ia + 1
|
|
|
|
! endif
|
|
|
|
! enddo
|
|
|
|
! endif
|
|
|
|
! write(6,*) 'Coordinates from Molecule2 block: External file'
|
|
|
|
! do ia= 1, na
|
|
|
|
! write(6,'(A4,3F10.6)') symbol(ia), (xa(i,ia),i=1,3)
|
|
|
|
! enddo
|
2021-02-23 22:44:22 +01:00
|
|
|
|
|
|
|
|
|
|
|
|
2021-02-25 14:57:29 +01:00
|
|
|
! write(6,'(A)')
|
2021-02-23 22:44:22 +01:00
|
|
|
|
2021-02-25 14:57:29 +01:00
|
|
|
! write(6,*) '------------------------------------------------------'
|
2021-02-23 22:44:22 +01:00
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
2021-02-09 22:33:39 +01:00
|
|
|
|
|
|
|
|
|
|
|
|
2021-02-25 14:57:29 +01:00
|
|
|
! if ( fdf_block('ListBlock',bfdf) ) then
|
|
|
|
! i = 0
|
|
|
|
! do while ( fdf_bline(bfdf,pline) )
|
|
|
|
! i = i + 1
|
|
|
|
! na = fdf_bnlists(pline)
|
|
|
|
! write(*,'(2(a,i0),a)') 'Listblock line: ',i,' has ',na,' lists'
|
|
|
|
! do ia = 1 , na
|
|
|
|
! j = -1
|
2021-02-09 22:33:39 +01:00
|
|
|
|
2021-02-25 14:57:29 +01:00
|
|
|
! call fdf_bilists(pline,ia,j,isa)
|
|
|
|
! write(*,'(tr5,2(a,i0),a)') 'list ',ia,' has ',j,' entries'
|
|
|
|
! call fdf_bilists(pline,ia,j,isa)
|
|
|
|
! write(*,'(tr5,a,1000(tr1,i0))') 'list: ',isa(1:j)
|
2021-02-19 02:05:50 +01:00
|
|
|
|
2021-02-25 14:57:29 +01:00
|
|
|
! end do
|
|
|
|
! end do
|
|
|
|
! end if
|
2021-02-09 22:33:39 +01:00
|
|
|
|
2021-02-19 02:05:50 +01:00
|
|
|
|
2021-02-25 14:57:29 +01:00
|
|
|
! if ( fdf_islreal('list_floats') .and. fdf_islist('list_floats') &
|
|
|
|
! .and. (.not. fdf_islinteger('list_floats')) ) then
|
|
|
|
! na = -1
|
|
|
|
! call fdf_list('list_floats',na,listr)
|
|
|
|
! write(*,'(tr1,a,i0,a)') 'list_floats has ',na,' entries'
|
|
|
|
! if ( na < 2 ) stop 1
|
|
|
|
! call fdf_list('list_floats',na,listr)
|
|
|
|
! write(*,'(tr5,a,1000(tr1,f12.8))') 'list_floats: ',listr(1:na)
|
|
|
|
! else
|
|
|
|
! write(*,*)'list_floats was not recognized'
|
|
|
|
! stop 1
|
|
|
|
! end if
|
2021-02-09 22:33:39 +01:00
|
|
|
|
2021-02-25 14:57:29 +01:00
|
|
|
! write(6,'(A)')
|
2021-02-23 22:44:22 +01:00
|
|
|
|
2021-02-25 14:57:29 +01:00
|
|
|
! write(6,*) '------------------------------------------------------'
|
2021-02-23 22:44:22 +01:00
|
|
|
|
|
|
|
write(6,'(A)') " Determinants Block"
|
|
|
|
|
|
|
|
write(6,*) '------------------------------------------------------'
|
|
|
|
|
|
|
|
|
2021-03-03 15:53:47 +01:00
|
|
|
if (.not. fdf_block('determinants', bfdf)) then
|
2021-02-23 22:44:22 +01:00
|
|
|
! External file reading
|
2021-03-03 15:53:47 +01:00
|
|
|
write(6,*) 'Reading the determinants block from an external file '
|
2021-02-23 22:44:22 +01:00
|
|
|
ia = 1
|
|
|
|
! call io_status()
|
2021-03-03 15:53:47 +01:00
|
|
|
! print*, "printing label ", bfdf%label , trim(bfdf%mark%pline%line)
|
2021-02-23 22:44:22 +01:00
|
|
|
|
2021-03-03 15:53:47 +01:00
|
|
|
! print*, "pline obtained", (fdf_bline(bfdf, pline))
|
2021-02-23 22:44:22 +01:00
|
|
|
|
2021-03-03 15:53:47 +01:00
|
|
|
open (unit=11,file=file_determinants, iostat=iostat, action='read' )
|
2021-02-23 22:44:22 +01:00
|
|
|
read(11,*) temp1, temp2, nelectrons, temp3, nalpha
|
2021-03-03 15:53:47 +01:00
|
|
|
|
|
|
|
read(11,*) temp1, ndeterminants, nexcitation
|
|
|
|
if (.not. allocated(det_coeff)) allocate(det_coeff(ndeterminants))
|
|
|
|
|
2021-02-23 22:44:22 +01:00
|
|
|
read(11,*) (det_coeff(i), i=1,ndeterminants)
|
2021-02-24 09:47:16 +01:00
|
|
|
write(fmt,*) '(', ndeterminants, '(f11.8,1x))'
|
|
|
|
write(*,fmt) (det_coeff(i), i=1,ndeterminants)
|
2021-03-03 15:53:47 +01:00
|
|
|
! write(*,'(<ndeterminants>(f11.8, 1x))') (det_coeff(i), i=1,ndeterminants) ! for Intel Fortran
|
2021-02-23 22:44:22 +01:00
|
|
|
|
2021-03-03 15:53:47 +01:00
|
|
|
nbeta = nelectrons - nalpha
|
|
|
|
! allocate the orbital mapping array
|
|
|
|
if (.not. allocated(iworbd)) allocate(iworbd(nelectrons, ndeterminants))
|
2021-02-23 22:44:22 +01:00
|
|
|
|
2021-03-03 15:53:47 +01:00
|
|
|
write(*,*) "total number of electrons ", nelectrons
|
|
|
|
write(*,*) " number of alpha electrons ", nalpha
|
|
|
|
write(*,*) " number of beta electrons ", nbeta
|
2021-02-23 22:44:22 +01:00
|
|
|
|
2021-03-03 15:53:47 +01:00
|
|
|
do i = 1, ndeterminants
|
|
|
|
read(11,*) (iworbd(j,i), j=1,nelectrons)
|
|
|
|
enddo
|
2021-02-23 22:44:22 +01:00
|
|
|
|
2021-03-03 15:53:47 +01:00
|
|
|
write(fmt,*) '(i4,1x)'
|
|
|
|
do i = 1, ndeterminants
|
|
|
|
write(*,'(<nelectrons>(i4, 1x))') (iworbd(j,i), j=1,nelectrons)
|
|
|
|
enddo
|
|
|
|
|
|
|
|
read(11,*) temp1
|
|
|
|
if (temp1 == "end" ) write(*,*) "Determinant File read successfully "
|
2021-02-23 22:44:22 +01:00
|
|
|
|
2021-03-03 15:53:47 +01:00
|
|
|
|
2021-02-23 22:44:22 +01:00
|
|
|
|
2021-03-03 15:53:47 +01:00
|
|
|
close(11)
|
2021-02-23 22:44:22 +01:00
|
|
|
|
|
|
|
endif
|
|
|
|
|
|
|
|
write(6,'(A)')
|
|
|
|
|
|
|
|
write(6,*) '------------------------------------------------------'
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
2021-02-09 22:33:39 +01:00
|
|
|
|
|
|
|
call fdf_shutdown()
|
|
|
|
|
|
|
|
!----------------------------------------------------------------------------END
|
|
|
|
END PROGRAM iochamp
|