-
-
Notifications
You must be signed in to change notification settings - Fork 360
/
Copy pathverlet.f90
122 lines (99 loc) · 2.95 KB
/
verlet.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
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
SUBROUTINE verlet(pos, acc, dt, time)
IMPLICIT NONE
REAL(8), INTENT(INOUT) :: pos, acc, dt, time
REAL(8) :: prev_pos, next_pos
prev_pos = pos
time = 0d0
DO
IF (pos > 0d0) THEN
time = time + dt
next_pos = pos * 2d0 - prev_pos + acc * dt ** 2
prev_pos = pos
pos = next_pos
ELSE
EXIT
END IF
END DO
END SUBROUTINE verlet
SUBROUTINE stormer_verlet(pos, acc, dt, time, vel)
IMPLICIT NONE
REAL(8), INTENT(INOUT) :: pos, acc, dt, time, vel
REAL(8) :: prev_pos, next_pos
prev_pos = pos
time = 0d0
vel = 0d0
DO
IF (pos > 0d0) THEN
time = time + dt
next_pos = pos * 2 - prev_pos + acc * dt ** 2
prev_pos = pos
pos = next_pos
vel = vel + acc * dt
ELSE
EXIT
END IF
END DO
END SUBROUTINE stormer_verlet
SUBROUTINE velocity_verlet(pos, acc, dt, time, vel)
IMPLICIT NONE
REAL(8), INTENT(INOUT) :: pos, acc, dt, time, vel
time = 0d0
vel = 0d0
DO
IF (pos > 0d0) THEN
time = time + dt
pos = pos + vel * dt + 0.5d0 * acc * dt ** 2
vel = vel + acc * dt
ELSE
EXIT
END IF
END DO
END SUBROUTINE velocity_verlet
PROGRAM verlet_integration
IMPLICIT NONE
REAL(8) :: pos,acc, dt, time, vel
INTERFACE
SUBROUTINE verlet(pos, acc, dt, time)
REAL(8), INTENT(INOUT) :: pos, acc, dt, time
REAL(8) :: prev_pos, next_pos
END SUBROUTINE
END INTERFACE
INTERFACE
SUBROUTINE stormer_verlet(pos, acc, dt, time, vel)
REAL(8), INTENT(INOUT) :: pos, acc, dt, time, vel
REAL(8) :: prev_pos, next_pos
END SUBROUTINE
END INTERFACE
INTERFACE
SUBROUTINE velocity_verlet(pos, acc, dt, time, vel)
REAL(8), INTENT(INOUT) :: pos, acc, dt, time, vel
REAL(8) :: prev_pos, next_pos
END SUBROUTINE
END INTERFACE
pos = 5d0
acc = -10d0
dt = 0.01d0
! Verlet
CALL verlet(pos, acc, dt, time)
WRITE(*,*) '[#]'
WRITE(*,*) 'Time for Verlet integration:'
WRITE(*,*) time
! stormer Verlet
pos = 5d0
CALL stormer_verlet(pos, acc, dt, time, vel)
WRITE(*,*) '[#]'
WRITE(*,*) 'Time for Stormer Verlet integration:'
WRITE(*,*) time
WRITE(*,*) '[#]'
WRITE(*,*) 'Velocity for Stormer Verlet integration:'
WRITE(*,*) vel
! Velocity Verlet
pos = 5d0
CALL velocity_verlet(pos, acc, dt, time, vel)
WRITE(*,*) '[#]'
WRITE(*,*) 'Time for velocity Verlet integration:'
WRITE(*,*) time
WRITE(*,*) '[#]'
WRITE(*,*) 'Velocity for velocity Verlet integration:'
WRITE(*,*) vel
END PROGRAM verlet_integration