Skip to content
Snippets Groups Projects
weight.f90 1.24 KiB
module weight_m

  implicit none

  private rossby_number

contains

  pure real function weight(e1, e2)

    ! Computes the weight of an edge.

    use derived_types, only: eddy

    type(eddy), intent(in):: e1, e2

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

    weight = abs(rossby_number(e2) - rossby_number(e1))

  end function weight

  !****************************************************

  pure real function rossby_number(e)

    ! Computes the Rossby number for the maximum-speed
    ! contour. Assumes that e%out_cont is not null. e%max_speed can be
    ! a quiet NaN, and then the result is a quiet NaN.

    use derived_types, only: eddy
    use nr_util, only: pi, twopi

    type(eddy), intent(in):: e

    ! Local:

    real, parameter:: omega = twopi / 86164.
    ! angular speed of rotation of the Earth, in rad s-1

    real radius ! of the disk of same area
    
    !----------------------------------------------------------

    if (e%speed_cont%n_points /= 0) then
       radius = sqrt(e%speed_cont%area / pi)
    else
       radius = sqrt(e%out_cont%area / pi)
    end if
    
    rossby_number = abs(e%max_speed &
         / (radius * 2. * omega * sin(e%coord_extr(2))))

  end function rossby_number

end module weight_m