Skip to content

Commit

Permalink
Inclusion of approximate electrostatics based on the electronegativit…
Browse files Browse the repository at this point in the history
…y weighted CN as charges. Incorporation of calculator error handling. Update of the parameters and tests to the second version of CEH.
  • Loading branch information
thfroitzheim committed Jul 30, 2024
1 parent 55c4c45 commit 5a4d1fd
Show file tree
Hide file tree
Showing 21 changed files with 1,797 additions and 922 deletions.
4 changes: 2 additions & 2 deletions app/cli.f90
Original file line number Diff line number Diff line change
Expand Up @@ -75,7 +75,7 @@ module tblite_cli
!> Electronic temperature
real(wp) :: etemp = 300.0_wp
!> Electronic temperature for the guess (currently only CEH)
real(wp) :: etemp_guess = 5000.0_wp
real(wp) :: etemp_guess = 4000.0_wp
!> Electric field
real(wp), allocatable :: efield(:)
!> Spin polarization
Expand Down Expand Up @@ -107,7 +107,7 @@ module tblite_cli
!> File for output of JSON dump
character(len=:), allocatable :: json_output
!> Electronic temperature for the guess (currently only CEH)
real(wp) :: etemp_guess = 5000.0_wp
real(wp) :: etemp_guess = 4000.0_wp
!> Electric field
real(wp), allocatable :: efield(:)
!> Algorithm for electronic solver
Expand Down
2 changes: 1 addition & 1 deletion app/driver_guess.f90
Original file line number Diff line number Diff line change
Expand Up @@ -115,7 +115,7 @@ subroutine guess_main(config, error)
method = "ceh"
if (allocated(config%method)) method = config%method
if (method == "ceh") then
call new_ceh_calculator(calc_ceh, mol)
call new_ceh_calculator(calc_ceh, mol, error)
call new_wavefunction(wfn_ceh, mol%nat, calc_ceh%bas%nsh, calc_ceh%bas%nao, 1, config%etemp_guess * kt)
end if

Expand Down
9 changes: 5 additions & 4 deletions app/driver_run.f90
Original file line number Diff line number Diff line change
Expand Up @@ -142,11 +142,11 @@ subroutine run_main(config, error)
case default
call fatal_error(error, "Unknown method '"//method//"' requested")
case("gfn2")
call new_gfn2_calculator(calc, mol)
call new_gfn2_calculator(calc, mol, error)
case("gfn1")
call new_gfn1_calculator(calc, mol)
call new_gfn1_calculator(calc, mol, error)
case("ipea1")
call new_ipea1_calculator(calc, mol)
call new_ipea1_calculator(calc, mol, error)
end select
end if
if (allocated(error)) return
Expand All @@ -156,13 +156,14 @@ subroutine run_main(config, error)
call new_wavefunction(wfn, mol%nat, calc%bas%nsh, calc%bas%nao, nspin, config%etemp * kt)

if (config%guess == "ceh") then
call new_ceh_calculator(calc_ceh, mol)
call new_ceh_calculator(calc_ceh, mol, error)
call new_wavefunction(wfn_ceh, mol%nat, calc_ceh%bas%nsh, calc_ceh%bas%nao, 1, config%etemp_guess * kt)
if (config%grad) then
call ctx%message("WARNING: CEH gradient not yet implemented. Stopping.")
return
end if
end if
if (allocated(error)) return

if (allocated(config%efield)) then
block
Expand Down
35 changes: 29 additions & 6 deletions src/tblite/api/calculator.f90
Original file line number Diff line number Diff line change
Expand Up @@ -88,6 +88,7 @@ function new_gfn2_calculator_api(vctx, vmol) result(vcalc) &
type(vp_structure), pointer :: mol
type(c_ptr) :: vcalc
type(vp_calculator), pointer :: calc
type(error_type), allocatable :: error

if (debug) print '("[Info]", 1x, a)', "new_gfn2_calculator"

Expand All @@ -99,8 +100,14 @@ function new_gfn2_calculator_api(vctx, vmol) result(vcalc) &
call c_f_pointer(vmol, mol)

allocate(calc)
call new_gfn2_calculator(calc%ptr, mol%ptr)
vcalc = c_loc(calc)
call new_gfn2_calculator(calc%ptr, mol%ptr, error)
if (allocated(error)) then
deallocate(calc)
call ctx%ptr%set_error(error)
return
else
vcalc = c_loc(calc)
end if

end function new_gfn2_calculator_api

Expand All @@ -113,6 +120,7 @@ function new_ipea1_calculator_api(vctx, vmol) result(vcalc) &
type(vp_structure), pointer :: mol
type(c_ptr) :: vcalc
type(vp_calculator), pointer :: calc
type(error_type), allocatable :: error

if (debug) print '("[Info]", 1x, a)', "new_ipea1_calculator"

Expand All @@ -124,8 +132,14 @@ function new_ipea1_calculator_api(vctx, vmol) result(vcalc) &
call c_f_pointer(vmol, mol)

allocate(calc)
call new_ipea1_calculator(calc%ptr, mol%ptr)
vcalc = c_loc(calc)
call new_ipea1_calculator(calc%ptr, mol%ptr, error)
if (allocated(error)) then
deallocate(calc)
call ctx%ptr%set_error(error)
return
else
vcalc = c_loc(calc)
end if

end function new_ipea1_calculator_api

Expand All @@ -138,6 +152,7 @@ function new_gfn1_calculator_api(vctx, vmol) result(vcalc) &
type(vp_structure), pointer :: mol
type(c_ptr) :: vcalc
type(vp_calculator), pointer :: calc
type(error_type), allocatable :: error

if (debug) print '("[Info]", 1x, a)', "new_gfn1_calculator"

Expand All @@ -149,8 +164,14 @@ function new_gfn1_calculator_api(vctx, vmol) result(vcalc) &
call c_f_pointer(vmol, mol)

allocate(calc)
call new_gfn1_calculator(calc%ptr, mol%ptr)
vcalc = c_loc(calc)
call new_gfn1_calculator(calc%ptr, mol%ptr, error)
if (allocated(error)) then
deallocate(calc)
call ctx%ptr%set_error(error)
return
else
vcalc = c_loc(calc)
end if

end function new_gfn1_calculator_api

Expand Down Expand Up @@ -184,6 +205,8 @@ function new_xtb_calculator_api(vctx, vmol, vparam) result(vcalc) &
call new_xtb_calculator(calc%ptr, mol%ptr, param%ptr, error)
if (allocated(error)) then
deallocate(calc)
call ctx%ptr%set_error(error)
return
else
vcalc = c_loc(calc)
end if
Expand Down
Loading

0 comments on commit 5a4d1fd

Please sign in to comment.