Octopus
lennard_jones.F90
Go to the documentation of this file.
1!! Copyright (C) 2023 F. Bonafe
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
27 use, intrinsic :: iso_fortran_env
32
33 implicit none
34
35 private
36 public :: &
38
40 type, extends(force_interaction_t) :: lennard_jones_t
41 private
42 real(real64), pointer :: system_pos(:,:) => null()
43 real(real64), public :: lj_epsilon
44 real(real64), public :: lj_sigma
45
46 integer, public :: partner_np = 0
47 real(real64), allocatable, public :: partner_pos(:,:)
48
49 contains
50 procedure :: init => lennard_jones_init
51 procedure :: calculate => lennard_jones_calculate
52 procedure :: calculate_energy => lennard_jones_calculate_energy
54 end type lennard_jones_t
55
56 interface lennard_jones_t
57 module procedure lennard_jones_constructor
58 end interface lennard_jones_t
59
60contains
61
62 ! ---------------------------------------------------------
63 function lennard_jones_constructor(partner) result(this)
64 class(interaction_partner_t), target, intent(inout) :: partner
65 class(lennard_jones_t), pointer :: this
66
68
69 allocate(this)
70
71 this%label = "lennard_jones"
72
73 this%partner => partner
74
75 ! The Lennard Jones interaction needs the position of the particles and the parameters
76 this%system_quantities = [position]
77
78 ! The Lennard Jones interaction needs the position of the partner
79 this%couplings_from_partner = [position]
80
82 end function lennard_jones_constructor
83
84 ! ---------------------------------------------------------
85 subroutine lennard_jones_init(this, dim, system_np, system_pos, system_eps, system_sigma)
86 class(lennard_jones_t), intent(inout) :: this
87 integer, intent(in) :: dim
88 integer, intent(in) :: system_np
89 real(real64), target, intent(in) :: system_pos(:,:)
90 real(real64), intent(in) :: system_eps
91 real(real64), intent(in) :: system_sigma
92
93 push_sub(lennard_jones_init)
94
95 this%dim = dim
96 this%system_np = system_np
97 safe_allocate(this%force(1:dim, 1:system_np))
98 this%force = m_zero
99
100 this%lj_epsilon = system_eps
101 this%lj_sigma = system_sigma
102
103 this%system_pos => system_pos
104
105 pop_sub(lennard_jones_init)
106 end subroutine lennard_jones_init
107
108 ! ---------------------------------------------------------
109 subroutine lennard_jones_calculate(this)
110 class(lennard_jones_t), intent(inout) :: this
111
112 integer :: ip, jp
113 real(real64) :: dist, rr(1:this%dim), lj_force
116
117 assert(allocated(this%partner_pos))
118
119 do ip = 1, this%system_np
120 do jp = 1, this%partner_np
121 if (this%intra_interaction .and. ip == jp ) cycle
122
123 ! r_ij = r_i - r_j
124 rr(1:this%dim) = this%system_pos(1:this%dim, ip) - this%partner_pos(1:this%dim, jp)
125 dist = sqrt(sum(rr(1:this%dim)**2))
126
127 ! lj_force = -d U(|r_ij|) / d |r_ij|
128 lj_force = 48.0_real64 * this%lj_epsilon * (this%lj_sigma**12 / dist**13 - &
129 m_half * this%lj_sigma**6 / dist**7)
130
131 ! F_i = - d U(r) / d r_i = - (d U (r) / d |r_ij|) * (d r_ij / d r_i) =
132 ! = - d U (r) / d r_ij, because d r_ij / d r_i = 1
133 this%force(1:this%dim, ip) = rr(1:this%dim) / dist * lj_force
134 end do
135 end do
138 end subroutine lennard_jones_calculate
140 ! ---------------------------------------------------------
141 subroutine lennard_jones_calculate_energy(this)
142 class(lennard_jones_t), intent(inout) :: this
144 integer :: ip, jp
145 real(real64) :: dist
148
149 assert(allocated(this%partner_pos))
150
151 this%energy = m_zero
152 do ip = 1, this%system_np
153 do jp = 1, this%partner_np
154 if (this%intra_interaction .and. ip == jp ) cycle
155
156 dist = sqrt(sum((this%system_pos(1:this%dim, ip) - this%partner_pos(1:this%dim, jp))**2)) + m_epsilon
157
158 ! this%energy = this%energy + 0.5 * U(r_ij)
159 this%energy = this%energy + m_two * this%lj_epsilon * ( (this%lj_sigma / dist)**12 - &
160 (this%lj_sigma / dist)**6 )
161 end do
162 end do
163
165 end subroutine lennard_jones_calculate_energy
166
167
168 ! ---------------------------------------------------------
169 subroutine lennard_jones_finalize(this)
170 type(lennard_jones_t), intent(inout) :: this
171
172 push_sub(lennard_jones_finalize)
173
174 this%force = m_zero
175 nullify(this%system_pos)
176 safe_deallocate_a(this%partner_pos)
177 safe_deallocate_a(this%force)
179 call interaction_end(this)
180
182 end subroutine lennard_jones_finalize
183
184end module lennard_jones_oct_m
185
186!! Local Variables:
187!! mode: f90
188!! coding: utf-8
189!! End:
double sqrt(double __x) __attribute__((__nothrow__
real(real64), parameter, public m_two
Definition: global.F90:189
real(real64), parameter, public m_zero
Definition: global.F90:187
real(real64), parameter, public m_epsilon
Definition: global.F90:203
real(real64), parameter, public m_half
Definition: global.F90:193
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.
subroutine lennard_jones_calculate_energy(this)
subroutine lennard_jones_init(this, dim, system_np, system_pos, system_eps, system_sigma)
subroutine lennard_jones_calculate(this)
class(lennard_jones_t) function, pointer lennard_jones_constructor(partner)
subroutine lennard_jones_finalize(this)
This module defines the quantity_t class and the IDs for quantities, which can be exposed by a system...
Definition: quantity.F90:137
integer, parameter, public position
Definition: quantity.F90:146
Lennard-Jones interaction between two systems of particles.