Skip to content
Snippets Groups Projects
nearby_extr.f90 1.30 KiB
module nearby_extr_m

  implicit none

contains

  pure function nearby_extr(extr_map, list, i)

    ! Returns a list of extrema that cannot be engulfed in a good
    ! contour around the target extremum.

    use derived_types, only: eddy

    real, allocatable:: nearby_extr(:, :) ! (2, :) longitude and
    ! latitude, in rad, of extrema

    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(:)
    ! Visible eddies at a given date. We need components coord_extr,
    ! valid and cyclone to be defined.
    
    integer, intent(in):: i ! identifying number of the target extremum

    ! Local:

    integer, allocatable:: selection(:)
    ! identifying numbers of a selection of eddies

    integer n_select, l

    !--------------------------------------------------------------------------

    selection = pack(extr_map, extr_map /= 0)
    selection = pack(selection, selection /= i &
         .and. ((list(selection)%cyclone .neqv. list(i)%cyclone) &
         .or. list(selection)%valid))
    n_select = size(selection)
    allocate(nearby_extr(2, n_select))
    forall (l = 1:n_select) &
         nearby_extr(:, l) = list(selection(l))%coord_extr

  end function nearby_extr

end module nearby_extr_m