-
Lionel GUEZ authored
Bug fix in procedure overlap: `delta_out` and `delta_in` should not increase.
Lionel GUEZ authoredBug fix in procedure overlap: `delta_out` and `delta_in` should not increase.
candidate_overlap.f90 1.43 KiB
module candidate_overlap_m
implicit none
contains
function candidate_overlap(extr_map, list_vis, cyclone, delta_out, delta)
! Find the eddies in extr_map that are valid, have a given
! cyclonicity. Also, if delta_out < delta then the eddies should
! not have a predecessor at time distance < delta.
use derived_types, only: eddy
integer, allocatable:: candidate_overlap(:)
integer, intent(in):: extr_map(:, :)
! At a point of extremum SSH: identification number or this
! extremum. 0 at other points.
type(eddy), intent(in):: list_vis(:)
! Visible eddies at a given date. We need components valid,
! cyclone and delta_in to be defined. Arriving in this subroutine,
! list_vis%delta_in could be <= delta or huge(0).
logical, intent(in):: cyclone ! cyclonicity of the target extremum
integer, intent(in):: delta_out
! Arriving in this subroutine, delta_out could be <= delta or
! huge(0).
integer, intent(in):: delta
!---------------------------------------------------------------------
candidate_overlap = pack(extr_map, extr_map /= 0)
candidate_overlap = pack(candidate_overlap, &
list_vis(candidate_overlap)%valid &
.and. (list_vis(candidate_overlap)%cyclone .eqv. cyclone) &
.and. (delta_out >= delta &
.or. list_vis(candidate_overlap)%delta_in >= delta))
end function candidate_overlap
end module candidate_overlap_m