-
Notifications
You must be signed in to change notification settings - Fork 9
/
maxima.f90
176 lines (128 loc) · 3.58 KB
/
maxima.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
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
!
! $Id: $
!
! Given an array of floating point numbers, returns an array of
! integers containing the indexes of the maxima of the array
!
subroutine find_maxima(x,nx,maxima,nindex,w_level)
implicit none
integer, parameter :: UP = 1
integer, parameter :: DOWN = -1
integer, parameter :: FLAT = 0
double precision, dimension (*), intent(in) :: x
integer, intent(in) :: nx
double precision, intent(in) :: w_level
integer, dimension (*), intent(out) :: maxima
integer,intent(out) :: nindex
integer :: i,k, prev_dir, next_dir
integer, external :: direction
k=0
! set up the starting previous direction
prev_dir=direction(x(1),x(2), w_level)
! iterate through the points in the array
do i=2, nx-1
!the next direction
next_dir=direction(x(i),x(i+1),w_level)
if(next_dir.eq.DOWN .and. prev_dir .eq. UP) then
k=k+1
maxima(k)=i
endif
! set up prev_dir for next iternation
prev_dir = next_dir
enddo
nindex=k
end subroutine find_maxima
integer function direction(a,b,w_level)
implicit none
integer, parameter :: UP = 1
integer, parameter :: DOWN = -1
integer, parameter :: FLAT = 0
double precision, parameter :: EPS = 1.0e-12
double precision, intent(in) :: a,b,w_level
! write(*,*) 'Direction entered'
if ( a < w_level .or. b < w_level ) then
direction = FLAT
elseif ( abs(a-b) < EPS) then
direction = FLAT
elseif (b > a) then
direction = UP
else
direction = DOWN
endif
! write(*,*) 'Direction =', direction
end function direction
! given an array, the index of a local maximum, and a water level, give
! the index of the closest points in the array that dip below the water
! level
subroutine bracket_maximum(x, nx, imax , w_level, i1, i2)
implicit none
double precision, dimension(*), intent(in) :: x
integer, intent(in) :: nx , imax
double precision, intent(in) :: w_level
integer, intent(out) :: i1, i2
integer :: i
i1=1
i2=nx
do i = imax, 1, -1
if(x(i)<w_level) then
i1=i
exit
endif
enddo
do i = imax, nx, +1
if(x(i)<w_level) then
i2=i
exit
endif
enddo
!write(*,*)'DEBUG: bracket returns :', i1, i2, nx
end subroutine
!!$! given an array and the index of two end points, calculate the
!!$! area under the curve by simple trapezium integration
!!$
!!$ function area_under_curve(x,dx,i1,i2)
!!$ double precision, dimension(*) :: x
!!$ double precision :: dx
!!$ integer :: i1, i2
!!$
!!$ integer :: i
!!$ double precision :: area
!!$
!!$ area=0.0
!!$
!!$ do i = i1, i2-1
!!$ area=area + dx*(x(i)+x(i+1))/2.0
!!$ enddo
!!$
!!$ ! compilation warning for this line, but do we use this?
!!$ area_under_curve = area
!!$
!!$ end function
subroutine find_minima(x,nx,minima,nindex,w_level)
implicit none
integer, parameter :: UP = 1
integer, parameter :: DOWN = -1
integer, parameter :: FLAT = 0
double precision, dimension (*), intent(in) :: x
integer, intent(in) :: nx
double precision, intent(in) :: w_level
integer, dimension (*), intent(out) :: minima
integer, intent(out) :: nindex
integer :: i,k, prev_dir, next_dir
integer, external :: direction
k=0
! set up the starting previous direction
prev_dir=direction(x(1),x(2), w_level)
! iterate through the points in the array
do i=2, nx-1
!the next direction
next_dir=direction(x(i),x(i+1),w_level)
if(next_dir.eq.UP .and. prev_dir .eq. DOWN) then
k=k+1
minima(k)=i
endif
! set up prev_dir for next iternation
prev_dir = next_dir
enddo
nindex=k
end subroutine find_minima