Skip to content
Snippets Groups Projects
mean_speed.f90 1.52 KiB
module mean_speed_m

  implicit none

contains

  real function mean_speed(u, v, p, center, corner, step)

    ! Interpolates the wind at each point of the input polygon and
    ! computes the mean azimuthal speed at interpolation points.

    ! Libraries:
    use contour_531, only: polyline
    use numer_rec_95, only: bilinear_interp2_reg

    real, intent(in):: u(:, :), v(:, :) ! velocity
    type(polyline), intent(in):: p ! should be closed

    real, intent(in):: center(:) ! (2)
    ! Longitude and latitude, in rad. Azimuthal speed is computed with
    ! respect to this point.
    
    real, intent(in):: corner(:) ! (2)
    ! longitude and latitude corresponding to u(1,1) and v(1, 1), in rad

    real, intent(in):: step(:) ! (2) ! longitude and latitude steps, in rad

    ! Local:

    real ui(p%n_points - 1), vi(p%n_points - 1) ! (ni)
    ! speed interpolated at polygon points

    real x, y ! coordinates in tangent plane, divided by Earth radius
    real v_azim(p%n_points - 1) ! (ni) azimuthal speed at polygon points
    integer j
    integer ni ! number of interpolation points

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

    ni = p%n_points - 1
    call bilinear_interp2_reg(corner, step, u, v, p%points(:, :ni), ui, vi)
    
    do j = 1, ni
       x = cos(center(2)) * (p%points(1, j) - center(1))
       y = p%points(2, j) - center(2)
       v_azim(j) = (x * vi(j) - y * ui(j)) / sqrt(x**2 + y**2)
    end do

    mean_speed = sum(v_azim) / ni

  end function mean_speed

end module mean_speed_m