subroutine prepare_polelec(eel, arg_dogg)
use mod_memory, only: mallocate
implicit none
type(ommp_electrostatics_type), intent(inout) :: eel
logical, optional, intent(in) :: arg_dogg
logical :: do_gg
do_gg = .false.
if(present(arg_dogg)) then
if(arg_dogg) do_gg = .true.
end if
if(.not. do_gg .and. eel%M2D_done) return
if(do_gg .and. eel%M2D_done .and. eel%M2Dgg_done) return
if(.not. allocated(eel%V_M2D) .and. eel%use_fmm) then
! This is needed just as a placeholder in fmm calls
call mallocate('prepare_polelec [V_M2D]', eel%pol_atoms, &
eel%n_ipd, eel%V_M2D)
end if
if(.not. allocated(eel%E_M2D)) then
call mallocate('prepare_polelec [E_M2D]', 3_ip, eel%pol_atoms, &
eel%n_ipd, eel%E_M2D)
end if
if(do_gg .or. eel%use_fmm) then
if(.not. eel%ipd_done .and. do_gg) call fatal_error("IPD should be computed &
&before computing analytical geometrical gradients of &
&polarization energy.")
if(.not. allocated(eel%Egrd_M2D)) then
call mallocate('prepare_polelec [Egrd_M2D]', 6_ip, eel%pol_atoms, &
eel%n_ipd, eel%Egrd_M2D)
end if
if(.not. allocated(eel%V_D2D) .and. eel%use_fmm) then
call mallocate('prepare_polelec [V_D2D]', eel%pol_atoms, &
eel%n_ipd, eel%V_D2D)
end if
if(.not. allocated(eel%E_D2D) .and. eel%use_fmm) then
call mallocate('prepare_polelec [E_D2D]', 3_ip, eel%pol_atoms, &
eel%n_ipd, eel%E_D2D)
end if
if(.not. allocated(eel%Egrd_D2D)) then
call mallocate('prepare_polelec [Egrd_D2D]', 6_ip, eel%pol_atoms, &
eel%n_ipd, eel%Egrd_D2D)
end if
if(.not. allocated(eel%EHes_D2D) .and. eel%use_fmm) then
call mallocate('prepare_polelec [EHes_D2D]', 10_ip, eel%pol_atoms, &
eel%n_ipd, eel%EHes_D2D)
end if
if(.not. allocated(eel%V_D2M) .and. eel%use_fmm) then
call mallocate('prepare_polelec [V_D2M]', eel%top%mm_atoms, &
eel%V_D2M)
end if
if(.not. allocated(eel%E_D2M)) then
call mallocate('prepare_polelec [E_D2M]', 3_ip, eel%top%mm_atoms, &
eel%E_D2M)
end if
if(.not. allocated(eel%Egrd_D2M) .and. eel%amoeba) then
call mallocate('prepare_polelec [Egrd_D2M]', 6_ip, eel%top%mm_atoms, &
eel%Egrd_D2M)
end if
if(.not. allocated(eel%EHes_D2M) .and. eel%amoeba) then
call mallocate('prepare_polelec [E_D2M]', 10_ip, eel%top%mm_atoms, &
eel%EHes_D2M)
end if
end if
if(.not. do_gg) then
eel%E_M2D = 0.0_rp
call elec_prop_M2D(eel, .false., .true., .false., .false.)
else
eel%E_M2D = 0.0_rp
eel%Egrd_M2D = 0.0_rp
call elec_prop_M2D(eel, .false., .true., .true., .false.)
eel%E_D2M = 0.0_rp
eel%Egrd_D2D = 0.0_rp
if(eel%amoeba) then
eel%Egrd_D2M = 0.0_rp
eel%EHes_D2M = 0.0_rp
call elec_prop_D2M(eel, 'P', .false., .true., .true., .true.)
call elec_prop_D2M(eel, 'D', .false., .true., .true., .true.)
eel%E_D2M = eel%E_D2M * 0.5
eel%Egrd_D2M = eel%Egrd_D2M * 0.5
eel%EHes_D2M = eel%EHes_D2M * 0.5
call elec_prop_D2D(eel, 'P', .false., .false., .true., .false.)
call elec_prop_D2D(eel, 'D', .false., .false., .true., .false.)
else
call elec_prop_D2M(eel, '-', .false., .true., .false., .false.)
call elec_prop_D2D(eel, '-', .false., .false., .true., .false.)
end if
end if
if(do_gg) eel%M2Dgg_done = .true.
eel%M2D_done = .true.
end subroutine prepare_polelec