-
Notifications
You must be signed in to change notification settings - Fork 103
/
test_pot_bend.f90
106 lines (85 loc) · 4.68 KB
/
test_pot_bend.f90
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
! test_pot_bend.f90
! bend angle, cos(theta) potential
MODULE test_pot_module
!------------------------------------------------------------------------------------------------!
! This software was written in 2016/17 !
! by Michael P. Allen <[email protected]>/<[email protected]> !
! and Dominic J. Tildesley <[email protected]> ("the authors"), !
! to accompany the book "Computer Simulation of Liquids", second edition, 2017 ("the text"), !
! published by Oxford University Press ("the publishers"). !
! !
! LICENCE !
! Creative Commons CC0 Public Domain Dedication. !
! To the extent possible under law, the authors have dedicated all copyright and related !
! and neighboring rights to this software to the PUBLIC domain worldwide. !
! This software is distributed without any warranty. !
! You should have received a copy of the CC0 Public Domain Dedication along with this software. !
! If not, see <http://creativecommons.org/publicdomain/zero/1.0/>. !
! !
! DISCLAIMER !
! The authors and publishers make no warranties about the software, and disclaim liability !
! for all uses of the software, to the fullest extent permitted by applicable law. !
! The authors and publishers do not recommend use of this software for any purpose. !
! It is made freely available, solely to clarify points made in the text. When using or citing !
! the software, you should not imply endorsement by the authors or publishers. !
!------------------------------------------------------------------------------------------------!
USE, INTRINSIC :: iso_fortran_env, ONLY : error_unit
IMPLICIT NONE
PRIVATE
! Public routine
PUBLIC :: force
! Public data
INTEGER, PARAMETER, PUBLIC :: n = 3 ! Three-body potential
CONTAINS
SUBROUTINE force ( r, pot, f )
IMPLICIT NONE
REAL, DIMENSION(:,:), INTENT(in) :: r
REAL, INTENT(out) :: pot
REAL, DIMENSION(:,:), OPTIONAL, INTENT(out) :: f
! We choose to make the polymer the minimum length needed for testing
INTEGER :: a, b
REAL, DIMENSION(3,2:n) :: d ! the d vectors
REAL, DIMENSION(2:n,2:n) :: cc ! the C coefficients
REAL :: prefac, fac, fac1, fac2
! Routine to demonstrate the calculation of forces from the
! polymer angle-bending potential
! Written for ease of comparison with the text, rather than efficiency!
! Check dimensions to be sure
IF ( ANY ( SHAPE(r) /= [3,n] ) ) THEN
WRITE ( unit=error_unit, fmt='(a,4i15)' ) 'r shape error', SHAPE(r), 3, n
STOP 'Error in test_pot_bend'
END IF
! Set up d vectors
DO a = 2, n
d(:,a) = r(:,a) - r(:,a-1)
END DO
! Store C coefficients in a matrix
! In the general case we would not need to calculate every pair
! and also we would make use of the symmetry cc(b,a)=cc(a,b)
DO a = 2, n
DO b = 2, n
cc(a,b) = DOT_PRODUCT ( d(:,a), d(:,b) )
END DO
END DO
! For this test there is just one angle
a = n
! Here is the potential as a function of cos(theta)
! For testing we use the simplest form: v= -cos(theta)
! The notation matches that used in the appendix
prefac = 1.0 / SQRT(cc(a,a)*cc(a-1,a-1))
fac = cc(a,a-1)
pot = -prefac*fac ! This is -cos(theta)
IF ( .NOT. PRESENT(f) ) RETURN
IF ( ANY ( SHAPE(f) /= [3,n] ) ) THEN
WRITE ( unit=error_unit, fmt='(a,4i15)' ) 'f shape error', SHAPE(f), 3, n
STOP 'Error in test_pot_bend'
END IF
! Here we include the derivative of the potential with respect to cos(theta) in the prefactor
! For this simple case it is -1, so the forces are simply gradients of cos(theta) as in the text
fac1 = fac / cc(a,a)
fac2 = fac / cc(a-1,a-1)
f(:,a) = -prefac * ( fac1*d(:,a) - d(:,a-1) )
f(:,a-1) = prefac * ( fac1*d(:,a) - fac2*d(:,a-1) + d(:,a) - d(:,a-1) )
f(:,a-2) = prefac * ( fac2*d(:,a-1) - d(:,a) )
END SUBROUTINE force
END MODULE test_pot_module