Octopus
coulomb_force.F90
Go to the documentation of this file.
1!! Copyright (C) 2020 Heiko Appel
2!!
3!! This program is free software; you can redistribute it and/or modify
4!! it under the terms of the GNU General Public License as published by
5!! the Free Software Foundation; either version 2, or (at your option)
6!! any later version.
7!!
8!! This program is distributed in the hope that it will be useful,
9!! but WITHOUT ANY WARRANTY; without even the implied warranty of
10!! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
11!! GNU General Public License for more details.
12!!
13!! You should have received a copy of the GNU General Public License
14!! along with this program; if not, write to the Free Software
15!! Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
16!! 02110-1301, USA.
17!!
18
19#include "global.h"
20
22 use debug_oct_m
24 use global_oct_m
30
31 implicit none
32
33 private
34 public :: &
36
38 type, extends(force_interaction_t) :: coulomb_force_t
39 private
40 real(real64), pointer :: system_charge(:) => null()
41 real(real64), pointer :: system_pos(:,:) => null()
42
43 integer, public :: partner_np = 0
44 real(real64), allocatable, public :: partner_charge(:)
45 real(real64), allocatable, public :: partner_pos(:,:)
46
47 contains
48 procedure :: init => coulomb_force_init
49 procedure :: calculate => coulomb_force_calculate
50 procedure :: calculate_energy => coulomb_force_calculate_energy
52 end type coulomb_force_t
53
54 interface coulomb_force_t
55 module procedure coulomb_force_constructor
56 end interface coulomb_force_t
57
58contains
59
60 ! ---------------------------------------------------------
61 function coulomb_force_constructor(partner) result(this)
62 class(interaction_partner_t), target, intent(inout) :: partner
63 class(coulomb_force_t), pointer :: this
64
66
67 allocate(this)
68
69 this%label = "coulomb_force"
70
71 this%partner => partner
72
73 ! The Coulomb force needs the position and charge of the system
74 this%system_quantities = [character(8) :: "position", "charge"]
75
76 ! The Coulomb force needs the position and charge of the partner
77 this%couplings_from_partner = [character(8) :: "position", "charge"]
78
80 end function coulomb_force_constructor
81
82 ! ---------------------------------------------------------
83 subroutine coulomb_force_init(this, dim, system_np, system_charge, system_pos)
84 class(coulomb_force_t), intent(inout) :: this
85 integer, intent(in) :: dim
86 integer, intent(in) :: system_np
87 real(real64), target, intent(in) :: system_charge(:)
88 real(real64), target, intent(in) :: system_pos(:,:)
89
90 push_sub(coulomb_force_init)
91
92 this%dim = dim
93 this%system_np = system_np
94 safe_allocate(this%force(1:dim, 1:system_np))
95 this%force = m_zero
96
97 this%system_charge => system_charge
98 this%system_pos => system_pos
99
100 pop_sub(coulomb_force_init)
101 end subroutine coulomb_force_init
102
103 ! ---------------------------------------------------------
104 subroutine coulomb_force_calculate(this)
105 class(coulomb_force_t), intent(inout) :: this
106
107 integer :: ip, jp
108 real(real64), parameter :: COULCONST = m_one ! Coulomb constant in atomic units
109 real(real64) :: dist3
110
112
113 assert(allocated(this%partner_charge))
114 assert(allocated(this%partner_pos))
115
116 do ip = 1, this%system_np
117 do jp = 1, this%partner_np
118 if (this%intra_interaction .and. ip == jp ) cycle
119
120 dist3 = sum((this%partner_pos(1:this%dim, jp) - this%system_pos(1:this%dim, ip))**2)**(m_three/m_two)
121
122 this%force(1:this%dim, ip) = -(this%partner_pos(1:this%dim, jp) - this%system_pos(1:this%dim, ip)) &
123 / (dist3 + m_epsilon) * (coulconst * this%system_charge(ip) * this%partner_charge(jp))
124 end do
125 end do
126
128 end subroutine coulomb_force_calculate
129
130 ! ---------------------------------------------------------
132 class(coulomb_force_t), intent(inout) :: this
134 integer :: ip, jp
135 real(real64), parameter :: coulconst = m_one ! Coulomb constant in atomic units
136 real(real64) :: dist
139
140 assert(allocated(this%partner_charge))
141 assert(allocated(this%partner_pos))
143 this%energy = m_zero
144 do ip = 1, this%system_np
145 do jp = 1, this%partner_np
146 if (this%intra_interaction .and. ip == jp ) cycle
147
148 dist = sqrt(sum((this%partner_pos(1:this%dim, jp) - this%system_pos(1:this%dim, ip))**2))
149
150 this%energy = this%energy + m_half / (dist + m_epsilon) * (coulconst * this%system_charge(ip) * this%partner_charge(jp))
151 end do
152 end do
153
155 end subroutine coulomb_force_calculate_energy
156
157
158 ! ---------------------------------------------------------
159 subroutine coulomb_force_finalize(this)
160 type(coulomb_force_t), intent(inout) :: this
161
162 push_sub(coulomb_force_finalize)
163
164 this%force = m_zero
165 nullify(this%system_charge)
166 nullify(this%system_pos)
167 safe_deallocate_a(this%partner_pos)
168 safe_deallocate_a(this%partner_charge)
169 safe_deallocate_a(this%force)
170
171 call interaction_end(this)
172
174 end subroutine coulomb_force_finalize
175
177
178!! Local Variables:
179!! mode: f90
180!! coding: utf-8
181!! End:
double sqrt(double __x) __attribute__((__nothrow__
subroutine coulomb_force_calculate_energy(this)
subroutine coulomb_force_calculate(this)
subroutine coulomb_force_finalize(this)
subroutine coulomb_force_init(this, dim, system_np, system_charge, system_pos)
class(coulomb_force_t) function, pointer coulomb_force_constructor(partner)
real(real64), parameter, public m_two
Definition: global.F90:190
real(real64), parameter, public m_zero
Definition: global.F90:188
real(real64), parameter, public m_epsilon
Definition: global.F90:204
real(real64), parameter, public m_half
Definition: global.F90:194
real(real64), parameter, public m_one
Definition: global.F90:189
real(real64), parameter, public m_three
Definition: global.F90:191
This module defines the abstract interaction_t class, and some auxiliary classes for interactions.
subroutine, public interaction_end(this)
This module defines classes and functions for interaction partners.
Coulomb interaction between two systems of particles.